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.219.12020000.9 2013/03/07 13:59:30 harsanan ship $ */
3 
4   -- Bug 13904341
5   G_CURRENT_RUNTIME_LEVEL CONSTANT NUMBER       := FND_LOG.G_CURRENT_RUNTIME_LEVEL;
6   G_LEVEL_UNEXPECTED      CONSTANT NUMBER       := FND_LOG.LEVEL_UNEXPECTED;
7   G_LEVEL_ERROR           CONSTANT NUMBER       := FND_LOG.LEVEL_ERROR;
8   G_LEVEL_EXCEPTION       CONSTANT NUMBER       := FND_LOG.LEVEL_EXCEPTION;
9   G_LEVEL_EVENT           CONSTANT NUMBER       := FND_LOG.LEVEL_EVENT;
10   G_LEVEL_PROCEDURE       CONSTANT NUMBER       := FND_LOG.LEVEL_PROCEDURE;
11   G_LEVEL_STATEMENT       CONSTANT NUMBER       := FND_LOG.LEVEL_STATEMENT;
12   G_MODULE_NAME           CONSTANT VARCHAR2(30) := 'AP_IMPORT_VALIDATION_PKG.';
13 ------------------------------------------------------------------------
14 -- This function is used to perform invoice header level validations.
15 --
16 ------------------------------------------------------------------------
17 
18 -- bug 8497933
19 l_is_inv_date_null	 VARCHAR2(1);
20 -- bug 8497933
21 --bug 15862708 starts
22 lg_ship_to_loc_id_code AP_IMPORT_VALIDATION_PKG.g_ship_to_loc_id_code;
23 lg_ship_to_loc_id_site AP_IMPORT_VALIDATION_PKG.g_ship_to_loc_id_site;
24 --bug 15862708 ends
25 
26 FUNCTION v_check_invoice_validation(
27        p_invoice_rec                 IN OUT NOCOPY
28          AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
29        p_match_mode                     OUT NOCOPY VARCHAR2,
30        p_min_acct_unit_inv_curr         OUT NOCOPY NUMBER,
31        p_precision_inv_curr             OUT NOCOPY NUMBER,
32 	   p_positive_price_tolerance      OUT NOCOPY      NUMBER,
33 	   p_negative_price_tolerance      OUT NOCOPY      NUMBER,
34 	   p_qty_tolerance                 OUT NOCOPY      NUMBER,
35 	   p_qty_rec_tolerance             OUT NOCOPY      NUMBER,
36 	   p_max_qty_ord_tolerance         OUT NOCOPY      NUMBER,
37 	   p_max_qty_rec_tolerance         OUT NOCOPY      NUMBER,
38 	   p_amt_tolerance		           OUT NOCOPY      NUMBER,
39 	   p_amt_rec_tolerance		       OUT NOCOPY	   NUMBER,
40 	   p_max_amt_ord_tolerance         OUT NOCOPY      NUMBER,
41 	   p_max_amt_rec_tolerance         OUT NOCOPY      NUMBER,
42 	   p_goods_ship_amt_tolerance      OUT NOCOPY      NUMBER,
43 	   p_goods_rate_amt_tolerance      OUT NOCOPY      NUMBER,
44 	   p_goods_total_amt_tolerance     OUT NOCOPY      NUMBER,
45 	   p_services_ship_amt_tolerance   OUT NOCOPY      NUMBER,
46 	   p_services_rate_amt_tolerance   OUT NOCOPY      NUMBER,
47 	   p_services_total_amt_tolerance  OUT NOCOPY      NUMBER,
48            p_base_currency_code          IN            VARCHAR2,
49            p_multi_currency_flag         IN            VARCHAR2,
50            p_set_of_books_id             IN            NUMBER,
51            p_default_exchange_rate_type  IN            VARCHAR2,
52            p_make_rate_mandatory_flag    IN            VARCHAR2,
53            p_default_last_updated_by     IN            NUMBER,
54            p_default_last_update_login   IN            NUMBER,
55            p_fatal_error_flag            OUT NOCOPY    VARCHAR2,
56            p_current_invoice_status      IN OUT NOCOPY VARCHAR2,
57            p_calc_user_xrate             IN            VARCHAR2,
58            p_prepay_period_name          IN OUT NOCOPY VARCHAR2,
59 	   p_prepay_invoice_id		 OUT NOCOPY    NUMBER,
60 	   p_prepay_case_name		 OUT NOCOPY    VARCHAR2,
61            p_request_id                  IN            NUMBER,
62 	   p_allow_interest_invoices         IN	           VARCHAR2, --Bug4113223
63            p_calling_sequence            IN            VARCHAR2)
64 RETURN BOOLEAN IS
65 
66   check_inv_validation_failure  EXCEPTION;
67   import_invoice_failure	EXCEPTION;
68 
69   l_current_invoice_status      VARCHAR2(1) := 'Y';
70   l_vendor_id                   PO_VENDORS.VENDOR_ID%TYPE;
71   l_vendor_site_id              PO_VENDOR_SITES.VENDOR_SITE_ID%TYPE;
72   l_vendor_site_id_per_po       PO_VENDOR_SITES.VENDOR_SITE_ID%TYPE;
73   l_invoice_num                 AP_INVOICES.INVOICE_NUM%TYPE;
74   l_inv_currency_code           AP_INVOICES.INVOICE_CURRENCY_CODE%TYPE;
75   l_exchange_rate               AP_INVOICES.EXCHANGE_RATE%TYPE;
76   l_exchange_date               AP_INVOICES.EXCHANGE_DATE%TYPE;
77   l_invoice_type_lookup_code    AP_INVOICES.INVOICE_TYPE_LOOKUP_CODE%TYPE;
78   l_awt_group_id                AP_INVOICES.AWT_GROUP_ID%TYPE;
79   l_pay_awt_group_id            AP_INVOICES.PAY_AWT_GROUP_ID%TYPE;--bug6639866
80   l_terms_id                    AP_INVOICES.TERMS_ID%TYPE;
81   l_terms_date                  AP_INVOICES.TERMS_DATE%TYPE;
82   l_pay_currency_code           AP_INVOICES.PAYMENT_CURRENCY_CODE%TYPE;
83   l_pay_cross_rate_date         AP_INVOICES.PAYMENT_CROSS_RATE_DATE%TYPE;
84   l_pay_cross_rate              AP_INVOICES.PAYMENT_CROSS_RATE%TYPE;
85   l_pay_cross_rate_type         AP_INVOICES.PAYMENT_CROSS_RATE_TYPE%TYPE;
86   l_invoice_base_amount         AP_INVOICES.BASE_AMOUNT%TYPE;
87   l_temp_invoice_status         VARCHAR2(1) := 'Y';
88   l_po_exists_flag              VARCHAR2(1) := 'N';
89   current_calling_sequence      VARCHAR2(2000);
90   debug_info                    VARCHAR2(500);
91   l_terms_date_basis            VARCHAR2(25);
92   l_primary_paysite_id          PO_VENDOR_SITES.VENDOR_SITE_ID%TYPE;
93   --For bug 2713327 Added temporary variable to hold the value of
94   --vendor_id in the interface table
95   l_temp_vendor_id                NUMBER(15) := p_invoice_rec.vendor_id;
96   --Bug 4051803
97   l_positive_price_tolerance      NUMBER;
98   l_negative_price_tolerance      NUMBER;
99   l_qty_tolerance                 NUMBER;
100   l_qty_rec_tolerance             NUMBER;
101   l_max_qty_ord_tolerance         NUMBER;
102   l_max_qty_rec_tolerance         NUMBER;
103   l_max_amt_ord_tolerance         NUMBER;
104   l_max_amt_rec_tolerance         NUMBER;
105   l_ship_amt_tolerance            NUMBER;
106   l_rate_amt_tolerance            NUMBER;
107   l_total_amt_tolerance           NUMBER;
108 
109   l_party_site_id                 NUMBER(15);
110   /* 9738820 additional parameters */
111   l_country_code                  HR_LOCATIONS_ALL.COUNTRY%TYPE;
112   l_return_status                 VARCHAR2(1);
113   l_msg_count                     NUMBER;
114   l_msg_data                      VARCHAR2(1000);
115   /* End Bug 9738820 parameters */
116 
117 BEGIN
118 
119   -- Update the calling sequence
120   current_calling_sequence :=
121              'AP_IMPORT_VALIDATION_PKG.v_check_invoice_validation<-'
122              ||P_calling_sequence;
123 
124   --------------------------------------------------------------------------
125   -- Step 0a
126   -- Initialize invoice_date if null
127   --------------------------------------------------------------------------
128   debug_info := '(Check Invoice Validation 0) Initialize invoice_date if null';
129   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
130     AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
131                                   debug_info);
132   END IF;
133 
134   IF (p_invoice_rec.invoice_date IS NULL) THEN
135     p_invoice_rec.invoice_date := trunc(AP_IMPORT_INVOICES_PKG.g_inv_sysdate);
136     -- bug 8497933
137     l_is_inv_date_null := 'Y';
138   ELSE
139     l_is_inv_date_null := 'N';
140     -- bug 8497933
141   END IF;
142 
143   --------------------------------------------------------------------------
144   -- Step 1
145   -- Check for Invalid or Inactive PO
146   --------------------------------------------------------------------------
147   debug_info :=
148      '(Check Invoice Validation 1) Check for Invalid and Inactive PO';
149   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
150     AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
151                                   debug_info);
152   END IF;
153   --
154   IF (p_invoice_rec.po_number IS NOT NULL) THEN
155     -- IF PO Number is given , we should not check for Supplier Number
156     -- or Supplier Site.  PO Number can also be used for this check, but a
157     -- flag is set for this purpose.
158     l_po_exists_flag := 'Y';
159 
160     IF (AP_IMPORT_VALIDATION_PKG.v_check_invalid_po (
161           p_invoice_rec,                                  -- IN
162           p_default_last_updated_by,                      -- IN
163           p_default_last_update_login,                    -- IN
164           l_temp_invoice_status,                          -- OUT
165           p_po_vendor_id      => l_vendor_id,             -- OUT
166           p_po_vendor_site_id => l_vendor_site_id_per_po, -- OUT
167           p_po_exists_flag    => l_po_exists_flag,        -- OUT
168           p_calling_sequence  => current_calling_sequence) <> TRUE )THEN
169       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
170         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
171                      'v_check_invalid_po<-'||current_calling_sequence);
172       END IF;
173       RAISE check_inv_validation_failure;
174     END IF;
175 
176     -- We need to set the current status to 'N' only if the temp invoice status
177     -- returns 'N'. So all temp returns of 'N' will overwrite the current
178     -- invoice status to 'N' which finally would be returned to the calling
179     -- function.
180     IF (l_temp_invoice_status = 'N') THEN
181       l_current_invoice_status := l_temp_invoice_status;
182     END IF;
183 
184     --
185     -- show output values (only if debug_switch = 'Y')
186     --
187     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
188       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
189                 '------------------>
190                 l_temp_invoice_status   = '||l_temp_invoice_status
191             ||' l_vendor_id             = '||to_char(l_vendor_id)
192             ||' l_vendor_site_id_per_po = '||to_char(l_vendor_site_id_per_po)
193             ||' l_po_exists_flag        = '||l_po_exists_flag);
194     END IF;
195 
196     -- It is possible to create a PO for a Supplier / Supplier Site
197     -- that has been end dated or in some other way invalidated
198     -- before running  the import.  If the PO exists it is assumed
199     -- that the Supplier /  Supplier Site is valid.  This allows an
200     -- invoice to be created for an invalid Supplier / Supplier Site.
201     -- We no longer check the PO flag before validating the Supplier
202     -- info.  Also since we are no longer assuming a correct Supplier
203     -- if the PO exists, we have to get the  vendor_id from the PO if
204     -- it is not in the Interface table row.
205     IF (p_invoice_rec.vendor_id IS NULL AND l_po_exists_flag = 'Y') then
206       p_invoice_rec.vendor_id := l_vendor_id;
207     END IF;
208 
209   END IF; -- p_invoice_rec.po_number is not null
210 
211   ---------------------------------------------------------------------------
212   -- Step 2
213   -- Check for Invalid or Inconsistent Legal Entity Name and Id
214   ---------------------------------------------------------------------------
215   debug_info := '(Check Invoice Validation 2) Check for Invalid Legal Entity';
216   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
217     AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
218                                   debug_info);
219   END IF;
220 
221 -- YIDSAL.  Include here call the validate function for the LE Id and NaMe
222 --  Surekha will give us the API name.
223 
224   ---------------------------------------------------------------------------
225   -- Step 3
226   -- Check for Invalid Supplier or Inconsistent Supplier
227   ---------------------------------------------------------------------------
228   debug_info := '(Check Invoice Validation 2) Check for Invalid Supplier';
229   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
230     AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
231                                   debug_info);
232   END IF;
233 
234   -- Added party validation for payment request project
235   IF p_invoice_rec.invoice_type_lookup_code = 'PAYMENT REQUEST' THEN
236 
237      IF (AP_IMPORT_VALIDATION_PKG.v_check_invalid_party (
238         p_invoice_rec,                                       -- IN
239         p_default_last_updated_by,                           -- IN
240         p_default_last_update_login,                         -- IN
241         p_current_invoice_status => l_temp_invoice_status,   -- IN OUT
242         p_calling_sequence       => current_calling_sequence) <> TRUE )THEN
243         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
244           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
245             'v_check_invalid_party <-'||current_calling_sequence);
246         END IF;
247         RAISE check_inv_validation_failure;
248       END IF;
249 
250   ELSE
251 
252       IF (AP_IMPORT_VALIDATION_PKG.v_check_invalid_supplier (
253             p_invoice_rec,                                       -- IN
254             p_default_last_updated_by,                           -- IN
255             p_default_last_update_login,                         -- IN
256             p_return_vendor_id       => l_vendor_id,             -- OUT
257             p_current_invoice_status => l_temp_invoice_status,   -- IN OUT
258             p_calling_sequence       => current_calling_sequence) <> TRUE )THEN
259         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
260           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
261             'v_check_invalid_supplier<-'||current_calling_sequence);
262         END IF;
263         RAISE check_inv_validation_failure;
264       END IF;
265 
266       IF p_invoice_rec.vendor_id IS NULL  THEN
267          p_invoice_rec.vendor_id := l_vendor_id;
268 
269       END IF;
270 
271   END IF;
272 
273  --For bug 2713327 changed p_invoice_rec.vendor_id to l_temp_vendor_id
274  --At this point the value of p_invoice_rec.vendor_id will not be NULL as
275  --it would have been retrieved from PO if one exists or it would have been keyed in.
276  --So the value of vendor id in interface table should be updated with correct value
277  --for retrieving the output as it is checking for ii.vendor_id=i.vendor_id in
278  --the query Q_AUDIT
279 
280  --added nvl for bug 7314487
281   IF l_temp_vendor_id is NULL
282               AND nvl(p_invoice_rec.invoice_type_lookup_code,'STANDARD') <> 'PAYMENT REQUEST'
283   THEN UPDATE ap_invoices_interface
284        SET vendor_id = l_vendor_id
285        WHERE invoice_id = p_invoice_rec.invoice_id;
286   END IF;
287 
288   IF (l_temp_invoice_status = 'N') THEN
289     l_current_invoice_status := l_temp_invoice_status;
290   END IF;
291 
292   debug_info := '(Check Invoice Validation 2) Validated Supplier';
293   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
294     AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
295                                   debug_info);
296   END IF;
297   --
298   -- show output values (only if debug_switch = 'Y')
299   --
300   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
301     AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
302           '------------------>
303             l_temp_invoice_status  = '||l_temp_invoice_status
304         ||' l_vendor_id             = '||to_char(l_vendor_id));
305   END IF;
306 
307   IF (p_invoice_rec.vendor_id is NOT NULL)
308            OR (p_invoice_rec.party_id IS NOT NULL) THEN
309 
310     -------------------------------------------------------------------------
311     -- Step 4
312     -- Check for Invalid Supplier Site only if there is a valid Supplier
313     -- Also, populate vendor_site_id if all the following
314     -- conditions are met:
315     -- 1) vendor_site_id is null
316     -- 2) vendor_site_id could be derived in the find primary paysite function
317     --    or the vendor site check function
318     -- 3) if either the find primary paysite succeded or the vendor site
319     --    check function returned that the invoice is valid
320     --    as far as vendor site is concerned.
321     -------------------------------------------------------------------------
322     debug_info := '(Check Invoice Validation 3) '||
323                    'Check for Invalid Supplier Site, if Supplier is valid';
324     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
325       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
326                                     debug_info);
327     END IF;
328 
329 
330     -- Payment Request: Added Payment Request invoice type to the IF condition
331 
332     -- Check for invalid supplier site.  If an invalid supplier site exists,
333     -- or inconsistent data exists, this is a fatal error.
334     -- Do not perform further validation.  If a valid vendor site exists,
335     -- the function will return the value of the vendor site.
336     IF ((p_invoice_rec.vendor_site_id is null) and
337         (p_invoice_rec.vendor_site_code is null) and
338         --(p_invoice_rec.invoice_type_lookup_code <> 'PAYMENT REQUEST')) Then   .. B# 8528132
339         (nvl(p_invoice_rec.invoice_type_lookup_code, 'STANDARD') <> 'PAYMENT REQUEST')) Then   -- B# 8528132
340 
341       debug_info := '(Check Invoice Validation 3.1) Supplier Site is per PO';
342       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
343         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
344                                       debug_info);
345       END IF;
346 
347       IF (AP_IMPORT_UTILITIES_PKG.find_vendor_primary_paysite(
348             p_vendor_id                  => p_invoice_rec.vendor_id, -- IN
349             p_vendor_primary_paysite_id  => l_primary_paysite_id,    -- OUT
350             p_calling_sequence           => current_calling_sequence)
351             <> true ) THEN
352         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
353           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
354             'find_vendor_primary_paysite<-'||current_calling_sequence);
355         END IF;
356         RAISE check_inv_validation_failure;
357       END IF;
358 
359       IF (l_primary_paysite_id is NOT NULL ) THEN
360         p_invoice_rec.vendor_site_id := l_primary_paysite_id;
361       ELSE
362         p_invoice_rec.vendor_site_id := l_vendor_site_id_per_po;
363       END IF;
364 
365     ELSE
366       debug_info := '(Check Invoice Validation 3.2) Supplier Site is per EDI';
367       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
368         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
369           debug_info);
370       END IF;
371 
372     END IF;
373 
374 
375     --Bug8323165 Start
376     IF (p_invoice_rec.invoice_type_lookup_code = 'PAYMENT REQUEST' AND
377         NVL(p_invoice_rec.source,'A') NOT IN
378        ('CREDIT CARD','SelfService','Both Pay','XpenseXpress')) THEN
379 
380         IF (AP_IMPORT_VALIDATION_PKG.v_check_invalid_party_site (
381               p_invoice_rec,                                       -- IN
382               p_default_last_updated_by,                           -- IN
383               p_default_last_update_login,                         -- IN
384               p_return_party_site_id    => l_party_site_id,        -- OUT
385               p_terms_date_basis        => l_terms_date_basis,     -- OUT
386               p_current_invoice_status  => l_temp_invoice_status,  -- IN OUT
387               p_calling_sequence => current_calling_sequence) <> TRUE ) THEN
388 
389           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
390             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
391                                   'v_check_invalid_party_site<-'
392                                   ||current_calling_sequence);
393           END IF;
394           RAISE check_inv_validation_failure;
395         END IF;
396         p_invoice_rec.party_site_id := l_party_site_id;
397     ELSE
398         IF (p_invoice_rec.invoice_type_lookup_code = 'PAYMENT REQUEST'
399             OR (p_invoice_rec.invoice_type_lookup_code = 'EXPENSE REPORT'
400             AND p_invoice_rec.party_site_id IS NOT NULL)
401             AND NVL(p_invoice_rec.source,'A') IN ('CREDIT CARD','SelfService'
402                 ,'Both Pay','XpenseXpress')) THEN
403 
404             IF (AP_IMPORT_VALIDATION_PKG.v_check_invalid_party_site (
405               p_invoice_rec,                                       -- IN
406               p_default_last_updated_by,                           -- IN
407               p_default_last_update_login,                         -- IN
408               p_return_party_site_id    => l_party_site_id,        -- OUT
409               p_terms_date_basis        => l_terms_date_basis,     -- OUT
410               p_current_invoice_status  => l_temp_invoice_status,  -- IN OUT
411               p_calling_sequence => current_calling_sequence) <> TRUE ) THEN
412 
413               IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
414                   AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
415                                   'v_check_invalid_party_site<-'
416                                   ||current_calling_sequence);
417               END IF;
418               RAISE check_inv_validation_failure;
419             END IF;
420             p_invoice_rec.party_site_id := l_party_site_id;
421         END IF;
422 
423         IF (AP_IMPORT_VALIDATION_PKG.v_check_invalid_supplier_site (
424             p_invoice_rec,                                       -- IN
425             l_vendor_site_id_per_po,                             -- IN
426             p_default_last_updated_by,                           -- IN
427             p_default_last_update_login,                         -- IN
428             p_return_vendor_site_id   => l_vendor_site_id,       -- OUT
429             p_terms_date_basis        => l_terms_date_basis,     -- OUT
430             p_current_invoice_status  => l_temp_invoice_status,  -- IN OUT
431             p_calling_sequence => current_calling_sequence) <> TRUE ) THEN
432 
433               IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
434                 AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
435                                       'v_check_invalid_supplier_site<-'
436                                       ||current_calling_sequence);
437               END IF;
438               RAISE check_inv_validation_failure;
439             END IF;
440             p_invoice_rec.vendor_site_id := l_vendor_site_id;
441     END IF;
442     --Bug8323165 End
443 
444     IF (l_temp_invoice_status = 'N') THEN
445       l_current_invoice_status := l_temp_invoice_status;
446     /*ELSE
447       --Bug 6711062
448       IF (p_invoice_rec.invoice_type_lookup_code = 'PAYMENT REQUEST'
449             OR (p_invoice_rec.invoice_type_lookup_code = 'EXPENSE REPORT' --Bug 8247859
450             AND p_invoice_rec.party_site_id is NOT NULL))  THEN --Bug 8247859
451          p_invoice_rec.party_site_id := l_party_site_id;
452       ELSE
453          p_invoice_rec.vendor_site_id := l_vendor_site_id;
454          p_invoice_rec.party_site_id := l_party_site_id;
455       END IF;*/ --Removed this assignment immediately after calling validation of party site and vendor site
456     END IF;
457 
458     debug_info := '(Check Invoice Validation 3) Validated Supplier Site';
459     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
460       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
461                                     debug_info);
462     END IF;
463 
464     --
465     -- show output values (only if debug_switch = 'Y')
466     --
467     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
468       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
469             '------------------>
470             l_temp_invoice_status        = '||l_temp_invoice_status
471         ||' l_vendor_site_id         = '||to_char(l_vendor_site_id)
472         ||' l_party_site_id          = '||to_char(l_party_site_id));
473 
474     END IF;
475 
476 
477 
478     --we should make sure the party and supplier info is consistent as well as
479     --populate the id's that may be missing
480 
481     if(AP_IMPORT_VALIDATION_PKG.v_check_party_vendor(
482         p_invoice_rec,
483         l_temp_invoice_status,
484         current_calling_sequence,
485         p_default_last_updated_by,
486         p_default_last_update_login) <> TRUE) then
487       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
488               AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
489                                         'v_check_party_vendor<-'
490                                         ||current_calling_sequence);
491       END IF;
492       RAISE check_inv_validation_failure;
493     END IF;
494 
495     IF (l_temp_invoice_status = 'N') THEN
496       l_current_invoice_status := l_temp_invoice_status;
497     END IF;
498 
499     debug_info := '(Check Invoice Validation 3.5) Validated party and vendor info ' ||
500                   'l_temp_invoice_status = '||l_temp_invoice_status;
501     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
502       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
503                                     debug_info);
504     END IF;
505 
506 
507 
508     --Bug:4051803
509     --Contract Payments: Tolerances Redesign, added the max_amt_ord and max_amt_rec
510     --tolerances.
511     IF (p_invoice_rec.vendor_site_id IS NOT NULL AND
512           --p_invoice_rec.invoice_type_lookup_code <> 'PAYMENT REQUEST') THEN   .. B# 8528132
513           nvl(p_invoice_rec.invoice_type_lookup_code, 'STANDARD') <> 'PAYMENT REQUEST') Then   -- B# 8528132
514        IF ( ap_import_utilities_pkg.get_tolerance_info(
515        		p_invoice_rec.vendor_site_id,   -- IN
516 		p_positive_price_tolerance,     -- OUT
517 		p_negative_price_tolerance,     -- OUT
518 	        p_qty_tolerance,                -- OUT
519 	        p_qty_rec_tolerance,            -- OUT
520 	        p_max_qty_ord_tolerance,        -- OUT
521 	        p_max_qty_rec_tolerance,        -- OUT
522 		p_amt_tolerance,		-- OUT
523 		p_amt_rec_tolerance,		-- OUT
524 		p_max_amt_ord_tolerance,        -- OUT
525 	        p_max_amt_rec_tolerance,        -- OUT
526 	        p_goods_ship_amt_tolerance,     -- OUT
527 	        p_goods_rate_amt_tolerance,     -- OUT
528 	        p_goods_total_amt_tolerance,    -- OUT
529 		p_services_ship_amt_tolerance,  -- OUT
530 	        p_services_rate_amt_tolerance,  -- OUT
531 	        p_services_total_amt_tolerance, -- OUT
532 	        current_calling_sequence
533 	        ) <> TRUE) THEN
534 
535              if AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' then
536                 AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch, 'get_tolerance_info()<-'||
537 	                     current_calling_sequence);
538              end if;
539              RAISE import_invoice_failure;
540         END IF;
541     END IF;
542 
543 
544     IF ((p_invoice_rec.vendor_site_id is NOT NULL)
545             OR (p_invoice_rec.party_site_id IS NOT NULL)) THEN
546 
547       -----------------------------------------------------------------------
548       -- Step 5
549       -- Check for invoice number already in use within either
550       -- the permanent tables or interface tables.  If the invoice
551       -- number is already in use, this is a fatal error.  Do not
552       -- perform further validation checking.
553       -- Check performed only if there is a valid Supplier and Supplier Site
554       -----------------------------------------------------------------------
555       debug_info := '(Check Invoice Validation 4) '||
556                      'Check for Invalid Invoice Number '||
557                      ',if Supplier Site is valid';
558       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
559         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
560                                       debug_info);
561       END IF;
562 
563       IF (AP_IMPORT_VALIDATION_PKG.v_check_invalid_invoice_num (
564             p_invoice_rec,                                           -- IN
565 	    --bug4113223
566 	    p_allow_interest_invoices,				     -- IN
567             l_invoice_num,                                           -- OUT
568             p_default_last_updated_by,                               -- IN
569             p_default_last_update_login,                             -- IN
570             p_current_invoice_status     => l_temp_invoice_status,   -- IN OUT
571             p_calling_sequence           => current_calling_sequence)
572             <> TRUE ) THEN
573         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
574           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
575             'v_check_invalid_invoice_num<- '||current_calling_sequence);
576         END IF;
577         RAISE check_inv_validation_failure;
578       END IF;
579 
580       IF (l_temp_invoice_status = 'N') THEN
581         l_current_invoice_status := l_temp_invoice_status;
582       ELSE
583         IF (p_invoice_rec.invoice_num is NULL AND
584         l_invoice_num is not NULL) THEN
585           p_invoice_rec.invoice_num := l_invoice_num;
586         END IF;
587       END IF;
588 
589       --
590       -- show output values (only if debug_switch = 'Y')
591       --
592       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
593         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
594         '------------------> l_temp_invoice_status  = '||l_temp_invoice_status);
595       END IF;
596 
597       -- only continue if a valid invoice number was found
598       IF l_current_invoice_status = 'Y' THEN
599 
600         -----------------------------------------------------------------------
601         -- Step 6
602         -- Check for Invalid Currency Code only if there is a valid Invoice No
603         -- Also, populate currency code if all the following
604         -- conditions are met:
605         -- 1) invoice_currency_code is null
606         -- 2) invoice_currency_code could be derived in the inv curr
607         --    check function
608         -- 3) the inv curr check function returned that the invoice is valid
609         --    as far as inv currency code is concerned.
610         -----------------------------------------------------------------------
611         debug_info := '(Check Invoice Validation 5) Check for Currency Code ,'
612                       ||'if Invoice No. is valid';
613         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
614           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
615                                         debug_info);
616         END IF;
617 
618         IF (AP_IMPORT_VALIDATION_PKG.v_check_invalid_inv_curr_code (
619             p_invoice_rec,                                             -- IN
620             p_inv_currency_code      => l_inv_currency_code,           -- OUT
621             p_min_acc_unit_inv_curr  => p_min_acct_unit_inv_curr,      -- OUT
622             p_precision_inv_curr     => p_precision_inv_curr,          -- OUT
623             p_default_last_updated_by => p_default_last_updated_by,    -- IN
624             p_default_last_update_login => p_default_last_update_login,-- IN
625             p_current_invoice_status => l_temp_invoice_status,         -- IN OUT
626             p_calling_sequence       => current_calling_sequence)
627               <> TRUE ) THEN
628           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
629             AP_IMPORT_UTILITIES_PKG.Print(
630               AP_IMPORT_INVOICES_PKG.g_debug_switch,
631               'v_check_invalid_currency_code<-'||current_calling_sequence);
632           END IF;
633           RAISE check_inv_validation_failure;
634         END IF;
635 
636         IF (l_temp_invoice_status = 'N') THEN
637           l_current_invoice_status := l_temp_invoice_status;
638         ELSE
639           IF (p_invoice_rec.invoice_currency_code is NULL AND
640               l_inv_currency_code is not NULL) THEN
641             p_invoice_rec.invoice_currency_code := l_inv_currency_code;
642           END IF;
643         END IF;
644         --
645 
646         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
647           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
648             '--------------> l_temp_invoice_status  = ' ||l_temp_invoice_status
649             ||' l_inv_currency_code = '|| l_inv_currency_code);
650         END IF;
651 
652         ----------------------------------------------------------------------
653         -- Step 7
654         -- Check for Invalid Invoice Lookup Code and Amt.
655         -- only if there is a valid Invoice No.
656         -- Also, populate invoice type lookup code if all the following
657         -- conditions are met:
658         -- 1) invoice_type_lookup_code is null null
659         -- 2) invoice_type lookup_code could be derived in the invoice type
660         --    check function and
661         -- 3) the invoice type check function returned that the invoice is
662         --    valid as far as invoice type/amount information is concerned.
663         ----------------------------------------------------------------------
664         debug_info := '(Check Invoice Validation 6) Check for Invoice Lookup '
665                       ||'Code and Amount ,if Invoice No. is valid';
666         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
667           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
668                                         debug_info);
669         END IF;
670 
671         IF (AP_IMPORT_VALIDATION_PKG.v_check_invoice_type_amount (
672               p_invoice_rec,                                          -- IN
673               l_invoice_type_lookup_code,                             -- OUT
674               p_match_mode,                                           -- OUT
675               p_precision_inv_curr,                                   -- IN
676               p_default_last_updated_by,                              -- IN
677               p_default_last_update_login,                            -- IN
678               p_current_invoice_status     => l_temp_invoice_status,  -- IN OUT
679               p_calling_sequence           => current_calling_sequence)
680               <> TRUE ) THEN
681           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
682             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
683               'v_check_invoice_type_amount<-'||current_calling_sequence);
684           END IF;
685           RAISE check_inv_validation_failure;
686         END IF;
687 
688         IF (l_temp_invoice_status = 'N') THEN
689           l_current_invoice_status := l_temp_invoice_status;
690         ELSE
691           IF (p_invoice_rec.invoice_type_lookup_code is NULL AND
692               l_invoice_type_lookup_code is not NULL) THEN
693             p_invoice_rec.invoice_type_lookup_code :=
694                                 l_invoice_type_lookup_code;
695           END IF;
696         END IF;
697 
698         --
699         -- show output values (only if debug_switch = 'Y')
700         --
701         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
702           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
703             '------------------>
704             l_temp_invoice_status  = '||l_temp_invoice_status
705             ||' p_match_mode = '||p_match_mode);
706         END IF;
707 
708         ----------------------------------------------------------------------
709         -- Step 8
710         -- Check for Invalid AWT Group only if there is a valid Invoice No.
711         -- Also, populate awt_group_id if all the following conditions are met:
712         -- 1) awt_group_id is null
713         -- 2) awt_group_id could be derived in the awt group check function
714         -- 3) the awt group check function returned that the invoice is valid
715         --    as far as awt group information is concerned.
716         ----------------------------------------------------------------------
717         debug_info := '(Check Invoice Validation 7) Check for AWT Group ,'
718                        ||'if Invoice No. is valid';
719         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
720           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
721                                         debug_info);
722         END IF;
723 
724         IF (AP_IMPORT_VALIDATION_PKG.v_check_invalid_awt_group(
725            p_invoice_rec,                                             -- IN
726            p_awt_group_id              => l_awt_group_id,             -- OUT
727            p_default_last_updated_by   => p_default_last_updated_by,  -- IN
728            p_default_last_update_login => p_default_last_update_login,-- IN
729            p_current_invoice_status  => l_temp_invoice_status,      -- IN OUT
730            p_calling_sequence        => current_calling_sequence)
731               <> TRUE ) THEN
732           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
733             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
734               'v_check_invalid_awt_group<-'||current_calling_sequence);
735           END IF;
736           RAISE check_inv_validation_failure;
737         END IF;
738 
739         --
740         IF (l_temp_invoice_status = 'N') THEN
741           l_current_invoice_status := l_temp_invoice_status;
742         ELSE
743           IF (p_invoice_rec.awt_group_id is NULL AND
744               l_awt_group_id is NOT NULL) THEN
745             p_invoice_rec.awt_group_id := l_awt_group_id;
746           END IF;
747         END IF;
748 
749         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
750           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
751             '------------------>
752             l_temp_invoice_status  = '||l_temp_invoice_status);
753         END IF;
754        --bug6639866
755         ----------------------------------------------------------------------
756         -- Step 8.1
757         -- Check for Invalid pay AWT Group only if there is a valid Invoice No.
758         -- Also, populate pay_awt_group_id if all the following conditions are met:
759         -- 1) pay_awt_group_id is null
760         -- 2) pay_awt_group_id could be derived in the pay awt group check function
761         -- 3) the pay awt group check function returned that the invoice is valid
762         --    as far as pay awt group information is concerned.
763         ----------------------------------------------------------------------
764         debug_info := '(Check Invoice Validation 7) Check for pay AWT Group ,'
765                        ||'if Invoice No. is valid';
766         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
767           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
768                                         debug_info);
769         END IF;
770 
771         IF (AP_IMPORT_VALIDATION_PKG.v_check_invalid_pay_awt_group(
772            p_invoice_rec,                                             -- IN
773            p_pay_awt_group_id              => l_pay_awt_group_id,     -- OUT
774            p_default_last_updated_by   => p_default_last_updated_by,  -- IN
775            p_default_last_update_login => p_default_last_update_login,-- IN
776            p_current_invoice_status  => l_temp_invoice_status,      -- IN OUT
777            p_calling_sequence        => current_calling_sequence)
778               <> TRUE ) THEN
779           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
780             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
781               'v_check_invalid_pay_awt_group<-'||current_calling_sequence);
782           END IF;
783           RAISE check_inv_validation_failure;
784         END IF;
785 
786         --
787         IF (l_temp_invoice_status = 'N') THEN
788           l_current_invoice_status := l_temp_invoice_status;
789         ELSE
790         IF (p_invoice_rec.pay_awt_group_id is NULL AND
791               l_pay_awt_group_id is NOT NULL) THEN
792             p_invoice_rec.pay_awt_group_id := l_pay_awt_group_id;
793           END IF;
794         END IF;
795 
796         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
797           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
798             '------------------>
799             l_temp_invoice_status  = '||l_temp_invoice_status);
800         END IF;
801 
802         ----------------------------------------------------------------------
803         -- Step 9
804         -- Check for Invalid Exchange Rate Type only if there is a valid
805         -- Invoice No.
806         -- Also, populate exchange_rate, exchange_rate_type and
807         -- exchange_rate_date if all the following conditions are met:
808         -- 1) exchange_rate, exchange_rate_type and/or exchange_rate_date are
809         --    null
810         -- 2) the exchange rate type check could derived value for those
811         --    columns
812         -- 3) the exchange rate type check returned that the invoice is valid
813         --    as far as exchange rate is concerned.
814         ----------------------------------------------------------------------
815         debug_info := '(Check Invoice Validation 8) Check for Exchange Rate '
816                        ||'Type ,if Invoice No. is valid';
817         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
818           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
819                                         debug_info);
820         END IF;
821 
822         IF (AP_IMPORT_VALIDATION_PKG.v_check_exchange_rate_type (
823             p_invoice_rec,                                        -- IN
824             p_exchange_rate            => l_exchange_rate,        -- OUT
825             p_exchange_date            => l_exchange_date,        -- OUT
826             p_base_currency_code => p_base_currency_code,         -- IN
827             p_multi_currency_flag => p_multi_currency_flag,       -- IN
828             p_set_of_books_id => p_set_of_books_id,               -- IN
829             p_default_exchange_rate_type => p_default_exchange_rate_type, -- IN
830             p_make_rate_mandatory_flag => p_make_rate_mandatory_flag,  -- IN
831             p_default_last_updated_by => p_default_last_updated_by,    -- IN
832             p_default_last_update_login => p_default_last_update_login,-- IN
833             p_current_invoice_status    => l_temp_invoice_status, -- IN OUT
834             p_calling_sequence          => current_calling_sequence)
835               <> TRUE ) THEN
836           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
837             AP_IMPORT_UTILITIES_PKG.Print(
838               AP_IMPORT_INVOICES_PKG.g_debug_switch,
839               'v_check_exchange_rate_type<-'||current_calling_sequence);
840           END IF;
841           RAISE check_inv_validation_failure;
842         END IF;
843 
844         IF (l_temp_invoice_status = 'N') THEN
845           l_current_invoice_status := l_temp_invoice_status;
846         ELSE
847           IF (p_invoice_rec.exchange_rate_type IS NULL AND
848               p_default_exchange_rate_type IS NOT NULL AND
849               p_invoice_rec.invoice_currency_code <> p_base_currency_code) THEN
850             p_invoice_rec.exchange_rate_type := p_default_exchange_rate_type;
851           END IF;
852           IF (p_invoice_rec.exchange_rate is NULL AND
853               l_exchange_rate is NOT NULL) THEN
854             p_invoice_rec.exchange_rate := l_exchange_rate;
855           END IF;
856           IF (p_invoice_rec.exchange_date is NULL AND
857               l_exchange_date is NOT NULL) THEN
858             p_invoice_rec.exchange_date := l_exchange_date;
859           END IF;
860 	  /*Bug 8887650 begin*/
861            IF (p_invoice_rec.invoice_currency_code = p_base_currency_code)
862 	      AND NOT (p_invoice_rec.exchange_rate_type IS NULL
863 	               AND p_invoice_rec.exchange_rate is NULL
864 		       AND p_invoice_rec.exchange_date is NULL) THEN
865 
866               p_invoice_rec.exchange_rate_type := NULL;
867               p_invoice_rec.exchange_rate := NULL;
868               p_invoice_rec.exchange_date := NULL;
869            END IF;
870 	  /*Bug 8887650 End*/
871         END IF;
872 
873         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
874           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
875            '------------------>
876             l_temp_invoice_status  = '||l_temp_invoice_status);
877         END IF;
878 
879         ---------------------------------------------------------------------
880         -- Step 10
881         -- Check for Invalid Terms Info only if there is a valid Invoice No.
882         -- If PO Number exists then get terms from PO.
883         -- Also, populate terms_id and terms_date if all the following
884         -- conditions are met:
885         -- 1) terms id and/or terms date are null
886         -- 2) values for terms id and/or terms date could be derived
887         --    in the terms check function
888         -- 3) the terms date function returned that the invoice is valid
889         --    as far as terms are concerned.
890         ----------------------------------------------------------------------
891         debug_info := '(Check Invoice Validation 9) Check for Terms Info ,'
892                       ||'if Invoice No. is valid';
893         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
894           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
895                                         debug_info);
896         END IF;
897 
898         IF (AP_IMPORT_VALIDATION_PKG.v_check_invalid_terms (
899               p_invoice_rec,                                         -- IN
900               p_terms_id                  => l_terms_id,             -- OUT
901               p_terms_date                => l_terms_date,           -- OUT
902               p_terms_date_basis          => l_terms_date_basis,     -- IN
903               p_default_last_updated_by => p_default_last_updated_by,    -- IN
904               p_default_last_update_login => p_default_last_update_login,-- IN
905               p_current_invoice_status    => l_temp_invoice_status,  -- IN OUT
906               p_calling_sequence          => current_calling_sequence)
907               <> TRUE ) THEN
908           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
909         AP_IMPORT_UTILITIES_PKG.Print(
910         AP_IMPORT_INVOICES_PKG.g_debug_switch,
911                 'v_check_invalid_terms<-'||current_calling_sequence);
912           END IF;
913           RAISE check_inv_validation_failure;
914         END IF;
915 
916         IF (l_temp_invoice_status = 'N') THEN
917           l_current_invoice_status := l_temp_invoice_status;
918         ELSE
919           IF (p_invoice_rec.terms_id is NULL AND
920               l_terms_id is NOT NULL) THEN
921             p_invoice_rec.terms_id := l_terms_id;
922         END IF;
923       IF (p_invoice_rec.terms_date IS NULL AND
924           l_terms_date IS NOT NULL) THEN
925         p_invoice_rec.terms_date := l_terms_date;
926       END IF;
927         END IF;
928 
929         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
930           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
931             '------------------>
932             l_temp_invoice_status  = '||l_temp_invoice_status
933             ||'terms_id = '||to_char(l_terms_id) );
934         END IF;
935 
936         ----------------------------------------------------------------------
937         -- Step 11
938         -- Check for Misc Invoice info
939         ----------------------------------------------------------------------
940         debug_info := '(Check Invoice Validation 10) Check for Misc Info ';
941         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
942           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
943                                         debug_info);
944         END IF;
945         IF (AP_IMPORT_VALIDATION_PKG.v_check_misc_invoice_info (
946               p_invoice_rec,                                         -- IN
947               p_set_of_books_id,                                     -- IN
948               p_default_last_updated_by,                             -- IN
949               p_default_last_update_login,                           -- IN
950               p_current_invoice_status     => l_temp_invoice_status, -- IN OUT
951               p_calling_sequence           => current_calling_sequence)
952               <> TRUE ) THEN
953           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
954             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
955               'v_check_misc_invoice_info<-'||current_calling_sequence);
956           END IF;
957           RAISE check_inv_validation_failure;
958         END IF;
959 
960         IF (l_temp_invoice_status = 'N') THEN
961           l_current_invoice_status := l_temp_invoice_status;
962         END IF;
963 
964         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
965           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
966             '------------------>
967             l_temp_invoice_status  = '||l_temp_invoice_status);
968         END IF;
969 
970          /* -------------------------------------------------------------------
971             Step 11a: Get/Validate Legal Entity Information
972                There are two forms of LE derivation.
973                1) Internal products could optionally pass the LE in the
974                   LEGAL_ENTITY_ID Column. This will be validated by the API
975                   provided by LE Team.
976 
977                2)For the invoices coming via EDI, XML, they could
978                  provide us with Customer Registration CODE/Numbers, which
979                  will be used to derive the LE using a LE API.
980         --------------------------------------------------------------------*/
981         debug_info := '(Check Invoice Validation 11a) Check for LE Info ';
982         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
983           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
984                                         debug_info);
985         END IF;
986 
987         IF (AP_IMPORT_VALIDATION_PKG.v_check_Legal_Entity_info (
988               p_invoice_rec,                                         -- IN OUT
989               p_set_of_books_id,                                     -- IN
990               p_default_last_updated_by,                             -- IN
991               p_default_last_update_login,                           -- IN
992               p_current_invoice_status     => l_temp_invoice_status, -- IN OUT
993               p_calling_sequence           => current_calling_sequence)
994               <> TRUE ) THEN
995           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
996             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
997               'v_check_Legal_Entity_info<-'||current_calling_sequence);
998           END IF;
999           RAISE check_inv_validation_failure;
1000         END IF;
1001 
1002         IF (l_temp_invoice_status = 'N') THEN
1003           l_current_invoice_status := l_temp_invoice_status;
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         ----------------------------------------------------------------------
1013         -- Step 12
1014         -- Check for Invalid Payment Currency Info only if there is a valid
1015         -- Invoice No.
1016         -- Also, populate payment_currency_code and payment cross rate
1017         -- information if all the following conditions are met:
1018         -- 1) payment currency code and/or payment cross rate information are
1019         --    null
1020         -- 2) payment currency code and/or payment cross rate information was
1021         --    derived as part of the pay curr check.
1022         -- 3) the pay curr check function returned that the invoice is valid
1023         --    as far as pay curr info is concerned.
1024         ----------------------------------------------------------------------
1025         debug_info := '(Check Invoice Validation 11) Check for '||
1026                        'Payment Currency Info ,if Invoice No. is valid';
1027         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1028           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1029           debug_info);
1030         END IF;
1031 
1032         IF (AP_IMPORT_VALIDATION_PKG.v_check_invalid_pay_curr (
1033               p_invoice_rec,                                           -- IN
1034               p_pay_currency_code            => l_pay_currency_code,   -- OUT
1035               p_payment_cross_rate_date      => l_pay_cross_rate_date, -- OUT
1036               p_payment_cross_rate           => l_pay_cross_rate,      --OUT
1037               p_payment_cross_rate_type      => l_pay_cross_rate_type, --OUT
1038               p_default_last_updated_by   => p_default_last_updated_by,-- IN
1039               p_default_last_update_login => p_default_last_update_login,-- IN
1040               p_current_invoice_status    => l_temp_invoice_status, -- IN OUT
1041               p_calling_sequence          => current_calling_sequence)
1042               <> TRUE ) THEN
1043           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1044             AP_IMPORT_UTILITIES_PKG.Print(
1045               AP_IMPORT_INVOICES_PKG.g_debug_switch,
1046               'v_check_invalid_pay_curr<-'||current_calling_sequence);
1047           END IF;
1048           RAISE check_inv_validation_failure;
1049         END IF;
1050 
1051         IF (l_temp_invoice_status = 'N') THEN
1052           l_current_invoice_status := l_temp_invoice_status;
1053         ELSE
1054           IF (p_invoice_rec.payment_currency_code is NULL AND
1055               l_pay_currency_code is NOT NULL) THEN
1056             p_invoice_rec.payment_currency_code := l_pay_currency_code;
1057           END IF;
1058           IF (p_invoice_rec.payment_cross_rate_date is NULL AND
1059               l_pay_cross_rate_date is NOT NULL) THEN
1060             p_invoice_rec.payment_cross_rate_date := l_pay_cross_rate_date;
1061           END IF;
1062           IF ((p_invoice_rec.payment_cross_rate is NULL AND
1063                l_pay_cross_rate is NOT NULL) OR
1064           (p_invoice_rec.payment_cross_rate is NOT NULL AND
1065            l_pay_cross_rate is NOT NULL AND
1066            p_invoice_rec.payment_cross_rate <> l_pay_cross_rate)) THEN
1067             p_invoice_rec.payment_cross_rate := l_pay_cross_rate;
1068           END IF;
1069           IF (p_invoice_rec.payment_cross_rate_type is NULL AND
1070               l_pay_cross_rate_type is NOT NULL) THEN
1071             p_invoice_rec.payment_cross_rate_type := l_pay_cross_rate_type;
1072           END IF;
1073         END IF;
1074         --
1075         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1076           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1077             '------------------>
1078             l_temp_invoice_status  = '||l_temp_invoice_status);
1079         END IF;
1080 
1081 /* Bug 4014019: Commenting the call to jg_globe_flex_val due to build issues.
1082 
1083         ----------------------------------------------------------------------
1084         -- Step 13
1085         -- Check for Invalid Global Flexfield Value.
1086         -- Retropricing: This may require JG modifications as parent table can
1087         -- now also be the Temp table AP_PPA_INVOICES_GT
1088         ----------------------------------------------------------------------
1089         debug_info := '(Check Invoice Validation 13) Check for GDFF';
1090         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1091           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1092                                         debug_info);
1093         END IF;
1094         jg_globe_flex_val.check_attr_value(
1095                       'APXIIMPT',
1096                       p_invoice_rec.global_attribute_category,
1097                       p_invoice_rec.global_attribute1,
1098                       p_invoice_rec.global_attribute2,
1099                       p_invoice_rec.global_attribute3,
1100                       p_invoice_rec.global_attribute4,
1101                       p_invoice_rec.global_attribute5,
1102                       p_invoice_rec.global_attribute6,
1103                       p_invoice_rec.global_attribute7,
1104                       p_invoice_rec.global_attribute8,
1105                       p_invoice_rec.global_attribute9,
1106                       p_invoice_rec.global_attribute10,
1107                       p_invoice_rec.global_attribute11,
1108                       p_invoice_rec.global_attribute12,
1109                       p_invoice_rec.global_attribute13,
1110                       p_invoice_rec.global_attribute14,
1111                       p_invoice_rec.global_attribute15,
1112                       p_invoice_rec.global_attribute16,
1113                       p_invoice_rec.global_attribute17,
1114                       p_invoice_rec.global_attribute18,
1115                       p_invoice_rec.global_attribute19,
1116                       p_invoice_rec.global_attribute20,
1117                       TO_CHAR(p_set_of_books_id),
1118                       fnd_date.date_to_canonical(p_invoice_rec.invoice_date),
1119                       AP_IMPORT_INVOICES_PKG.g_invoices_table,  --Retropricing
1120                       TO_CHAR(p_invoice_rec.invoice_id),
1121                       TO_CHAR(p_default_last_updated_by),
1122                       TO_CHAR(p_default_last_update_login),
1123                       current_calling_sequence,
1124                       TO_CHAR(p_invoice_rec.vendor_site_id), -- arg 8
1125                       p_invoice_rec.payment_currency_code,   -- arg 9
1126                       NULL,NULL,NULL,NULL,NULL,NULL,NULL,
1127                       NULL,NULL,NULL,NULL,NULL,NULL,NULL,NULL,NULL,NULL,
1128                       NULL,NULL,NULL,NULL,
1129                       p_current_status => l_temp_invoice_status);
1130 
1131         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1132           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1133             'Global Flexfield Header Processed  '|| l_temp_invoice_status);
1134           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1135             'Invoice_id  '|| to_char(p_invoice_rec.invoice_id));
1136         END IF;
1137         IF (l_temp_invoice_status = 'N') THEN
1138           l_current_invoice_status := l_temp_invoice_status;
1139         END IF;
1140 
1141 */
1142 
1143         ----------------------------------------------------------------------
1144         -- Step 14
1145         -- Check for Valid Prepayment Info.
1146         -- Retropricing: All prepayment fields will be NULL for PPA's
1147         ----------------------------------------------------------------------
1148         IF AP_IMPORT_INVOICES_PKG.g_source <> 'PPA' THEN   --Retropricing
1149             debug_info :=
1150                      '(Check Invoice Validation 14) Check for Prepayment Info.';
1151             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1152               AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1153                                             debug_info);
1154             END IF;
1155 
1156             IF (AP_IMPORT_VALIDATION_PKG.v_check_prepay_info(
1157                   p_invoice_rec,                                       -- IN OUT
1158                   p_base_currency_code,                                -- IN
1159                   p_prepay_period_name,                                -- IN OUT
1160 		  p_prepay_invoice_id,				       -- OUT
1161 		  p_prepay_case_name,				       -- OUT
1162                   p_request_id,                                        -- IN
1163                   p_default_last_updated_by,                           -- IN
1164                   p_default_last_update_login,                         -- IN
1165                   p_current_invoice_status   => l_temp_invoice_status, -- IN OUT
1166                   p_calling_sequence         => current_calling_sequence)
1167                   <> TRUE ) THEN
1168               IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1169                 AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1170                   'v_check_prepay_info<-' ||current_calling_sequence);
1171               END IF;
1172               RAISE check_inv_validation_failure;
1173 
1174             END IF;
1175 
1176             IF (l_temp_invoice_status = 'N') THEN
1177               l_current_invoice_status := l_temp_invoice_status;
1178             END IF;
1179 
1180             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1181               AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1182                             '------------------>
1183                       l_temp_invoice_status  = '||l_temp_invoice_status);
1184             END IF;
1185         END IF;
1186         ----------------------------------------------------------------------
1187         -- Step 15
1188         -- Check for Tax info at invoice level
1189         -- Although all eTax related fields(control_amount,tax_related_invoice_id,
1190         -- calc_tax_during_import_flag will be NULL on the Invoice Header
1191         -- some sql statemnts in the v_check_tax_info will get executed.
1192         ----------------------------------------------------------------------
1193         IF AP_IMPORT_INVOICES_PKG.g_source <> 'PPA' THEN   --Retropricing
1194             debug_info :=
1195               '(Check Invoice Validation 15) Check for tax drivers or invoice level '||
1196               'tax validations.';
1197             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1198               AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1199                                             debug_info);
1200             END IF;
1201 
1202             IF (AP_IMPORT_VALIDATION_PKG.v_check_tax_info(
1203                p_invoice_rec                => p_invoice_rec,
1204                p_default_last_updated_by    => p_default_last_updated_by,
1205                p_default_last_update_login  => p_default_last_update_login,
1206                p_current_invoice_status     => l_temp_invoice_status,
1207                p_calling_sequence           => current_calling_sequence)
1208                   <> TRUE ) THEN
1209 
1210               IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1211                 AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1212                   'v_check_tax_info<-' ||current_calling_sequence);
1213               END IF;
1214               RAISE check_inv_validation_failure;
1215 
1216             END IF;
1217 
1218             IF (l_temp_invoice_status = 'N') THEN
1219               l_current_invoice_status := l_temp_invoice_status;
1220             END IF;
1221 
1222             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1223               AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1224                 '------------------> l_temp_invoice_status  = '
1225                 ||l_temp_invoice_status);
1226 
1227             END IF;
1228         END IF;
1229 
1230    ------------------------------------------------
1231    /* Step 15.a.  Populate default taxation_county
1232                   when null.  Bug 9738820        */
1233    ------------------------------------------------
1234    IF p_invoice_rec.taxation_country is null THEN
1235      BEGIN
1236        xle_utilities_grp.get_fp_countrycode_ou (
1237                              p_api_version       => 1.0,
1238                              p_init_msg_list     => FND_API.G_FALSE,
1239                              p_commit            => FND_API.G_FALSE,
1240                              x_return_status     => l_return_status,
1241                              x_msg_count         => l_msg_count,
1242                              x_msg_data          => l_msg_data,
1243                              p_operating_unit    => p_invoice_rec.org_id,
1244                              x_country_code      => l_country_code);
1245        p_invoice_rec.taxation_country := l_country_code;
1246      /* taxation_country is not required so we will continue
1247         processing without a rejection when it can't be populated */
1248      EXCEPTION
1249        WHEN OTHERS THEN
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                 'Error when attempting to set default taxation_country.');
1253           END IF;
1254      END;
1255 
1256    END IF;
1257    /* End Bug 9738820 */
1258 
1259    ------------------------------------------------
1260     -- Step 16
1261     -- Check for Invalid Remit to Supplier
1262    ------------------------------------------------
1263 
1264    debug_info := 'Check for Invalid Remit to Supplier';
1265         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1266           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1267                                   debug_info);
1268         END IF;
1269 
1270         IF (AP_IMPORT_VALIDATION_PKG.v_check_invalid_remit_supplier (
1271             p_invoice_rec			=>	p_invoice_rec, -- IN OUT
1272             p_default_last_updated_by =>	p_default_last_updated_by, -- IN
1273             p_default_last_update_login =>	p_default_last_update_login,                           -- IN
1274             p_current_invoice_status     =>	l_temp_invoice_status, -- IN OUT
1275             p_calling_sequence		=>	current_calling_sequence) <> TRUE )THEN
1276 	      IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1277 		  AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1278 			'v_check_invalid_remit_supplier<-'||current_calling_sequence);
1279 	      END IF;
1280 	      RAISE check_inv_validation_failure;
1281         END IF;
1282 
1283 	IF (l_temp_invoice_status = 'N') THEN
1284               l_current_invoice_status := l_temp_invoice_status;
1285         END IF;
1286 
1287 	IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1288 		AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1289 		'------------------> l_temp_invoice_status  = '
1290 		||l_temp_invoice_status);
1291 	END IF;
1292 
1293         ----------------------------------------------------------------------
1294         -- Step 17
1295         -- Check for User Xrate information
1296         -- Also populate no_xrate_base_amount to be used as base amount if
1297         -- the following conditions are met:
1298         -- 1) no_xrate_base_amount is null
1299         -- 2) invoice currency code is different than base currency
1300         -- 3) base amount could be derived as part of no xrate base amt check
1301         -- 4) no xrate base amount check function returned that the invoice
1302         --    is valid as far as xrate is concerned.
1303         -- Retropricing:
1304         -- Although the function calculates invoice_base_amount, for PPA's the
1305         -- base_Amount is provided in the PPA Invoice. Also since base amounts
1306         -- are re-calculated during validation, there is no need to call the
1307         -- validation below for PPA's
1308         ----------------------------------------------------------------------
1309         IF AP_IMPORT_INVOICES_PKG.g_source <> 'PPA' THEN   --Retropricing
1310             debug_info :=
1311                     '(Check Invoice Validation 16) Check for Exchange Rate Info.';
1312             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1313               AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1314                                             debug_info);
1315             END IF;
1316 
1317             IF (AP_IMPORT_VALIDATION_PKG.v_check_no_xrate_base_amount (
1318                   p_invoice_rec,                                          -- IN
1319                   p_base_currency_code,                                   -- IN
1320                   p_multi_currency_flag,                                  -- IN
1321                   p_calc_user_xrate,                                      -- IN
1322                   p_default_last_updated_by,                              -- IN
1323                      p_default_last_update_login,                            -- IN
1324                   p_invoice_base_amount        => l_invoice_base_amount,  -- OUT
1325                   p_current_invoice_status     => l_temp_invoice_status,  -- IN OUT
1326                   p_calling_sequence           => current_calling_sequence)
1327                   <> TRUE ) THEN
1328               IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1329                   AP_IMPORT_UTILITIES_PKG.Print(
1330                     AP_IMPORT_INVOICES_PKG.g_debug_switch,
1331                     'v_check_inavlid_currency_code<-' ||current_calling_sequence);
1332               END IF;
1333               RAISE check_inv_validation_failure;
1334             END IF;
1335 
1336             IF (l_temp_invoice_status = 'N' )THEN
1337               l_current_invoice_Status := l_temp_invoice_status;
1338             ELSE
1339               IF (p_invoice_rec.no_xrate_base_amount IS NULL AND
1340                   l_invoice_base_amount IS NOT NULL AND
1341                   p_invoice_rec.invoice_currency_code <> p_base_currency_code) THEN
1342                  p_invoice_rec.no_xrate_base_amount := l_invoice_base_amount;
1343               END IF;
1344             END IF;
1345         END IF;  --Retropricing
1346 
1347         debug_info := '(Check Invoice Validation 17) Check Payment Info ';
1348         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1349           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1350                                         debug_info);
1351         END IF;
1352 
1353         IF (AP_IMPORT_VALIDATION_PKG.v_check_payment_defaults (
1354               p_invoice_rec,
1355               l_temp_invoice_status,
1356               current_calling_sequence,
1357               p_default_last_updated_by,
1358               p_default_last_update_login)
1359               <> TRUE ) THEN
1360           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1361             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1362               'v_check_payment_defaults<-'||current_calling_sequence);
1363           END IF;
1364           RAISE check_inv_validation_failure;
1365         END IF;
1366 
1367         IF (l_temp_invoice_status = 'N') THEN
1368           l_current_invoice_status := l_temp_invoice_status;
1369         END IF;
1370 
1371         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1372           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1373             '------------------>
1374             l_temp_invoice_status  = '||l_temp_invoice_status);
1375         END IF;
1376 
1377 
1378 
1379 
1380 
1381 
1382 
1383       END IF; -- status not N after validating invoice number
1384 
1385     ELSE -- IF (p_invoice_rec.vendor_site_id or party_site_id is NOT NULL)
1386       -- fatal error - no valid vendor site found - stop processing for
1387       -- this invoice.  A row was already inserted into
1388       -- AP_INTERFACE_REJECTIONS within CHECK_INVALID_SUPPLIER_SITE
1389       p_fatal_error_flag := 'Y';
1390       l_current_invoice_status := 'N';
1391     END IF; -- IF (p_invoice_rec.vendor_site_id is NOT NULL) THEN
1392 
1393   ELSE -- IF (p_invoice_rec.vendor_id or party_id is NOT NULL)
1394     -- fatal error - no valid vendor found - stop processing for this
1395     -- invoice.  A row was already inserted into AP_INTERFACE_REJECTIONS
1396     -- within CHECK_INVALID_SUPPLIER
1397     p_fatal_error_flag := 'Y';
1398     l_current_invoice_status := 'N';
1399   END IF; -- IF (p_invoice_rec.vendor_id or party_id is NOT NULL)
1400 
1401   -- Bug 9452076. Start
1402   -- Added condition.
1403   IF (l_current_invoice_status = 'N') THEN
1404      p_current_invoice_status := l_current_invoice_status;
1405   END IF ;
1406   -- Bug 9452076. End
1407 
1408 RETURN (TRUE);
1409 
1410 EXCEPTION
1411   WHEN OTHERS THEN
1412     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1413       AP_IMPORT_UTILITIES_PKG.Print(
1414         AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
1415     END IF;
1416 
1417     IF (SQLCODE < 0) then
1418       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1419         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,SQLERRM);
1420       END IF;
1421     END IF;
1422     RETURN(FALSE);
1423 
1424 END v_check_invoice_validation;
1425 
1426 
1427 -----------------------------------------------------------------------------
1428 -- This function is used to perform PO validation.
1429 --
1430 FUNCTION v_check_invalid_po (
1431            p_invoice_rec    IN AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
1432            p_default_last_updated_by   IN             NUMBER,
1433            p_default_last_update_login IN             NUMBER,
1434            p_current_invoice_status    IN OUT NOCOPY  VARCHAR2,
1435            p_po_vendor_id                 OUT NOCOPY  NUMBER,
1436            p_po_vendor_site_id            OUT NOCOPY  NUMBER,
1437            p_po_exists_flag               OUT NOCOPY  VARCHAR2,
1438            p_calling_sequence          IN             VARCHAR2) RETURN BOOLEAN
1439 IS
1440 
1441 invalid_po_check_failure    EXCEPTION;
1442 l_current_invoice_status    VARCHAR2(1) := 'Y';
1443 l_closed_date               DATE;
1444 l_vendor_id                 NUMBER;
1445 l_vendor_site_id            NUMBER;
1446 l_po_exists_flag            VARCHAR2(1) := 'N';
1447 current_calling_sequence    VARCHAR2(2000);
1448 debug_info                  VARCHAR2(500);
1449 l_invoice_vendor_name       po_vendors.vendor_name%TYPE := '';
1450 l_closed_code               VARCHAR2(25);  /* 1Off Bug 10288184 / 11i Bug 8410175 */
1451 
1452 BEGIN
1453   -- Update the calling sequence
1454   --
1455   current_calling_sequence :=  'AP_IMPORT_VALIDATION_PKG.v_check_invalid_po<-'
1456                                 ||P_calling_sequence;
1457 
1458   -- differentiate PO from RFQ and Quotation
1459   SELECT closed_date, vendor_id, vendor_site_id, closed_code /* Added closed_code - 1Off Bug 10288184 / 11i Bug 8410175 */
1460     INTO l_closed_date ,l_vendor_id, l_vendor_site_id, l_closed_code /* Added l_closed_code - 1Off Bug 10288184 / 11i Bug 8410175 */
1461     FROM po_headers
1462    WHERE segment1 = p_invoice_rec.po_number
1463      AND type_lookup_code in ('BLANKET', 'PLANNED', 'STANDARD')
1464    /* BUG  2902452 added*/
1465    AND nvl(authorization_status,'INCOMPLETE') in ('APPROVED','REQUIRES REAPPROVAL','IN PROCESS');--Bug5687122 --Added In Process condition
1466 
1467   IF (l_vendor_id IS NOT NULL) Then
1468     l_po_exists_flag := 'Y';
1469   END IF;
1470 
1471   --------------------------------------------------------------------------
1472   -- Step 1
1473   -- Check for Inactive PO NUMBER.
1474   --------------------------------------------------------------------------
1475   debug_info := '(Check PO Number 1) Check for Inactive PO Number.';
1476   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1477     AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1478                                   debug_info);
1479   END IF;
1480   --Bypass this rejections for PPA's  --Retropricing
1481   /* Added l_closed_code condition to avoid rejecting the PO's that are 'CLOSED - 1Off Bug 10288184 / 11i Bug 8410175 */
1482   IF (l_closed_date is not null AND
1483       AP_IMPORT_INVOICES_PKG.g_source <> 'PPA'
1484       AND l_closed_code in ('FINALLY CLOSED')
1485       ) THEN
1486     -- PO has been closed
1487     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
1488           AP_IMPORT_INVOICES_PKG.g_invoices_table,
1489           p_invoice_rec.invoice_id,
1490           'INACTIVE PO',
1491           p_default_last_updated_by,
1492           p_default_last_update_login,
1493           current_calling_sequence) <> 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     l_current_invoice_status := 'N';
1503 
1504   ELSE
1505     ------------------------------------------------------------------------
1506     -- Step 2
1507     -- Check for Inconsistent PO Vendor.
1508     ------------------------------------------------------------------------
1509     debug_info := '(Check PO Number 2) Check for Inconsistent PO Vendor.';
1510     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1511       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1512                                     debug_info);
1513     END IF;
1514 
1515     IF (l_vendor_id <> nvl(p_invoice_rec.vendor_id, l_vendor_id)) THEN
1516     --Retropricing There is no need for the IF statement mentioned below
1517       IF (AP_IMPORT_INVOICES_PKG.g_source = 'XML GATEWAY' ) THEN
1518         BEGIN
1519           -- Get contextual Information for XML Gateway
1520           SELECT vendor_name
1521             INTO l_invoice_vendor_name
1522             FROM po_vendors
1523            WHERE vendor_id = p_invoice_rec.vendor_id;
1524 
1525       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
1526               (AP_IMPORT_INVOICES_PKG.g_invoices_table,
1527                p_invoice_rec.invoice_id,
1528                'INCONSISTENT PO SUPPLIER',
1529                p_default_last_updated_by,
1530                p_default_last_update_login,
1531                current_calling_sequence,
1532                'Y',
1533                'SUPPLIER NAME',
1534                l_invoice_vendor_name) <> TRUE) THEN
1535             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1536               AP_IMPORT_UTILITIES_PKG.Print(
1537                 AP_IMPORT_INVOICES_PKG.g_debug_switch,
1538                 'insert_rejections<-'||current_calling_sequence);
1539             END IF;
1540             RAISE invalid_po_check_failure;
1541           END IF;
1542 
1543         EXCEPTION
1544           WHEN NO_DATA_FOUND THEN
1545             NULL;
1546         END;
1547       ELSE
1548         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
1549              (AP_IMPORT_INVOICES_PKG.g_invoices_table,
1550               p_invoice_rec.invoice_id,
1551               'INCONSISTENT PO SUPPLIER',
1552               p_default_last_updated_by,
1553               p_default_last_update_login,
1554               current_calling_sequence) <> TRUE) THEN
1555           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1556             AP_IMPORT_UTILITIES_PKG.Print(
1557               AP_IMPORT_INVOICES_PKG.g_debug_switch,
1558               'insert_rejections<-'||
1559               current_calling_sequence);
1560           END IF;
1561           RAISE invalid_po_check_failure;
1562         END IF;
1563 
1564       END IF; -- g_source = 'XML GATEWAY'
1565 
1566       l_current_invoice_status := 'N';
1567 
1568     END IF; -- vendor id <> vendor id on interface invoice
1569   END IF;  -- closed date is not null
1570 
1571   p_po_vendor_id := l_vendor_id;
1572   p_po_vendor_site_id := l_vendor_site_id;
1573   p_po_exists_flag := l_po_exists_flag;
1574   p_current_invoice_status := l_current_invoice_status;
1575   RETURN (TRUE);
1576 
1577 EXCEPTION
1578   WHEN no_data_found THEN
1579 
1580     -------------------------------------------------------------------------
1581     -- Step 3
1582     -- Invalid PO NUMBER.
1583     -------------------------------------------------------------------------
1584     debug_info := '(Check PO Number 3) Check for Invalid PO Number.';
1585     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1586       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1587                                     debug_info);
1588     END IF;
1589 
1590     -- include context for XML GATEWAY
1591     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
1592                           (AP_IMPORT_INVOICES_PKG.g_invoices_table,
1593                             p_invoice_rec.invoice_id,
1594                            'INVALID PO NUM',
1595                             p_default_last_updated_by,
1596                             p_default_last_update_login,
1597                             current_calling_sequence,
1598                             'Y',
1599                             'PO NUMBER',
1600                             p_invoice_rec.po_number) <> TRUE) THEN
1601       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1602         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1603                                       'insert_rejections<-'||
1604                                        current_calling_sequence);
1605       END IF;
1606       RAISE invalid_po_check_failure;
1607     END IF;
1608 
1609     p_po_exists_flag := l_po_exists_flag;
1610     l_current_invoice_status := 'N';
1611     p_current_invoice_status := l_current_invoice_status;
1612     RETURN (TRUE);
1613 
1614   WHEN OTHERS THEN
1615     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1616       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1617                                     debug_info);
1618     END IF;
1619 
1620     IF (SQLCODE < 0) then
1621       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1622         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1623                                       SQLERRM);
1624       END IF;
1625     END IF;
1626     RETURN(FALSE);
1627 
1628 END v_check_invalid_po;
1629 
1630 
1631 -----------------------------------------------------------------------------
1632 -- This function is used to perform Supplier validation
1633 --
1634 -----------------------------------------------------------------------------
1635 FUNCTION v_check_invalid_supplier(
1636          p_invoice_rec   IN AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
1637          p_default_last_updated_by     IN            NUMBER,
1638          p_default_last_update_login   IN            NUMBER,
1639          p_return_vendor_id               OUT NOCOPY NUMBER,
1640          p_current_invoice_status      IN OUT NOCOPY VARCHAR2,
1641          p_calling_sequence            IN            VARCHAR2)
1642 RETURN BOOLEAN IS
1643 
1644 supplier_check_failure      EXCEPTION;
1645 l_vendor_id                 PO_VENDORS.VENDOR_ID%TYPE :=
1646                               p_invoice_rec.vendor_id;
1647 l_vendor_id_per_num         PO_VENDORS.VENDOR_ID%TYPE;
1648 l_vendor_id_per_name        PO_VENDORS.VENDOR_ID%TYPE;
1649 l_current_invoice_status    VARCHAR2(1) := 'Y';
1650 return_vendor_id            NUMBER(15);
1651 current_calling_sequence    VARCHAR2(2000);
1652 debug_info                  VARCHAR2(500);
1653 
1654 
1655 BEGIN
1656   -- Update the calling sequence
1657   --
1658   current_calling_sequence :=
1659     'AP_IMPORT_VALIDATION_PKG.v_check_invalid_supplier<-'
1660     ||P_calling_sequence;
1661 
1662   IF ((p_invoice_rec.vendor_id is NULL) AND
1663       (p_invoice_rec.vendor_num is NULL) AND
1664       (p_invoice_rec.vendor_name is NULL)) THEN
1665 
1666     -------------------------------------------------------------------------
1667     -- Step 1
1668     -- Check for Null Supplier.
1669     -------------------------------------------------------------------------
1670     debug_info := '(Check Invalid Supplier 1) Check for Null Supplier.';
1671     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1672       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1673                                     debug_info);
1674     END IF;
1675 
1676     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
1677             (AP_IMPORT_INVOICES_PKG.g_invoices_table,
1678              p_invoice_rec.invoice_id,
1679              'NO SUPPLIER',
1680              p_default_last_updated_by,
1681              p_default_last_update_login,
1682              current_calling_sequence) <> TRUE) THEN
1683       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1684         AP_IMPORT_UTILITIES_PKG.Print(
1685           AP_IMPORT_INVOICES_PKG.g_debug_switch,
1686           'insert_rejections<-'||current_calling_sequence);
1687       END IF;
1688       RAISE supplier_check_failure;
1689     END IF;
1690     return_vendor_id := null;
1691 
1692   ELSE
1693 
1694      IF (p_invoice_rec.vendor_id is NOT NULL) THEN
1695 
1696        ----------------------------------------------------------------------
1697        -- Step 2
1698        -- validate vendor id
1699        ----------------------------------------------------------------------
1700        debug_info := '(Check Invalid Supplier 2) Validate vendor id.';
1701        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1702          AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1703                                        debug_info);
1704        END IF;
1705 
1706        SELECT vendor_id
1707          INTO l_vendor_id
1708          FROM po_vendors pv
1709         WHERE vendor_id = p_invoice_rec.vendor_id
1710           AND nvl(trunc(PV.START_DATE_ACTIVE),
1711                   AP_IMPORT_INVOICES_PKG.g_inv_sysdate)
1712               <= AP_IMPORT_INVOICES_PKG.g_inv_sysdate
1713           AND nvl(trunc(PV.END_DATE_ACTIVE),
1714                   AP_IMPORT_INVOICES_PKG.g_inv_sysdate+1)
1715               > AP_IMPORT_INVOICES_PKG.g_inv_sysdate ;
1716 
1717      END IF;
1718 
1719      IF (p_invoice_rec.vendor_num is NOT NULL) THEN
1720 
1721        ----------------------------------------------------------------------
1722        -- Step 3
1723        -- Validate vendor number and retrieve vendor id
1724        ----------------------------------------------------------------------
1725        debug_info := '(Check Invalid Supplier 3) Validate vendor number and '
1726                       ||'retrieve vendor id';
1727        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1728          AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1729                                        debug_info);
1730        END IF;
1731 
1732        SELECT vendor_id
1733          INTO l_vendor_id_per_num
1734          FROM po_vendors PV
1735         WHERE segment1 = p_invoice_rec.vendor_num
1736           AND nvl(trunc(PV.START_DATE_ACTIVE),
1737                   AP_IMPORT_INVOICES_PKG.g_inv_sysdate)
1738               <= AP_IMPORT_INVOICES_PKG.g_inv_sysdate
1739           AND nvl(trunc(PV.END_DATE_ACTIVE),
1740                   AP_IMPORT_INVOICES_PKG.g_inv_sysdate+1)
1741               > AP_IMPORT_INVOICES_PKG.g_inv_sysdate;
1742 
1743      END IF;
1744 
1745      IF (p_invoice_rec.vendor_name is NOT NULL) THEN
1746 
1747        ----------------------------------------------------------------------
1748        -- Step 4
1749        -- Validate vendor name and retrieve vendor id
1750        ----------------------------------------------------------------------
1751        debug_info := '(Check Invalid Supplier 4) Validate vendor name and '
1752                      ||'retrieve vendor id';
1753        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1754          AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1755                                        debug_info);
1756        END IF;
1757 
1758        SELECT vendor_id
1759          INTO l_vendor_id_per_name
1760          FROM po_vendors PV
1761         WHERE vendor_name = p_invoice_rec.vendor_name
1762           AND nvl(trunc(PV.START_DATE_ACTIVE),
1763                   AP_IMPORT_INVOICES_PKG.g_inv_sysdate)
1764               <= AP_IMPORT_INVOICES_PKG.g_inv_sysdate
1765           AND nvl(trunc(PV.END_DATE_ACTIVE),
1766                   AP_IMPORT_INVOICES_PKG.g_inv_sysdate+1)
1767               > AP_IMPORT_INVOICES_PKG.g_inv_sysdate ;
1768 
1769      END IF;
1770 
1771      IF ((l_vendor_id is NOT NULL)                           AND
1772                  (((l_vendor_id_per_num is NOT NULL) AND
1773                    (l_vendor_id <> l_vendor_id_per_num))     OR
1774                  ((l_vendor_id_per_name is NOT NULL) AND
1775                   (l_vendor_id <> l_vendor_id_per_name)))
1776         ) THEN
1777 
1778        -----------------------------------------------------------------------
1779        -- Step 5
1780        -- Check for Inconsitent Supplier based on not null supplier id provided
1781        -----------------------------------------------------------------------
1782        debug_info := '(Check Invalid Supplier 5) Check for inconsistent '
1783                      ||'Supplier - supplier id not null';
1784        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1785          AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1786                                        debug_info);
1787        END IF;
1788 
1789        IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
1790                        (AP_IMPORT_INVOICES_PKG.g_invoices_table,
1791                         p_invoice_rec.invoice_id,
1792                         'INCONSISTENT SUPPLIER',
1793                         p_default_last_updated_by,
1794                         p_default_last_update_login,
1795                         current_calling_sequence) <> TRUE) THEN
1796          IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1797            AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1798                                          'insert_rejections<-'
1799                                           ||current_calling_sequence);
1800          END IF;
1801          RAISE supplier_check_failure;
1802        END IF;
1803 
1804        l_current_invoice_status := 'N';
1805 
1806      END IF;
1807 
1808 
1809      IF ((l_vendor_id_per_num is NOT NULL) AND
1810          (l_vendor_id_per_name is NOT NULL) AND
1811          (l_vendor_id_per_num <> l_vendor_id_per_name) AND
1812          (l_current_invoice_status = 'Y')) THEN
1813 
1814        ----------------------------------------------------------------------
1815        -- Step 6
1816        -- Check for Inconsitent Supplier number and Name.
1817        ----------------------------------------------------------------------
1818        debug_info := '(Check Invalid Supplier 6) Check for inconsistent '
1819                      ||'Supplier Number and Name.';
1820        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1821          AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1822                                        debug_info);
1823        END IF;
1824 
1825        IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
1826                   (AP_IMPORT_INVOICES_PKG.g_invoices_table,
1827                    p_invoice_rec.invoice_id,
1828                    'INCONSISTENT SUPPLIER',
1829                    p_default_last_updated_by,
1830                    p_default_last_update_login,
1831                    current_calling_sequence) <> TRUE) THEN
1832          IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1833            AP_IMPORT_UTILITIES_PKG.Print(
1834              AP_IMPORT_INVOICES_PKG.g_debug_switch,
1835              'insert_rejections<-'||current_calling_sequence);
1836          END IF;
1837          RAISE supplier_check_failure;
1838        END IF;
1839 
1840        l_current_invoice_status := 'N';
1841 
1842      END IF;
1843 
1844      IF (l_current_invoice_status = 'Y') THEN
1845 
1846        ----------------------------------------------------------------------
1847        -- Step 7
1848        -- Save Supplier id for further processing.
1849        ----------------------------------------------------------------------
1850        debug_info := '(Check Invalid Supplier 7) Save Supplier id for '
1851                      ||'further processing.';
1852        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1853          AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1854                                        debug_info);
1855        END IF;
1856 
1857        IF (l_vendor_id is NULL) THEN
1858 
1859          IF (l_vendor_id_per_num is NOT NULL) THEN
1860            return_vendor_id := l_vendor_id_per_num;
1861          ELSE
1862            return_vendor_id := l_vendor_id_per_name;
1863          END IF;
1864        ELSE
1865          return_vendor_id := l_vendor_id;
1866        END IF;
1867      END IF;
1868 
1869   END IF;
1870   p_return_vendor_id := return_vendor_id;
1871   p_current_invoice_status := l_current_invoice_status;
1872   RETURN (TRUE);
1873 EXCEPTION
1874   WHEN no_data_found THEN
1875 
1876     -------------------------------------------------------------------------
1877     -- Step 8
1878     -- Check for invalid Supplier.
1879     -------------------------------------------------------------------------
1880     debug_info := '(Check Invalid Supplier 8) Check for invalid Supplier.';
1881     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1882       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1883                                     debug_info);
1884     END IF;
1885 
1886     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
1887                (AP_IMPORT_INVOICES_PKG.g_invoices_table,
1888                 p_invoice_rec.invoice_id,
1889                 'INVALID SUPPLIER',
1890                 p_default_last_updated_by,
1891                 p_default_last_update_login,
1892                 current_calling_sequence) <> TRUE) THEN
1893       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1894         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1895           'insert_rejections<-'||current_calling_sequence);
1896       END IF;
1897       RAISE supplier_check_failure;
1898 
1899     END IF;
1900     l_current_invoice_status := 'N';
1901     p_return_vendor_id := return_vendor_id;
1902     p_current_invoice_status := l_current_invoice_status;
1903     RETURN (TRUE);
1904 
1905 
1906   WHEN OTHERS THEN
1907     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1908       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1909                                     debug_info);
1910     END IF;
1911 
1912     IF (SQLCODE < 0) then
1913       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1914         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1915                                       SQLERRM);
1916       END IF;
1917     END IF;
1918     RETURN(FALSE);
1919 
1920 END v_check_invalid_supplier;
1921 
1922 
1923 ------------------------------------------------------------------
1924 -- This function is used to perform Supplier Site validation
1925 --
1926 ------------------------------------------------------------------
1927 FUNCTION v_check_invalid_supplier_site (
1928          p_invoice_rec  IN  AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
1929          p_vendor_site_id_per_po      IN            NUMBER,
1930          p_default_last_updated_by    IN            NUMBER,
1931          p_default_last_update_login  IN            NUMBER,
1932          p_return_vendor_site_id         OUT NOCOPY NUMBER,
1933          p_terms_date_basis              OUT NOCOPY VARCHAR2,
1934          p_current_invoice_status     IN OUT NOCOPY VARCHAR2,
1935          p_calling_sequence           IN VARCHAR2) RETURN BOOLEAN
1936 IS
1937 
1938 supplier_site_check_failure        EXCEPTION;
1939 l_vendor_site_id                   NUMBER(15);
1940 l_vendor_site_id_per_code          NUMBER(15);
1941 l_check_vendor_id                  NUMBER;
1942 l_current_invoice_status           VARCHAR2(1):='Y';
1943 l_valid_vendor                     VARCHAR2(1);
1944 return_vendor_site_id              NUMBER(15);
1945 l_pay_site_flag                    VARCHAR2(1);
1946 l_pay_site_flag_per_code           VARCHAR2(1);
1947 current_calling_sequence           VARCHAR2(2000);
1948 debug_info                         VARCHAR2(500);
1949 
1950 BEGIN
1951   -- Update the calling sequence
1952   --
1953   current_calling_sequence :=
1954     'AP_IMPORT_VALIDATION_PKG.v_check_invalid_supplier_site<-'
1955      ||P_calling_sequence;
1956 
1957   debug_info := '(Check Invalid Site 1) Check Supplier Site';
1958   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1959     AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1960                                   debug_info);
1961   END IF;
1962 
1963   IF ((p_invoice_rec.vendor_site_id is null) AND
1964       (p_invoice_rec.vendor_site_code is null) AND
1965       (p_vendor_site_id_per_po is null)) THEN
1966 
1967     debug_info := '(Check Invalid Site 2) No Supplier Site, Reject';
1968     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1969       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1970                                     debug_info);
1971     END IF;
1972 
1973     -- no supplier site exists
1974     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
1975            (AP_IMPORT_INVOICES_PKG.g_invoices_table,
1976             p_invoice_rec.invoice_id,
1977             'NO SUPPLIER SITE',
1978             p_default_last_updated_by,
1979             p_default_last_update_login,
1980             current_calling_sequence) <> TRUE) THEN
1981       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1982         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1983                                       'insert_rejections<-'
1984                                       ||current_calling_sequence);
1985       END IF;
1986       RAISE supplier_site_check_failure;
1987     END IF;
1988 
1989     return_vendor_site_id := null;
1990     l_current_invoice_status := 'N';
1991 
1992   ELSE
1993 
1994     IF p_invoice_rec.vendor_site_id is not null THEN
1995       debug_info := '(Check Invalid Site 3) Get Supplier Site details '
1996                     ||'from p_invoice_rec.vendor_site_id';
1997       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1998         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1999                                       debug_info);
2000       END IF;
2001     /*Bug5503712 Done the code changes so that if vendor site id is not null
2002       CADIP will not reject PPA invoices in following cases.
2003         1.  primary pay site is present  OR
2004         2.  only 1 pay site is present. */
2005       BEGIN
2006         --validate vendor site id
2007         SELECT vendor_site_id, pay_site_flag, terms_date_basis
2008         INTO l_vendor_site_id, l_pay_site_flag, p_terms_date_basis
2009         FROM po_vendor_sites pvs
2010         WHERE vendor_site_id = p_invoice_rec.vendor_site_id
2011          AND nvl(trunc(PVS.INACTIVE_DATE),
2012                  AP_IMPORT_INVOICES_PKG.g_inv_sysdate+1)
2013              > AP_IMPORT_INVOICES_PKG.g_inv_sysdate ;
2014       EXCEPTION
2015         WHEN no_data_found THEN
2016           /* Added the if condition AP_IMPORT_INVOICES_PKG.g_source <> 'PPA'
2017              for bug#9727865 */
2018           IF AP_IMPORT_INVOICES_PKG.g_source <> 'PPA' THEN
2019              IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
2020                   (AP_IMPORT_INVOICES_PKG.g_invoices_table,
2021                        p_invoice_rec.invoice_id,
2022                        'INVALID SUPPLIER SITE',
2023                         p_default_last_updated_by,
2024                         p_default_last_update_login,
2025                         current_calling_sequence) <> TRUE
2026                 ) THEN
2027                 IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2028                      AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2029                                       'insert_rejections<-'
2030                                       ||current_calling_sequence);
2031                 END IF;
2032                 RAISE supplier_site_check_failure;
2033              END IF;
2034              return_vendor_site_id := null;
2035              l_current_invoice_status := 'N';
2036           ELSE
2037 
2038              BEGIN
2039               --Get Primary Pay site
2040               SELECT vendor_site_id, pay_site_flag, terms_date_basis
2041               INTO l_vendor_site_id, l_pay_site_flag, p_terms_date_basis
2042               FROM po_vendor_sites pvs
2043               WHERE vendor_id = p_invoice_rec.vendor_id
2044               AND   nvl(Primary_pay_site_flag,'N')='Y'
2045               AND   pvs.Org_id=p_invoice_rec.org_id
2046               AND nvl(trunc(PVS.INACTIVE_DATE),
2047                     AP_IMPORT_INVOICES_PKG.g_inv_sysdate+1)
2048                         > AP_IMPORT_INVOICES_PKG.g_inv_sysdate ;
2049 
2050               UPDATE AP_ppa_invoices_gt H
2051                  SET vendor_site_id = l_vendor_site_id
2052                WHERE invoice_id = p_invoice_rec.invoice_id;
2053 
2054 
2055       EXCEPTION
2056         WHEN no_data_found THEN
2057 
2058           BEGIN
2059            --Get pay site id if only one pay site is present
2060            SELECT vendor_site_id, pay_site_flag, terms_date_basis
2061              INTO l_vendor_site_id, l_pay_site_flag, p_terms_date_basis
2062              FROM po_vendor_sites pvs
2063             WHERE vendor_id = p_invoice_rec.vendor_id
2064               AND pvs.Org_id=p_invoice_rec.org_id
2065               AND NVL(pvs.pay_site_flag,'N')='Y'
2066               AND nvl(trunc(PVS.INACTIVE_DATE),
2067                      AP_IMPORT_INVOICES_PKG.g_inv_sysdate+1)
2068                          > AP_IMPORT_INVOICES_PKG.g_inv_sysdate ;
2069 
2070               UPDATE AP_ppa_invoices_gt H
2071                  SET vendor_site_id = l_vendor_site_id
2072                WHERE invoice_id = p_invoice_rec.invoice_id;
2073 
2074           EXCEPTION
2075              WHEN OTHERS THEN
2076         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
2077           (AP_IMPORT_INVOICES_PKG.g_invoices_table,
2078             p_invoice_rec.invoice_id,
2079             'INVALID SUPPLIER SITE',
2080             p_default_last_updated_by,
2081             p_default_last_update_login,
2082             current_calling_sequence) <> TRUE) THEN
2083           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2084             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2085                                     'insert_rejections<-'
2086                                     ||current_calling_sequence);
2087           END IF;
2088           RAISE supplier_site_check_failure;
2089         END IF;
2090         return_vendor_site_id := null;
2091         l_current_invoice_status := 'N';
2092       END;
2093      END;
2094      END IF; -- AP_IMPORT_INVOICES_PKG.g_source <> 'PPA'
2095     END;
2096 
2097     END IF; -- p_invoice_rec.vendor_site_id is not null
2098 
2099     IF p_invoice_rec.vendor_site_code is not null THEN
2100 
2101       debug_info := '(Check Invalid Site 4) Get Supplier Site details '
2102                    ||'from p_invoice_rec.vendor_site_code';
2103       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2104         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2105                                      debug_info);
2106       END IF;
2107 
2108       --validate vendor site code and retrieve vendor site id
2109       BEGIN
2110         SELECT vendor_site_id, pay_site_flag,
2111             terms_date_basis
2112         INTO l_vendor_site_id_per_code, l_pay_site_flag_per_code,
2113             p_terms_date_basis
2114         FROM po_vendor_sites
2115         WHERE vendor_site_code = p_invoice_rec.vendor_site_code
2116         AND vendor_id = p_invoice_rec.vendor_id
2117         AND nvl(trunc(INACTIVE_DATE),AP_IMPORT_INVOICES_PKG.g_inv_sysdate+1)
2118             > AP_IMPORT_INVOICES_PKG.g_inv_sysdate ;
2119        EXCEPTION
2120 
2121         -- Bug 5579196
2122         WHEN too_many_rows THEN
2123           IF p_invoice_rec.org_id is NULL then
2124              NULL;
2125            END IF;
2126 
2127         WHEN no_data_found THEN
2128         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
2129           (AP_IMPORT_INVOICES_PKG.g_invoices_table,
2130             p_invoice_rec.invoice_id,
2131             'INVALID SUPPLIER 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(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2137                                     'insert_rejections<-'
2138                                     ||current_calling_sequence);
2139           END IF;
2140           RAISE supplier_site_check_failure;
2141         END IF;
2142         return_vendor_site_id := null;
2143         l_current_invoice_status := 'N';
2144 
2145       END;
2146 
2147     END IF; -- p_invoice_rec.vendor_site_code is not null
2148 
2149 
2150     IF l_vendor_site_id iS NOT NULL AND
2151       l_vendor_site_id_per_code IS NOT NULL AND
2152       l_vendor_site_id <> l_vendor_site_id_per_code THEN
2153       debug_info :=
2154        '(Check Invalid Site 5) Supplier Site info is inconsistent';
2155       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2156         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2157                                      debug_info);
2158       END IF;
2159 
2160       --vendor site id and vendor site code inconsistent
2161       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
2162            (AP_IMPORT_INVOICES_PKG.g_invoices_table,
2163             p_invoice_rec.invoice_id,
2164             'INCONSISTENT SUPPL SITE',
2165             p_default_last_updated_by,
2166             p_default_last_update_login,
2167             current_calling_sequence) <> TRUE) THEN
2168          IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2169            AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2170                                        'insert_rejections<-'
2171                                        ||current_calling_sequence);
2172          END IF;
2173          RAISE supplier_site_check_failure;
2174        END IF;
2175        return_vendor_site_id := null;
2176        l_current_invoice_status := 'N';
2177 
2178      END IF; -- vendor site id is not null, site id from code
2179            -- is not null and they differ
2180 
2181      -- Make sure the vendor site and vendor match
2182      --
2183      IF ((l_vendor_site_id is not null OR
2184        l_vendor_site_id_per_code is not null) AND
2185        p_invoice_rec.vendor_id IS NOT NULL) THEN
2186        debug_info := '(Check Invalid Site 6) Check Supplier Site for'
2187                    ||' given vendor';
2188        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2189           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2190                                      debug_info);
2191        END IF;
2192 
2193        BEGIN
2194          SELECT 'X'
2195          INTO l_valid_vendor
2196          FROM po_vendor_sites
2197          WHERE vendor_site_id = nvl(l_vendor_site_id ,l_vendor_site_id_per_code)
2198          AND vendor_id = p_invoice_rec.vendor_id;
2199 
2200        EXCEPTION
2201          WHEN no_data_found THEN
2202          IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
2203           (AP_IMPORT_INVOICES_PKG.g_invoices_table,
2204             p_invoice_rec.invoice_id,
2205             'INCONSISTENT SUPPL SITE',
2206             p_default_last_updated_by,
2207             p_default_last_update_login,
2208             current_calling_sequence) <> TRUE) THEN
2209             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2210               AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2211                                     'insert_rejections<-'
2212                                     ||current_calling_sequence);
2213             END IF;
2214             RAISE supplier_site_check_failure;
2215          END IF;
2216          return_vendor_site_id := null;
2217          l_current_invoice_status := 'N';
2218        END;
2219 
2220        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2221           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2222                    '------------------> l_valid_vendor = '|| l_valid_vendor);
2223        END IF;
2224 
2225      END IF; -- Make sure vendor site and vendor match
2226 
2227      IF l_current_invoice_status = 'Y' THEN
2228      -- Make sure that the EDI site and
2229      -- the PO site belong to the same supplier
2230      -- if not then reject
2231        IF (((l_vendor_site_id is not null) OR
2232           (l_vendor_site_id_per_code is not null)) AND
2233           (p_vendor_site_id_per_po is not null)) THEN
2234 
2235          debug_info := '(Check Invalid Site 7) Check Supplier Site info for EDI'
2236                      ||' and PO site';
2237          IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2238            AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2239                                        debug_info);
2240          END IF;
2241 
2242          BEGIN
2243            SELECT distinct vendor_id
2244            INTO l_check_vendor_id
2245            FROM po_vendor_sites
2246            WHERE vendor_site_id IN (l_vendor_site_id, p_vendor_site_id_per_po,
2247                 l_vendor_site_id_per_code);
2248 
2249          EXCEPTION
2250            WHEN NO_DATA_FOUND THEN
2251            debug_info := '(Check Invalid Site 8) EDI and PO site are '
2252                          ||'invalid: Reject';
2253            IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2254              AP_IMPORT_UTILITIES_PKG.Print(
2255                AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
2256            END IF;
2257 
2258            IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
2259                 (AP_IMPORT_INVOICES_PKG.g_invoices_table,
2260                  p_invoice_rec.invoice_id,
2261                  'INCONSISTENT SUPPL SITE',
2262                  p_default_last_updated_by,
2263                  p_default_last_update_login,
2264                  current_calling_sequence) <> TRUE) THEN
2265              IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2266                AP_IMPORT_UTILITIES_PKG.Print(
2267                  AP_IMPORT_INVOICES_PKG.g_debug_switch,
2268                  'insert_rejections<-'||current_calling_sequence);
2269              END IF;
2270              RAISE supplier_site_check_failure;
2271            END IF;
2272 
2273            l_current_invoice_status := 'N';
2274 
2275          WHEN TOO_MANY_ROWS THEN
2276            debug_info := '(Check Invalid Site 9) EDI and PO site are '
2277                          ||'for different supplier';
2278            IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2279              AP_IMPORT_UTILITIES_PKG.Print(
2280                AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
2281            END IF;
2282 
2283            IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
2284                 (AP_IMPORT_INVOICES_PKG.g_invoices_table,
2285                  p_invoice_rec.invoice_id,
2286                  'INCONSISTENT SUPPL SITE',
2287                  p_default_last_updated_by,
2288                  p_default_last_update_login,
2289                  current_calling_sequence) <> TRUE) THEN
2290              IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2291                AP_IMPORT_UTILITIES_PKG.Print(
2292                  AP_IMPORT_INVOICES_PKG.g_debug_switch,
2293                  'insert_rejections<-' ||current_calling_sequence);
2294              END IF;
2295              RAISE supplier_site_check_failure;
2296            END IF;
2297 
2298            l_current_invoice_status := 'N';
2299 
2300        END;
2301      END IF; -- Do vendor site, vendor site per code and per po
2302              -- belong to same supplier?
2303 
2304      if l_vendor_site_id is null THEN
2305        if nvl(l_pay_site_flag_per_code, 'N') = 'N' THEN
2306          -- pay site is not a pay site
2307          debug_info := '(Check Invalid Site 10) Not a pay site per '
2308                        ||'supplier site code';
2309          IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2310            AP_IMPORT_UTILITIES_PKG.Print(
2311              AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
2312          END IF;
2313 
2314          IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
2315               (AP_IMPORT_INVOICES_PKG.g_invoices_table,
2316                p_invoice_rec.invoice_id,
2317               'NOT PAY SITE',
2318                p_default_last_updated_by,
2319                p_default_last_update_login,
2320                current_calling_sequence) <> TRUE) THEN
2321            IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2322              AP_IMPORT_UTILITIES_PKG.Print(
2323                AP_IMPORT_INVOICES_PKG.g_debug_switch,
2324                'insert_rejections<-' ||current_calling_sequence);
2325            END IF;
2326            RAISE supplier_site_check_failure;
2327          END IF;
2328          l_current_invoice_status := 'N';
2329        END IF; -- Pay site flag per code is N
2330 
2331      ELSE -- Vendor site id is not null
2332        if nvl(l_pay_site_flag, 'N') = 'N' THEN
2333          -- pay site is not a pay site
2334          debug_info := '(Check Invalid Site 11) Not a pay site '
2335                        ||'per supplier site id';
2336          IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2337            AP_IMPORT_UTILITIES_PKG.Print(
2338            AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
2339          END IF;
2340 
2341          IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
2342            (AP_IMPORT_INVOICES_PKG.g_invoices_table,
2343             p_invoice_rec.invoice_id,
2344             'NOT PAY SITE',
2345             p_default_last_updated_by,
2346             p_default_last_update_login,
2347             current_calling_sequence) <> TRUE) THEN
2348            IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2349              AP_IMPORT_UTILITIES_PKG.Print(
2350              AP_IMPORT_INVOICES_PKG.g_debug_switch,
2351              'insert_rejections<-'||current_calling_sequence);
2352            END IF;
2353            RAISE supplier_site_check_failure;
2354          END IF;
2355          l_current_invoice_status := 'N';
2356        END IF; -- vendor site pay site flag is N
2357 
2358      END IF; -- Vendor site id is null
2359 
2360    END IF; -- Make sure site and PO site  belong to the same supplier
2361 
2362    -- if all checks passed successfully, save vendor_site_id
2363    if l_current_invoice_status = 'Y' THEN
2364      if l_vendor_site_id is null THEN
2365        return_vendor_site_id := l_vendor_site_id_per_code;
2366      else
2367        return_vendor_site_id := l_vendor_site_id;
2368      end if;
2369    end if;
2370 
2371  END IF; -- p_invoice_rec.vendor_site_id is null
2372          -- p_invoice_rec.vendor_site_code is null AND
2373          -- p_vendor_site_id_per_po is null
2374 
2375  p_return_vendor_site_id := return_vendor_site_id;
2376  p_current_invoice_status := l_current_invoice_status;
2377  RETURN (TRUE);
2378 
2379 EXCEPTION
2380   WHEN no_data_found THEN
2381     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
2382           (AP_IMPORT_INVOICES_PKG.g_invoices_table,
2383             p_invoice_rec.invoice_id,
2384             'INVALID SUPPLIER SITE',
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<-'
2391                                     ||current_calling_sequence);
2392       END IF;
2393       RAISE supplier_site_check_failure;
2394     END IF;
2395 
2396     l_current_invoice_status := 'N';
2397 
2398     p_return_vendor_site_id := return_vendor_site_id;
2399     p_current_invoice_status := l_current_invoice_status;
2400     RETURN (TRUE);
2401 
2402   WHEN OTHERS THEN
2403     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2404       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2405                                     debug_info);
2406     END IF;
2407 
2408     IF (SQLCODE < 0) then
2409       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2410         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2411                                       SQLERRM);
2412       END IF;
2413     END IF;
2414     RETURN (FALSE);
2415 
2416 END v_check_invalid_supplier_site;
2417 
2418 
2419 
2420 -----------------------------------------------------------------------------
2421 -- This function is used to perform Party validation
2422 --
2423 -----------------------------------------------------------------------------
2424 FUNCTION v_check_invalid_party(
2425          p_invoice_rec   IN AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
2426          p_default_last_updated_by     IN            NUMBER,
2427          p_default_last_update_login   IN            NUMBER,
2428          p_current_invoice_status      IN OUT NOCOPY VARCHAR2,
2429          p_calling_sequence            IN            VARCHAR2)
2430 RETURN BOOLEAN IS
2431 
2432 party_check_failure         EXCEPTION;
2433 l_party_id                  NUMBER;
2434 l_current_invoice_status    VARCHAR2(1) := 'Y';
2435 current_calling_sequence    VARCHAR2(2000);
2436 debug_info                  VARCHAR2(500);
2437 
2438 
2439 BEGIN
2440   -- Update the calling sequence
2441   --
2442   current_calling_sequence :=
2443     'AP_IMPORT_VALIDATION_PKG.v_check_invalid_party<-'
2444     ||P_calling_sequence;
2445 
2446   IF (p_invoice_rec.party_id is NULL) THEN
2447 
2448     -------------------------------------------------------------------------
2449     -- Step 1
2450     -- Check for Null Party.
2451     -------------------------------------------------------------------------
2452     debug_info := '(Check Invalid Party 1) Check for Null Party.';
2453     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2454       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2455                                     debug_info);
2456     END IF;
2457 
2458     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
2459             (AP_IMPORT_INVOICES_PKG.g_invoices_table,
2460              p_invoice_rec.invoice_id,
2461              'INVALID PARTY',
2462              p_default_last_updated_by,
2463              p_default_last_update_login,
2464              current_calling_sequence) <> TRUE) THEN
2465       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2466         AP_IMPORT_UTILITIES_PKG.Print(
2467           AP_IMPORT_INVOICES_PKG.g_debug_switch,
2468           'insert_rejections<-'||current_calling_sequence);
2469       END IF;
2470       RAISE party_check_failure;
2471     END IF;
2472 
2473   ELSE
2474 
2475      IF (p_invoice_rec.party_id is NOT NULL) THEN
2476        ----------------------------------------------------------------------
2477        -- Step 2
2478        -- validate party id
2479        ----------------------------------------------------------------------
2480        debug_info := '(Check Invalid Party 2) Validate party id.';
2481        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2482          AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2483                                        debug_info);
2484        END IF;
2485 
2486        SELECT party_id
2487          INTO l_party_id
2488          FROM hz_parties hzp
2489         WHERE party_id = p_invoice_rec.party_id;
2490 
2491      END IF;
2492 
2493   END IF;
2494 
2495   p_current_invoice_status := l_current_invoice_status;
2496   RETURN (TRUE);
2497 
2498 EXCEPTION
2499   WHEN no_data_found THEN
2500 
2501     -------------------------------------------------------------------------
2502     -- Step 8
2503     -- Check for invalid Party.
2504     -------------------------------------------------------------------------
2505     debug_info := '(Check Invalid Party 8) Check for invalid Party.';
2506     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2507       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2508                                     debug_info);
2509     END IF;
2510 
2511     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
2512                (AP_IMPORT_INVOICES_PKG.g_invoices_table,
2513                 p_invoice_rec.invoice_id,
2514                 'INVALID PARTY',
2515                 p_default_last_updated_by,
2516                 p_default_last_update_login,
2517                 current_calling_sequence) <> TRUE) THEN
2518       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2519         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2520           'insert_rejections<-'||current_calling_sequence);
2521       END IF;
2522       RAISE party_check_failure;
2523 
2524     END IF;
2525     l_current_invoice_status := 'N';
2526     p_current_invoice_status := l_current_invoice_status;
2527     RETURN (TRUE);
2528 
2529 
2530   WHEN OTHERS THEN
2531     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2532       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2533                                     debug_info);
2534     END IF;
2535 
2536     IF (SQLCODE < 0) then
2537       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2538         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2539                                       SQLERRM);
2540       END IF;
2541     END IF;
2542     RETURN(FALSE);
2543 
2544 END v_check_invalid_party;
2545 
2546 
2547 
2548 ------------------------------------------------------------------
2549 -- This function is used to perform Party Site validation
2550 --
2551 ------------------------------------------------------------------
2552 FUNCTION v_check_invalid_party_site (
2553          p_invoice_rec  IN  AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
2554          p_default_last_updated_by    IN            NUMBER,
2555          p_default_last_update_login  IN            NUMBER,
2556          p_return_party_site_id       OUT NOCOPY    NUMBER,
2557          p_terms_date_basis           OUT NOCOPY    VARCHAR2,
2558          p_current_invoice_status     IN OUT NOCOPY VARCHAR2,
2559          p_calling_sequence           IN            VARCHAR2)
2560 RETURN BOOLEAN IS
2561 
2562 party_site_check_failure        EXCEPTION;
2563 l_party_site_id                 NUMBER(15);
2564 l_current_invoice_status        VARCHAR2(1):='Y';
2565 return_party_site_id            NUMBER(15);
2566 current_calling_sequence        VARCHAR2(2000);
2567 debug_info                      VARCHAR2(500);
2568 
2569 BEGIN
2570   -- Update the calling sequence
2571   --
2572   current_calling_sequence :=
2573     'AP_IMPORT_VALIDATION_PKG.v_check_invalid_party_site<-'
2574      ||P_calling_sequence;
2575 
2576   debug_info := '(Check Invalid Party Site 1) Check Party Site';
2577   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2578     AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2579                                   debug_info);
2580   END IF;
2581 
2582   IF (p_invoice_rec.party_site_id is null) THEN
2583 
2584       BEGIN
2585         SELECT party_site_id
2586         INTO   l_party_site_id
2587         FROM   HZ_Party_Sites HPS
2588         WHERE  HPS.Party_ID = p_invoice_rec.party_id
2589         AND    HPS.Identifying_Address_Flag = 'Y'
2590         AND    NVL(HPS.Start_Date_Active, AP_IMPORT_INVOICES_PKG.g_inv_sysdate)
2591                          <= AP_IMPORT_INVOICES_PKG.g_inv_sysdate
2592         AND    NVL(HPS.End_Date_Active, AP_IMPORT_INVOICES_PKG.g_inv_sysdate)
2593                          >= AP_IMPORT_INVOICES_PKG.g_inv_sysdate;
2594 
2595       EXCEPTION
2596         when no_data_found then
2597              debug_info := '(Check Invalid Party Site 2) No Party Site, Reject';
2598 
2599              IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2600                  AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2601                                        debug_info);
2602              END IF;
2603 
2604              -- no party site exists
2605              IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
2606                 (AP_IMPORT_INVOICES_PKG.g_invoices_table,
2607                       p_invoice_rec.invoice_id,
2608                       'INVALID PARTY SITE',
2609                       p_default_last_updated_by,
2610                       p_default_last_update_login,
2611                       current_calling_sequence) <> TRUE) THEN
2612                    IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2613                        AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2614                                        'insert_rejections<-'
2615                                        ||current_calling_sequence);
2616                    END IF;
2617                    RAISE party_site_check_failure;
2618              END IF;
2619              l_current_invoice_status := 'N';
2620        END;
2621 
2622   ELSE
2623 
2624       debug_info := '(Check Invalid Party Site 3) Check Party Site ';
2625       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2626         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2627                                       debug_info);
2628       END IF;
2629 
2630       BEGIN
2631         --validate party site id
2632         SELECT party_site_id
2633         INTO   l_party_site_id
2634         FROM   hz_party_sites hps
2635         WHERE  party_site_id = p_invoice_rec.party_site_id
2636         AND    party_id = p_invoice_rec.party_id
2637         AND    status = 'A'
2638         AND    NVL(HPS.Start_Date_Active, AP_IMPORT_INVOICES_PKG.g_inv_sysdate)
2639                          <= AP_IMPORT_INVOICES_PKG.g_inv_sysdate
2640         AND    NVL(HPS.End_Date_Active, AP_IMPORT_INVOICES_PKG.g_inv_sysdate)
2641                          >= AP_IMPORT_INVOICES_PKG.g_inv_sysdate;
2642 
2643       EXCEPTION
2644         when no_data_found then
2645              debug_info := '(Check Invalid Party Site 2) Invalid Party Site, Reject';
2646              IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2647                  AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2648                                        debug_info);
2649              END IF;
2650 
2651              -- invalid party site
2652              IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
2653                 (AP_IMPORT_INVOICES_PKG.g_invoices_table,
2654                       p_invoice_rec.invoice_id,
2655                       'INVALID PARTY SITE',
2656                       p_default_last_updated_by,
2657                       p_default_last_update_login,
2658                       current_calling_sequence) <> TRUE) THEN
2659                    IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2660                        AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2661                                        'insert_rejections<-'
2662                                        ||current_calling_sequence);
2663                    END IF;
2664                    RAISE party_site_check_failure;
2665              END IF;
2666              l_current_invoice_status := 'N';
2667        END;
2668 
2669     END IF;
2670 
2671 
2672     -- Get terms_date_basis from ap_system_parameters
2673     /*SELECT terms_date_basis
2674     INTO   p_terms_date_basis
2675     FROM   ap_system_parameters
2676     WHERE  org_id = p_invoice_rec.org_id;*/ --Bug8323165
2677 
2678     SELECT terms_date_basis
2679     INTO   p_terms_date_basis
2680     FROM   ap_product_setup;--Bug8323165
2681 
2682 
2683 
2684     -- if all checks passed successfully, save party_site_id
2685     if l_current_invoice_status = 'Y' THEN
2686        return_party_site_id := l_party_site_id;
2687     end if;
2688 
2689 
2690   p_return_party_site_id := return_party_site_id;
2691   p_current_invoice_status := l_current_invoice_status;
2692   RETURN (TRUE);
2693 
2694 EXCEPTION
2695 
2696   WHEN OTHERS THEN
2697     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2698         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2699                                       debug_info);
2700     END IF;
2701 
2702     IF (SQLCODE < 0) then
2703       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2704           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2705                                        SQLERRM);
2706       END IF;
2707     END IF;
2708     RETURN (FALSE);
2709 
2710 END v_check_invalid_party_site;
2711 
2712 
2713 ------------------------------------------------------------------------------
2714 -- This function is used to validate that the invoice num is
2715 -- neither null, nor a duplicate of an existing or interface
2716 -- invoice.
2717 --
2718 -----------------------------------------------------------------------------
2719 FUNCTION v_check_invalid_invoice_num (
2720    p_invoice_rec                 IN AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
2721    p_allow_interest_invoices     IN VARCHAR2,   --Bug4113223
2722    p_invoice_num                    OUT NOCOPY VARCHAR2,
2723    p_default_last_updated_by     IN            NUMBER,
2724    p_default_last_update_login   IN            NUMBER,
2725    p_current_invoice_status      IN OUT NOCOPY VARCHAR2,
2726    p_calling_sequence            IN            VARCHAR2) RETURN BOOLEAN
2727 IS
2728 
2729 invoice_num_check_failure    EXCEPTION;
2730 l_invoice_count              NUMBER;
2731 l_count_in_history_invoices  NUMBER;
2732 l_invoice_num                AP_INVOICES.INVOICE_NUM%TYPE;
2733 l_current_invoice_status     VARCHAR2(1) := 'Y';
2734 current_calling_sequence     VARCHAR2(2000);
2735 debug_info                   VARCHAR2(500);
2736 
2737 BEGIN
2738   -- Update the calling sequence
2739   --
2740   current_calling_sequence :=
2741     'AP_IMPORT_VALIDATION_PKG.v_check_invalid_invoice_num<-'
2742     ||P_calling_sequence;
2743 
2744   IF (p_invoice_rec.invoice_num IS NULL) Then
2745     l_invoice_num := to_char(nvl(p_invoice_rec.invoice_date,
2746                                  AP_IMPORT_INVOICES_PKG.g_inv_sysdate),
2747                              'DD/MM/RR');
2748   ELSE
2749     l_invoice_num := p_invoice_rec.invoice_num;
2750   End If;
2751 
2752 
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                         '------------------> l_invoice_num  =
2756                         '||l_invoice_num);
2757   END IF;
2758 
2759   IF (l_invoice_num is NULL) THEN
2760 
2761      ------------------------------------------------------------------------
2762      -- Step 1
2763      -- Check for NULL Invoice NUMBER.
2764      -- This should never happen
2765      ------------------------------------------------------------------------
2766      debug_info := '(Check Invoice Number 1) Check for Null Invoice Number.';
2767      IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2768        AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2769                                      debug_info);
2770      END IF;
2771 
2772      IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
2773           (AP_IMPORT_INVOICES_PKG.g_invoices_table,
2774             p_invoice_rec.invoice_id,
2775             'NO INVOICE NUMBER',
2776             p_default_last_updated_by,
2777             p_default_last_update_login,
2778             current_calling_sequence) <> TRUE) THEN
2779        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2780          AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2781                                        'insert_rejections<-'
2782                                        ||current_calling_sequence);
2783        END IF;
2784        RAISE invoice_num_check_failure;
2785      END IF;
2786 
2787      l_current_invoice_status := 'N';
2788 
2789   ELSE
2790      ------------------------------------------------------------------------
2791      -- Step 2
2792      -- Check for Invalid Invoice NUMBER.
2793      ------------------------------------------------------------------------
2794 
2795      /* Bugfix: 4113223
2796      Raise an exception if the invoice number has more than 45 characters
2797      and interest invoices option is enabled*/
2798 
2799      debug_info := '(Check Invoice Number 2) Check for Invalid Invoice Number.';
2800      IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2801        AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2802                                      debug_info);
2803      END IF;
2804 
2805      IF (nvl(p_allow_interest_invoices,'N') = 'Y'
2806          AND LENGTH(l_invoice_num) > 45) THEN
2807 
2808 	IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
2809                        (AP_IMPORT_INVOICES_PKG.g_invoices_table,
2810                         p_invoice_rec.invoice_id,
2811                         'INVALID INVOICE NUMBER',
2812                         p_default_last_updated_by,
2813                         p_default_last_update_login,
2814                         current_calling_sequence,
2815                         'Y',
2816                         'INVOICE NUMBER',
2817                         l_invoice_num) <> TRUE) THEN
2818          IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2819            AP_IMPORT_UTILITIES_PKG.Print(
2820              AP_IMPORT_INVOICES_PKG.g_debug_switch,
2821              'insert_rejections<-'||current_calling_sequence);
2822          END IF;
2823          RAISE invoice_num_check_failure;
2824        END IF;
2825 
2826        l_current_invoice_status := 'N';
2827 
2828      END IF;
2829 
2830      ------------------------------------------------------------------------
2831      -- Step 3
2832      -- Check for Duplicate Invoice NUMBER.
2833      ------------------------------------------------------------------------
2834      debug_info := '(Check Invoice Number 3) Check for Duplicate '
2835                    ||'Invoice Number.';
2836      IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2837        AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2838                                      debug_info);
2839      END IF;
2840 
2841      SELECT count(*)
2842       INTO  l_invoice_count
2843       FROM  ap_invoices
2844      WHERE  vendor_id = p_invoice_rec.vendor_id
2845        AND  invoice_num = l_invoice_num
2846        AND (party_site_id = p_invoice_rec.party_site_id /*Bug9105666*/
2847  	OR (party_site_id is null and p_invoice_rec.party_site_id is null)) /*Bug9105666*/
2848        AND  rownum = 1;
2849 
2850 
2851      SELECT count(*)
2852        INTO l_count_in_history_invoices
2853        FROM ap_history_invoices ahi,
2854             ap_supplier_sites ass /*Bug9105666*/
2855        WHERE ahi.vendor_id = ass.vendor_id /*Bug9105666*/
2856  	 AND ahi.org_id = ass.org_id /*Bug9105666*/
2857  	 AND ahi.vendor_id = p_invoice_rec.vendor_id
2858  	 AND (ass.party_site_id = p_invoice_rec.party_site_id /*Bug9105666*/
2859  	      OR (ass.party_site_id is null and p_invoice_rec.party_site_id is null)) /*Bug9105666*/
2860  	 AND ahi.invoice_num = l_invoice_num;
2861 
2862 
2863      IF ((l_invoice_count > 0) OR (l_count_in_history_invoices > 0)) THEN
2864 
2865        -- Pass context for XML GATEWAY
2866        IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
2867                        (AP_IMPORT_INVOICES_PKG.g_invoices_table,
2868                         p_invoice_rec.invoice_id,
2869                         'DUPLICATE INVOICE NUMBER',
2870                         p_default_last_updated_by,
2871                         p_default_last_update_login,
2872                         current_calling_sequence,
2873                         'Y',
2874                         'INVOICE NUMBER',
2875                         l_invoice_num) <> TRUE) THEN
2876          IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2877            AP_IMPORT_UTILITIES_PKG.Print(
2878              AP_IMPORT_INVOICES_PKG.g_debug_switch,
2879              'insert_rejections<-'||current_calling_sequence);
2880          END IF;
2881          RAISE invoice_num_check_failure;
2882        END IF;
2883 
2884        l_current_invoice_status := 'N';
2885 
2886      END IF;
2887   END IF;
2888 
2889   p_current_invoice_status := l_current_invoice_status;
2890   p_invoice_num := l_invoice_num;
2891   RETURN (TRUE);
2892 
2893 EXCEPTION
2894   WHEN OTHERS THEN
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 (SQLCODE < 0) then
2901       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2902         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2903                                       SQLERRM);
2904       END IF;
2905     END IF;
2906     RETURN(FALSE);
2907 
2908 END v_check_invalid_invoice_num;
2909 
2910 
2911 ------------------------------------------------------------------
2912 -- This function is used to validate that the invoice currency code
2913 -- is neither inactive, nor invalid.
2914 --
2915 ------------------------------------------------------------------
2916 FUNCTION v_check_invalid_inv_curr_code (
2917            p_invoice_rec IN    AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
2918            p_inv_currency_code            OUT NOCOPY VARCHAR2,
2919            p_min_acc_unit_inv_curr        OUT NOCOPY NUMBER,
2920            p_precision_inv_curr           OUT NOCOPY NUMBER,
2921            p_default_last_updated_by   IN            NUMBER,
2922            p_default_last_update_login IN            NUMBER,
2923            p_current_invoice_status    IN OUT NOCOPY VARCHAR2,
2924            p_calling_sequence          IN            VARCHAR2) RETURN BOOLEAN
2925 IS
2926 
2927 invalid_inv_curr_code_failure  EXCEPTION;
2928 l_current_invoice_status       VARCHAR2(1) := 'Y';
2929 l_start_date_active            DATE;
2930 l_end_date_active              DATE;
2931 current_calling_sequence       VARCHAR2(2000);
2932 debug_info                     VARCHAR2(500);
2933 l_min_acc_unit_inv_curr        fnd_currencies.minimum_accountable_unit%TYPE;
2934 l_precision_inv_curr           fnd_currencies.precision%TYPE;
2935 l_enabled_flag                 fnd_currencies.enabled_flag%TYPE;
2936 
2937 l_valid_inv_currency           fnd_currencies.currency_code%TYPE;
2938 
2939 BEGIN
2940   -- Update the calling sequence
2941   --
2942   current_calling_sequence :=
2943     'AP_IMPORT_VALIDATION_PKG.v_check_invalid_inv_curr_code<-'
2944     ||P_calling_sequence;
2945 
2946   p_inv_currency_code := p_invoice_rec.invoice_currency_code;
2947 
2948 
2949   --------------------------------------------------------------------------
2950   -- Step 1
2951   -- If Invoice Currency Code is null ,default from PO Vendor Sites
2952   --------------------------------------------------------------------------
2953   IF (p_invoice_rec.invoice_currency_code IS NULL) Then
2954     debug_info := '(Check Invoice Currency Code 1) Invoice Currency Code is '
2955                   ||'null ,default from PO Vendor Sites.';
2956     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2957       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2958                                     debug_info);
2959     END IF;
2960 
2961     -- Added for payment requests project --commented for Bug9184247
2962 /*    IF (p_invoice_rec.party_site_id IS NOT NULL) THEN
2963         -- If No curr code in vendor site ,then the default exception
2964         -- will reject.
2965         SELECT Invoice_currency_code
2966           INTO p_inv_currency_code
2967           FROM AP_System_Parameters
2968          WHERE Org_ID = p_invoice_rec.org_id;
2969 
2970     ELSE
2971         -- If No curr code in vendor site ,then the default exception
2972         -- will reject.
2973         SELECT Invoice_currency_code
2974           INTO p_inv_currency_code
2975           FROM po_vendor_sites
2976          WHERE vendor_site_id = p_invoice_rec.vendor_site_id;
2977     END IF;*/ --commented for Bug9184247
2978   --Start Bug9184247
2979             IF p_invoice_rec.vendor_site_id IS NOT NULL
2980             THEN
2981             BEGIN
2982                 SELECT Invoice_currency_code
2983                 INTO p_inv_currency_code
2984                 FROM po_vendor_sites
2985                 WHERE vendor_site_id = p_invoice_rec.vendor_site_id;
2986             EXCEPTION
2987               WHEN OTHERS THEN
2988                 p_inv_currency_code := null;
2989             END;
2990           END IF;
2991 
2992           IF p_inv_currency_code IS NULL
2993           THEN
2994             SELECT Invoice_currency_code
2995               INTO p_inv_currency_code
2996               FROM AP_System_Parameters
2997              WHERE Org_ID = p_invoice_rec.org_id;
2998           END IF;
2999 
3000 --End Bug9184247
3001   END IF;
3002 
3003   --------------------------------------------------------------------------
3004   -- Step 2
3005   -- Get the state of the invoice currency and precision and mau
3006   --------------------------------------------------------------------------
3007   debug_info := '(Check Invoice Currency Code 2) Get precision, '
3008                 ||'mau for Invoice Currency Code.';
3009   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3010     AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
3011                                   debug_info);
3012   END IF;
3013 
3014   /*SELECT start_date_active, end_date_active,
3015          minimum_accountable_unit, precision, enabled_flag
3016     INTO l_start_date_active, l_end_date_active,
3017          l_min_acc_unit_inv_curr,l_precision_inv_curr, l_enabled_flag
3018     FROM fnd_currencies
3019    WHERE currency_code = p_inv_currency_code; */
3020 
3021    -- Bug 5448579
3022   FOR i IN AP_IMPORT_INVOICES_PKG.g_fnd_currency_tab.First..AP_IMPORT_INVOICES_PKG.g_fnd_currency_tab.Last
3023   LOOP
3024     IF AP_IMPORT_INVOICES_PKG.g_fnd_currency_tab(i).currency_code = p_inv_currency_code THEN
3025         l_valid_inv_currency  := AP_IMPORT_INVOICES_PKG.g_fnd_currency_tab(i).currency_code;
3026         l_start_date_active   := AP_IMPORT_INVOICES_PKG.g_fnd_currency_tab(i).start_date_active;
3027         l_end_date_active     := AP_IMPORT_INVOICES_PKG.g_fnd_currency_tab(i).end_date_active;
3028         l_min_acc_unit_inv_curr := AP_IMPORT_INVOICES_PKG.g_fnd_currency_tab(i).minimum_accountable_unit;
3029         l_precision_inv_curr  := AP_IMPORT_INVOICES_PKG.g_fnd_currency_tab(i).precision;
3030         l_enabled_flag        := AP_IMPORT_INVOICES_PKG.g_fnd_currency_tab(i).enabled_flag;
3031       EXIT;
3032     END IF;
3033   END LOOP;
3034 
3035   debug_info := 'l_valid_inv_currency: '||l_valid_inv_currency;
3036   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3037     AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
3038                                     debug_info);
3039   END IF;
3040 
3041 
3042   p_min_acc_unit_inv_curr := l_min_acc_unit_inv_curr;
3043   p_precision_inv_curr := l_precision_inv_curr;
3044 
3045   IF ((trunc(AP_IMPORT_INVOICES_PKG.g_inv_sysdate) <
3046        nvl(l_start_date_active,
3047            trunc(AP_IMPORT_INVOICES_PKG.g_inv_sysdate))) OR
3048       (AP_IMPORT_INVOICES_PKG.g_inv_sysdate >=
3049        nvl(l_end_date_active,
3050            AP_IMPORT_INVOICES_PKG.g_inv_sysdate+1))) OR
3051       l_enabled_flag <> 'Y' THEN
3052 
3053     -------------------------------------------------------------------------
3054     -- Step 3
3055     -- Check for Inactive Invoice Currency Code.
3056     -------------------------------------------------------------------------
3057     debug_info := '(Check Invoice Currency Code 3) Check for Inactive Invoice'
3058                   ||' Currency Code.';
3059     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3060       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
3061                                     debug_info);
3062     END IF;
3063 
3064     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
3065           (AP_IMPORT_INVOICES_PKG.g_invoices_table,
3066             p_invoice_rec.invoice_id,
3067             'INACTIVE CURRENCY CODE',
3068             p_default_last_updated_by,
3069             p_default_last_update_login,
3070             current_calling_sequence) <> TRUE) THEN
3071       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3072         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
3073                             'insert_rejections<-'||current_calling_sequence);
3074       END IF;
3075       RAISE invalid_inv_curr_code_failure;
3076     END IF;
3077 
3078     l_current_invoice_status := 'N';
3079   END IF;
3080 
3081   --Bug8770461
3082   IF( l_valid_inv_currency is null) then
3083     --------------------------------------------------------------------------
3084     -- Step 4
3085     -- Check for Invalid Invoice Currency Code.
3086     --------------------------------------------------------------------------
3087     debug_info := '(Check Invoice Currency Code 4) Check for Invalid Invoice '
3088                   ||'Currency Code.';
3089     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3090       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
3091                                     debug_info);
3092     END IF;
3093 
3094     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
3095           (AP_IMPORT_INVOICES_PKG.g_invoices_table,
3096             p_invoice_rec.invoice_id,
3097             'INVALID CURRENCY CODE',
3098             p_default_last_updated_by,
3099             p_default_last_update_login,
3100             current_calling_sequence) <> TRUE) THEN
3101       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3102         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
3103         'insert_rejections<-'||current_calling_sequence);
3104       END IF;
3105       RAISE invalid_inv_curr_code_failure;
3106     END IF;
3107 	l_current_invoice_status := 'N';
3108   END IF;
3109   --End of Bug8770461
3110 
3111   p_current_invoice_status := l_current_invoice_status;
3112   RETURN (TRUE);
3113 
3114 EXCEPTION
3115   --Bug8770461: This exception block is not required since the
3116   -- query was commented for bug5448579.
3117   /*
3118   WHEN no_data_found THEN
3119 
3120     --------------------------------------------------------------------------
3121     -- Step 4
3122     -- Check for Invalid Invoice Currency Code.
3123     --------------------------------------------------------------------------
3124     debug_info := '(Check Invoice Currency Code 4) Check for Invalid Invoice '
3125                   ||'Currency Code.';
3126     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3127       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
3128                                     debug_info);
3129     END IF;
3130 
3131     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
3132           (AP_IMPORT_INVOICES_PKG.g_invoices_table,
3133             p_invoice_rec.invoice_id,
3134             'INVALID CURRENCY CODE',
3135             p_default_last_updated_by,
3136             p_default_last_update_login,
3137             current_calling_sequence) <> TRUE) THEN
3138       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3139         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
3140         'insert_rejections<-'||current_calling_sequence);
3141       END IF;
3142       RAISE invalid_inv_curr_code_failure;
3143     END IF;
3144 
3145     l_current_invoice_status := 'N';
3146     p_current_invoice_status := l_current_invoice_status;
3147     RETURN (TRUE);
3148     End of bug8770461*/
3149   WHEN OTHERS THEN
3150     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3151       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
3152                                     debug_info);
3153     END IF;
3154 
3155     IF (SQLCODE < 0) then
3156       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3157         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
3158                                       SQLERRM);
3159       END IF;
3160     END IF;
3161     RETURN(FALSE);
3162 
3163 END v_check_invalid_inv_curr_code;
3164 
3165 
3166 ------------------------------------------------------------------------------
3167 -- This function is used to validate that the invoice type and
3168 -- amount are appropriate.  It also reads the invoice type if
3169 -- null and also sets the match mode based on invoice type.
3170 --
3171 ------------------------------------------------------------------------------
3172 FUNCTION v_check_invoice_type_amount (
3173          p_invoice_rec               IN
3174           AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
3175          p_invoice_type_lookup_code     OUT NOCOPY VARCHAR2,
3176          p_match_mode                   OUT NOCOPY VARCHAR2,
3177          p_precision_inv_curr        IN            NUMBER,
3178          p_default_last_updated_by   IN            NUMBER,
3179          p_default_last_update_login IN            NUMBER,
3180          p_current_invoice_status    IN OUT NOCOPY VARCHAR2,
3181          p_calling_sequence          IN            VARCHAR2) RETURN BOOLEAN
3182 IS
3183 
3184 invalid_type_lookup_failure    EXCEPTION;
3185 l_current_invoice_status       VARCHAR2(1) := 'Y';
3186 l_lines_amount_sum             NUMBER := 0;
3187 l_no_of_lines                  NUMBER := 0;
3188 current_calling_sequence       VARCHAR2(2000);
3189 debug_info                     VARCHAR2(500);
3190 
3191 BEGIN
3192   -- Update the calling sequence
3193   --
3194   current_calling_sequence :=
3195     'AP_IMPORT_INVOICES_PKG.v_check_invoice_type_amount<-'
3196     ||P_calling_sequence;
3197 
3198   --------------------------------------------------------------------------
3199   -- Step 1
3200   -- Check for Invalid Invoice type lookup code.
3201   --------------------------------------------------------------------------
3202   debug_info := '(Check Invoice Type and Amount 1) Check for Invalid Invoice'
3203                 ||' type lookup code.';
3204   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3205     AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
3206                                   debug_info);
3207   END IF;
3208 
3209   p_invoice_type_lookup_code := p_invoice_rec.invoice_type_lookup_code;
3210 
3211   -- We only support importing invoice types 'STANDARD', 'CREDIT',
3212   -- 'PREPAYMENT'  -- Contract Payments
3213   -- and 'PO PRICE ADJUST' --Retropricing
3214   -- and 'DEBIT' -- Debit Memo
3215   -- Also we check for invalid lookup code only if it is not null
3216   -- Else we populate STANDARD for invoice amount >=0 and CREDIT for
3217   -- invoice amount <0
3218 
3219   --Bug 4410499 Added EXPENSE REPORT  to the list of
3220   --invoice types we support thru open interface import
3221 
3222   --Contract Payments : Added 'PREPAYMENT' to the IF condition.
3223   --Payment Requests : Added 'PAYMENT REQUEST' to the IF condition
3224   --Bug 7299826 EC Subcon Project : Added 'DEBIT' to the IF condition
3225   IF ((p_invoice_rec.invoice_type_lookup_code IS NOT NULL) AND
3226      (p_invoice_rec.invoice_type_lookup_code NOT IN (
3227                   'STANDARD','CREDIT', 'DEBIT', 'PO PRICE ADJUST','PREPAYMENT','EXPENSE REPORT',
3228                   'PAYMENT REQUEST')))
3229     THEN
3230 
3231     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
3232           (AP_IMPORT_INVOICES_PKG.g_invoices_table,
3233             p_invoice_rec.invoice_id,
3234             'INVALID INV TYPE LOOKUP',
3235             p_default_last_updated_by,
3236             p_default_last_update_login,
3237             current_calling_sequence) <> TRUE) THEN
3238       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3239         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
3240         'insert_rejections<-'||current_calling_sequence);
3241       END IF;
3242       RAISE invalid_type_lookup_failure;
3243     END IF;
3244 
3245     l_current_invoice_status := 'N';
3246 
3247   ELSIF ((p_invoice_rec.invoice_type_lookup_code IS NULL) AND
3248          (p_invoice_rec.invoice_amount >=0)) THEN
3249 
3250     debug_info := '(Check Invoice Type and Amount 2) Invoice type lookup '
3251                   ||'code is null, setting to STANDARD.';
3252     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3253       AP_IMPORT_UTILITIES_PKG.Print(
3254       AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
3255     END IF;
3256 
3257     p_invoice_type_lookup_code := 'STANDARD';
3258 
3259   ELSIF ((p_invoice_rec.invoice_type_lookup_code IS NULL) AND
3260          (p_invoice_rec.invoice_amount < 0)) THEN
3261 
3262     debug_info := '(Check Invoice Type and Amount 2) Invoice type lookup '
3263                   ||'code is null, setting to CREDIT.';
3264     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3265       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
3266                                     debug_info);
3267     END IF;
3268 
3269     p_invoice_type_lookup_code := 'CREDIT';
3270 
3271   END IF;
3272 
3273   --------------------------------------------------------------------------
3274   -- Step 2
3275   -- Check for Null Invoice Amount.
3276   --------------------------------------------------------------------------
3277   debug_info := '(Check Invoice Type and Amount 2) Check for Null Invoice'
3278                 ||' amount.';
3279   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3280     AP_IMPORT_UTILITIES_PKG.Print(
3281     AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
3282   END IF;
3283 
3284   IF (p_invoice_rec.invoice_amount IS NULL) THEN
3285 
3286     -- Set contextual information for XML GATEWAY
3287     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
3288                          (AP_IMPORT_INVOICES_PKG.g_invoices_table,
3289                           p_invoice_rec.invoice_id,
3290                           'INVALID INVOICE AMOUNT',
3291                           p_default_last_updated_by,
3292                           p_default_last_update_login,
3293                           current_calling_sequence,
3294                           'Y') <> TRUE) THEN
3295       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3296         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
3297         'insert_rejections<-'||current_calling_sequence);
3298       END IF;
3299       RAISE invalid_type_lookup_failure;
3300     END IF;
3301 
3302     l_current_invoice_status := 'N';
3303 
3304   ELSE
3305 
3306     --------------------------------------------------------------------------
3307     -- Step 3
3308     -- Check for Invalid Invoice amount.
3309     --------------------------------------------------------------------------
3310     debug_info := '(Check Invoice Type and Amount 3) Check for Invalid '
3311                   ||'Invoice amount.';
3312     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3313       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
3314                                     debug_info);
3315     END IF;
3316 
3317     --Contract Payments: Modified the IF condition to add 'Prepayment' type
3318     --Payment Requests: Added 'PAYMENT REQUEST' type to the IF condition
3319     IF (((nvl(p_invoice_type_lookup_code,'DUMMY')
3320                     IN ('Standard','STANDARD','Prepayment','PREPAYMENT'/*, -- Bug 7002267
3321                         'PAYMENT REQUEST'*/)) AND
3322                        (p_invoice_rec.invoice_amount < 0))  OR
3323        ((nvl(p_invoice_type_lookup_code,'DUMMY') IN ('CREDIT', 'DEBIT')) AND --Bug 7299826 - Added DEBIT
3324           (p_invoice_rec.invoice_amount > 0))) THEN        -- Bug 2822878
3325 
3326       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
3327            (AP_IMPORT_INVOICES_PKG.g_invoices_table,
3328             p_invoice_rec.invoice_id,
3329             'INCONSISTENT INV TYPE/AMT',
3330             p_default_last_updated_by,
3331             p_default_last_update_login,
3332             current_calling_sequence) <> TRUE) THEN
3333         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3334           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
3335           'insert_rejections<-'||current_calling_sequence);
3336         END IF;
3337         RAISE invalid_type_lookup_failure;
3338       END IF;
3339       l_current_invoice_status := 'N';
3340     END IF;
3341 
3342     --------------------------------------------------------------------------
3343     -- Step 4
3344     -- Check for Invoice amount to match sum of invoice lines amount.
3345     -- Also check that number of lines is not 0.
3346     -- The amount check will only be done for EDI GATEWAY invoices since all
3347     -- other type of invoices should go through as they would in the Invoice
3348     -- Workbench. Specifically, this change came about due to the need to have
3349     -- ERS invoices entered with lines exclusive of tax and no tax line in
3350     -- which case the invoice amount will not total the sum of the lines.
3351     -- The tax is then calculated through either calculate tax in the invoice
3352     -- workbench or approval.  In any case, if the total of the lines does
3353     -- not equal the invoice total the invoice would go on hold.
3354     -------------------------------------------------------------------------
3355     --Retropricing
3356     IF AP_IMPORT_INVOICES_PKG.g_source <> 'PPA' THEN
3357         debug_info := '(Check Invoice Type and Amount 4) Check for Invoice amount'
3358                       ||' to match sum of invoice line amounts.';
3359         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3360           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
3361                                         debug_info);
3362         END IF;
3363 
3364         SELECT nvl(sum(amount),0) , count(*)
3365           INTO l_lines_amount_sum, l_no_of_lines
3366           FROM ap_invoice_lines_interface
3367          WHERE invoice_id = p_invoice_rec.invoice_id;
3368 
3369         IF (AP_IMPORT_INVOICES_PKG.g_source = 'EDI GATEWAY') THEN
3370           debug_info := '(Check Invoice step 4) Check Invoice amount to match '
3371                         ||'sum of invoice line amounts for EDI only.';
3372           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3373             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
3374                                           debug_info);
3375           END IF;
3376 
3377           IF (l_lines_amount_sum <> p_invoice_rec.invoice_amount) THEN
3378 
3379             IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
3380                (AP_IMPORT_INVOICES_PKG.g_invoices_table,
3381                 p_invoice_rec.invoice_id,
3382                 'INVOICE AMOUNT INCORRECT',
3383                 p_default_last_updated_by,
3384                 p_default_last_update_login,
3385                 current_calling_sequence) <> TRUE) THEN
3386               IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3387                 AP_IMPORT_UTILITIES_PKG.Print(
3388                 AP_IMPORT_INVOICES_PKG.g_debug_switch,
3389                 'insert_rejections<-'||current_calling_sequence);
3390               END IF;
3391               RAISE invalid_type_lookup_failure;
3392             END IF;
3393             l_current_invoice_status := 'N';
3394           END IF;
3395         END IF; -- Source EDI GATEWAY
3396 
3397         IF (l_no_of_lines = 0) THEN
3398           debug_info := '(Check Invoice Type and Amount 4) No Lines for this '
3399                         ||'invoice.';
3400           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3401             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
3402                                           debug_info);
3403           END IF;
3404 
3405           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
3406               (AP_IMPORT_INVOICES_PKG.g_invoices_table,
3407                 p_invoice_rec.invoice_id,
3408                 'NO INVOICE LINES',
3409                 p_default_last_updated_by,
3410                 p_default_last_update_login,
3411                 current_calling_sequence) <> TRUE) THEN
3412             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3413               AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
3414               'insert_rejections<-'||current_calling_sequence);
3415             END IF;
3416             RAISE invalid_type_lookup_failure;
3417           END IF;
3418           l_current_invoice_status := 'N';
3419         END IF; -- No of lines is 0
3420     END IF; --source <> PPA
3421 
3422     --------------------------------------------------------------------------
3423     -- Step 5
3424     -- Check for appropriate formatting of the invoice amount.
3425     --------------------------------------------------------------------------
3426     IF LENGTH((ABS(p_invoice_rec.invoice_amount) -
3427                  TRUNC(ABS(p_invoice_rec.invoice_amount)))) - 1
3428                > NVL(p_precision_inv_curr,0) THEN
3429       debug_info := '(Check Invoice Type and Amount 5) Invoice or Lines '
3430                     ||'amount exceeds precision.';
3431       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3432         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
3433                                       debug_info);
3434       END IF;
3435 
3436       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
3437                        (AP_IMPORT_INVOICES_PKG.g_invoices_table,
3438                         p_invoice_rec.invoice_id,
3439                         'AMOUNT EXCEEDS PRECISION',
3440                         p_default_last_updated_by,
3441                         p_default_last_update_login,
3442                         current_calling_sequence) <> TRUE) THEN
3443         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3444           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
3445           'insert_rejections<-'||current_calling_sequence);
3446         END IF;
3447         RAISE invalid_type_lookup_failure;
3448       END IF;
3449       l_current_invoice_status := 'N';
3450     END IF; -- Precision exceeded
3451 
3452   END IF; -- Invoice amount is null
3453 
3454   --------------------------------------------------------------------------
3455   -- Step 6
3456   -- Determine match mode.
3457   --------------------------------------------------------------------------
3458   debug_info := '(Check Invoice Type and Amount 6) Determine Match Mode.';
3459   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3460     AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
3461                                   debug_info);
3462   END IF;
3463 
3464   If (p_invoice_type_lookup_code = 'PO PRICE ADJUST') Then
3465 
3466       p_match_mode := 'PO PRICE ADJUSTMENT';
3467 
3468   End If;
3469 
3470   p_current_invoice_status := l_current_invoice_status;
3471   RETURN (TRUE);
3472 
3473 EXCEPTION
3474   WHEN OTHERS THEN
3475     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3476       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
3477                                     debug_info);
3478     END IF;
3479 
3480     IF (SQLCODE < 0) then
3481       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3482         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
3483                                       SQLERRM);
3484       END IF;
3485     END IF;
3486   RETURN(FALSE);
3487 
3488 END v_check_invoice_type_amount;
3489 
3490 
3491 ----------------------------------------------------------------------------
3492 -- This function is used to validate that the awt information
3493 -- is valid and consistent.
3494 --
3495 ----------------------------------------------------------------------------
3496 FUNCTION v_check_invalid_awt_group (
3497     p_invoice_rec        IN AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
3498     p_awt_group_id                  OUT NOCOPY NUMBER,
3499     p_default_last_updated_by    IN            NUMBER,
3500     p_default_last_update_login  IN            NUMBER,
3501     p_current_invoice_status     IN OUT NOCOPY VARCHAR2,
3502     p_calling_sequence           IN            VARCHAR2) RETURN BOOLEAN
3503 IS
3504 
3505 awt_group_check_failure     EXCEPTION;
3506 l_current_invoice_status    VARCHAR2(1) := 'Y';
3507 l_awt_group_id              AP_INVOICES.AWT_GROUP_ID%TYPE;
3508 l_awt_group_id_per_name     AP_INVOICES.AWT_GROUP_ID%TYPE;
3509 l_inactive_date             DATE;
3510 l_inactive_date_per_name    DATE;
3511 current_calling_sequence    VARCHAR2(2000);
3512 debug_info                  VARCHAR2(500);
3513 
3514 BEGIN
3515   -- Update the calling sequence
3516   --
3517   current_calling_sequence :=
3518     'AP_IMPORT_VALIDATION_PKG.v_check_invalid_awt_group<-'
3519     ||P_calling_sequence;
3520 
3521   IF p_invoice_rec.awt_group_id is not null THEN
3522 
3523     --validate awt_group_id
3524     SELECT group_id, inactive_date
3525       INTO l_awt_group_id, l_inactive_date
3526       FROM ap_awt_groups
3527      WHERE group_id = p_invoice_rec.awt_group_id;
3528 
3529   END IF;
3530 
3531   IF (p_invoice_rec.awt_group_name is NOT NULL) THEN
3532     --validate awt group name and retrieve awt group id
3533     SELECT group_id, inactive_date
3534       INTO l_awt_group_id_per_name, l_inactive_date_per_name
3535       FROM ap_awt_groups
3536      WHERE name = p_invoice_rec.awt_group_name;
3537   END IF;
3538 
3539   IF (l_awt_group_id is NOT NULL) AND
3540      (l_awt_group_id_per_name is NOT NULL) AND
3541      (l_awt_group_id <> l_awt_group_id_per_name) THEN
3542 
3543     -------------------------------------------------------------------------
3544     -- Step 1
3545     -- Check for AWT Group Id and Group Name Inconsistency.
3546     -------------------------------------------------------------------------
3547     debug_info := '(Check AWT Group 1) Check for AWT Group Id and Group Name'
3548                   ||' Inconsistency.';
3549     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3550       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
3551                                     debug_info);
3552     END IF;
3553 
3554     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
3555           (AP_IMPORT_INVOICES_PKG.g_invoices_table,
3556             p_invoice_rec.invoice_id,
3557             'INCONSISTENT AWT GROUP',
3558             p_default_last_updated_by,
3559             p_default_last_update_login,
3560             current_calling_sequence) <> TRUE) THEN
3561       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3562         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
3563         'insert_rejections<-'||current_calling_sequence);
3564       END IF;
3565       RAISE awt_group_check_failure;
3566     END IF;
3567     l_current_invoice_status := 'N';
3568 
3569   ELSE
3570 
3571     ------------------------------------------------------------------------
3572     -- Step 2
3573     -- Check for Inactive AWT Group
3574     ------------------------------------------------------------------------
3575     debug_info := '(Check AWT Group 2) Check for Inactive AWT Group';
3576     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3577       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
3578                                     debug_info);
3579     END IF;
3580 
3581     IF ((l_awt_group_id is NULL) and
3582         (l_awt_group_id_per_name is NOT NULL)) THEN
3583 
3584       IF AP_IMPORT_INVOICES_PKG.g_inv_sysdate >=
3585          nvl(l_inactive_date_per_name,
3586              AP_IMPORT_INVOICES_PKG.g_inv_sysdate+1) THEN
3587         --------------------------------------------------------------
3588         -- inactive AWT group (per name)
3589         --
3590         ---------------------------------------------------------------
3591         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
3592                              (AP_IMPORT_INVOICES_PKG.g_invoices_table,
3593                             p_invoice_rec.invoice_id,
3594             'INACTIVE AWT GROUP',
3595             p_default_last_updated_by,
3596             p_default_last_update_login,
3597             current_calling_sequence) <> TRUE) THEN
3598           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3599             AP_IMPORT_UTILITIES_PKG.Print(
3600             AP_IMPORT_INVOICES_PKG.g_debug_switch,
3601             'insert_rejections<-'||current_calling_sequence);
3602           END IF;
3603           RAISE awt_group_check_failure;
3604         END IF;
3605 
3606         l_current_invoice_status := 'N';
3607 
3608       END IF; -- Inactive AWT Group per name
3609 
3610     ELSIF (((l_awt_group_id is NOT NULL) and
3611             (l_awt_group_id_per_name is NULL)) OR
3612            ((l_awt_group_id is NOT NULL) and
3613             (l_awt_group_id_per_name is NOT NULL) and
3614             (l_awt_group_id = l_awt_group_id_per_name))) THEN
3615 
3616       IF AP_IMPORT_INVOICES_PKG.g_inv_sysdate >=
3617          nvl(l_inactive_date, AP_IMPORT_INVOICES_PKG.g_inv_sysdate+1) THEN
3618 
3619         --------------------------------------------------------------
3620         -- inactive AWT group (as per id)
3621         --
3622         --------------------------------------------------------------
3623         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
3624           (AP_IMPORT_INVOICES_PKG.g_invoices_table,
3625             p_invoice_rec.invoice_id,
3626             'INACTIVE AWT GROUP',
3627             p_default_last_updated_by,
3628             p_default_last_update_login,
3629             current_calling_sequence) <> TRUE) THEN
3630           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3631             AP_IMPORT_UTILITIES_PKG.Print(
3632             AP_IMPORT_INVOICES_PKG.g_debug_switch,
3633             'insert_rejections<-'||current_calling_sequence);
3634           END IF;
3635           RAISE awt_group_check_failure;
3636         END IF;
3637 
3638         l_current_invoice_status := 'N';
3639 
3640       END IF; -- Inactive AWT Group per id
3641 
3642     END IF; -- awt group id is null and awt group id per name is not null
3643 
3644   END IF; -- awt group id is not null, awt group id per name is not null
3645           -- but they differ
3646 
3647   IF (l_awt_group_id is not null) then
3648     p_awt_group_id := l_awt_group_id;
3649   ELSIF (l_awt_group_id_per_name IS NOT NULL) THEN
3650     p_awt_group_id := l_awt_group_id_per_name;
3651   ELSE
3652     IF ((l_current_invoice_status <> 'N') AND
3653            (p_invoice_rec.invoice_type_lookup_code <> 'PAYMENT REQUEST')) THEN
3654        -- Get awt group id from supplier site
3655       BEGIN
3656         SELECT awt_group_id
3657           INTO p_awt_group_id
3658       FROM po_vendor_sites
3659          WHERE vendor_id = p_invoice_rec.vendor_id
3660          AND vendor_site_id = p_invoice_rec.vendor_site_id;
3661       EXCEPTION
3662     WHEN no_data_found THEN
3663       RAISE awt_group_check_failure;
3664     WHEN OTHERS THEN
3665       RAISE awt_group_check_failure;
3666       END;
3667     END IF;
3668   END IF;
3669 
3670 
3671   p_current_invoice_status := l_current_invoice_status;
3672 
3673   RETURN (TRUE);
3674 
3675 EXCEPTION
3676   WHEN no_data_found THEN
3677     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
3678        (AP_IMPORT_INVOICES_PKG.g_invoices_table,
3679          p_invoice_rec.invoice_id,
3680          'INVALID AWT GROUP',
3681          p_default_last_updated_by,
3682          p_default_last_update_login,
3683          current_calling_sequence) <> TRUE) THEN
3684       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3685         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
3686         'insert_rejections<-'||current_calling_sequence);
3687       END IF;
3688       RAISE awt_group_check_failure;
3689     END IF;
3690 
3691     l_current_invoice_status := 'N';
3692     p_current_invoice_status := l_current_invoice_status;
3693     RETURN (TRUE);
3694 
3695   WHEN OTHERS THEN
3696     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3697       AP_IMPORT_UTILITIES_PKG.Print(
3698       AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
3699     END IF;
3700 
3701     IF (SQLCODE < 0) then
3702       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3703     AP_IMPORT_UTILITIES_PKG.Print(
3704          AP_IMPORT_INVOICES_PKG.g_debug_switch,SQLERRM);
3705       END IF;
3706     END IF;
3707     RETURN(FALSE);
3708 
3709 END v_check_invalid_awt_group;
3710 
3711 --bug6639866
3712 ----------------------------------------------------------------------------
3713 -- This function is used to validate that the pay awt information
3714 -- is valid and consistent.
3715 --
3716 ----------------------------------------------------------------------------
3717 FUNCTION v_check_invalid_pay_awt_group (
3718     p_invoice_rec        IN AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
3719     p_pay_awt_group_id                  OUT NOCOPY NUMBER,
3720     p_default_last_updated_by    IN            NUMBER,
3721     p_default_last_update_login  IN            NUMBER,
3722     p_current_invoice_status     IN OUT NOCOPY VARCHAR2,
3723     p_calling_sequence           IN            VARCHAR2) RETURN BOOLEAN
3724 IS
3725 
3726 pay_awt_group_check_failure     EXCEPTION;
3727 l_current_invoice_status    VARCHAR2(1) := 'Y';
3728 l_pay_awt_group_id              AP_INVOICES.pay_AWT_GROUP_ID%TYPE;
3729 l_pay_awt_group_id_per_name     AP_INVOICES.pay_AWT_GROUP_ID%TYPE;
3730 l_inactive_date             DATE;
3731 l_inactive_date_per_name    DATE;
3732 current_calling_sequence    VARCHAR2(2000);
3733 debug_info                  VARCHAR2(500);
3734 
3735 BEGIN
3736   -- Update the calling sequence
3737   --
3738   current_calling_sequence :=
3739     'AP_IMPORT_VALIDATION_PKG.v_check_invalid_pay_awt_group<-'
3740     ||P_calling_sequence;
3741 
3742   IF p_invoice_rec.pay_awt_group_id is not null THEN
3743 
3744     --validate pay_awt_group_id
3745     SELECT group_id, inactive_date
3746     INTO l_pay_awt_group_id, l_inactive_date
3747       FROM ap_awt_groups
3748      WHERE group_id = p_invoice_rec.pay_awt_group_id;
3749 
3750   END IF;
3751 
3752   IF (p_invoice_rec.pay_awt_group_name is NOT NULL) THEN
3753     --validate pay awt group name and retrieve pay awt group id
3754     SELECT group_id, inactive_date
3755       INTO l_pay_awt_group_id_per_name, l_inactive_date_per_name
3756       FROM ap_awt_groups
3757      WHERE name = p_invoice_rec.pay_awt_group_name;
3758   END IF;
3759 
3760   IF (l_pay_awt_group_id is NOT NULL) AND
3761      (l_pay_awt_group_id_per_name is NOT NULL) AND
3762      (l_pay_awt_group_id <> l_pay_awt_group_id_per_name) THEN
3763 
3764     -------------------------------------------------------------------------
3765     -- Step 1
3766     -- Check for pay AWT Group Id and Group Name Inconsistency.
3767     -------------------------------------------------------------------------
3768     debug_info := '(Check AWT Group 1) Check for pay AWT Group Id and pay Group Name'
3769                   ||' Inconsistency.';
3770     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3771       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
3772                                     debug_info);
3773     END IF;
3774 
3775     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
3776           (AP_IMPORT_INVOICES_PKG.g_invoices_table,
3777             p_invoice_rec.invoice_id,
3778             'INCONSISTENT PAY AWT GROUP',
3779             p_default_last_updated_by,
3780             p_default_last_update_login,
3781 current_calling_sequence) <> TRUE) THEN
3782       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3783         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
3784         'insert_rejections<-'||current_calling_sequence);
3785       END IF;
3786       RAISE pay_awt_group_check_failure;
3787     END IF;
3788     l_current_invoice_status := 'N';
3789 
3790   ELSE
3791 
3792     ------------------------------------------------------------------------
3793     -- Step 2
3794     -- Check for Inactive pay AWT Group
3795     ------------------------------------------------------------------------
3796     debug_info := '(Check AWT Group 2) Check for Inactive pay AWT Group';
3797     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3798       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
3799                                     debug_info);
3800     END IF;
3801 
3802     IF ((l_pay_awt_group_id is NULL) and
3803         (l_pay_awt_group_id_per_name is NOT NULL)) THEN
3804 
3805       IF AP_IMPORT_INVOICES_PKG.g_inv_sysdate >=
3806          nvl(l_inactive_date_per_name,
3807              AP_IMPORT_INVOICES_PKG.g_inv_sysdate+1) THEN
3808         --------------------------------------------------------------
3809         -- inactive pay AWT group (per name)
3810         --
3811         ---------------------------------------------------------------
3812         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
3813            (AP_IMPORT_INVOICES_PKG.g_invoices_table,
3814             p_invoice_rec.invoice_id,
3815             'INACTIVE PAY AWT GROUP',
3816             p_default_last_updated_by,
3817             p_default_last_update_login,
3818             current_calling_sequence) <> TRUE) THEN
3819           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3820             AP_IMPORT_UTILITIES_PKG.Print(
3821             AP_IMPORT_INVOICES_PKG.g_debug_switch,
3822             'insert_rejections<-'||current_calling_sequence);
3823           END IF;
3824           RAISE pay_awt_group_check_failure;
3825         END IF;
3826 
3827         l_current_invoice_status := 'N';
3828 
3829       END IF; -- Inactive pay AWT Group per name
3830 
3831     ELSIF (((l_pay_awt_group_id is NOT NULL) and
3832             (l_pay_awt_group_id_per_name is NULL)) OR
3833            ((l_pay_awt_group_id is NOT NULL) and
3834             (l_pay_awt_group_id_per_name is NOT NULL) and
3835             (l_pay_awt_group_id = l_pay_awt_group_id_per_name))) THEN
3836 
3837       IF AP_IMPORT_INVOICES_PKG.g_inv_sysdate >=
3838          nvl(l_inactive_date, AP_IMPORT_INVOICES_PKG.g_inv_sysdate+1) THEN
3839 
3840         --------------------------------------------------------------
3841         -- inactive pay AWT group (as per id)
3842         --
3843         --------------------------------------------------------------
3844         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
3845           (AP_IMPORT_INVOICES_PKG.g_invoices_table,
3846             p_invoice_rec.invoice_id,
3847             'INACTIVE PAY AWT GROUP',
3848             p_default_last_updated_by,
3849             p_default_last_update_login,
3850             current_calling_sequence) <> TRUE) THEN
3851  IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3852             AP_IMPORT_UTILITIES_PKG.Print(
3853             AP_IMPORT_INVOICES_PKG.g_debug_switch,
3854             'insert_rejections<-'||current_calling_sequence);
3855           END IF;
3856           RAISE pay_awt_group_check_failure;
3857         END IF;
3858 
3859         l_current_invoice_status := 'N';
3860 
3861       END IF; -- Inactive pay AWT Group per id
3862 
3863     END IF; -- pay awt group id is null and pay awt group id per name is not null
3864 
3865   END IF; -- pay awt group id is not null, pay awt group id per name is not null
3866           -- but they differ
3867 
3868   IF (l_pay_awt_group_id is not null) then
3869     p_pay_awt_group_id := l_pay_awt_group_id;
3870   ELSIF (l_pay_awt_group_id_per_name IS NOT NULL) THEN
3871     p_pay_awt_group_id := l_pay_awt_group_id_per_name;
3872   ELSE
3873     IF ((l_current_invoice_status <> 'N') AND
3874            (p_invoice_rec.invoice_type_lookup_code <> 'PAYMENT REQUEST')) THEN
3875        -- Get pay awt group id from supplier site
3876       BEGIN
3877         SELECT pay_awt_group_id
3878           INTO p_pay_awt_group_id
3879       FROM po_vendor_sites
3880          WHERE vendor_id = p_invoice_rec.vendor_id
3881          AND vendor_site_id = p_invoice_rec.vendor_site_id;
3882       EXCEPTION
3883     WHEN no_data_found THEN
3884       RAISE pay_awt_group_check_failure;
3885     WHEN OTHERS THEN
3886       RAISE pay_awt_group_check_failure;
3887       END;
3888      END IF;
3889     END IF;
3890 
3891 
3892   p_current_invoice_status := l_current_invoice_status;
3893 
3894   RETURN (TRUE);
3895 
3896 EXCEPTION
3897   WHEN no_data_found THEN
3898     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
3899        (AP_IMPORT_INVOICES_PKG.g_invoices_table,
3900          p_invoice_rec.invoice_id,
3901          'INVALID PAY AWT GROUP',
3902          p_default_last_updated_by,
3903          p_default_last_update_login,
3904          current_calling_sequence) <> TRUE) THEN
3905       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3906         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
3907         'insert_rejections<-'||current_calling_sequence);
3908       END IF;
3909       RAISE pay_awt_group_check_failure;
3910     END IF;
3911 
3912     l_current_invoice_status := 'N';
3913     p_current_invoice_status := l_current_invoice_status;
3914     RETURN (TRUE);
3915 
3916   WHEN OTHERS THEN
3917     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3918       AP_IMPORT_UTILITIES_PKG.Print(
3919       AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
3920     END IF;
3921  IF (SQLCODE < 0) then
3922       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3923     AP_IMPORT_UTILITIES_PKG.Print(
3924          AP_IMPORT_INVOICES_PKG.g_debug_switch,SQLERRM);
3925       END IF;
3926     END IF;
3927     RETURN(FALSE);
3928 
3929 END v_check_invalid_pay_awt_group;
3930 
3931 ----------------------------------------------------------------------------
3932 -- This function is used to validate exchange rate information
3933 -- for the invoice.
3934 ----------------------------------------------------------------------------
3935 FUNCTION v_check_exchange_rate_type (
3936     p_invoice_rec     IN AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
3937     p_exchange_rate                 OUT NOCOPY  NUMBER,
3938     p_exchange_date                 OUT NOCOPY  DATE,
3939     p_base_currency_code         IN             VARCHAR2,
3940     p_multi_currency_flag        IN             VARCHAR2,
3941     p_set_of_books_id            IN             NUMBER,
3942     p_default_exchange_rate_type IN             VARCHAR2,
3943     p_make_rate_mandatory_flag   IN             VARCHAR2,
3944     p_default_last_updated_by    IN             NUMBER,
3945     p_default_last_update_login  IN             NUMBER,
3946     p_current_invoice_status     IN OUT NOCOPY  VARCHAR2,
3947     p_calling_sequence           IN             VARCHAR2) RETURN BOOLEAN
3948 IS
3949 
3950 exchange_rate_type_failure    EXCEPTION;
3951 l_conversion_type             VARCHAR2(30) := p_invoice_rec.exchange_rate_type;
3952 l_exchange_date               DATE := p_invoice_rec.exchange_date;
3953 l_exchange_rate               NUMBER := p_invoice_rec.exchange_rate;
3954 l_current_invoice_status      VARCHAR2(1) := 'Y';
3955 l_valid_conversion_type       VARCHAR2(30);
3956 current_calling_sequence      VARCHAR2(2000);
3957 debug_info                    VARCHAR2(500);
3958 
3959 BEGIN
3960   -- Update the calling sequence
3961   --
3962   current_calling_sequence :=
3963     'AP_IMPORT_VALIDATION_PKG.v_check_invalid_inv_curr_code<-'
3964     ||P_calling_sequence;
3965 
3966   IF (NVL(p_multi_currency_flag,'N') = 'Y') AND
3967      (p_base_currency_code <> p_invoice_rec.invoice_currency_code) Then
3968 
3969     -------------------------------------------------------------------------
3970     -- Step 1
3971     -- Check for invalid exchange rate type
3972     -------------------------------------------------------------------------
3973     debug_info := '(Check Exchange Rate Type 1) Check for invalid Exchange '
3974                   ||'Rate Type';
3975     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3976       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
3977                                     debug_info);
3978     END IF;
3979 
3980     IF (l_conversion_type is NULL) Then
3981       debug_info := '(Check Exchange Rate Type 1a) Get Default Exchange '
3982                     ||'Rate Type';
3983       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3984         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
3985                                       debug_info);
3986       END IF;
3987       l_conversion_type := p_default_exchange_rate_type;
3988     END IF;
3989 
3990     IF (l_conversion_type is NOT NULL) Then
3991       debug_info :=
3992            '(Check Exchange Rate Type 1b) Check if Rate Type is valid';
3993       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3994         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
3995                                       debug_info);
3996       END IF;
3997 
3998       BEGIN
3999         SELECT 'X'
4000           INTO l_valid_conversion_type
4001           FROM gl_daily_conversion_types
4002           WHERE conversion_type = l_conversion_type;
4003 
4004       EXCEPTION
4005         WHEN no_data_found THEN
4006           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
4007                    (AP_IMPORT_INVOICES_PKG.g_invoices_table,
4008                     p_invoice_rec.invoice_id,
4009                     'INVALID EXCH RATE TYPE',
4010                     p_default_last_updated_by,
4011                     p_default_last_update_login,
4012                     current_calling_sequence) <> TRUE) THEN
4013             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4014               AP_IMPORT_UTILITIES_PKG.Print(
4015               AP_IMPORT_INVOICES_PKG.g_debug_switch,
4016               'insert_rejections<-'||current_calling_sequence);
4017             END IF;
4018             RAISE exchange_rate_type_failure;
4019           END IF;
4020           l_current_invoice_status := 'N';
4021 
4022       END;
4023 
4024     END IF; -- conversion type not null
4025 
4026     -------------------------------------------------------------------------
4027     -- Step 2
4028     -- Get exchange date
4029     -------------------------------------------------------------------------
4030     IF (p_invoice_rec.exchange_date IS NULL) THEN
4031       debug_info :=
4032           '(Check Exchange Rate Type 2) Get Sysdate as Exchange Date';
4033       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4034         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
4035                                       debug_info);
4036       END IF;
4037 
4038       -- Invoice date was initialized to sysdate if null at the beginning
4039       -- of the invoice validation process.
4040       l_exchange_date := nvl(p_invoice_rec.gl_date,
4041                  p_invoice_rec.invoice_date);
4042     END IF;
4043 
4044 
4045     IF (l_valid_conversion_type ='X') Then
4046       ----------------------------------------------------------------------
4047       -- Step 3
4048       -- Check for Inconsistent exchange rate
4049       ----------------------------------------------------------------------
4050       debug_info := '(Check Exchange Rate Type 3a) Check for inconsistent '
4051                     ||'Exchange Rate, if type valid';
4052       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4053         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
4054                                       debug_info);
4055       END IF;
4056       debug_info := 'l_coversion_type: '||l_conversion_type ||'  '||
4057                      'p_invoice_rec.exchange_rate: '||p_invoice_rec.exchange_rate;
4058 
4059       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4060         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
4061                                       debug_info);
4062       END IF;
4063 
4064 --Start of bug8766019
4065       IF (p_invoice_rec.exchange_rate <= 0) THEN
4066          IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
4067                     (AP_IMPORT_INVOICES_PKG.g_invoices_table,
4068                      p_invoice_rec.invoice_id,
4069                      'INVALID EXCH RATE',
4070                      p_default_last_updated_by,
4071                      p_default_last_update_login,
4072                      current_calling_sequence) <> TRUE) THEN
4073                IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4074                  AP_IMPORT_UTILITIES_PKG.Print(
4075                    AP_IMPORT_INVOICES_PKG.g_debug_switch,
4076                    'insert_rejections<-'||current_calling_sequence);
4077                END IF;
4078                RAISE exchange_rate_type_failure;
4079          END IF;
4080          l_current_invoice_status := 'N';
4081 --End of bug8766019
4082       ELSIF ((l_conversion_type <> 'User') AND
4083           (p_invoice_rec.exchange_rate is NOT NULL)) AND   -- Bug 5003374
4084            nvl(ap_utilities_pkg.get_exchange_rate(       -- Added this Condition.
4085                                 p_invoice_rec.invoice_currency_code,
4086                                 p_base_currency_code,
4087                                 l_conversion_type,
4088                                 l_exchange_date,
4089                                 current_calling_sequence),-999) <> p_exchange_rate THEN
4090         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
4091             (AP_IMPORT_INVOICES_PKG.g_invoices_table,
4092               p_invoice_rec.invoice_id,
4093              'INCONSISTENT RATE',
4094               p_default_last_updated_by,
4095               p_default_last_update_login,
4096               current_calling_sequence) <> TRUE) THEN
4097           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
4098             AP_IMPORT_UTILITIES_PKG.Print(
4099             AP_IMPORT_INVOICES_PKG.g_debug_switch,
4100             'insert_rejections<-'||current_calling_sequence);
4101           END IF;
4102           RAISE exchange_rate_type_failure;
4103         END IF;
4104 
4105         l_current_invoice_status := 'N';
4106 
4107       ELSIF ((l_conversion_type = 'User') AND
4108               (p_invoice_rec.exchange_rate is NULL))  AND
4109              (AP_UTILITIES_PKG.calculate_user_xrate (
4110                   p_invoice_rec.invoice_currency_code,
4111                   p_base_currency_code,
4112                   l_exchange_date,
4113                   l_conversion_type) <> 'Y') THEN
4114         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
4115                                      (AP_IMPORT_INVOICES_PKG.g_invoices_table,
4116                                       p_invoice_rec.invoice_id,
4117                                      'NO EXCHANGE RATE',
4118                                       p_default_last_updated_by,
4119                                       p_default_last_update_login,
4120                                       current_calling_sequence) <> TRUE) THEN
4121           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
4122             AP_IMPORT_UTILITIES_PKG.Print(
4123               AP_IMPORT_INVOICES_PKG.g_debug_switch,
4124               'insert_rejections<-'||current_calling_sequence);
4125           END IF;
4126           RAISE exchange_rate_type_failure;
4127         END IF;
4128 
4129         l_current_invoice_status := 'N';
4130 
4131       ELSIF ((l_conversion_type <> 'User') AND
4132        (p_invoice_rec.exchange_rate is NULL))   Then
4133         null;
4134 
4135         debug_info := '(Check Exchange Rate Type 3b) Get Exchange Rate for'
4136                       ||' type other than User';
4137         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4138           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
4139                                         debug_info);
4140         END IF;
4141 
4142         l_exchange_rate := ap_utilities_pkg.get_exchange_rate(
4143                 p_invoice_rec.invoice_currency_code,
4144                 p_base_currency_code,
4145                 l_conversion_type,
4146                 l_exchange_date,
4147                 current_calling_sequence);
4148         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4149           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
4150           '----------------> exchange_rate = '|| to_char(l_exchange_rate)
4151           ||'set_of_books_id = '||to_char(p_set_of_books_id)
4152           ||'invoice_currency_code = '||p_invoice_rec.invoice_currency_code
4153           ||'exchange_date= '||to_char(l_exchange_date)
4154           ||'conversion_type = '||l_conversion_type);
4155         END IF;
4156 
4157         IF (l_exchange_rate IS NULL) THEN
4158 
4159           IF (NVL(p_make_rate_mandatory_flag,'N') = 'Y') then
4160             debug_info :=
4161               '(Check Exchange Rate Type 3c) Reject:No Exchange Rate ';
4162             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4163               AP_IMPORT_UTILITIES_PKG.Print(
4164                 AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
4165             END IF;
4166 
4167             IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
4168                     (AP_IMPORT_INVOICES_PKG.g_invoices_table,
4169                      p_invoice_rec.invoice_id,
4170                      'NO EXCHANGE RATE',
4171                      p_default_last_updated_by,
4172                      p_default_last_update_login,
4173                      current_calling_sequence) <> TRUE) THEN
4174               IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4175                 AP_IMPORT_UTILITIES_PKG.Print(
4176                   AP_IMPORT_INVOICES_PKG.g_debug_switch,
4177                   'insert_rejections<-'||current_calling_sequence);
4178               END IF;
4179               RAISE exchange_rate_type_failure;
4180             END IF;
4181 
4182             l_current_invoice_status := 'N';
4183 
4184           ELSE
4185             debug_info := '(Check Exchange Rate Type 3d) No Exchange'
4186                           ||' Rate:Rate Not Reqd ';
4187             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4188               AP_IMPORT_UTILITIES_PKG.Print(
4189                      AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
4190             END IF;
4191 
4192           END IF; -- make_rate_mandatory
4193 
4194         END IF;  -- exchange_rate is null
4195             --4091870
4196        ELSIF ((l_conversion_type = 'User') AND
4197                     (p_exchange_rate <= 0))  then
4198 
4199                 IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
4200                     (AP_IMPORT_INVOICES_PKG.g_invoices_table,
4201                      p_invoice_rec.invoice_id,
4202                      'INVALID EXCH RATE',
4203                      p_default_last_updated_by,
4204                      p_default_last_update_login,
4205                      current_calling_sequence) <> TRUE) THEN
4206               IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4207                 AP_IMPORT_UTILITIES_PKG.Print(
4208                   AP_IMPORT_INVOICES_PKG.g_debug_switch,
4209                   'insert_rejections<-'||current_calling_sequence);
4210               END IF;
4211               RAISE exchange_rate_type_failure;
4212             END IF;
4213 
4214                 l_current_invoice_status := 'N';
4215               --4091870 end
4216       END IF; -- l_conversion_type <>User
4217 
4218 
4219       IF ((l_conversion_type <> 'User') AND
4220           (p_invoice_rec.exchange_rate is NOT NULL) AND
4221           (p_invoice_rec.exchange_rate <> l_exchange_rate)) Then
4222 
4223         debug_info := '(Check Exchange Rate Type 3e) Exchange rate in '
4224                       ||'interface differs rate defined';
4225         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4226           AP_IMPORT_UTILITIES_PKG.Print(
4227                AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
4228         END IF;
4229 
4230         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
4231              (AP_IMPORT_INVOICES_PKG.g_invoices_table,
4232               p_invoice_rec.invoice_id,
4233               'INCONSISTENT RATE',
4234               p_default_last_updated_by,
4235                p_default_last_update_login,
4236                current_calling_sequence) <> TRUE) THEN
4237           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4238             AP_IMPORT_UTILITIES_PKG.Print(
4239               AP_IMPORT_INVOICES_PKG.g_debug_switch,
4240               'insert_rejections<-'||current_calling_sequence);
4241           END IF;
4242           RAISE exchange_rate_type_failure;
4243         END IF;
4244         l_current_invoice_status := 'N';
4245 
4246       END IF; -- exchange rate in interface other than defined in system
4247 
4248     END IF; -- l_valid_conversion_type = 'X'
4249 
4250   ELSIF ((nvl(p_multi_currency_flag,'N') = 'N') AND
4251          (p_base_currency_code <> p_invoice_rec.invoice_currency_code)) THEN
4252 
4253     -------------------------------------------------------------------------
4254     -- Step 4
4255     -- Check for Inconsistent Information Entered
4256     -------------------------------------------------------------------------
4257     debug_info := '(Check Exchange Rate Type 9) Check for inconsistent '
4258                   ||'Information Entered';
4259     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4260       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
4261                                     debug_info);
4262     END IF;
4263 
4264     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
4265         (AP_IMPORT_INVOICES_PKG.g_invoices_table,
4266           p_invoice_rec.invoice_id,
4267          'INCONSISTENT INFO ENTERED',
4268           p_default_last_updated_by,
4269           p_default_last_update_login,
4270           current_calling_sequence) <> TRUE) THEN
4271       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4272         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
4273            'insert_rejections<-'||current_calling_sequence);
4274       END IF;
4275       RAISE exchange_rate_type_failure;
4276     END IF;
4277 
4278     l_current_invoice_status := 'N';
4279     /*bug 8887650 begin*/
4280   ELSIF (p_base_currency_code = p_invoice_rec.invoice_currency_code)
4281        AND NOT(p_invoice_rec.exchange_rate_type IS NULL AND
4282                p_invoice_rec.exchange_date IS NULL AND
4283 	       p_invoice_rec.exchange_rate IS NULL) THEN
4284 
4285     ------------------------------------------------------------------------------
4286     -- Step 4.a
4287     -- Check for Inconsistent Information Entered when base and funct curr is same
4288     ------------------------------------------------------------------------------
4289     debug_info := '(Check Exchange Rate Type 9.a) Check for inconsistent exchange '
4290                   ||'Information Entered';
4291     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4292       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
4293                                     debug_info);
4294     END IF;
4295 
4296        IF nvl(p_invoice_rec.exchange_rate,1) <> 1 THEN
4297 
4298          IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
4299                     (AP_IMPORT_INVOICES_PKG.g_invoices_table,
4300                      p_invoice_rec.invoice_id,
4301 		     'INCONSISTENT RATE',
4302 		     p_default_last_updated_by,
4303 		     p_default_last_update_login,
4304 		     current_calling_sequence) <> TRUE) THEN
4305 
4306             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4307               AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
4308                'insert_rejections<-'||current_calling_sequence);
4309             END IF;
4310            RAISE exchange_rate_type_failure;
4311 
4312          END IF;
4313 
4314          l_current_invoice_status := 'N';
4315       ELSE
4316        --Need not populate exchange rate infos when base and func currency
4317        --are same. This will forbade accounting issues out of base amount calculation.
4318 
4319          l_exchange_rate := NULL;
4320          l_exchange_date := NULL;
4321 
4322 	debug_info := '(Check Exchange Rate Type 9.b) Exchange'
4323                           ||' Rate info :Nullified ';
4324         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4325              AP_IMPORT_UTILITIES_PKG.Print(
4326               AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
4327         END IF;
4328 
4329       END IF;
4330      /*bug 8887650 end*/
4331 
4332   END IF; -- multi currency flag and foreign currency invoice
4333 
4334   p_exchange_rate := l_exchange_rate;
4335   p_exchange_date := l_exchange_date;
4336   p_current_invoice_status := l_current_invoice_status;
4337   RETURN (TRUE);
4338 
4339 EXCEPTION
4340   WHEN OTHERS THEN
4341     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4342       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
4343     END IF;
4344 
4345   IF (SQLCODE < 0) then
4346     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4347       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,SQLERRM);
4348     END IF;
4349   END IF;
4350 
4351   RETURN(FALSE);
4352 
4353 END v_check_exchange_rate_type;
4354 
4355 ------------------------------------------------------------------
4356 -- This function is used to validate payment terms information.
4357 --
4358 ------------------------------------------------------------------
4359 FUNCTION v_check_invalid_terms (
4360     p_invoice_rec  IN      AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
4361     p_terms_id                      OUT NOCOPY NUMBER,
4362     p_terms_date                    OUT NOCOPY DATE,
4363     p_terms_date_basis           IN            VARCHAR2,
4364     p_default_last_updated_by    IN            NUMBER,
4365     p_default_last_update_login  IN            NUMBER,
4366     p_current_invoice_status     IN OUT NOCOPY VARCHAR2,
4367     p_calling_sequence           IN            VARCHAR2) RETURN BOOLEAN
4368 IS
4369 
4370 terms_check_failure           EXCEPTION;
4371 l_current_invoice_status      VARCHAR2(1) := 'Y';
4372 l_term_id                     NUMBER := Null;
4373 l_term_id_per_name            NUMBER := Null;
4374 l_start_date_active           DATE;
4375 l_end_date_active             DATE;
4376 l_start_date_active_per_name  DATE;
4377 l_end_date_active_per_name    DATE;
4378 current_calling_sequence      VARCHAR2(2000);
4379 debug_info                    VARCHAR2(500);
4380 
4381 l_term_name                     VARCHAR2(50);--Bug 4115712
4382 l_no_calendar_exists            VARCHAR2(1); --Bug 4115712
4383 
4384 BEGIN
4385   -- Update the calling sequence
4386   --
4387   current_calling_sequence :=
4388      'AP_IMPORT_VALIDATION_PKG.v_check_invalid_terms<-'
4389      ||P_calling_sequence;
4390   --------------------------------------------------------------------------
4391   -- Fidelity needs to ignore terms info if you have PO as well.
4392   -- In this case we should not check/reject for inconsistency
4393   -- instead take the terms from PO / Supplier.
4394   -- terms defaulting: If terms provided in the interface (default
4395   -- from supplier using IG) use them unconditionally. If terms not provided
4396   -- and PO exists, use PO terms else default terms from Supplier Site.
4397   --------------------------------------------------------------------------
4398   BEGIN
4399 
4400     IF (p_invoice_rec.terms_id is not null) THEN
4401      --validate term_id
4402      SELECT term_id, start_date_active, end_date_active
4403        INTO l_term_id, l_start_date_active, l_end_date_active
4404        FROM ap_terms
4405       WHERE term_id = p_invoice_rec.terms_id;
4406     END IF;
4407 
4408     IF (p_invoice_rec.terms_name is not null) THEN
4409      --validate terms name and retrieve term id
4410      SELECT term_id, start_date_active, end_date_active
4411        INTO l_term_id_per_name, l_start_date_active_per_name,
4412             l_end_date_active_per_name
4413        FROM ap_terms
4414       WHERE name = p_invoice_rec.terms_name;
4415     END IF;
4416 
4417   EXCEPTION
4418 
4419     WHEN no_data_found THEN
4420       ----------------------------------------------------------------------
4421       -- Step 1
4422       -- Check invalid terms.
4423       ----------------------------------------------------------------------
4424      debug_info := '(Check Invalid Terms 1) Check for invalid Terms.';
4425      IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4426        AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
4427                                      debug_info);
4428      END IF;
4429 
4430      IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
4431           (AP_IMPORT_INVOICES_PKG.g_invoices_table,
4432             p_invoice_rec.invoice_id,
4433             'INVALID TERMS',
4434             p_default_last_updated_by,
4435             p_default_last_update_login,
4436             current_calling_sequence) <> TRUE) THEN
4437        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4438          AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
4439          'insert_rejections<- '||current_calling_sequence);
4440        END IF;
4441        RAISE terms_check_failure;
4442     END IF;
4443 
4444     l_current_invoice_status := 'N';
4445     p_current_invoice_status := l_current_invoice_status;
4446 
4447   END;
4448 
4449   --------------------------------------------------------------
4450   -- Step 2
4451   -- If no payment term, get from PO or Supplier Site.
4452   -- Retropricing: For PPA's p_invoice_rec.terms_id is NOT NULL
4453   --------------------------------------------------------------
4454   IF ((p_invoice_rec.terms_id is NULL) AND
4455       (p_invoice_rec.terms_name is NULL)) THEN
4456 
4457     IF (p_invoice_rec.po_number is NOT NULL) Then
4458       debug_info :=
4459           '(Check Invalid Terms 2.1) Get term_id from header po_number';
4460       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4461         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
4462                                       debug_info);
4463       END IF;
4464 
4465       SELECT terms_id
4466         INTO l_term_id
4467         FROM po_headers
4468        WHERE segment1 = p_invoice_rec.po_number
4469          AND type_lookup_code in ('BLANKET', 'PLANNED', 'STANDARD');
4470     END IF;
4471 
4472     -- no term from header level po_number, try lines level po_number
4473     IF (l_term_id is null ) THEN
4474       debug_info :=
4475          '(Check Invalid Terms 2.2) Get term_id from lines po_numbers';
4476       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4477         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
4478                                       debug_info);
4479       END IF;
4480       BEGIN
4481         SELECT p.terms_id
4482           INTO l_term_id
4483           FROM po_headers p, ap_invoice_lines_interface l
4484          WHERE p.type_lookup_code in ('BLANKET', 'PLANNED', 'STANDARD')
4485            AND ((l.po_header_id = p.po_header_id) OR
4486                 (l.po_number    = p.segment1))
4487            AND l.invoice_id = p_invoice_rec.invoice_id
4488            AND p.terms_id IS NOT NULL
4489          GROUP BY p.terms_id;
4490       EXCEPTION
4491         WHEN NO_DATA_FOUND THEN
4492           NULL;
4493         WHEN TOO_MANY_ROWS THEN
4494           l_term_id        := null;
4495           l_current_invoice_status := 'N';
4496           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
4497                                (AP_IMPORT_INVOICES_PKG.g_invoices_table,
4498                                  p_invoice_rec.invoice_id,
4499                                  'INCONSISTENT TERMS INFO',
4500                                  p_default_last_updated_by,
4501                                  p_default_last_update_login,
4502                                  current_calling_sequence) <> TRUE) THEN
4503             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4504               AP_IMPORT_UTILITIES_PKG.Print(
4505               AP_IMPORT_INVOICES_PKG.g_debug_switch,
4506               'insert_rejections<- '||current_calling_sequence);
4507             END IF;
4508             RAISE terms_check_failure;
4509           END IF;
4510       END;
4511 
4512       -- no term from line level PO, try line level receipt
4513       IF (l_term_id is null) THEN
4514         debug_info := '(Check Invalid Terms 2.3) Get term_id from lines'
4515                       ||' receipt';
4516         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4517           AP_IMPORT_UTILITIES_PKG.Print(
4518              AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
4519         END IF;
4520         BEGIN
4521           SELECT p.terms_id
4522             INTO l_term_id
4523             FROM rcv_transactions r,
4524                  po_headers p,
4525                  ap_invoice_lines_interface l
4526            WHERE p.po_header_id = r.po_header_id
4527              AND r.transaction_id = l.rcv_transaction_id
4528              AND l.invoice_id = p_invoice_rec.invoice_id
4529              AND p.terms_id IS NOT NULL
4530            GROUP BY p.terms_id;
4531         EXCEPTION
4532           WHEN NO_DATA_FOUND THEN
4533             NULL;
4534           WHEN TOO_MANY_ROWS THEN
4535             debug_info := 'too many rows';
4536             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4537               AP_IMPORT_UTILITIES_PKG.Print(
4538                 AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
4539             END IF;
4540             l_term_id        := null;
4541             l_current_invoice_status := 'N';
4542             IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
4543                                   (AP_IMPORT_INVOICES_PKG.g_invoices_table,
4544                                    p_invoice_rec.invoice_id,
4545                                    'INCONSISTENT TERMS INFO',
4546                                    p_default_last_updated_by,
4547                                    p_default_last_update_login,
4548                                    current_calling_sequence) <> TRUE) THEN
4549               IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4550                 AP_IMPORT_UTILITIES_PKG.Print(
4551                 AP_IMPORT_INVOICES_PKG.g_debug_switch,
4552                 'insert_rejections<- '||current_calling_sequence);
4553               END IF;
4554               RAISE terms_check_failure;
4555             END IF;
4556         END;
4557 
4558       END IF; -- end get term from line level receipt
4559 
4560     END IF; -- end get term from line level
4561 
4562     -- no term from header or line level
4563     IF ( (nvl(l_current_invoice_status,'Y') = 'Y') AND -- not rejected already
4564          (l_term_id is null) AND
4565          (p_invoice_rec.invoice_type_lookup_code <> 'PAYMENT REQUEST') ) Then
4566 
4567       debug_info := '(Check Invalid Terms 2.4) Get term_id from supplier site';
4568       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4569         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
4570                                       debug_info);
4571       END IF;
4572 
4573       SELECT terms_id
4574       INTO   l_term_id
4575       FROM   po_vendor_sites
4576       WHERE  vendor_id      = p_invoice_rec.vendor_id
4577       AND    vendor_site_id = p_invoice_rec.vendor_site_id;
4578 
4579     ELSIF ( (nvl(l_current_invoice_status,'Y') = 'Y') AND -- not rejected already
4580          (l_term_id is null) AND
4581          (p_invoice_rec.invoice_type_lookup_code = 'PAYMENT REQUEST') ) Then
4582 
4583       debug_info := '(Check Invalid Terms 2.4) Get term_id from financials options';
4584       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4585         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
4586                                       debug_info);
4587       END IF;
4588 
4589       SELECT terms_id
4590       INTO   l_term_id
4591       FROM   ap_product_setup;
4592       -- Bug 5519299. Terms_Id for Payment request based on ap_product_setup
4593       -- FROM   financials_system_parameters
4594       -- WHERE  org_id = p_invoice_rec.org_id;
4595 
4596     END IF;
4597 
4598     IF ( nvl(l_current_invoice_status,'Y') = 'Y' ) THEN
4599       IF ( l_term_id is null ) THEN
4600         debug_info := '(Check Invalid Terms 2.5) no term_id found, '
4601                       ||'invoice rejected';
4602         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4603           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
4604                                         debug_info);
4605         END IF;
4606 
4607         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
4608                              (AP_IMPORT_INVOICES_PKG.g_invoices_table,
4609                               p_invoice_rec.invoice_id,
4610                               'NO TERMS INFO',
4611                               p_default_last_updated_by,
4612                               p_default_last_update_login,
4613                               current_calling_sequence) <> TRUE) THEN
4614           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4615             AP_IMPORT_UTILITIES_PKG.Print(
4616             AP_IMPORT_INVOICES_PKG.g_debug_switch,
4617             'insert_rejections<- '||current_calling_sequence);
4618           END IF;
4619           RAISE terms_check_failure;
4620         END IF;
4621 
4622         l_current_invoice_status := 'N';
4623 
4624       ELSE
4625         debug_info := '(Check Invalid Terms 2.6) getting term active date';
4626         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4627           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
4628                                         debug_info);
4629         END IF;
4630 
4631         SELECT start_date_active, end_date_active
4632           INTO l_start_date_active, l_end_date_active
4633           FROM ap_terms
4634          WHERE term_id = l_term_id;
4635 
4636       END IF; -- l_terms_id is null
4637     END IF; -- nvl(l_current_invoice_status,'Y') = 'Y'
4638 
4639   END IF; -- interface invoice terms_id and terms_name are null
4640 
4641   --------------------------------------------------------------------------
4642   -- Step 3
4643   -- Check Inconsistent and Inactive terms info.
4644   ---------------------------------------------------------------------------
4645   IF ((l_term_id is not null) AND
4646       (l_term_id_per_name is not null) AND
4647       (l_term_id <> l_term_id_per_name)) THEN
4648 
4649     debug_info := '(Check Invalid Terms 3) Check for inconsistent Terms id '
4650                    ||'and Name.';
4651     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4652       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
4653                                     debug_info);
4654     END IF;
4655 
4656     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
4657           (AP_IMPORT_INVOICES_PKG.g_invoices_table,
4658             p_invoice_rec.invoice_id,
4659             'INCONSISTENT TERMS INFO',
4660             p_default_last_updated_by,
4661             p_default_last_update_login,
4662             current_calling_sequence) <> TRUE) THEN
4663       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4664         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
4665         'insert_rejections<- '||current_calling_sequence);
4666       END IF;
4667       RAISE terms_check_failure;
4668     END IF;
4669 
4670     l_current_invoice_status := 'N';
4671 
4672   ELSIF ((l_term_id is null) and
4673          (l_term_id_per_name is NOT NULL)) THEN
4674 
4675     IF (not((AP_IMPORT_INVOICES_PKG.g_inv_sysdate >
4676              nvl(l_start_date_active_per_name,
4677                  AP_IMPORT_INVOICES_PKG.g_inv_sysdate - 1))
4678         AND (AP_IMPORT_INVOICES_PKG.g_inv_sysdate <
4679              nvl(l_end_date_active_per_name,
4680                  AP_IMPORT_INVOICES_PKG.g_inv_sysdate + 1)))) THEN
4681 
4682       -----------------------------------------------------------------------
4683       -- Step 4
4684       -- Check inactive terms per name
4685       -----------------------------------------------------------------------
4686       debug_info :=
4687         '(Check Invalid Terms 4) Check for inactive Terms as per Terms Name.';
4688       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4689         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
4690                                       debug_info);
4691       END IF;
4692 
4693       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
4694           (AP_IMPORT_INVOICES_PKG.g_invoices_table,
4695             p_invoice_rec.invoice_id,
4696             'INACTIVE TERMS',
4697             p_default_last_updated_by,
4698             p_default_last_update_login,
4699             current_calling_sequence) <> TRUE) THEN
4700         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4701           AP_IMPORT_UTILITIES_PKG.Print(
4702           AP_IMPORT_INVOICES_PKG.g_debug_switch,
4703           'insert_rejections<- '||current_calling_sequence);
4704         END IF;
4705         RAISE terms_check_failure;
4706       END IF;
4707 
4708       l_current_invoice_status := 'N';
4709     ELSE
4710        p_terms_id := l_term_id_per_name;
4711 
4712     END IF;
4713 
4714   ELSIF ((l_term_id is NOT NULL) AND
4715          ((l_term_id_per_name is NULL) OR
4716           (l_term_id_per_name is NOT NULL AND
4717            l_term_id = l_term_id_per_name))) THEN
4718 
4719     IF (not((AP_IMPORT_INVOICES_PKG.g_inv_sysdate >
4720              nvl(l_start_date_active,
4721                  AP_IMPORT_INVOICES_PKG.g_inv_sysdate - 1))
4722         AND (AP_IMPORT_INVOICES_PKG.g_inv_sysdate <
4723              nvl(l_end_date_active,
4724                  AP_IMPORT_INVOICES_PKG.g_inv_sysdate + 1)))) THEN
4725 
4726       ----------------------------------------------------------------------
4727       -- Step 5
4728       -- Check inactive terms as per id
4729       ----------------------------------------------------------------------
4730       debug_info :=
4731         '(Check Invalid Terms 5) Check for inactive Terms as per Terms Id.';
4732       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4733         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
4734                                       debug_info);
4735       END IF;
4736 
4737       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
4738           (AP_IMPORT_INVOICES_PKG.g_invoices_table,
4739             p_invoice_rec.invoice_id,
4740             'INACTIVE TERMS',
4741             p_default_last_updated_by,
4742             p_default_last_update_login,
4743             current_calling_sequence) <> TRUE) THEN
4744         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4745           AP_IMPORT_UTILITIES_PKG.Print(
4746           AP_IMPORT_INVOICES_PKG.g_debug_switch,
4747           'insert_rejections<- '||current_calling_sequence);
4748         END IF;
4749         RAISE terms_check_failure;
4750       END IF;
4751 
4752       l_current_invoice_status := 'N';
4753 
4754     ELSE
4755 
4756       p_terms_id := l_term_id;
4757 
4758     END IF;
4759 
4760   END IF; -- Check Inconsistent and Inactive Terms
4761 
4762   --------------------------------------------------------------------------
4763   -- Step 6
4764   -- Check for Invoice and Goods Received Date.
4765   -- Reject the invoice if the Invoice and Goods Received Date is null
4766   -- but the terms date basis is set to Invoice Received or Goods Received.
4767   --
4768   --------------------------------------------------------------------------
4769   debug_info := '(Check Invalid Terms 6a) Check for Terms Date provided as input :'
4770                 ||p_invoice_rec.terms_date;
4771   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4772     AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
4773                                   debug_info);
4774   END IF;
4775 
4776   /* Added following validation for bug 9918860
4777   As per PM input, if p_invoice_rec.terms_date is populated then we do not
4778   need to verify whether p_invoice_rec.invoice_received_date and
4779   p_invoice_rec.goods_received_date are populated. */
4780 
4781   IF p_invoice_rec.terms_date IS NULL THEN
4782 	debug_info := '(Check Invalid Terms 6b) Check for Invoice and Goods '
4783 					||'Received Date';
4784 	IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4785 		AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
4786 									debug_info);
4787 	END IF;
4788 
4789 	IF (p_terms_date_basis = 'Invoice Received' AND
4790 		p_invoice_rec.invoice_received_date is null) THEN
4791 
4792 		IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
4793 						(AP_IMPORT_INVOICES_PKG.g_invoices_table,
4794 						p_invoice_rec.invoice_id,
4795 						'DATE INVOICE RECEIVED REQ',
4796 						p_default_last_updated_by,
4797 						p_default_last_update_login,
4798 						current_calling_sequence) <> TRUE) THEN
4799 			IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4800 				AP_IMPORT_UTILITIES_PKG.Print(
4801 				AP_IMPORT_INVOICES_PKG.g_debug_switch,
4802 				'insert_rejections<-'||current_calling_sequence);
4803 			END IF;
4804 			RAISE terms_check_failure;
4805 		END IF;
4806 
4807 		l_current_invoice_status := 'N';
4808 
4809 	ELSIF (p_terms_date_basis = 'Goods Received' AND
4810 			p_invoice_rec.goods_received_date is null) THEN
4811 		IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
4812                      (AP_IMPORT_INVOICES_PKG.g_invoices_table,
4813                       p_invoice_rec.invoice_id,
4814                       'DATE GOODS RECEIVED REQ',
4815                       p_default_last_updated_by,
4816                       p_default_last_update_login,
4817                       current_calling_sequence) <> TRUE) THEN
4818 			IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4819 				AP_IMPORT_UTILITIES_PKG.Print(
4820 				AP_IMPORT_INVOICES_PKG.g_debug_switch,
4821 				'insert_rejections<-'||current_calling_sequence);
4822 			END IF;
4823 			RAISE terms_check_failure;
4824 		END IF;
4825 
4826 		l_current_invoice_status := 'N';
4827 	END IF;
4828 
4829   	--------------------------------------------------------------------------
4830    	-- Step 7
4831   	-- Derive terms date if possible
4832 	--
4833   	--------------------------------------------------------------------------
4834 	IF (l_current_invoice_status <> 'N') THEN
4835 
4836 		/* Commented for bug 9918860 since this validation has been placed
4837 		at the top before checking for other dates related to terms */
4838 		-- IF (p_invoice_rec.terms_date IS NULL) THEN
4839 		IF (p_terms_date_basis = 'Invoice Received') THEN
4840 			p_terms_date := p_invoice_rec.invoice_received_date;
4841 		ELSIF (p_terms_date_basis = 'Goods Received') THEN
4842 			p_terms_date := p_invoice_rec.goods_received_date;
4843 		ELSIF (p_terms_date_basis = 'Invoice') THEN
4844 			p_terms_date := p_invoice_rec.invoice_date;
4845 		ELSIF (p_terms_date_basis = 'Current') THEN
4846 			p_terms_date := AP_IMPORT_INVOICES_PKG.g_inv_sysdate;
4847 		ELSE
4848 			p_terms_date := AP_IMPORT_INVOICES_PKG.g_inv_sysdate;
4849 		END IF;
4850 	END IF;
4851 
4852   ELSE /*Bug 7635794*/
4853       p_terms_date := p_invoice_rec.terms_date; --bug 7635794
4854   END IF; -- p_invoice_rec.terms_date is null
4855 
4856   p_terms_date := nvl(p_terms_date, AP_IMPORT_INVOICES_PKG.g_inv_sysdate);
4857   --END IF; -- Commented for bug 9918860
4858 
4859  -- Bug 4115712
4860  ------------------------------------------------------------------------------
4861   -- Step 8
4862   -- For calendar based payment terms :
4863   -- Check if special calendar exists for the period
4864   -- in which the terms date falls, else fail insert.
4865   -----------------------------------------------------------------------------
4866    debug_info := '(Check Invalid Terms 8) Check calendar based payment terms';
4867 
4868    IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4869       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
4870                                   debug_info);
4871    END IF;
4872 
4873    --Bug:4115712
4874    IF (l_term_id IS NOT NULL)  THEN
4875     -- Bug 5448579. Calendar will be verified based on term_id
4876 
4877     --  select name
4878     --  into l_term_name
4879     --  from ap_terms
4880     --  where term_id = l_term_id;
4881 
4882     -- END IF;
4883 
4884      AP_IMPORT_UTILITIES_PKG.Check_For_Calendar_Term(
4885        P_Terms_Id         =>  l_term_id,
4886        P_Terms_Date       =>  p_terms_date,
4887        P_No_Cal           =>  l_no_calendar_exists,
4888        P_Calling_Sequence =>  'v_check_invalidate_terms');
4889 
4890      IF (l_no_calendar_exists = 'Y') THEN
4891        IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
4892                      (AP_IMPORT_INVOICES_PKG.g_invoices_table,
4893                       p_invoice_rec.invoice_id,
4894                       'NO SPECIAL CALENDAR FOR TERMS',
4895                       p_default_last_updated_by,
4896                       p_default_last_update_login,
4897                       current_calling_sequence) <> TRUE) THEN
4898          IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4899            AP_IMPORT_UTILITIES_PKG.Print(
4900            AP_IMPORT_INVOICES_PKG.g_debug_switch,
4901               'insert_rejections<-'||current_calling_sequence);
4902          END IF;
4903          RAISE terms_check_failure;
4904        END IF;
4905        l_current_invoice_status := 'N';
4906      END IF;
4907 
4908    END IF;
4909 
4910 --End bug 4115712
4911 
4912   p_current_invoice_status := l_current_invoice_status;
4913   RETURN (TRUE);
4914 
4915 EXCEPTION
4916   WHEN OTHERS THEN
4917     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4918       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
4919                                     debug_info);
4920     END IF;
4921 
4922     IF (SQLCODE < 0) THEN
4923       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4924         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
4925                                       SQLERRM);
4926       END IF;
4927     END IF;
4928     RETURN(FALSE);
4929 
4930 END v_check_invalid_terms;
4931 
4932 
4933 ----------------------------------------------------------------------------
4934 -- This function is used to validate several elements in the
4935 -- invoice: liability account, payment method, pay group,
4936 -- voucher num and requester.
4937 --
4938 ----------------------------------------------------------------------------
4939 FUNCTION v_check_misc_invoice_info (
4940     p_invoice_rec           IN OUT NOCOPY AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
4941     --Bug 6509776
4942     p_set_of_books_id           IN            NUMBER,
4943     p_default_last_updated_by   IN            NUMBER,
4944     p_default_last_update_login IN            NUMBER,
4945     p_current_invoice_status    IN OUT NOCOPY VARCHAR2,
4946     p_calling_sequence          IN            VARCHAR2)
4947 RETURN BOOLEAN IS
4948 
4949 misc_invoice_info_failure    EXCEPTION;
4950 l_valid_info                 VARCHAR2(1);
4951 l_current_invoice_status     VARCHAR2(1) := 'Y';
4952 current_calling_sequence     VARCHAR2(2000);
4953 debug_info                   VARCHAR2(500);
4954 l_invoice_count              NUMBER;
4955 l_emp_count                  NUMBER;
4956 l_chart_of_accounts_id       NUMBER;
4957 l_catsegs                    VARCHAR2(200);
4958 l_acct_type                  VARCHAR2(1);
4959 -- Bug 5448579
4960 l_valid_pay_group            PO_LOOKUP_CODES.Lookup_Code%TYPE;
4961 -- Bug 6509776
4962 l_ccid                       GL_CODE_COMBINATIONS.Code_Combination_ID%TYPE;
4963 
4964 l_debug_info          VARCHAR2(2000);                               -- Bug 13904341
4965 l_api_name   CONSTANT VARCHAR2(100) := 'v_check_misc_invoice_info'; -- Bug 13904341
4966 
4967 BEGIN
4968 
4969   --
4970   -- Update the calling sequence
4971   --
4972   current_calling_sequence :=
4973    'AP_IMPORT_VALIDATION_PKG.v_check_misc_invoice_info<-'||P_calling_sequence;
4974 
4975     -- 7531219
4976     -------------------------------------------------------------------------------
4977     -- step 0.1
4978     -- default the liability ccid if no liability account is entered
4979     -- This is required here as we need to validate the defaulted liability accounts too
4980     --------------------------------------------------------------------------------
4981     if p_invoice_rec.accts_pay_code_concatenated is null
4982        and p_invoice_rec.accts_pay_code_combination_id is null
4983     then
4984        debug_info := '(step 10.1 default the liability account';
4985        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4986          AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
4987                                        debug_info);
4988        END IF;
4989 
4990       begin
4991        if (p_invoice_rec.invoice_type_lookup_code = 'PAYMENT REQUEST') then
4992          SELECT fsp.accts_pay_code_combination_id
4993            INTO p_invoice_rec.accts_pay_code_combination_id
4994            FROM ap_system_parameters asp,
4995                 financials_system_parameters fsp
4996           WHERE asp.org_id = p_invoice_rec.org_id
4997             AND asp.org_id = fsp.org_id;
4998        else
4999          SELECT accts_pay_code_combination_id
5000            INTO p_invoice_rec.accts_pay_code_combination_id
5001            FROM ap_supplier_sites_all
5002           WHERE vendor_id = p_invoice_rec.vendor_id
5003             AND vendor_site_id = p_invoice_rec.vendor_site_id;
5004        end if;
5005       exception
5006          when others then
5007             debug_info := '(step 0.1 default the liability account';
5008             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5009               AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
5010                                             debug_info);
5011             END IF;
5012       end;
5013     end if;
5014 
5015   --
5016   -- Bug 6509776 - Adds validation for accts_pay_code_concatenated
5017   --
5018 
5019   IF (p_invoice_rec.accts_pay_code_concatenated is NOT NULL) THEN
5020     -------------------------------------------------------------------------
5021     -- Step 1 a
5022     -- Check for Liab account if entered
5023     -- Else we would default the liability account from the supplier site
5024     -- Note: No validation is done for the liab acct from the supplier, we
5025     -- just transfer the liabilty from the supplier as such. If at later
5026     -- point need be, the supplier site liab account validation logic
5027     -- can be included here.
5028     -------------------------------------------------------------------------
5029     debug_info :=
5030       '(Check Misc Invoice Info 1 a) Check for valid accts_pay_concat.';
5031      IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5032        AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
5033                                      debug_info);
5034      END IF;
5035 
5036      -- Validate liability account concat
5037      BEGIN
5038      IF AP_IMPORT_INVOICES_PKG.g_segment_delimiter <> '-' THEN
5039         p_invoice_rec.accts_pay_code_concatenated :=
5040         TRANSLATE(p_invoice_rec.accts_pay_code_concatenated, '-',
5041                   AP_IMPORT_INVOICES_PKG.g_segment_delimiter);
5042      END IF;
5043 
5044        --Fetch chart of accounts
5045        SELECT chart_of_accounts_id
5046          INTO l_chart_of_accounts_id
5047          FROM gl_sets_of_books
5048         WHERE set_of_books_id = p_set_of_books_id;
5049 
5050          IF (fnd_flex_keyval.validate_segs
5051                       ('CREATE_COMB_NO_AT', --bugfix:3888581
5052                        'SQLGL',
5053                        'GL#',
5054                         l_chart_of_accounts_id,
5055                         p_invoice_rec.accts_pay_code_concatenated,
5056                         'V',
5057                         nvl(p_invoice_rec.gl_date,sysdate),  -- BUG 3000219
5058                         'ALL',
5059                         NULL,
5060                     -- Bug 4102147
5061                     -- '\nSUMMARY_FLAG\nI\nAPPL=SQLGL;' ||
5062                     -- 'NAME=GL_CTAX_SUMMARY_ACCOUNT\nN',
5063                         'GL_GLOBAL\nDETAIL_POSTING_ALLOWED\nI\nAPPL=SQLGL;'||
5064   'NAME=GL_CTAX_DETAIL_POSTING\nY\0GL_GLOBAL\nSUMMARY_FLAG\nI\nAPPL=SQLGL;'||
5065                         'NAME=GL_CTAX_SUMMARY_ACCOUNT\nN',
5066                     -- End bug 4102147
5067                         NULL,
5068                         NULL,
5069                         FALSE,
5070                         FALSE,
5071                         NULL,
5072                         NULL,
5073                         NULL))  THEN
5074             l_ccid := fnd_flex_keyval.combination_id;
5075           ELSE
5076            IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5077              AP_IMPORT_UTILITIES_PKG.Print(
5078              AP_IMPORT_INVOICES_PKG.g_debug_switch,
5079              '(v_check_misc_invoice_info 1 a) Invalid accts_pay_concat');
5080            END IF;
5081 
5082            IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
5083                 (AP_IMPORT_INVOICES_PKG.g_invoices_table,
5084                   p_invoice_rec.invoice_id,
5085                   'INVALID LIABILITY ACCT',
5086                   p_default_last_updated_by,
5087                   p_default_last_update_login,
5088                   current_calling_sequence) <> TRUE) THEN
5089              IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5090                AP_IMPORT_UTILITIES_PKG.Print(
5091                AP_IMPORT_INVOICES_PKG.g_debug_switch,
5092                'insert_rejections<- '||current_calling_sequence);
5093              END IF;
5094              RAISE misc_invoice_info_failure;
5095            END IF;
5096            l_current_invoice_status := 'N';
5097          END IF; -- If validate segments is TRUE
5098 
5099        SELECT account_type
5100          INTO l_acct_type
5101          FROM gl_code_combinations
5102         WHERE code_combination_id = l_ccid;
5103 
5104        IF l_acct_type <> 'L' THEN
5105          IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5106            AP_IMPORT_UTILITIES_PKG.Print(
5107            AP_IMPORT_INVOICES_PKG.g_debug_switch,
5108            '(v_check_misc_invoice_info 1 a) Invalid accts_pay_concat');
5109          END IF;
5110 
5111          IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
5112                (AP_IMPORT_INVOICES_PKG.g_invoices_table,
5113                  p_invoice_rec.invoice_id,
5114                  'INVALID LIABILITY ACCT',
5115                  p_default_last_updated_by,
5116                  p_default_last_update_login,
5117                  current_calling_sequence) <> TRUE) THEN
5118            IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5119              AP_IMPORT_UTILITIES_PKG.Print(
5120              AP_IMPORT_INVOICES_PKG.g_debug_switch,
5121              'insert_rejections<- '||current_calling_sequence);
5122            END IF;
5123            RAISE misc_invoice_info_failure;
5124          END IF;
5125 
5126          l_current_invoice_status := 'N';
5127 
5128        END IF; -- Account type is other than L
5129 
5130        -- If liab acct ccid is not null, compare both
5131        -- if not same reject as inconsistent
5132        IF p_invoice_rec.accts_pay_code_combination_id IS NOT NULL THEN
5133           IF p_invoice_rec.accts_pay_code_combination_id <> l_ccid THEN
5134              IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5135                  AP_IMPORT_UTILITIES_PKG.Print(
5136                  AP_IMPORT_INVOICES_PKG.g_debug_switch,
5137                 '(v_check_misc_invoice_info 1 a) Inconsistent accts_pay');
5138              END IF;
5139 
5140              IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
5141                     (AP_IMPORT_INVOICES_PKG.g_invoices_table,
5142                       p_invoice_rec.invoice_id,
5143                       'INCONSISTENT LIAB ACCOUNT INFO',
5144                       p_default_last_updated_by,
5145                       p_default_last_update_login,
5146                       current_calling_sequence) <> TRUE) THEN
5147                IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5148                   AP_IMPORT_UTILITIES_PKG.Print(
5149                   AP_IMPORT_INVOICES_PKG.g_debug_switch,
5150                   'insert_rejections<- '||current_calling_sequence);
5151                END IF;
5152                 RAISE misc_invoice_info_failure;
5153              END IF;
5154              l_current_invoice_status := 'N';
5155            END IF;   -- END IF invoice liab ccid not equal to concat ccid
5156         ELSIF p_invoice_rec.accts_pay_code_combination_id IS NULL THEN
5157            p_invoice_rec.accts_pay_code_combination_id := l_ccid;
5158         END IF;
5159 
5160 
5161      EXCEPTION
5162        WHEN NO_DATA_FOUND Then
5163          IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5164            AP_IMPORT_UTILITIES_PKG.Print(
5165            AP_IMPORT_INVOICES_PKG.g_debug_switch,
5166            '(v_check_misc_invoice_info 1 a) Invalid accts_pay_concat ');
5167          END IF;
5168 
5169          IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
5170                AP_IMPORT_INVOICES_PKG.g_invoices_table,
5171                 p_invoice_rec.invoice_id,
5172                 'INVALID LIABILITY ACCT',
5173                 p_default_last_updated_by,
5174                 p_default_last_update_login,
5175                  current_calling_sequence) <> TRUE) THEN
5176            IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5177              AP_IMPORT_UTILITIES_PKG.Print(
5178              AP_IMPORT_INVOICES_PKG.g_debug_switch,
5179              'insert_rejections<-'||current_calling_sequence);
5180            END IF;
5181           RAISE misc_invoice_info_failure;
5182          END IF;
5183 
5184          l_current_invoice_status := 'N';
5185 
5186      END; -- valdiate liab acct concat
5187   END IF;
5188   -- Bug 6509776
5189 
5190   IF (p_invoice_rec.accts_pay_code_combination_id is NOT NULL) THEN
5191 
5192     -------------------------------------------------------------------------
5193     -- Step 1
5194     -- Check for Liab account if entered
5195     -- Else we would default the liability account from the supplier site
5196     -- Note: No validation is done for the liab acct from the supplier, we
5197     -- just transfer the liabilty from the supplier as such. If at later
5198     -- point need be, the supplier site liab account validation logic
5199     -- can be included here.
5200     -------------------------------------------------------------------------
5201     debug_info :=
5202       '(Check Misc Invoice Info 1) Check for valid accts_pay_ccid.';
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                                      debug_info);
5206      END IF;
5207 
5208      -- Validate liability account information
5209      BEGIN
5210        SELECT account_type
5211          INTO l_acct_type
5212          FROM gl_code_combinations
5213         WHERE code_combination_id =
5214                 p_invoice_rec.accts_pay_code_combination_id;
5215 
5216        SELECT chart_of_accounts_id
5217          INTO l_chart_of_accounts_id
5218          FROM gl_sets_of_books
5219         WHERE set_of_books_id = p_set_of_books_id;
5220 
5221        IF l_acct_type <> 'L' THEN
5222          IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5223            AP_IMPORT_UTILITIES_PKG.Print(
5224            AP_IMPORT_INVOICES_PKG.g_debug_switch,
5225            '(v_check_misc_invoice_info 1) Invalid accts_pay_ccid');
5226          END IF;
5227 
5228          IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
5229                (AP_IMPORT_INVOICES_PKG.g_invoices_table,
5230                  p_invoice_rec.invoice_id,
5231                  'INVALID LIABILITY ACCT',
5232                  p_default_last_updated_by,
5233                  p_default_last_update_login,
5234                  current_calling_sequence) <> TRUE) THEN
5235            IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5236              AP_IMPORT_UTILITIES_PKG.Print(
5237              AP_IMPORT_INVOICES_PKG.g_debug_switch,
5238              'insert_rejections<- '||current_calling_sequence);
5239            END IF;
5240            RAISE misc_invoice_info_failure;
5241          END IF;
5242 
5243          l_current_invoice_status := 'N';
5244 
5245        END IF; -- Account type is other than L
5246 
5247        IF fnd_flex_keyval.validate_ccid(
5248             appl_short_name  => 'SQLGL',
5249             key_flex_code    => 'GL#',
5250             structure_number => l_chart_of_accounts_id,
5251             combination_id   => p_invoice_rec.accts_pay_code_combination_id)
5252          THEN
5253          l_catsegs := fnd_flex_keyval.concatenated_values;
5254 
5255            --For BUG 3000219. CCID is to be validated with respect to
5256            --GL_DATE. Changed sysdate to p_invoice_rec.gl_date for validation
5257 
5258          IF (fnd_flex_keyval.validate_segs
5259                       ('CREATE_COMB_NO_AT', --bugfix:3888581
5260                        'SQLGL',
5261                        'GL#',
5262                         l_chart_of_accounts_id,
5263                         l_catsegs,
5264                         'V',
5265                         nvl(p_invoice_rec.gl_date,sysdate),  -- BUG 3000219
5266                         'ALL',
5267                         NULL,
5268                     -- Bug 4102147
5269                     -- '\nSUMMARY_FLAG\nI\nAPPL=SQLGL;' ||
5270                     -- 'NAME=GL_CTAX_SUMMARY_ACCOUNT\nN',
5271                          'GL_GLOBAL\nDETAIL_POSTING_ALLOWED\nI\nAPPL=SQLGL;'||
5272   'NAME=GL_CTAX_DETAIL_POSTING\nY\0GL_GLOBAL\nSUMMARY_FLAG\nI\nAPPL=SQLGL;'||
5273                         'NAME=GL_CTAX_SUMMARY_ACCOUNT\nN',
5274                     -- End bug 4102147
5275                         NULL,
5276                         NULL,
5277                         FALSE,
5278                         FALSE,
5279                         NULL,
5280                         NULL,
5281                         NULL)<>TRUE)  THEN
5282 
5283            IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5284              AP_IMPORT_UTILITIES_PKG.Print(
5285              AP_IMPORT_INVOICES_PKG.g_debug_switch,
5286              '(v_check_misc_invoice_info 1) Invalid accts_pay_ccid');
5287            END IF;
5288 
5289            IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
5290                 (AP_IMPORT_INVOICES_PKG.g_invoices_table,
5291                   p_invoice_rec.invoice_id,
5292                   'INVALID LIABILITY ACCT',
5293                   p_default_last_updated_by,
5294                   p_default_last_update_login,
5295                   current_calling_sequence) <> TRUE) THEN
5296              IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5297                AP_IMPORT_UTILITIES_PKG.Print(
5298                AP_IMPORT_INVOICES_PKG.g_debug_switch,
5299                'insert_rejections<- '||current_calling_sequence);
5300              END IF;
5301              RAISE misc_invoice_info_failure;
5302            END IF;
5303 
5304            l_current_invoice_status := 'N';
5305 
5306          END IF; -- If validate segments is other than TRUE
5307 
5308        ELSE -- Validate CCID returned false
5309          IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5310            AP_IMPORT_UTILITIES_PKG.Print(
5311            AP_IMPORT_INVOICES_PKG.g_debug_switch,
5312            '(v_check_misc_invoice_info 1) Invalid accts_pay_ccid');
5313          END IF;
5314 
5315          IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
5316                               (AP_IMPORT_INVOICES_PKG.g_invoices_table,
5317                                p_invoice_rec.invoice_id,
5318                                'INVALID LIABILITY ACCT',
5319                                p_default_last_updated_by,
5320                                p_default_last_update_login,
5321                                current_calling_sequence) <> TRUE) THEN
5322            IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5323              AP_IMPORT_UTILITIES_PKG.Print(
5324              AP_IMPORT_INVOICES_PKG.g_debug_switch,
5325              'insert_rejections<- '||current_calling_sequence);
5326            END IF;
5327            RAISE misc_invoice_info_failure;
5328          END IF;
5329 
5330          l_current_invoice_status := 'N';
5331 
5332        END IF; -- Validate CCID returned TRUE
5333 
5334      EXCEPTION -- Validate liability account information
5335        WHEN NO_DATA_FOUND Then
5336          IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5337            AP_IMPORT_UTILITIES_PKG.Print(
5338            AP_IMPORT_INVOICES_PKG.g_debug_switch,
5339            '(v_check_misc_invoice_info 1) Invalid accts_pay_ccid ');
5340          END IF;
5341 
5342          IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
5343                AP_IMPORT_INVOICES_PKG.g_invoices_table,
5344                 p_invoice_rec.invoice_id,
5345                 'INVALID LIABILITY ACCT',
5346                 p_default_last_updated_by,
5347                 p_default_last_update_login,
5348                  current_calling_sequence) <> TRUE) THEN
5349            IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5350              AP_IMPORT_UTILITIES_PKG.Print(
5351              AP_IMPORT_INVOICES_PKG.g_debug_switch,
5352              'insert_rejections<-'||current_calling_sequence);
5353            END IF;
5354           RAISE misc_invoice_info_failure;
5355          END IF;
5356 
5357          l_current_invoice_status := 'N';
5358 
5359      END; -- Validate liability account information
5360 
5361   END IF; -- liab account is not null
5362 
5363 
5364   IF (p_invoice_rec.pay_group_lookup_code is NOT NULL) THEN
5365 
5366     -------------------------------------------------------------------------
5367     -- Step 3
5368     -- Check for pay group
5369     -------------------------------------------------------------------------
5370     debug_info := '(Check Misc Invoice Info 3) Check for valid pay group';
5371     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5372       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
5373                                     debug_info);
5374     END IF;
5375 
5376     -- Bug 5448579
5377     FOR i IN AP_IMPORT_INVOICES_PKG.g_pay_group_tab.First..AP_IMPORT_INVOICES_PKG.g_pay_group_tab.Last
5378     LOOP
5379       IF AP_IMPORT_INVOICES_PKG.g_pay_group_tab(i).pay_group = p_invoice_rec.pay_group_lookup_code THEN
5380         l_valid_pay_group  := AP_IMPORT_INVOICES_PKG.g_pay_group_tab(i).pay_group;
5381         EXIT;
5382       END IF;
5383     END LOOP;
5384 
5385     debug_info := 'l_valid_pay_group: '||l_valid_pay_group;
5386     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5387       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
5388                                     debug_info);
5389     END IF;
5390 
5391     IF l_valid_pay_group IS NULL THEN
5392 
5393 
5394       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5395           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
5396           '(v_check_misc_invoice_info 3) Invalid pay group');
5397       END IF;
5398 
5399       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
5400                AP_IMPORT_INVOICES_PKG.g_invoices_table,
5401                 p_invoice_rec.invoice_id,
5402                 'INVALID PAY GROUP',
5403                 p_default_last_updated_by,
5404                 p_default_last_update_login,
5405                  current_calling_sequence) <> TRUE) THEN
5406         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5407             AP_IMPORT_UTILITIES_PKG.Print(
5408             AP_IMPORT_INVOICES_PKG.g_debug_switch,
5409             'insert_rejections<-'||current_calling_sequence);
5410         END IF;
5411         RAISE misc_invoice_info_failure;
5412       END IF;
5413 
5414       l_current_invoice_status := 'N';
5415 
5416     END IF;
5417 
5418   END IF; -- pay group is not nul
5419    /*  -- Invalid Info
5420     BEGIN
5421       SELECT 'X'
5422         INTO l_valid_info
5423         FROM po_lookup_codes
5424        WHERE lookup_code = p_invoice_rec.pay_group_lookup_code
5425          AND lookup_type = 'PAY GROUP'
5426          AND DECODE(SIGN(NVL(inactive_date,
5427                              AP_IMPORT_INVOICES_PKG.g_inv_sysdate) -
5428                          AP_IMPORT_INVOICES_PKG.g_inv_sysdate),
5429                     -1,'','*') = '*';
5430 
5431     EXCEPTION
5432       WHEN NO_DATA_FOUND Then
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           '(v_check_misc_invoice_info 3) Invalid pay group');
5436         END IF;
5437 
5438         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
5439                AP_IMPORT_INVOICES_PKG.g_invoices_table,
5440                 p_invoice_rec.invoice_id,
5441                 'INVALID PAY GROUP',
5442                 p_default_last_updated_by,
5443                 p_default_last_update_login,
5444                  current_calling_sequence) <> TRUE) THEN
5445           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5446             AP_IMPORT_UTILITIES_PKG.Print(
5447             AP_IMPORT_INVOICES_PKG.g_debug_switch,
5448             'insert_rejections<-'||current_calling_sequence);
5449           END IF;
5450           RAISE misc_invoice_info_failure;
5451         END IF;
5452 
5453         l_current_invoice_status := 'N';
5454     END; */
5455 
5456 
5457   IF (p_invoice_rec.voucher_num IS NOT NULL) THEN
5458 
5459     --------------------------------------------------------------------------
5460     -- Step 4
5461     -- Check for duplicate voucher number.
5462     -- Retropricing: For PPA Invoices voucher num is NULL
5463     --------------------------------------------------------------------------
5464     debug_info :=
5465       '(Check Misc Invoice Info 4) Check for duplicate voucher number';
5466     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5467       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
5468                                     debug_info);
5469     END IF;
5470 
5471     SELECT count(*)
5472       INTO l_invoice_count
5473       FROM ap_invoices
5474      WHERE voucher_num = p_invoice_rec.voucher_num;
5475 
5476     IF (l_invoice_count > 0) THEN
5477       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5478         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
5479         '(v_check_misc_invoice_info 4) Reject: Duplicate Voucher Number');
5480       END IF;
5481 
5482       -- if data is found, an error exists
5483       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
5484           (AP_IMPORT_INVOICES_PKG.g_invoices_table,
5485             p_invoice_rec.invoice_id,
5486             'DUPLICATE VOUCHER',
5487             p_default_last_updated_by,
5488             p_default_last_update_login,
5489             current_calling_sequence) <> TRUE) THEN
5490         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5491           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
5492           'insert_rejections<-'||current_calling_sequence);
5493         END IF;
5494         RAISE misc_invoice_info_failure;
5495       END IF;
5496 
5497       l_current_invoice_status := 'N';
5498 
5499     END IF; -- invoice count > 0
5500 
5501   END IF; -- voucher number is not null
5502 
5503 -- Commented the below validation for Bug 5064959
5504 
5505  /* IF (p_invoice_rec.voucher_num IS NOT NULL) THEN
5506 
5507  --Bug 4158851 has added this step
5508 
5509      ------------------------------------------------------------------------------------
5510      -- Step 4.1
5511      -- Check for voucher number length (intended <= 8)
5512      ------------------------------------------------------------------------------------
5513      debug_info := '(Check Misc Invoice Info 4.1) Check for voucher number length <= 8';
5514 
5515     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5516       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
5517     END IF;
5518 
5519 
5520      IF (length(p_invoice_rec.voucher_num) > 8) THEN
5521 
5522     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5523       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
5524     end if;
5525 
5526          -- if data is found, an error exists
5527 
5528       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
5529                        (AP_IMPORT_INVOICES_PKG.g_invoices_table,
5530                         p_invoice_rec.invoice_id,
5531                         'INVALID REQUESTER',
5532                         p_default_last_updated_by,
5533                         p_default_last_update_login,
5534                         current_calling_sequence) <> TRUE) THEN
5535         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5536           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
5537           'insert_rejections<-'||current_calling_sequence);
5538         END IF;
5539          RAISE misc_invoice_info_failure;
5540          END IF;
5541 
5542          l_current_invoice_status := 'N';
5543 
5544      END IF;
5545 
5546   END IF; */-- voucher number is not null
5547   --------------------------------------------------------------------------
5548   -- Step 5
5549   -- Check for valid employee
5550   --------------------------------------------------------------------------
5551   debug_info := '(Check Misc Invoice Info 5) Check for valid employee';
5552   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5553     AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
5554                                   debug_info);
5555   END IF;
5556 
5557   /* start Bug10084709 */
5558   If(Ap_Import_Invoices_Pkg.G_Source <> 'PPA') Then
5559 
5560    -- Bug 13904341: Check if any of the requester field is populated
5561    IF (P_Invoice_Rec.Requester_Id  IS NOT NULL or
5562        P_Invoice_Rec.requester_Last_Name IS NOT NULL or
5563        P_Invoice_Rec.Requester_First_Name IS NOT NULL or
5564        p_invoice_rec.requester_employee_num IS NOT NULL) THEN
5565 
5566     -- Bug 13074307: Validate all requester info provided and make sure
5567     --               they belongs to one record in HRMS
5568     SELECT count(*)
5569     INTO l_emp_count
5570     FROM hr_employees_current_v
5571     Where Employee_Id  = nvl(P_Invoice_Rec.Requester_Id, Employee_Id)
5572     AND   Last_Name    = nvl(P_Invoice_Rec.requester_Last_Name, Last_Name)
5573     AND   First_Name   = nvl(P_Invoice_Rec.Requester_First_Name, First_Name)
5574     AND   employee_num = nvl(p_invoice_rec.requester_employee_num, employee_num);
5575 
5576     If L_Emp_Count <> 1 Then
5577 
5578       -- Bug 13904341
5579       l_debug_info := 'Invalid Requeste:, L_Emp_Count = '||L_Emp_Count;
5580       IF (G_LEVEL_PROCEDURE >= G_CURRENT_RUNTIME_LEVEL) THEN
5581         FND_LOG.STRING(G_LEVEL_PROCEDURE,G_MODULE_NAME||l_api_name,l_debug_info);
5582       END IF;
5583 
5584       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
5585                        (AP_IMPORT_INVOICES_PKG.g_invoices_table,
5586                         p_invoice_rec.invoice_id,
5587                         'INVALID REQUESTER',
5588                         p_default_last_updated_by,
5589                         p_default_last_update_login,
5590                         current_calling_sequence) <> TRUE) THEN
5591         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5592           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
5593           'insert_rejections<-'||current_calling_sequence);
5594         End If;
5595 
5596         RAISE misc_invoice_info_failure;
5597       END IF;
5598       L_Current_Invoice_Status := 'N';
5599 
5600     END IF; -- employee count is not 1
5601    END IF; -- Check if any of the requester field is populated
5602 
5603 /*	IF (p_invoice_rec.requester_id IS NOT NULL) THEN
5604 
5605 		SELECT count(*)
5606 		INTO l_emp_count
5607 		FROM hr_employees_current_v
5608 		WHERE employee_id = p_invoice_rec.requester_id;
5609 
5610 		IF l_emp_count = 0 THEN
5611 
5612 			IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
5613                        (AP_IMPORT_INVOICES_PKG.g_invoices_table,
5614                         p_invoice_rec.invoice_id,
5615                         'INVALID REQUESTER',
5616                         p_default_last_updated_by,
5617                         p_default_last_update_login,
5618                         current_calling_sequence) <> TRUE) THEN
5619 				IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5620 				AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
5621 				'insert_rejections<-'||current_calling_sequence);
5622 				END IF;
5623 
5624 				RAISE misc_invoice_info_failure;
5625 			END IF;
5626 
5627 			l_current_invoice_status := 'N';
5628 
5629 		END IF; -- employee count is 0
5630 	ELSIF
5631          (P_Invoice_Rec.Requester_last_Name Is Not Null And
5632           P_Invoice_Rec.Requester_First_Name Is Not Null) Then
5633 
5634 		Begin
5635                   Select Employee_Id
5636                   INTO p_invoice_rec.requester_id
5637                   From Hr_Employees_Current_V
5638                   Where (Last_Name) =(P_Invoice_Rec.requester_Last_Name)
5639                   And (First_Name) =(P_Invoice_Rec.Requester_First_Name);
5640 
5641 		Exception
5642 		When Others Then
5643                 	IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
5644                        	(AP_IMPORT_INVOICES_PKG.g_invoices_table,
5645                         	p_invoice_rec.invoice_id,
5646                         	'INVALID REQUESTER',
5647                         	p_default_last_updated_by,
5648                         	p_default_last_update_login,
5649                         	Current_Calling_Sequence) <> True) Then
5650                    	   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5651                            AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
5652                            'insert_rejections<-'||Current_Calling_Sequence);
5653                    	   End If;
5654 
5655 			Raise Misc_Invoice_Info_Failure;
5656                 	End If;
5657 
5658 			l_Current_Invoice_Status := 'N';
5659 		End;
5660 	** end  Bug10084709 **
5661 	** Added for bug 13074325 **
5662 	ELSIF (p_invoice_rec.requester_employee_num IS NOT NULL) THEN
5663 		Begin
5664 
5665 			Select Employee_Id
5666 			INTO p_invoice_rec.requester_id
5667 			FROM hr_employees_current_v
5668 			WHERE employee_num = p_invoice_rec.requester_employee_num;
5669 
5670 		Exception
5671 		When Others Then
5672                 	IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
5673                        	(AP_IMPORT_INVOICES_PKG.g_invoices_table,
5674                         	p_invoice_rec.invoice_id,
5675                         	'INVALID REQUESTER',
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 
5684 			   Raise Misc_Invoice_Info_Failure;
5685                 	End If;
5686 
5687 			l_Current_Invoice_Status := 'N';
5688 		End;
5689 
5690 	END IF; -- requester id is not null
5691 */
5692   p_current_invoice_status := l_current_invoice_status;
5693 END IF; /* g_source <> PPA */
5694 
5695   RETURN (TRUE);
5696 
5697 EXCEPTION
5698   WHEN OTHERS THEN
5699     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5700       AP_IMPORT_UTILITIES_PKG.Print(
5701       AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
5702     END IF;
5703 
5704     IF (SQLCODE < 0) then
5705       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5706         AP_IMPORT_UTILITIES_PKG.Print(
5707         AP_IMPORT_INVOICES_PKG.g_debug_switch,SQLERRM);
5708       END IF;
5709     END IF;
5710 
5711     RETURN(FALSE);
5712 
5713 END v_check_misc_invoice_info;
5714 
5715 ----------------------------------------------------------------------------
5716 -- This function is used to validate the Legal Entity information of the
5717 -- invoice that is being imported.
5718 --
5719 ----------------------------------------------------------------------------
5720 FUNCTION v_check_Legal_Entity_info (
5721     p_invoice_rec               IN OUT NOCOPY AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
5722     p_set_of_books_id           IN            NUMBER,
5723     p_default_last_updated_by   IN            NUMBER,
5724     p_default_last_update_login IN            NUMBER,
5725     p_current_invoice_status    IN OUT NOCOPY VARCHAR2,
5726     p_calling_sequence          IN            VARCHAR2) RETURN BOOLEAN
5727 IS
5728 
5729 le_invoice_info_failure         EXCEPTION;
5730 l_valid_info                    VARCHAR2(1);
5731 l_current_invoice_status        VARCHAR2(1) := 'Y';
5732 current_calling_sequence        VARCHAR2(2000);
5733 debug_info                      VARCHAR2(500);
5734 
5735 l_ptop_le_info                  XLE_BUSINESSINFO_GRP.ptop_le_rec;
5736 l_le_return_status              varchar2(1);
5737 l_msg_data                      varchar2(1000);
5738 l_bill_to_location_id           NUMBER(15);
5739 l_supp_site_liab_ccid           NUMBER(15);
5740 l_ccid_to_api                   NUMBER(15);
5741 l_valid_le                      VARCHAR2(100);
5742 
5743 BEGIN
5744   --
5745   -- Update the calling sequence
5746   --
5747   current_calling_sequence :=
5748    'AP_IMPORT_VALIDATION_PKG.v_check_legal_entity_info<-'||P_calling_sequence;
5749 
5750      IF (p_invoice_rec.legal_entity_id IS NOT NULL) THEN
5751          ----------------------------------------------------------------------
5752          -- Step 1
5753          -- LE ID is provided. Validate if it is a valid LE.
5754          -----------------------------------------------------------------------
5755          debug_info :=
5756                '(Check Legal Entity Info 1) Check Valid LE ID';
5757          IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5758             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
5759                                      debug_info);
5760          END IF;
5761 
5762          XLE_UTILITIES_GRP.IsLegalEntity_LEID
5763                            (l_le_return_status,
5764                             l_msg_data,
5765                             p_invoice_rec.legal_entity_id,
5766                             l_valid_le);
5767 
5768          IF l_le_return_status = FND_API.G_RET_STS_SUCCESS THEN
5769             IF l_valid_le = FND_API.G_FALSE THEN
5770               ------------------------------------------------------------------
5771               -- Step 1.1
5772               -- Invalid LE ID Case
5773               --
5774               ------------------------------------------------------------------
5775               debug_info :=
5776                          '(Check Legal Entity Info 1.1) InValid LE ID Flow';
5777               IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5778                  AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
5779                                             debug_info);
5780               END IF;
5781               IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
5782                    (AP_IMPORT_INVOICES_PKG.g_invoices_table,
5783                      p_invoice_rec.invoice_id,
5784                      'INVALID LEGAL ENTITY',
5785                      p_default_last_updated_by,
5786                      p_default_last_update_login,
5787                      current_calling_sequence) <> TRUE) THEN
5788                   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5789                      AP_IMPORT_UTILITIES_PKG.Print(
5790                             AP_IMPORT_INVOICES_PKG.g_debug_switch,
5791                            'insert_rejections<- '||current_calling_sequence);
5792                   END IF;
5793                   l_current_invoice_status := 'N';
5794                   RAISE le_invoice_info_failure;
5795               END IF;
5796             END IF;
5797          END IF;
5798      END IF;
5799 
5800      IF ((p_invoice_rec.cust_registration_code IS NOT NULL) AND
5801         (p_invoice_rec.cust_registration_number IS NOT NULL)) OR
5802          /* Bug 4516037. Added the following condition */
5803          (p_invoice_rec.legal_entity_id IS NULL) THEN
5804          -----------------------------------------------------------------------
5805          -- Step 2
5806          -- This case the registration code and the number are provided
5807          -- Call the LE API to validate the registration code and number to
5808          -- get the right LE information.
5809          --
5810          -----------------------------------------------------------------------
5811          debug_info :=
5812                '(Check Legal Entity Info 2) Check for reg code/number and Get LE.';
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          -- Step 2.1
5819          -- Get Bill TO Location ID from Supplier Site
5820          --
5821          -----------------------------------------------------------------------
5822 
5823          -- Bug 5518886 . Added the following condition If
5824          IF p_invoice_rec.invoice_type_lookup_code <> 'PAYMENT REQUEST' THEN
5825 
5826            debug_info :=
5827                '(Check Legal Entity Info 2.1) Get Bill TO Location ID';
5828            IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5829              AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
5830                                       debug_info);
5831            END IF;
5832 
5833 
5834            BEGIN
5835              SELECT bill_to_location_id,
5836                     accts_pay_code_combination_id
5837              INTO   l_bill_to_location_id,
5838                     l_supp_site_liab_ccid
5839              FROM   po_vendor_sites
5840              WHERE  vendor_site_id = p_invoice_rec.vendor_site_id;
5841 
5842              l_ccid_to_api := NVL(p_invoice_rec.accts_pay_code_combination_id,
5843                                 l_supp_site_liab_ccid);
5844            EXCEPTION
5845              WHEN OTHERS THEN
5846                l_bill_to_location_id := NULL;
5847                l_ccid_to_api := p_invoice_rec.accts_pay_code_combination_id;
5848            END;
5849 
5850          ELSE
5851 
5852            debug_info :=
5853                '(Check Legal Entity Info 2.1) For Payment Request Legal Entity will '
5854                || 'based on interface accts_pay_code_combination_id ';
5855            IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5856              AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
5857                                       debug_info);
5858            END IF;
5859 
5860            l_ccid_to_api := p_invoice_rec.accts_pay_code_combination_id;
5861 
5862          END IF;
5863 
5864          ----------------------------------------------------------------------
5865          -- Step 2.2
5866          -- Call the LE API
5867          --
5868          ----------------------------------------------------------------------
5869          debug_info :=
5870                '(Check Legal Entity Info 2.2) Call LE API';
5871          IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5872             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
5873                                      debug_info);
5874          END IF;
5875 
5876          XLE_BUSINESSINFO_GRP.Get_PurchasetoPay_Info
5877                               (l_le_return_status,
5878                                l_msg_data,
5879                                p_invoice_rec.cust_registration_code,
5880                                p_invoice_rec.cust_registration_number,
5881                                l_bill_to_location_id,
5882                                l_ccid_to_api,
5883                                p_invoice_rec.org_id,
5884                                l_ptop_le_info);
5885          IF (l_le_return_status = FND_API.G_RET_STS_SUCCESS) THEN
5886             --------------------------------------------------------------------
5887             -- Step 2.3
5888             -- Valid LE Returned by the API.
5889             --
5890             -------------------------------------------------------------------
5891             debug_info :=
5892                        '(Check Legal Entity Info 2.3) Valid LE Flow';
5893             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5894                AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
5895                                             debug_info);
5896             END IF;
5897             IF p_invoice_rec.legal_entity_id IS NOT NULL THEN
5898                IF p_invoice_rec.legal_entity_id <>
5899                   l_ptop_le_info.legal_entity_id THEN
5900                   -------------------------------------------------------------
5901                   -- Step 2.4
5902                   -- Inconsistent LE Info
5903                   --
5904                   -------------------------------------------------------------
5905                   debug_info :=
5906                              '(Check Legal Entity Info 2.4) Inconsistent LE Info';
5907                   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5908                       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
5909                                                  debug_info);
5910                   END IF;
5911                   IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
5912                      (AP_IMPORT_INVOICES_PKG.g_invoices_table,
5913                             p_invoice_rec.invoice_id,
5914                             'INCONSISTENT LE INFO',
5915                             p_default_last_updated_by,
5916                             p_default_last_update_login,
5917                             current_calling_sequence) <> TRUE) THEN
5918                      IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5919                          AP_IMPORT_UTILITIES_PKG.Print(
5920                            AP_IMPORT_INVOICES_PKG.g_debug_switch,
5921                           'insert_rejections<- '||current_calling_sequence);
5922                      END IF;
5923                      l_current_invoice_status := 'N';
5924                      RAISE le_invoice_info_failure;
5925                   END IF;
5926                END IF;
5927             END IF;
5928             p_invoice_rec.legal_entity_id := l_ptop_le_info.legal_entity_id;
5929             /* Bug 4516037. Added the following debug info for printing
5930                legal entity id */
5931             debug_info :=
5932                      '(Check Legal Entity Info 2.4a) Legal Entity ID: '||
5933                        p_invoice_rec.legal_entity_id;
5934             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5935               AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
5936                                            debug_info);
5937             END IF;
5938 
5939 
5940 
5941 
5942 
5943 
5944          ELSE
5945             -------------------------------------------------------------------
5946             -- Step 2.5
5947             -- Invalid LE Case
5948             --
5949             -------------------------------------------------------------------
5950             debug_info :=
5951                        '(Check Legal Entity Info 2.5) InValid LE Flow';
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             IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
5957                  (AP_IMPORT_INVOICES_PKG.g_invoices_table,
5958                    p_invoice_rec.invoice_id,
5959                    'INVALID LEGAL ENTITY',
5960                    p_default_last_updated_by,
5961                    p_default_last_update_login,
5962                    current_calling_sequence) <> TRUE) THEN
5963                 IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5964                    AP_IMPORT_UTILITIES_PKG.Print(
5965                           AP_IMPORT_INVOICES_PKG.g_debug_switch,
5966                          'insert_rejections<- '||current_calling_sequence);
5967                 END IF;
5968                 l_current_invoice_status := 'N';
5969                 RAISE le_invoice_info_failure;
5970             END IF;
5971          END IF;
5972      END IF;
5973 
5974   p_current_invoice_status := l_current_invoice_status;
5975   RETURN (TRUE);
5976 EXCEPTION
5977   WHEN OTHERS THEN
5978     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5979       AP_IMPORT_UTILITIES_PKG.Print(
5980       AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
5981     END IF;
5982 
5983     IF (SQLCODE < 0) then
5984       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5985         AP_IMPORT_UTILITIES_PKG.Print(
5986         AP_IMPORT_INVOICES_PKG.g_debug_switch,SQLERRM);
5987       END IF;
5988     END IF;
5989     RETURN(FALSE);
5990 END v_check_Legal_Entity_info;
5991 
5992 ------------------------------------------------------------------------------
5993 -- This function is used to validate payment currency.
5994 --
5995 ------------------------------------------------------------------------------
5996 FUNCTION v_check_invalid_pay_curr (
5997          p_invoice_rec            IN AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
5998          p_pay_currency_code            OUT NOCOPY VARCHAR2,
5999          p_payment_cross_rate_date      OUT NOCOPY DATE,
6000          p_payment_cross_rate           OUT NOCOPY NUMBER,
6001          p_payment_cross_rate_type      OUT NOCOPY VARCHAR2,
6002          p_default_last_updated_by   IN            NUMBER,
6003          p_default_last_update_login IN            NUMBER,
6004          p_current_invoice_status    IN OUT NOCOPY VARCHAR2,
6005          p_calling_sequence          IN            VARCHAR2) RETURN BOOLEAN
6006 IS
6007 
6008 invalid_pay_curr_code_failure    EXCEPTION;
6009 l_current_invoice_status         VARCHAR2(1) := 'Y';
6010 l_start_date_active              DATE;
6011 l_end_date_active                DATE;
6012 l_payment_cross_rate             AP_INVOICES_INTERFACE.payment_cross_rate%TYPE;
6013 l_warning                        VARCHAR2(240);
6014 current_calling_sequence         VARCHAR2(2000);
6015 debug_info                       VARCHAR2(500);
6016 
6017 l_fnd_currency_table             AP_IMPORT_INVOICES_PKG.Fnd_Currency_Tab_Type;
6018 l_valid_pay_currency             FND_CURRENCIES.Currency_Code%TYPE;
6019 
6020 BEGIN
6021   --
6022   -- Update the calling sequence
6023   --
6024   current_calling_sequence :=
6025    'AP_IMPORT_VALIDATION_PKG.v_check_invalid_pay_curr<-'||P_calling_sequence;
6026 
6027   -- Bug 5448579
6028   debug_info := '(Check Invalid Pay Currency 0)  Calling Caching Function for Currency';
6029   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
6030       AP_IMPORT_UTILITIES_PKG.Print(
6031         AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
6032   END IF;
6033   IF (AP_IMPORT_UTILITIES_PKG.Cache_Fnd_Currency (
6034            P_Fnd_Currency_Table   => l_fnd_currency_table,
6035            P_Calling_Sequence     => current_calling_sequence ) <> TRUE) THEN
6036     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
6037               AP_IMPORT_UTILITIES_PKG.Print(
6038                 AP_IMPORT_INVOICES_PKG.g_debug_switch,
6039                'Cache_Fnd_Currency <-'||current_calling_sequence);
6040     END IF;
6041     Raise invalid_pay_curr_code_failure;
6042   END IF;
6043 
6044   IF (p_invoice_rec.payment_currency_code IS NOT NULL) THEN
6045     -------------------------------------------------------------------------
6046     -- Step 1
6047     -- Check if the payment currency is inactive. If no data found then
6048     -- payment currency is invalid and will be handled in EXCEPTION clause
6049     -------------------------------------------------------------------------
6050 
6051     /*SELECT start_date_active, end_date_active
6052       INTO l_start_date_active, l_end_date_active
6053       FROM fnd_currencies
6054      WHERE currency_code = p_invoice_rec.payment_currency_code; */
6055 
6056      -- Bug 5448579
6057     FOR i IN l_fnd_currency_table.First..l_fnd_currency_table.Last LOOP
6058       IF l_fnd_currency_table(i).currency_code = p_invoice_rec.payment_currency_code THEN
6059         l_valid_pay_currency  := l_fnd_currency_table(i).currency_code;
6060         l_start_date_active   := l_fnd_currency_table(i).start_date_active;
6061         l_end_date_active     := l_fnd_currency_table(i).end_date_active;
6062         EXIT;
6063       END IF;
6064     END LOOP;
6065 
6066     debug_info := 'l_valid_pay_currency: '||l_valid_pay_currency;
6067     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
6068       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
6069                                     debug_info);
6070     END IF;
6071 
6072     IF l_valid_pay_currency IS NOT NULL THEN
6073       IF ((trunc(AP_IMPORT_INVOICES_PKG.g_inv_sysdate) <
6074         nvl(l_start_date_active,
6075             trunc(AP_IMPORT_INVOICES_PKG.g_inv_sysdate))) OR
6076         (AP_IMPORT_INVOICES_PKG.g_inv_sysdate >=
6077          nvl(l_end_date_active, AP_IMPORT_INVOICES_PKG.g_inv_sysdate+1))) THEN
6078 
6079         debug_info := '(Check Payment Currency Code 1) Check for Inactive '
6080                     ||'Payment Currency Code.';
6081         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
6082           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
6083                                       debug_info);
6084         END IF;
6085 
6086         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
6087           (AP_IMPORT_INVOICES_PKG.g_invoices_table,
6088             p_invoice_rec.invoice_id,
6089             'INACTIVE PAY CURR CODE',
6090             p_default_last_updated_by,
6091             p_default_last_update_login,
6092             current_calling_sequence) <> TRUE) THEN
6093           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
6094             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
6095             'insert_rejections<-'||current_calling_sequence);
6096           END IF;
6097           RAISE invalid_pay_curr_code_failure;
6098         END IF;
6099 
6100         l_current_invoice_status := 'N';
6101       END IF; -- Test of inactive payment currency code
6102     ELSE
6103       debug_info := '(Check Payment Currency Code 1.1) Check for Inactive '
6104                     ||'Payment Currency Code.';
6105       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
6106           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
6107                                       debug_info);
6108       END IF;
6109 
6110       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
6111           (AP_IMPORT_INVOICES_PKG.g_invoices_table,
6112             p_invoice_rec.invoice_id,
6113             'INACTIVE PAY CURR CODE',
6114             p_default_last_updated_by,
6115             p_default_last_update_login,
6116             current_calling_sequence) <> TRUE) THEN
6117          IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
6118             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
6119             'insert_rejections <-'||current_calling_sequence);
6120          END IF;
6121          RAISE invalid_pay_curr_code_failure;
6122        END IF;
6123 
6124     END IF;
6125     --------------------------------------------------------------------------
6126     -- Step 2
6127     -- Check if the payment cross rate date is null. If yes, assign the
6128     -- invoice_date to it.
6129     --------------------------------------------------------------------------
6130     IF (p_invoice_rec.payment_cross_rate_date IS NULL) THEN
6131       p_payment_cross_rate_date := p_invoice_rec.invoice_date;
6132     ELSE
6133       p_payment_cross_rate_date := p_invoice_rec.payment_cross_rate_date;
6134     END IF;
6135 
6136     --------------------------------------------------------------------------
6137     -- Step 3
6138     -- Check if the invoice and payment currency have fixed rate relationship.
6139     --------------------------------------------------------------------------
6140     IF ( p_invoice_rec.payment_currency_code <>
6141              p_invoice_rec.invoice_currency_code) THEN
6142 
6143       IF ( gl_currency_api.is_fixed_rate(
6144                p_invoice_rec.invoice_currency_code,
6145                p_invoice_rec.payment_currency_code,
6146                p_payment_cross_rate_date) <> 'Y' ) THEN
6147 
6148         debug_info := '(Check Payment Currency Code 3.1) Check for fixed '
6149                       ||'payment cross rate.';
6150         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
6151           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
6152                                         debug_info);
6153         END IF;
6154 
6155         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
6156                 AP_IMPORT_INVOICES_PKG.g_invoices_table,
6157                  p_invoice_rec.invoice_id,
6158                  'PAY X RATE NOT FIXED',
6159                  p_default_last_updated_by,
6160                  p_default_last_update_login,
6161                  current_calling_sequence) <> TRUE) THEN
6162           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
6163             AP_IMPORT_UTILITIES_PKG.Print(
6164                 AP_IMPORT_INVOICES_PKG.g_debug_switch,
6165                 'insert_rejections<-'||current_calling_sequence);
6166           END IF;
6167           RAISE invalid_pay_curr_code_failure;
6168         END IF;
6169 
6170         l_current_invoice_status := 'N';
6171       ELSE
6172         p_payment_cross_rate_type := 'EMU FIXED';
6173         l_payment_cross_rate := ap_utilities_pkg.get_exchange_rate(
6174                                     p_invoice_rec.invoice_currency_code,
6175                                     p_invoice_rec.payment_currency_code,
6176                                     p_payment_cross_rate_type,
6177                                     p_payment_cross_rate_date,
6178                                     current_calling_sequence);
6179         debug_info := '(Check Payment Currency Code 3.2) Check for fixed '
6180                       ||' and get payment cross rate.';
6181         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
6182           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
6183                                         debug_info);
6184         END IF;
6185 
6186         IF ( (l_payment_cross_rate <> p_invoice_rec.payment_cross_rate) AND
6187              (p_invoice_rec.payment_cross_rate IS NOT NULL)) THEN
6188           BEGIN
6189             SELECT  description
6190               INTO  l_warning
6191               FROM  ap_lookup_codes
6192              WHERE  lookup_type = 'REJECT CODE'
6193                AND  lookup_code = 'PAY RATE OVERWRITTEN';
6194              debug_info := '(Check Payment Currency Code 3.3) Check for fixed '
6195                           || l_warning;
6196              IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
6197                AP_IMPORT_UTILITIES_PKG.Print(
6198                 AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
6199              END IF;
6200           EXCEPTION WHEN no_data_found THEN
6201             NULL;
6202           END;
6203         END IF;
6204         p_payment_cross_rate := l_payment_cross_rate;
6205       END IF; -- end of gl_is_fix rate api call
6206     ELSE
6207 
6208       -- pay_curr_code = inv_curr_code case
6209       debug_info := '(Check Payment Currency Code 3.3) Check for fixed '
6210                       ||' pay_currency_code = inv_currency_code';
6211       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
6212           AP_IMPORT_UTILITIES_PKG.Print(
6213               AP_IMPORT_INVOICES_PKG.g_debug_switch,
6214               debug_info);
6215       END IF;
6216 
6217       p_pay_currency_code := p_invoice_rec.invoice_currency_code;
6218       IF (p_invoice_rec.payment_cross_rate_date IS NULL) THEN
6219         p_payment_cross_rate_date := p_invoice_rec.invoice_date;
6220       END IF;
6221 
6222       p_payment_cross_rate := 1;
6223       p_payment_cross_rate_type := NULL;
6224 
6225     END IF; -- Payment currency code is other than invoice currency code
6226 
6227   ELSIF (p_invoice_rec.payment_currency_code is NULL ) THEN
6228 
6229     p_pay_currency_code := p_invoice_rec.invoice_currency_code;
6230     IF (p_invoice_rec.payment_cross_rate_date IS NULL) THEN
6231       p_payment_cross_rate_date := p_invoice_rec.invoice_date;
6232     END IF;
6233 
6234     p_payment_cross_rate := 1;
6235     p_payment_cross_rate_type := NULL;
6236 
6237   END IF; -- endif for payment currency code not null
6238 
6239   p_current_invoice_status := l_current_invoice_status;
6240   RETURN (TRUE);
6241 
6242 EXCEPTION
6243   WHEN no_data_found THEN
6244 
6245     -------------------------------------------------------------------------
6246     -- Step 4
6247     -- Check for Invalid Payment Currency Code.
6248     -------------------------------------------------------------------------
6249     debug_info := '(Check Invoice Currency Code 4) Check for Invalid Invoice'
6250                   ||' Currency Code.';
6251     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
6252       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
6253                                     debug_info);
6254     END IF;
6255 
6256     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
6257           (AP_IMPORT_INVOICES_PKG.g_invoices_table,
6258             p_invoice_rec.invoice_id,
6259             'INVALID PAY CURR CODE',
6260             p_default_last_updated_by,
6261             p_default_last_update_login,
6262             current_calling_sequence) <> TRUE) THEN
6263       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
6264         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
6265         'insert_rejections<-'||current_calling_sequence);
6266       END IF;
6267       RAISE invalid_pay_curr_code_failure;
6268     END IF;
6269 
6270     l_current_invoice_status := 'N';
6271     p_current_invoice_status := l_current_invoice_status;
6272     RETURN (TRUE);
6273 
6274   WHEN OTHERS THEN
6275     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
6276       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
6277                                     debug_info);
6278     END IF;
6279 
6280     IF (SQLCODE < 0) then
6281       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
6282         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
6283                                       SQLERRM);
6284       END IF;
6285     END IF;
6286     RETURN(FALSE);
6287 
6288 END v_check_invalid_pay_curr;
6289 
6290 -----------------------------------------------------------------------------
6291 -- This function is used to validate prepayment information for
6292 -- application.
6293 -----------------------------------------------------------------------------
6294 
6295 FUNCTION v_check_prepay_info(
6296           p_invoice_rec               IN OUT NOCOPY
6297                                       AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
6298           p_base_currency_code        IN            VARCHAR2,
6299           p_prepay_period_name        IN OUT NOCOPY VARCHAR2,
6300 	  p_prepay_invoice_id	      OUT NOCOPY    NUMBER,
6301 	  p_prepay_case_name	      OUT NOCOPY    VARCHAR2,
6302           p_request_id                IN            NUMBER,
6303           p_default_last_updated_by   IN            NUMBER,
6304           p_default_last_update_login IN            NUMBER,
6305           p_current_invoice_status    IN OUT NOCOPY VARCHAR2,
6306           p_calling_sequence          IN            VARCHAR2) RETURN BOOLEAN
6307 IS
6308 
6309 l_current_invoice_status        VARCHAR2(1);
6310 l_reject_code                   VARCHAR2(30);
6311 current_calling_sequence        VARCHAR2(2000);
6312 debug_info                      VARCHAR2(500);
6313 check_prepay_failure            EXCEPTION;
6314 l_count_lines_matched	        NUMBER;
6315 
6316 BEGIN
6317   --
6318   --bug 9326733
6319   l_current_invoice_status := p_current_invoice_status;
6320 
6321   current_calling_sequence :=  'AP_IMPORT_VALIDATION_PKG.v_check_prepay_info<-'
6322                                 ||P_calling_sequence;
6323 
6324   l_count_lines_matched  := 0;
6325 
6326   --Contract Payments: Added the below IF condition so that we reject the invoices
6327   --which are of type 'PREPAYMENT' and have provided the prepayment application
6328   --information too.
6329 
6330   IF (((p_invoice_rec.prepay_num          IS NOT NULL) OR
6331        (p_invoice_rec.prepay_line_num     IS NOT NULL) OR
6332        (p_invoice_rec.prepay_apply_amount IS NOT NULL) OR
6333        (p_invoice_rec.prepay_gl_date      IS NOT NULL) OR
6334        (p_invoice_rec.invoice_includes_prepay_flag IS NOT NULL)) AND
6335       p_invoice_rec.invoice_type_lookup_code = 'PREPAYMENT')THEN
6336 
6337        debug_info := '(Check Prepayment Info 1) Check if it is a Prepayment Invoice';
6338 
6339        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
6340          AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
6341 		                                    debug_info);
6342        END IF;
6343 
6344        IF (AP_IMPORT_UTILITIES_PKG.insert_rejections (
6345                  AP_IMPORT_INVOICES_PKG.g_invoices_table,
6346 		 p_invoice_rec.invoice_id,
6347 		 'INCONSISTENT PREPAY APPL INFO',
6348 		 p_default_last_updated_by,
6349 		 p_default_last_update_login,
6350 		 current_calling_sequence) <> TRUE) THEN
6351 	   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
6352 	      AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
6353 			           'insert_rejections<-'||current_calling_sequence);
6354 	   END IF;
6355 	   RAISE check_prepay_failure;
6356        END IF;
6357 
6358        l_current_invoice_status := 'N';
6359 
6360   END IF;
6361 
6362   --Contract Payments: If the prepayment invoice is matched to financing pay items,
6363   --reject the invoice, as manual recoupment is not allowed.
6364   IF ((p_invoice_rec.prepay_num IS NOT NULL) AND
6365       (p_invoice_rec.invoice_type_lookup_code <> 'PREPAYMENT')) THEN
6366 
6367      debug_info := '(Check Prepayment Info 2) Check if it is a Prepayment Invoice matched'||
6368      				' to a complex works po';
6369 
6370     -- debug_info := 'p_invoice_rec.prepay_num , p_invoice_rec.org_id '|| p_invoice_rec.prepay_num||','||p_invoice_rec.org_id;
6371 
6372      IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
6373          AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
6374                                                debug_info);
6375      END IF;
6376 
6377 
6378      BEGIN
6379 
6380         SELECT count(*)
6381         INTO l_count_lines_matched
6382         FROM ap_invoice_lines ail,
6383           ap_invoices ai,
6384           po_line_locations pll
6385         WHERE ai.invoice_num = p_invoice_rec.prepay_num
6386         AND ai.org_id = p_invoice_rec.org_id
6387         AND ail.invoice_id = ai.invoice_id
6388         AND ail.po_line_location_id = pll.line_location_id
6389         AND pll.shipment_type = 'PREPAYMENT';
6390 
6391      EXCEPTION WHEN OTHERS THEN
6392        debug_info := '(Check Prepayment Info 2.1) In others exception and the error is '||sqlerrm;
6393        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
6394              AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
6395 	                                            debug_info);
6396        END IF;
6397 
6398 
6399      END ;
6400 
6401 
6402      IF (l_count_lines_matched > 0) THEN
6403 
6404 	debug_info := 'Reject as Cannot manually recoup ';
6405         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
6406          AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
6407 		                                    debug_info);
6408         END IF;
6409 
6410         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections (
6411                  AP_IMPORT_INVOICES_PKG.g_invoices_table,
6412 		 p_invoice_rec.invoice_id,
6413 		 'CANNOT MANUALLY RECOUP',
6414 		 p_default_last_updated_by,
6415 		 p_default_last_update_login,
6416 		 current_calling_sequence) <> TRUE) THEN
6417 	    IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
6418 	       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
6419 			           'insert_rejections<-'||current_calling_sequence);
6420 	    END IF;
6421  	    RAISE check_prepay_failure;
6422         END IF;
6423 
6424         l_current_invoice_status := 'N';
6425 
6426      END IF;
6427 
6428   END IF;
6429 
6430 
6431   IF (p_invoice_rec.invoice_type_lookup_code <> 'PREPAYMENT') THEN
6432 
6433      IF NOT ((p_invoice_rec.prepay_num          IS NULL) AND
6434              (p_invoice_rec.prepay_line_num     IS NULL) AND
6435              (p_invoice_rec.prepay_apply_amount IS NULL)
6436 	    ) THEN
6437        --------------------------------------------------------------------------
6438        -- Step 1
6439        -- Check Prepayment Info.
6440        --------------------------------------------------------------------------
6441 
6442        debug_info := '(Check Prepayment Info 1) Call Check Prepayment Function.';
6443 
6444        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
6445          AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
6446                                     debug_info);
6447        END IF;
6448        --
6449        l_reject_code := AP_PREPAY_PKG.check_prepay_info_import(
6450       			    	p_invoice_rec.prepay_num,
6451           			p_invoice_rec.prepay_line_num,
6452           			p_invoice_rec.prepay_apply_amount,
6453           			p_invoice_rec.invoice_amount,
6454           			p_invoice_rec.prepay_gl_date,
6455           			p_prepay_period_name,
6456           			p_invoice_rec.vendor_id,
6457           			p_invoice_rec.invoice_includes_prepay_flag,
6458           			p_invoice_rec.invoice_id,
6459           			p_invoice_rec.source,
6460           			p_invoice_rec.apply_advances_flag,
6461           			p_invoice_rec.invoice_date,
6462           			p_base_currency_code,
6463           			p_invoice_rec.invoice_currency_code,
6464           			p_invoice_rec.payment_currency_code,
6465           			current_calling_sequence,
6466           			p_request_id,
6467           			p_prepay_case_name,
6468           			p_prepay_invoice_id,
6469 				p_invoice_rec.invoice_type_lookup_code);  -- Bug 7004765;
6470     	--
6471     	-- show input/output values (only if debug_switch = 'Y')
6472 
6473     	IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
6474       		AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
6475           	'------------------> prepay_num = '|| p_invoice_rec.prepay_num
6476         	||' prepay_line_num  = '||to_char(p_invoice_rec.prepay_line_num)
6477         	||' prepay_apply_amount = '||to_char(p_invoice_rec.prepay_apply_amount)
6478         	||' invoice_amount  = '||to_char(p_invoice_rec.invoice_amount)
6479         	||' prepay_gl_date  = '||to_char(p_invoice_rec.prepay_gl_date)
6480         	||' prepay_period_name  = '|| NULL
6481         	||' vendor_id    = '||to_char(p_invoice_rec.vendor_id)
6482         	||' base_currency_code = '||p_base_currency_code
6483         	||' invoice_currency_code  = '||p_invoice_rec.invoice_currency_code
6484         	||' payment_currency_code  = '||p_invoice_rec.payment_currency_code);
6485     	END IF;
6486 
6487     	IF (l_reject_code IS NOT NULL) THEN
6488 
6489       	   IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
6490                   AP_IMPORT_INVOICES_PKG.g_invoices_table,
6491           	  p_invoice_rec.invoice_id,
6492                   l_reject_code,
6493                   p_default_last_updated_by,
6494                   p_default_last_update_login,
6495                   current_calling_sequence) <> TRUE) THEN
6496                IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
6497           	  AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
6498           	  'insert_rejections<-' ||current_calling_sequence);
6499                END IF;
6500                RAISE check_prepay_failure;
6501            END IF;
6502 
6503            l_current_invoice_status := 'N';
6504 
6505         END IF;  -- reject code is not null
6506 
6507      END IF; -- If not prepayment information is available
6508 
6509   END IF; --p_invoice_rec.invoice_type_lookup_code <> 'PREPAYMENT'
6510 
6511   p_current_invoice_status := l_current_invoice_status;
6512 
6513   RETURN(TRUE);
6514 
6515 EXCEPTION
6516   WHEN OTHERS THEN
6517     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
6518       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
6519                                     debug_info);
6520     END IF;
6521 
6522     IF (SQLCODE < 0) then
6523       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
6524         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
6525                                       SQLERRM);
6526       END IF;
6527     END IF;
6528     RETURN(FALSE);
6529 
6530 END v_check_prepay_info;
6531 
6532 
6533 -----------------------------------------------------------------------------
6534 -- This function is used to validate information provided to
6535 -- calculate rate based on base amount.
6536 --
6537 -----------------------------------------------------------------------------
6538 FUNCTION v_check_no_xrate_base_amount (
6539          p_invoice_rec               IN
6540              AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
6541          p_base_currency_code        IN            VARCHAR2,
6542          p_multi_currency_flag       IN            VARCHAR2,
6543          p_calc_user_xrate           IN            VARCHAR2,
6544          p_default_last_updated_by   IN            NUMBER,
6545          p_default_last_update_login IN            NUMBER,
6546      p_invoice_base_amount          OUT NOCOPY NUMBER,
6547          p_current_invoice_status    IN OUT NOCOPY VARCHAR2,
6548          p_calling_sequence          IN            VARCHAR2) RETURN BOOLEAN
6549 IS
6550 
6551 no_xrate_base_amount_failure    EXCEPTION;
6552 l_current_invoice_status    VARCHAR2(1) := 'Y';
6553 current_calling_sequence      VARCHAR2(2000);
6554 debug_info           VARCHAR2(500);
6555 
6556 --bug 9326733 starts
6557 l_make_rate_mand_flag	AP_SYSTEM_PARAMETERS_ALL.MAKE_RATE_MANDATORY_FLAG%TYPE;
6558 
6559 CURSOR c_get_rate_mand_flag(l_org_id IN NUMBER) IS
6560    select nvl(make_rate_mandatory_flag, 'N')
6561    from ap_system_parameters_all
6562    where org_id = l_org_id
6563    and multi_currency_flag = 'Y';
6564 --bug 9326733 ends
6565 
6566 BEGIN
6567 
6568   -- Update the calling sequence
6569   current_calling_sequence :=
6570     'AP_IMPORT_VALIDATION_PKG.v_check_no_xrate_base_amount<-'
6571      ||P_calling_sequence;
6572 
6573   -------------------------------------------------------------------------
6574   -- Step 1 - Check for invalid no_xrate_base_amount
6575   -------------------------------------------------------------------------
6576   debug_info := '(Check No Xrate Base Amount 1) Is Xrate_Base_Amount invalid?';
6577   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
6578      AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
6579                    debug_info);
6580   END IF;
6581 
6582   IF (nvl(p_multi_currency_flag,'N') = 'Y') AND
6583          (p_base_currency_code <> p_invoice_rec.invoice_currency_code) THEN
6584 
6585     IF ((p_calc_user_xrate <> 'Y') AND
6586         (p_invoice_rec.no_xrate_base_amount IS NOT NULL)) THEN
6587       debug_info := 'Trying to reject due to no_x_Curr';
6588       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
6589         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
6590                       debug_info);
6591       END IF;
6592 
6593       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
6594             (AP_IMPORT_INVOICES_PKG.g_invoices_table,
6595               p_invoice_rec.invoice_id,
6596               'BASE AMOUNT NOT ALLOWED',
6597               p_default_last_updated_by,
6598               p_default_last_update_login,
6599               current_calling_sequence) <> TRUE) THEN
6600         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
6601           AP_IMPORT_UTILITIES_PKG.Print(
6602           AP_IMPORT_INVOICES_PKG.g_debug_switch,
6603           'insert_rejections<-'||current_calling_sequence);
6604         END IF;
6605         RAISE no_xrate_base_amount_failure;
6606       END IF;
6607 
6608       l_current_invoice_status := 'N';
6609 
6610     ELSIF (p_calc_user_xrate = 'Y') AND
6611           ((p_invoice_rec.exchange_rate_type <> 'User') AND
6612            (p_invoice_rec.no_xrate_base_amount IS NOT NULL)) THEN
6613 
6614       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
6615             (AP_IMPORT_INVOICES_PKG.g_invoices_table,
6616               p_invoice_rec.invoice_id,
6617               'INVALID EXCH RATE TYPE',
6618               p_default_last_updated_by,
6619               p_default_last_update_login,
6620               current_calling_sequence) <> TRUE) THEN
6621         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
6622           AP_IMPORT_UTILITIES_PKG.Print(
6623           AP_IMPORT_INVOICES_PKG.g_debug_switch,
6624           'insert_rejections<-'||current_calling_sequence);
6625         END IF;
6626         RAISE no_xrate_base_amount_failure;
6627       END IF;
6628 
6629       l_current_invoice_status := 'N';
6630 
6631     ELSIF (p_calc_user_xrate = 'Y') AND
6632           ((p_invoice_rec.exchange_rate_type = 'User') AND
6633            (p_invoice_rec.no_xrate_base_amount IS NOT NULL) AND
6634            (p_invoice_rec.invoice_amount IS NOT NULL) AND
6635            (p_invoice_rec.exchange_rate is NOT NULL)) THEN
6636 
6637       IF (ap_utilities_pkg.ap_round_currency(
6638            (p_invoice_rec.invoice_amount*p_invoice_rec.exchange_rate),
6639            p_base_currency_code) <> p_invoice_rec.no_xrate_base_amount)
6640         THEN
6641 
6642         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
6643             (AP_IMPORT_INVOICES_PKG.g_invoices_table,
6644               p_invoice_rec.invoice_id,
6645              'INCONSISTENT XRATE INFO',
6646               p_default_last_updated_by,
6647               p_default_last_update_login,
6648               current_calling_sequence) <> TRUE) THEN
6649           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
6650             AP_IMPORT_UTILITIES_PKG.Print(
6651             AP_IMPORT_INVOICES_PKG.g_debug_switch,
6652             'insert_rejections<-'||current_calling_sequence);
6653           END IF;
6654           RAISE no_xrate_base_amount_failure;
6655         END IF;
6656 
6657         l_current_invoice_status := 'N';
6658       END IF;
6659 
6660     ELSIF (p_calc_user_xrate = 'Y') AND
6661           ((p_invoice_rec.exchange_rate_type = 'User') AND
6662            (p_invoice_rec.no_xrate_base_amount IS NULL) AND
6663            (p_invoice_rec.exchange_rate is NULL)) THEN
6664 
6665       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
6666                        (AP_IMPORT_INVOICES_PKG.g_invoices_table,
6667                         p_invoice_rec.invoice_id,
6668                         'NO EXCHANGE RATE',
6669                         p_default_last_updated_by,
6670                         p_default_last_update_login,
6671                         current_calling_sequence) <> TRUE) THEN
6672         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
6673           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
6674           'insert_rejections<-'||current_calling_sequence);
6675         END IF;
6676         RAISE no_xrate_base_amount_failure;
6677       END IF;
6678 
6679       l_current_invoice_status := 'N';
6680 
6681     END IF; -- Calculate user xrate is not Y and xrate base amount provided
6682   END IF; -- Multi currency flag is Y and this is a foreign currency invoice
6683 
6684   -------------------------------------------------------------------------
6685   -- Step 2 - Obtain base amount if no_xrate_base_amount null,
6686   --          invoice valid and it is a foreign currency invoice.
6687   -------------------------------------------------------------------------
6688   IF (l_current_invoice_status <> 'N' AND
6689       p_invoice_rec.no_xrate_base_amount IS NULL AND
6690       p_base_currency_code <> p_invoice_rec.invoice_currency_code) THEN
6691 
6692     debug_info := '(Check No Xrate Base Amount 2) Get invoice base amount';
6693     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
6694       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
6695                    debug_info);
6696     END IF;
6697 
6698     -- bug 9326733 starts
6699     OPEN c_get_rate_mand_flag(p_invoice_rec.org_id);
6700     FETCH c_get_rate_mand_flag into l_make_rate_mand_flag;
6701     CLOSE c_get_rate_mand_flag;
6702     -- bug 9326733 ends
6703 
6704     IF (p_invoice_rec.exchange_rate_type <> 'User' AND
6705     AP_UTILITIES_PKG.calculate_user_xrate (
6706                   p_invoice_rec.invoice_currency_code,
6707                   p_base_currency_code,
6708                   p_invoice_rec.exchange_date,
6709                   p_invoice_rec.exchange_rate_type) = 'N') THEN
6710 	--Bug8739726
6711 	BEGIN
6712            p_invoice_base_amount := gl_currency_api.convert_amount(
6713                         p_invoice_rec.invoice_currency_code,
6714                                         p_base_currency_code,
6715                                         p_invoice_rec.exchange_date,
6716                           p_invoice_rec.exchange_rate_type,
6717                     p_invoice_rec.invoice_amount);
6718 	EXCEPTION
6719 		  WHEN OTHERS THEN
6720 		--bug 9326733. Added if clause to avoid rejection records, in case of
6721 		-- rate is not mandatory.
6722 		IF (l_make_rate_mand_flag = 'Y') THEN
6723 			IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
6724 							   (AP_IMPORT_INVOICES_PKG.g_invoices_table,
6725 								p_invoice_rec.invoice_id,
6726 								'NO EXCHANGE RATE',
6727 								p_default_last_updated_by,
6728 								p_default_last_update_login,
6729 								current_calling_sequence) <> TRUE) THEN
6730 				IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
6731 				  AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
6732 				  'insert_rejections<-'||current_calling_sequence);
6733 				END IF;
6734 				RAISE no_xrate_base_amount_failure;
6735 			  END IF;
6736 
6737 			  l_current_invoice_status := 'N';
6738 		ELSE
6739 			l_current_invoice_status := 'Y';
6740 		END IF;
6741 
6742 	END;
6743 	--End of Bug8739726
6744     ELSE
6745       p_invoice_base_amount := ap_utilities_pkg.ap_round_currency(
6746                        (p_invoice_rec.invoice_amount *
6747                         p_invoice_rec.exchange_rate),
6748                         p_base_currency_code);
6749     END IF;
6750   END IF;
6751 
6752   p_current_invoice_status := l_current_invoice_status;
6753   RETURN (TRUE);
6754 
6755 EXCEPTION
6756   WHEN OTHERS THEN
6757     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
6758       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
6759                                     debug_info);
6760     END IF;
6761 
6762     IF (SQLCODE < 0) then
6763       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
6764         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
6765                                       SQLERRM);
6766       END IF;
6767     END IF;
6768 
6769     RETURN(FALSE);
6770 
6771 END v_check_no_xrate_base_amount;
6772 
6773 
6774 FUNCTION v_check_lines_validation (
6775 	 -- bug 8495005 : Change IN to IN OUT NOCOPY for p_invoice_rec parameter
6776          p_invoice_rec        IN OUT NOCOPY AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
6777          p_invoice_lines_tab  IN OUT NOCOPY AP_IMPORT_INVOICES_PKG.t_lines_table,
6778          p_gl_date_from_get_info        IN            DATE,
6779          p_gl_date_from_receipt_flag    IN            VARCHAR2,
6780          p_positive_price_tolerance     IN            NUMBER,
6781          p_pa_installed                 IN            VARCHAR2,
6782          p_qty_ord_tolerance            IN            NUMBER,
6783 	 p_amt_ord_tolerance            IN            NUMBER,
6784          p_max_qty_ord_tolerance        IN            NUMBER,
6785 	 p_max_amt_ord_tolerance	IN	      NUMBER,
6786          p_min_acct_unit_inv_curr       IN            NUMBER,
6787          p_precision_inv_curr           IN            NUMBER,
6788          p_base_currency_code           IN            VARCHAR2,
6789          p_base_min_acct_unit           IN            NUMBER,
6790          p_base_precision               IN            NUMBER,
6791          p_set_of_books_id              IN            NUMBER,
6792          p_asset_book_type              IN            VARCHAR2,  -- Bug 5448579
6793          p_chart_of_accounts_id         IN            NUMBER,
6794          p_freight_code_combination_id  IN            NUMBER,
6795          p_purch_encumbrance_flag       IN            VARCHAR2,
6796 	 p_retainage_ccid		IN	      NUMBER,
6797          p_default_last_updated_by      IN            NUMBER,
6798          p_default_last_update_login    IN            NUMBER,
6799          p_current_invoice_status       IN OUT NOCOPY VARCHAR2,
6800          p_calling_sequence             IN            VARCHAR2) RETURN BOOLEAN
6801 
6802 
6803 
6804 IS
6805 
6806 /* For Bug - 2823140. Added trim to trailing spaces wherever necessary */
6807 /* For Bug - 6349739 Added NVL to tax classification code
6808  * Added handling for retek generated concatenated accts */
6809 
6810 CURSOR    invoice_lines IS
6811 SELECT    rowid, -- BUG 1714845
6812           invoice_line_id,
6813           line_type_lookup_code,
6814           line_number,
6815           line_group_number,
6816           amount,
6817           NULL, -- base amount
6818           trunc(accounting_date),  /*16240104*/
6819           NULL, --period name
6820           deferred_acctg_flag,
6821           trunc(def_acctg_start_date), /*16240104*/
6822           trunc(def_acctg_end_date),   /*16240104*/
6823           def_acctg_number_of_periods,
6824           def_acctg_period_type,
6825           trim(description),
6826           prorate_across_flag,
6827           NULL, -- match_type
6828           po_header_id,
6829           po_number,
6830           po_line_id,
6831           po_line_number,
6832           po_release_id,
6833           release_num,
6834           po_line_location_id,
6835           po_shipment_num,
6836           po_distribution_id,
6837           po_distribution_num,
6838           unit_of_meas_lookup_code,
6839           inventory_item_id,
6840           item_description,
6841           quantity_invoiced,
6842           ship_to_location_code,
6843           unit_price,
6844           final_match_flag,
6845           distribution_set_id,
6846           distribution_set_name,
6847           NULL, -- partial segments
6848           -- bug 6349739
6849           DECODE(AP_IMPORT_INVOICES_PKG.g_source,
6850           'RETEK',
6851           TRANSLATE(RTRIM(dist_code_concatenated,'-'),
6852                     '-',
6853                     AP_IMPORT_INVOICES_PKG.g_segment_delimiter),
6854           dist_code_concatenated), -- 6349739
6855           dist_code_combination_id,
6856           awt_group_id,
6857           awt_group_name,
6858           pay_awt_group_id,--bug6639866
6859           pay_awt_group_name,--bug6639866
6860           balancing_segment,
6861           cost_center_segment,
6862           account_segment,
6863           trim(attribute_category),
6864           trim(attribute1),
6865           trim(attribute2),
6866           trim(attribute3),
6867           trim(attribute4),
6868           trim(attribute5),
6869           trim(attribute6),
6870           trim(attribute7),
6871           trim(attribute8),
6872           trim(attribute9),
6873           trim(attribute10),
6874           trim(attribute11),
6875           trim(attribute12),
6876           trim(attribute13),
6877           trim(attribute14),
6878           trim(attribute15),
6879           trim(global_attribute_category),
6880           trim(global_attribute1),
6881           trim(global_attribute2),
6882           trim(global_attribute3),
6883           trim(global_attribute4),
6884           trim(global_attribute5),
6885           trim(global_attribute6),
6886           trim(global_attribute7),
6887           trim(global_attribute8),
6888           trim(global_attribute9),
6889           trim(global_attribute10),
6890           trim(global_attribute11),
6891           trim(global_attribute12),
6892           trim(global_attribute13),
6893           trim(global_attribute14),
6894           trim(global_attribute15),
6895           trim(global_attribute16),
6896           trim(global_attribute17),
6897           trim(global_attribute18),
6898           trim(global_attribute19),
6899           trim(global_attribute20),
6900           project_id,
6901           task_id,
6902           award_id,
6903           expenditure_type,
6904           expenditure_item_date,
6905           expenditure_organization_id,
6906           pa_addition_flag,
6907           pa_quantity,
6908           stat_amount,
6909           type_1099,
6910           income_tax_region,
6911           assets_tracking_flag,
6912           asset_book_type_code,
6913           asset_category_id,
6914           serial_number,
6915           manufacturer,
6916           model_number,
6917           warranty_number,
6918           price_correction_flag,
6919           price_correct_inv_num,
6920           NULL, -- corrected_inv_id.
6921                 -- This will populated based on the price_correct_inv_num
6922           price_correct_inv_line_num,
6923           receipt_number,
6924           receipt_line_number,
6925           rcv_transaction_id,
6926 	  NULL,               -- bug 7344899
6927           match_option,
6928           packing_slip,
6929           vendor_item_num,
6930           taxable_flag,
6931           pa_cc_ar_invoice_id,
6932           pa_cc_ar_invoice_line_num,
6933           pa_cc_processed_code,
6934           reference_1,
6935           reference_2,
6936           credit_card_trx_id,
6937           requester_id,
6938           org_id,
6939           NULL, -- program_application_id
6940           NULL, -- program_id
6941           NULL, -- request_id
6942           NULL,  -- program_update_date
6943           control_amount,
6944           assessable_value,
6945           default_dist_ccid,
6946           primary_intended_use,
6947           ship_to_location_id,
6948           product_type,
6949           product_category,
6950           product_fisc_classification,
6951           user_defined_fisc_class,
6952           trx_business_category,
6953           tax_regime_code,
6954           tax,
6955           tax_jurisdiction_code,
6956           tax_status_code,
6957           tax_rate_id,
6958           tax_rate_code,
6959           tax_rate,
6960           incl_in_taxable_line_flag,
6961 	  application_id,
6962 	  product_table,
6963 	  reference_key1,
6964 	  reference_key2,
6965 	  reference_key3,
6966 	  reference_key4,
6967 	  reference_key5,
6968 	  purchasing_category_id,
6969 	  purchasing_category,
6970 	  cost_factor_id,
6971 	  cost_factor_name,
6972 	  source_application_id,
6973 	  source_entity_code,
6974 	  source_event_class_code,
6975 	  source_trx_id,
6976 	  source_line_id,
6977 	  source_trx_level_type,
6978 	  nvl(tax_classification_code, tax_code), --bug 6349739
6979 	  NULL, -- retained_amount
6980 	  amount_includes_tax_flag,
6981 	  --Bug6167068 starts Added the following columns to get related data for Expense reports
6982 	  cc_reversal_flag,
6983 	  company_prepaid_invoice_id,
6984 	  expense_group,
6985 	  justification,
6986 	  merchant_document_number,
6987 	  merchant_name,
6988 	  merchant_reference,
6989 	  merchant_taxpayer_id,
6990 	  merchant_tax_reg_number,
6991 	  receipt_conversion_rate,
6992 	  receipt_currency_amount,
6993 	  receipt_currency_code,
6994 	  country_of_supply
6995 	  --Bug6167068 ends
6996 	  --bug 8658097 starts
6997 	  ,expense_start_date
6998 	  ,expense_end_date
6999 	  --bug 8658097 ends
7000 	  /* Added for bug 10226070 */
7001 	  ,Requester_last_name
7002       	  ,Requester_first_name
7003       	  ,NULL /* Bug#10175718 For cascade flag */
7004 	  /* Added for bug 13074325 */
7005           ,REQUESTER_EMPLOYEE_NUM
7006     ,invoice_id --bug 15862708 starts
7007 	,NULL
7008 	,NULL
7009 	--bug 15862708 ends
7010         /*Bug 14271140 Starts*/
7011          ,Last_updated_By
7012          ,Last_update_login
7013          ,Created_By
7014          ,sysdate --CREATION_DATE
7015          ,sysdate --LAST_UPDATE_DATE
7016        /*Bug 14271140 End*/
7017      FROM ap_invoice_lines_interface
7018     WHERE invoice_id = p_invoice_rec.invoice_id
7019  ORDER BY invoice_line_id;
7020 --   FOR UPDATE OF invoice_line_id; -- Bug 1714845
7021 
7022 /* Bug 6369356:
7023  * For Retek invoices having multiple tax lines with same tax code,
7024  * we need to summarize the tax amounts on tax classification code.*/
7025 
7026 CURSOR    invoice_lines_tax_summarized IS
7027 SELECT    rowid, -- BUG 1714845
7028           invoice_line_id,
7029           line_type_lookup_code,
7030           line_number,
7031           line_group_number,
7032           --amount,
7033           -- Bug 6369356 summarize tax lines
7034           DECODE(line_type_lookup_code , 'TAX',
7035                  (SELECT SUM(ail3.amount)
7036                   FROM   ap_invoice_lines_interface ail3
7037                   WHERE  ail3.tax_code = ail.tax_code
7038                   AND    ail3.line_type_lookup_code = 'TAX'
7039                   AND    ail3.invoice_id = ail.invoice_id
7040                   GROUP BY tax_code),
7041                   amount) amount,
7042           -- Bug 6369356
7043           NULL, -- base amount
7044           trunc(accounting_date),  /*16240104*/
7045           NULL, --period name
7046           deferred_acctg_flag,
7047           trunc(def_acctg_start_date),  /*16240104*/
7048           trunc(def_acctg_end_date),    /*16240104*/
7049           def_acctg_number_of_periods,
7050           def_acctg_period_type,
7051           trim(description),
7052           prorate_across_flag,
7053           NULL, -- match_type
7054           po_header_id,
7055           po_number,
7056           po_line_id,
7057           po_line_number,
7058           po_release_id,
7059           release_num,
7060           po_line_location_id,
7061           po_shipment_num,
7062           po_distribution_id,
7063           po_distribution_num,
7064           unit_of_meas_lookup_code,
7065           inventory_item_id,
7066           item_description,
7067           quantity_invoiced,
7068           ship_to_location_code,
7069           unit_price,
7070           final_match_flag,
7071           distribution_set_id,
7072           distribution_set_name,
7073           NULL, -- partial segments
7074           -- bug 6349739
7075           DECODE(AP_IMPORT_INVOICES_PKG.g_source,
7076           'RETEK',
7077           TRANSLATE(RTRIM(dist_code_concatenated,'-'),
7078                     '-',
7079                     AP_IMPORT_INVOICES_PKG.g_segment_delimiter),
7080           dist_code_concatenated), -- 6349739
7081           dist_code_combination_id,
7082           awt_group_id,
7083           awt_group_name,
7084           pay_awt_group_id,--bug6639866
7085           pay_awt_group_name,--bug6639866
7086           balancing_segment,
7087           cost_center_segment,
7088           account_segment,
7089           trim(attribute_category),
7090           trim(attribute1),
7091           trim(attribute2),
7092           trim(attribute3),
7093           trim(attribute4),
7094           trim(attribute5),
7095           trim(attribute6),
7096           trim(attribute7),
7097           trim(attribute8),
7098           trim(attribute9),
7099           trim(attribute10),
7100           trim(attribute11),
7101           trim(attribute12),
7102           trim(attribute13),
7103           trim(attribute14),
7104           trim(attribute15),
7105           trim(global_attribute_category),
7106           trim(global_attribute1),
7107           trim(global_attribute2),
7108           trim(global_attribute3),
7109           trim(global_attribute4),
7110           trim(global_attribute5),
7111           trim(global_attribute6),
7112           trim(global_attribute7),
7113           trim(global_attribute8),
7114           trim(global_attribute9),
7115           trim(global_attribute10),
7116           trim(global_attribute11),
7117           trim(global_attribute12),
7118           trim(global_attribute13),
7119           trim(global_attribute14),
7120           trim(global_attribute15),
7121           trim(global_attribute16),
7122           trim(global_attribute17),
7123           trim(global_attribute18),
7124           trim(global_attribute19),
7125           trim(global_attribute20),
7126           project_id,
7127           task_id,
7128           award_id,
7129           expenditure_type,
7130           expenditure_item_date,
7131           expenditure_organization_id,
7132           pa_addition_flag,
7133           pa_quantity,
7134           stat_amount,
7135           type_1099,
7136           income_tax_region,
7137           assets_tracking_flag,
7138           asset_book_type_code,
7139           asset_category_id,
7140           serial_number,
7141           manufacturer,
7142           model_number,
7143           warranty_number,
7144           price_correction_flag,
7145           price_correct_inv_num,
7146           NULL, -- corrected_inv_id.
7147                 -- This will populated based on the price_correct_inv_num
7148           price_correct_inv_line_num,
7149           receipt_number,
7150           receipt_line_number,
7151           rcv_transaction_id,
7152 	  NULL,               -- bug 7344899
7153           match_option,
7154           packing_slip,
7155           vendor_item_num,
7156           taxable_flag,
7157           pa_cc_ar_invoice_id,
7158           pa_cc_ar_invoice_line_num,
7159           pa_cc_processed_code,
7160           reference_1,
7161           reference_2,
7162           credit_card_trx_id,
7163           requester_id,
7164           org_id,
7165           NULL, -- program_application_id
7166           NULL, -- program_id
7167           NULL, -- request_id
7168           NULL,  -- program_update_date
7169           control_amount,
7170           assessable_value,
7171           default_dist_ccid,
7172           primary_intended_use,
7173           ship_to_location_id,
7174           product_type,
7175           product_category,
7176           product_fisc_classification,
7177           user_defined_fisc_class,
7178           trx_business_category,
7179           tax_regime_code,
7180           tax,
7181           tax_jurisdiction_code,
7182           tax_status_code,
7183           tax_rate_id,
7184           tax_rate_code,
7185           tax_rate,
7186           incl_in_taxable_line_flag,
7187           application_id,
7188           product_table,
7189           reference_key1,
7190           reference_key2,
7191           reference_key3,
7192           reference_key4,
7193           reference_key5,
7194           purchasing_category_id,
7195           purchasing_category,
7196           cost_factor_id,
7197           cost_factor_name,
7198           source_application_id,
7199           source_entity_code,
7200           source_event_class_code,
7201           source_trx_id,
7202           source_line_id,
7203           source_trx_level_type,
7204           NVL(tax_classification_code, tax_code), --bug 6349739
7205           NULL, -- retained_amount
7206           amount_includes_tax_flag,
7207           --Bug6167068 starts Added the following columns to get related data
7208           --           for Expense reports
7209           cc_reversal_flag,
7210           company_prepaid_invoice_id,
7211           expense_group,
7212           justification,
7213           merchant_document_number,
7214           merchant_name,
7215           merchant_reference,
7216           merchant_taxpayer_id,
7217           merchant_tax_reg_number,
7218           receipt_conversion_rate,
7219           receipt_currency_amount,
7220           receipt_currency_code,
7221           country_of_supply
7222           --Bug6167068 ends
7223 	  --bug 8658097 starts
7224 	  ,expense_start_date
7225 	  ,expense_end_date
7226 	  --bug 8658097 ends
7227 	  /* Added for bug 10226070 */
7228 	  ,Requester_last_name
7229       	  ,Requester_first_name
7230       	  ,NULL /* Bug#10175718 For cascade flag */
7231 	  /* Added for bug 13074325 */
7232 	  ,REQUESTER_EMPLOYEE_NUM
7233     ,invoice_id --bug 15862708 starts
7234 	,NULL
7235 	,NULL
7236 	--bug 15862708 ends
7237           /*Bug 14271140 Starts*/
7238          ,Last_updated_By
7239          ,Last_update_login
7240          ,Created_By
7241          ,sysdate --CREATION_DATE
7242          ,sysdate --LAST_UPDATE_DATE
7243         /*Bug 14271140 End*/
7244      FROM ap_invoice_lines_interface ail
7245     WHERE invoice_id = p_invoice_rec.invoice_id
7246     -- Bug 6369356
7247     AND   ((line_type_lookup_code <> 'TAX')
7248           OR ( line_type_lookup_code = 'TAX' AND
7249           rowid =(SELECT max(ail2.rowid)
7250                   FROM   ap_invoice_lines_interface ail2
7251                   WHERE  ail2.tax_code = ail.tax_code
7252                   AND    ail2.line_type_lookup_code = 'TAX'
7253                   AND    ail2.invoice_id = ail.invoice_id
7254                   GROUP BY tax_code)
7255                   )
7256                   )
7257     -- Bug 6369356
7258  ORDER BY invoice_line_id;
7259 --   FOR UPDATE OF invoice_line_id; -- Bug 1714845
7260 
7261 
7262  -- bug# 13398814 starts
7263 Cursor c_ship_to_location (p_ship_to_loc_code HR_LOCATIONS.LOCATION_CODE%TYPE) Is
7264  Select ship_to_location_id
7265   From   hr_locations
7266  Where  location_code = p_ship_to_loc_code
7267   and	nvl(ship_to_site_flag, 'N') = 'Y';
7268 
7269 
7270  l_new_ship_to_location_id  ap_supplier_sites_all.ship_to_location_id%type;
7271  -- bug# 13398814 ends
7272 
7273 check_lines_failure          EXCEPTION;
7274 l_current_invoice_status      VARCHAR2(1) := 'Y';
7275 l_temp_line_status          VARCHAR2(1) := 'Y';
7276 l_max_line_number             NUMBER;
7277 l_employee_id                  NUMBER;
7278 l_error_message              VARCHAR2(200);
7279 l_pa_built_account            NUMBER /* := 0*/ ; /* Commented for bug 11782001 */
7280 current_calling_sequence      VARCHAR2(2000);
7281 debug_info                 VARCHAR2(500);
7282 /* bug 5039042 */
7283 l_product_registered       VARCHAR2(1) := 'N';
7284 l_dummy                    VARCHAR2(100);
7285 l_refresh VARCHAR2(1);     --Bug#13464635
7286 
7287 
7288 BEGIN
7289   -- Update the calling sequence
7290   --
7291   current_calling_sequence :=
7292     'AP_IMPORT_VALIDATION_PKG.v_check_lines_validation<-'||P_calling_sequence;
7293 
7294   --------------------------------------------------------
7295   -- Step 1
7296   -- Get Employee ID for PA Related Invoice Line
7297   ---------------------------------------------------------
7298 
7299   --Payment Requests: Added IF condition for Payment Requests
7300   --IF (p_invoice_rec.invoice_type_lookup_code <> 'PAYMENT REQUEST') THEN    .. B# 8528132
7301   IF (nvl(p_invoice_rec.invoice_type_lookup_code, 'STANDARD') <> 'PAYMENT REQUEST') THEN    -- B# 8528132
7302 
7303      debug_info := '(Check_lines 1) Call Get_employee_id';
7304      IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7305        AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7306                                      debug_info);
7307      END IF;
7308 
7309      IF (AP_IMPORT_UTILITIES_PKG.get_employee_id(
7310            p_invoice_rec.invoice_id,
7311            p_invoice_rec.vendor_id,
7312            l_employee_id,                -- OUT
7313            p_default_last_updated_by,
7314            p_default_last_update_login,
7315            l_temp_line_status,           -- OUT
7316            p_calling_sequence    => current_calling_sequence) <> TRUE ) THEN
7317        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7318          AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7319                          'get_employee_id<-' ||current_calling_sequence);
7320        END IF;
7321        RAISE check_lines_failure;
7322      END IF;
7323   END IF;
7324 
7325   --
7326   -- show output values (only if debug_switch = 'Y')
7327   --
7328   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7329     AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7330     '------------------> l_temp_line_status = '||l_temp_line_status
7331     ||' l_employee_id = '||to_char(l_employee_id));
7332   END IF;
7333 
7334   -- Since vendor is already validated
7335   -- Rejection should happen only if the Project Related
7336   -- invoices do not have a valid employee_id in PO_vendors
7337 
7338   IF (l_temp_line_status = 'N') THEN
7339      l_current_invoice_status := l_temp_line_status;
7340   END IF;
7341 
7342   --------------------------------------------------------------------------
7343   -- Step 2
7344   -- Get max line number for the invoice to be used in case a line does not
7345   -- provide a line number
7346   --------------------------------------------------------------------------
7347   debug_info := '(Check Lines 2) Get Max Line Number';
7348   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
7349     AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7350                                   debug_info);
7351   END IF;
7352   --
7353   IF AP_IMPORT_INVOICES_PKG.g_source = 'RETEK' THEN
7354       BEGIN
7355           SELECT NVL(MAX(line_number),0)
7356           INTO l_max_line_number
7357           FROM ap_invoice_lines_interface ail
7358          WHERE invoice_id = p_invoice_rec.invoice_id
7359          AND   ((line_type_lookup_code <> 'TAX')
7360           OR ( line_type_lookup_code = 'TAX' AND
7361           rowid =(SELECT MAX(ail2.rowid)
7362                   FROM   ap_invoice_lines_interface ail2
7363                   WHERE  ail2.tax_code = ail.tax_code
7364                   AND    ail2.line_type_lookup_code = 'TAX'
7365                   AND    ail2.invoice_id = ail.invoice_id
7366                   GROUP BY tax_code)
7367                   )
7368                   );
7369       EXCEPTION
7370         WHEN OTHERS THEN
7371           RAISE check_lines_failure;
7372       END;
7373   -- Bug 6369356
7374   --
7375   ELSIF AP_IMPORT_INVOICES_PKG.g_source <> 'PPA' THEN   --Retropricing
7376       BEGIN
7377 	--bugfix:4745899 , added the NVL condition
7378         SELECT NVL(MAX(line_number),0)
7379           INTO l_max_line_number
7380           FROM ap_invoice_lines_interface
7381          WHERE invoice_id = p_invoice_rec.invoice_id;
7382 
7383       EXCEPTION
7384         WHEN OTHERS THEN
7385           RAISE check_lines_failure;
7386       END;
7387   ELSE
7388     --
7389     l_max_line_number :=   p_invoice_lines_tab.COUNT;
7390     --
7391   END IF;
7392   --------------------------------------------------------------------------
7393   -- Step 3
7394   -- Open invoice_lines cursor.
7395   -- Retropricing: For PPA's the p_invoice_lines_tab is populated from
7396   -- AP_PPA_LINES_GT
7397   --------------------------------------------------------------------------
7398   debug_info := '(Check Lines 3) Open Cursor: invoice_lines';
7399   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7400     AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7401                                   debug_info);
7402   END IF;
7403 
7404   -- Bug 6369356
7405   IF AP_IMPORT_INVOICES_PKG.g_source = 'RETEK' THEN
7406       OPEN invoice_lines_tax_summarized;
7407       FETCH invoice_lines_tax_summarized BULK COLLECT INTO p_invoice_lines_tab;
7408       CLOSE invoice_lines_tax_summarized;
7409   ELSIF AP_IMPORT_INVOICES_PKG.g_source <> 'PPA' THEN   --Retropricing
7410       OPEN invoice_lines;
7411       FETCH invoice_lines BULK COLLECT INTO p_invoice_lines_tab;
7412       CLOSE invoice_lines;
7413   END IF;
7414 
7415    --Bug#13464635
7416    IF AP_INVOICES_UTILITY_PKG.FV_ENABLED THEN
7417        l_refresh := 'Y';
7418     ELSE
7419        l_refresh := 'N';
7420     END IF;
7421     --End bug#13464635
7422 
7423   FOR i IN 1..p_invoice_lines_tab.COUNT  --Retropricing
7424   LOOP
7425     --------------------------------------------------------------------------
7426     -- Step 4
7427     -- Loop through fetched invoice lines
7428     --------------------------------------------------------------------------
7429     debug_info := '(Check Lines 4) Looping through fetched invoice lines';
7430     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7431       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7432                                     debug_info);
7433     END IF;
7434 
7435     /* bug 12668114
7436        This value should be reset for each new line that is processed.
7437        Otherwise if a project line is processed first and a non-project
7438        line next, the l_pa_built_account from the prior line will be
7439        used */
7440     l_pa_built_account := NULL;
7441 
7442     -- Retropricing: Base Amount is populated for proposed PPA Lines
7443     IF AP_IMPORT_INVOICES_PKG.g_source <> 'PPA' THEN
7444         p_invoice_lines_tab(i).base_amount :=
7445              ap_utilities_pkg.ap_round_currency(
7446                 p_invoice_lines_tab(i).amount*p_invoice_rec.exchange_rate,
7447                 p_base_currency_code );
7448     END IF;
7449 
7450     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7451       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch ,
7452       '------------------>  invoice_line_id = '
7453         ||to_char(p_invoice_lines_tab(i).invoice_line_id )
7454       ||' line_type_lookup_code = '
7455         || p_invoice_lines_tab(i).line_type_lookup_code
7456       || 'line_number = '    || to_char(p_invoice_lines_tab(i).line_number)
7457       || 'line_group_number = '
7458         || to_char(p_invoice_lines_tab(i).line_group_number)
7459       || 'amount = '            || to_char(p_invoice_lines_tab(i).amount)
7460       || 'base amount  '
7461         || to_char(p_invoice_lines_tab(i).base_amount)
7462       || 'accounting_date = '
7463         || to_char(p_invoice_lines_tab(i).accounting_date)
7464       || 'deferred_acctg_flag = '|| p_invoice_lines_tab(i).deferred_acctg_flag
7465       || 'def_acctg_start_date = '
7466         || to_char(p_invoice_lines_tab(i).def_acctg_start_date)
7467       || 'def_acctg_end_date = '
7468         || to_char(p_invoice_lines_tab(i).def_acctg_end_date)
7469       || 'def_acctg_number_of_period = '
7470         || to_char(p_invoice_lines_tab(i).def_acctg_number_of_periods)
7471       || 'def_acctg_period_type = '
7472         || p_invoice_lines_tab(i).def_acctg_period_type
7473       || 'description = '    || p_invoice_lines_tab(i).description
7474       || 'prorate_across_flag = '
7475         || p_invoice_lines_tab(i).prorate_across_flag
7476       || 'po_header_id = ' ||    to_char(p_invoice_lines_tab(i).po_header_id)
7477       || 'po_number = '    || to_char(p_invoice_lines_tab(i).po_number)
7478       || 'po_line_id = '    || to_char(p_invoice_lines_tab(i).po_line_id)
7479       || 'po_line_number = ' || to_char(p_invoice_lines_tab(i).po_line_number)
7480       || 'po_release_id = '    || to_char(p_invoice_lines_tab(i).po_release_id)
7481       || 'release_num = '    || to_char(p_invoice_lines_tab(i).release_num)
7482       || 'po_line_location_id = '
7483         || to_char(p_invoice_lines_tab(i).po_line_location_id)
7484       || 'po_shipment_num = '
7485         || to_char(p_invoice_lines_tab(i).po_shipment_num)
7486       || 'po_distribution_id = '
7487         || to_char(p_invoice_lines_tab(i).po_distribution_id)
7488       || 'po_distribution_num = '
7489         || to_char(p_invoice_lines_tab(i).po_distribution_num)
7490       || 'unit_of_meas_lookup_code = '
7491         || p_invoice_lines_tab(i).unit_of_meas_lookup_code
7492       || 'inventory_item_id = '
7493         || to_char(p_invoice_lines_tab(i).inventory_item_id)
7494       || 'item_description = '    || p_invoice_lines_tab(i).item_description
7495       || 'purchasing_category_id = '   || p_invoice_lines_tab(i).purchasing_category_id
7496       || 'purchasing_category = '  || p_invoice_lines_tab(i).purchasing_category
7497       || 'quantity_invoiced = '
7498         || to_char(p_invoice_lines_tab(i).quantity_invoiced)
7499       || 'ship_to_location_code = '
7500         || p_invoice_lines_tab(i).ship_to_location_code
7501       || 'unit_price = '
7502         || to_char(p_invoice_lines_tab(i).unit_price)
7503       || 'final_match_flag = '    || p_invoice_lines_tab(i).final_match_flag
7504       || 'distribution_set_id = '
7505         || to_char(p_invoice_lines_tab(i).distribution_set_id)
7506       || 'distribution_set_name = '
7507      || p_invoice_lines_tab(i).distribution_set_name
7508       || 'dist_code_concatenated = '
7509         || p_invoice_lines_tab(i).dist_code_concatenated
7510       || 'dist_code_combination_id = '
7511         || to_char(p_invoice_lines_tab(i).dist_code_combination_id)
7512       || 'awt_group_id = '
7513         || to_char(p_invoice_lines_tab(i).awt_group_id)
7514       || 'awt_group_name = '    || p_invoice_lines_tab(i).awt_group_name
7515       || 'balancing_segment = '    || p_invoice_lines_tab(i).balancing_segment
7516       || 'cost_center_segment = ' || p_invoice_lines_tab(i).cost_center_segment
7517       || 'account_segment = '      || p_invoice_lines_tab(i).account_segment
7518       || 'attribute_category = '  || p_invoice_lines_tab(i).attribute_category
7519       || 'attribute1 = '    || p_invoice_lines_tab(i).attribute1
7520       || 'attribute2 = '    || p_invoice_lines_tab(i).attribute2
7521       || 'attribute3 = '    || p_invoice_lines_tab(i).attribute3
7522       || 'attribute4 = '    || p_invoice_lines_tab(i).attribute4
7523       || 'attribute5 = '    || p_invoice_lines_tab(i).attribute5
7524       || 'attribute6 = '    || p_invoice_lines_tab(i).attribute6
7525       || 'attribute7 = '    || p_invoice_lines_tab(i).attribute7
7526       || 'attribute8 = '    || p_invoice_lines_tab(i).attribute8
7527       || 'attribute9 = '    || p_invoice_lines_tab(i).attribute9
7528       || 'attribute10 = '    || p_invoice_lines_tab(i).attribute10
7529       || 'attribute11 = '    || p_invoice_lines_tab(i).attribute11
7530       || 'attribute12 = '    || p_invoice_lines_tab(i).attribute12
7531       || 'attribute13 = '    || p_invoice_lines_tab(i).attribute13
7532       || 'attribute14 = '    || p_invoice_lines_tab(i).attribute14
7533       || 'attribute15 = '    || p_invoice_lines_tab(i).attribute15
7534       || 'global_attribute_category = '
7535         || p_invoice_lines_tab(i).global_attribute_category
7536       || 'global_attribute1 = '    || p_invoice_lines_tab(i).global_attribute1
7537       || 'global_attribute2 = '    || p_invoice_lines_tab(i).global_attribute2
7538       || 'global_attribute3 = '    || p_invoice_lines_tab(i).global_attribute3
7539       || 'global_attribute4 = '    || p_invoice_lines_tab(i).global_attribute4
7540       || 'global_attribute5 = '    || p_invoice_lines_tab(i).global_attribute5
7541       || 'global_attribute6 = '    || p_invoice_lines_tab(i).global_attribute6
7542       || 'global_attribute7 = '    || p_invoice_lines_tab(i).global_attribute7
7543       || 'global_attribute8 = '    || p_invoice_lines_tab(i).global_attribute8
7544       || 'global_attribute9 = '    || p_invoice_lines_tab(i).global_attribute9
7545       || 'global_attribute10 = '|| p_invoice_lines_tab(i).global_attribute10
7546       || 'global_attribute11 = '|| p_invoice_lines_tab(i).global_attribute11
7547       || 'global_attribute12 = '|| p_invoice_lines_tab(i).global_attribute12
7548       || 'global_attribute13 = '|| p_invoice_lines_tab(i).global_attribute13
7549       || 'global_attribute14 = '|| p_invoice_lines_tab(i).global_attribute14
7550       || 'global_attribute15 = '|| p_invoice_lines_tab(i).global_attribute15
7551       || 'global_attribute16 = '|| p_invoice_lines_tab(i).global_attribute16
7552       || 'global_attribute17 = '|| p_invoice_lines_tab(i).global_attribute17
7553       || 'global_attribute18 = '|| p_invoice_lines_tab(i).global_attribute18
7554       || 'global_attribute19 = '|| p_invoice_lines_tab(i).global_attribute19
7555       || 'global_attribute20 = '|| p_invoice_lines_tab(i).global_attribute20
7556       || 'project_id = '         || to_char(p_invoice_lines_tab(i).project_id)
7557       || 'task_id = '           || to_char(p_invoice_lines_tab(i).task_id)
7558       || 'award_id = '            || to_char(p_invoice_lines_tab(i).award_id)
7559       || 'expenditure_type = '    || p_invoice_lines_tab(i).expenditure_type
7560       || 'expenditure_item_date = '
7561         || to_char(p_invoice_lines_tab(i).expenditure_item_date)
7562       || 'expenditure_organization_id = '
7563         || p_invoice_lines_tab(i).expenditure_organization_id
7564       || 'pa_addition_flag = '    || p_invoice_lines_tab(i).pa_addition_flag
7565       || 'pa_quantity = '    || to_char(p_invoice_lines_tab(i).pa_quantity)
7566       || 'stat_amount = '    || to_char(p_invoice_lines_tab(i).stat_amount)
7567       || 'type_1099 = '    || p_invoice_lines_tab(i).type_1099
7568       || 'income_tax_region = '    || p_invoice_lines_tab(i).income_tax_region
7569       || 'asset_tracking_flag = '
7570         || p_invoice_lines_tab(i).assets_tracking_flag
7571       || 'asset_book_type_code = '
7572         || p_invoice_lines_tab(i).asset_book_type_code
7573       || 'asset_category_id = '
7574         || to_char(p_invoice_lines_tab(i).asset_category_id)
7575       || 'serial_number = '    || to_char(p_invoice_lines_tab(i).serial_number)
7576       || 'manufacturer = '    || p_invoice_lines_tab(i).manufacturer
7577       || 'model_number = '    || p_invoice_lines_tab(i).model_number
7578       || 'warranty_number = '    || p_invoice_lines_tab(i).warranty_number
7579       || 'price_correction_flag = '
7580         || p_invoice_lines_tab(i).price_correction_flag
7581       || 'price_correct_inv_num = '
7582         || p_invoice_lines_tab(i).price_correct_inv_num
7583       || 'price_correct_inv_id = '
7584         || p_invoice_lines_tab(i).corrected_inv_id
7585       || 'price_correct_inv_line_num = '
7586         || p_invoice_lines_tab(i).price_correct_inv_line_num
7587       || 'receipt_number = '    || p_invoice_lines_tab(i).receipt_number
7588       || 'receipt_line_number = '
7589         || p_invoice_lines_tab(i).receipt_line_number
7590       || 'rcv_transaction_id = '
7591         || to_char(p_invoice_lines_tab(i).rcv_transaction_id)
7592       || 'match_option = '    || p_invoice_lines_tab(i).match_option
7593       || 'packing_slip = '    || p_invoice_lines_tab(i).packing_slip
7594       || 'vendor_item_num = '    || p_invoice_lines_tab(i).vendor_item_num
7595       || 'pa_cc_ar_invoice_id = '
7596         || to_char(p_invoice_lines_tab(i).pa_cc_ar_invoice_id)
7597       || 'pa_cc_ar_invoice_line_num = '
7598         ||to_char(p_invoice_lines_tab(i).pa_cc_ar_invoice_line_num)
7599       ||'pa_cc_processed_code = ' || p_invoice_lines_tab(i).pa_cc_processed_code
7600       || 'reference_1 = '    || p_invoice_lines_tab(i).reference_1
7601       || 'reference_2 = '    || p_invoice_lines_tab(i).reference_2
7602       || 'credit_card_trx_id = '
7603         || to_char(p_invoice_lines_tab(i).credit_card_trx_id)
7604       || 'requester_id = '    || to_char(p_invoice_lines_tab(i).requester_id)
7605       || 'org_id = '    || to_char(p_invoice_lines_tab(i).org_id)
7606     );
7607     END IF;
7608 
7609     -------------------------------------------------------------------------
7610     -- Step 5
7611     -- Validate line's org_id.
7612     -- Retropricing: Org Id's are populated for PPA Lines
7613     -------------------------------------------------------------------------
7614     IF AP_IMPORT_INVOICES_PKG.g_source <> 'PPA' THEN   --Retropricing
7615         debug_info := '(Check Lines 5) Validate org id for line';
7616         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7617           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7618                                         debug_info);
7619         END IF;
7620 
7621         IF p_invoice_lines_tab(i).org_id IS NOT NULL THEN
7622           debug_info := '(Check_lines 5.0) Org Id Is Not Null';
7623           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7624             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7625                                           debug_info);
7626           END IF;
7627 
7628           IF p_invoice_lines_tab(i).org_id <> p_invoice_rec.org_id THEN
7629 
7630             IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
7631                                 (AP_IMPORT_INVOICES_PKG.g_invoices_table,  -- Bug 9452076.
7632                                   p_invoice_rec.invoice_id,
7633                                   'INCONSISTENT OPERATING UNITS',
7634                                   p_default_last_updated_by,
7635                                   p_default_last_update_login,
7636                                   current_calling_sequence) <> TRUE ) Then
7637               IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7638                 AP_IMPORT_UTILITIES_PKG.Print(
7639                 AP_IMPORT_INVOICES_PKG.g_debug_switch,
7640                 'insert_rejections<- '      ||current_calling_sequence);
7641               END IF;
7642               RAISE check_lines_failure;
7643             END IF;
7644 
7645             l_current_invoice_status := 'N';
7646             EXIT;
7647           END IF;
7648 
7649         ELSE
7650 
7651           UPDATE ap_invoice_lines_interface
7652              SET org_id = p_invoice_rec.org_id
7653            WHERE rowid = p_invoice_lines_tab(i).row_id;
7654 
7655           p_invoice_lines_tab(i).org_id := p_invoice_rec.org_id;
7656         END IF;
7657     END IF;   -- source <> PPA
7658     --------------------------------------------------------------------
7659     -- Step 6
7660     -- Get new invoice line id.
7661     -- Retropricing: The code below will not execute for PPA's.
7662     -- Invoice_line_id is present for PPA's
7663     --------------------------------------------------------------------
7664     IF (p_invoice_lines_tab(i).invoice_line_id is NULL) THEN
7665         --
7666       debug_info := '(Check_lines 6.1) Get new invoice_line_id';
7667       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7668         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7669                                       debug_info);
7670       END IF;
7671 
7672       debug_info := '(Check_lines 6.2) Update new invoice_line_id to '
7673                     ||'ap_invoice_lines_interface';
7674       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7675         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7676                                       debug_info);
7677       END IF;
7678 
7679       UPDATE ap_invoice_lines_interface
7680          SET invoice_line_id =  ap_invoice_lines_interface_s.NEXTVAL
7681        WHERE rowid = p_invoice_lines_tab(i).row_id
7682       RETURNING invoice_line_id INTO p_invoice_lines_tab(i).invoice_line_id;
7683     END IF;
7684 
7685     ------------------------------------------------------------------------
7686     -- Step 7
7687     -- Check for partial segments
7688     -- Retropricing: The code below will not execute for PPA's.
7689     ------------------------------------------------------------------------
7690     IF (p_invoice_lines_tab(i).dist_code_concatenated IS NOT NULL) THEN
7691       debug_info := '(v_check_lines 7.0) Check for partial Segments';
7692       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7693         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7694                                       debug_info);
7695       END IF;
7696 
7697       IF (AP_UTILITIES_PKG.Check_partial(
7698             p_invoice_lines_tab(i).dist_code_concatenated,  -- IN
7699              P_invoice_lines_tab(i).partial_segments,        -- OUT
7700             p_set_of_books_id,                              -- IN
7701             l_error_message,                                 -- OUT
7702             current_calling_sequence) <> TRUE) THEN
7703         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7704           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7705           'AP_UTILITIES_PKG.Check_Partial<-'||current_calling_sequence);
7706         END IF;
7707         RAISE check_lines_failure;
7708       END IF;
7709 
7710       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7711           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7712             '------------------> partial_segments = '
7713             || p_invoice_lines_tab(i).partial_segments
7714             ||'l_error_message = '||l_error_message
7715             ||'dist_code_concatenated = '
7716             || p_invoice_lines_tab(i).dist_code_concatenated);
7717       END IF;
7718     END IF; --dist_code_concatenated
7719 
7720     -------------------------------------------------
7721     -- step 8
7722     -- Firstly we need to check line amount is NULL
7723     -- checking for the precision of the lines amount
7724     -------------------------------------------------
7725     -- Added for bug 9484163
7726     IF ( p_invoice_lines_tab(i).amount is null) THEN
7727          debug_info := '(Check Invoice Line amount 8.1) Invoice Line '
7728                     ||'Amount is null';
7729       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7730         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7731                                       debug_info);
7732       END IF;
7733       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
7734           (AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
7735                 p_invoice_lines_tab(i).invoice_line_id,
7736                 'LINE AMOUNT IS NULL',
7737                 p_default_last_updated_by,
7738                 p_default_last_update_login,
7739                 current_calling_sequence) <> TRUE) THEN
7740            IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7741                   AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7742                            'insert_rejections<-'||current_calling_sequence);
7743            END IF;
7744            RAISE check_lines_failure;
7745       END IF;
7746       l_temp_line_status :='N';
7747 
7748     ELSE -- Bug 9484163 ends
7749 
7750 	IF (p_invoice_lines_tab(i).amount <> 0 AND
7751 		p_invoice_lines_tab(i).invoice_line_id is not null)  THEN
7752 
7753 		debug_info := '(Check Invoice Line amount 8) Check for invoice line '
7754 			    ||'amount if it is not exceeding precision';
7755 		IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7756 			AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7757                                       debug_info);
7758 		END IF;
7759 		IF (AP_IMPORT_VALIDATION_PKG.v_check_invoice_line_amount (
7760 				p_invoice_lines_tab(i),
7761 			        p_precision_inv_curr,
7762 				p_default_last_updated_by,
7763 				p_default_last_update_login,
7764 				p_current_invoice_status => l_temp_line_status,  --IN OUT
7765 				p_calling_sequence  => current_calling_sequence) <> TRUE )THEN
7766 			IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7767 				AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7768 					'v_check_line_amount<-'||current_calling_sequence);
7769 		        END IF;
7770 			RAISE check_lines_failure;
7771 
7772 	      END IF;
7773 	      /*(IF (l_temp_line_status = 'N') THEN
7774 		l_current_invoice_status := l_temp_line_status;
7775 	      END IF;
7776 		--
7777 		-- show output values (only if debug_switch = 'Y')
7778 		--
7779 	      IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7780 			AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7781 			'------------------>
7782 			l_temp_invoice_status  = '||l_temp_line_status);
7783 	      END IF;*/ -- Commented and moved this code out of this IF Loop for bug 9484163
7784 
7785 	END IF;
7786     END IF; -- Invoice line amount is null
7787     -- For bug 9484163
7788     IF (l_temp_line_status = 'N') THEN
7789         l_current_invoice_status := l_temp_line_status;
7790     END IF;
7791       --
7792       -- show output values (only if debug_switch = 'Y')
7793       --
7794     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7795          AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7796          '------------------>
7797          l_temp_invoice_status  = '||l_temp_line_status);
7798     END IF; -- bug 9484163 ends
7799 
7800     --------------------------------------------------------
7801     -- Step 9
7802     -- check for PO Information
7803     -- only for ITEM Lines
7804     ---------------------------------------------------------
7805     debug_info := '(Check_lines 9) Call v_check_po_info only for ITEM Lines';
7806     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7807       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7808                                     debug_info);
7809     END IF;
7810 
7811     IF (nvl(p_invoice_lines_tab(i).line_type_lookup_code, 'ITEM' )
7812          IN ('ITEM','RETROITEM')) THEN
7813       debug_info := '(Check_lines 9.1) This is an ITEM Line';
7814       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7815         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7816                                       debug_info);
7817       END IF;
7818 
7819       IF (AP_IMPORT_VALIDATION_PKG.v_check_line_po_info(
7820            p_invoice_rec,                        -- IN
7821            p_invoice_lines_tab(i),                -- IN OUT
7822            p_set_of_books_id,                      -- IN
7823            p_positive_price_tolerance,             -- IN
7824            p_qty_ord_tolerance,                    -- IN
7825 	   p_amt_ord_tolerance,			   -- IN
7826            p_max_qty_ord_tolerance,                -- IN
7827 	   p_max_amt_ord_tolerance,		   -- IN
7828            p_default_last_updated_by,              -- IN
7829            p_default_last_update_login,            -- IN
7830            p_current_invoice_status => l_temp_line_status,  -- IN OUT NOCOPY
7831            p_calling_sequence       => current_calling_sequence)
7832           <> TRUE )THEN
7833         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7834           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7835             'v_check_po_info<-' ||current_calling_sequence);
7836         END IF;
7837         RAISE check_lines_failure;
7838       END IF;
7839 
7840       --
7841       -- show output values (only if debug_switch = 'Y')
7842       --
7843       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7844         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7845           '------------------> l_temp_line_status = '|| l_temp_line_status);
7846       END IF;
7847 
7848       -- We need to set the current status to 'N' only if the temp line status
7849       -- returns 'N'. So all temp returns of 'N' will overwrite the current
7850       -- invoice status to 'N' which finally would be returned to the calling
7851       -- function.
7852       IF (l_temp_line_status = 'N') THEN
7853         l_current_invoice_status := l_temp_line_status;
7854       END IF;
7855 
7856     -- bug 10158760: start
7857     ELSIF (nvl(p_invoice_lines_tab(i).line_type_lookup_code, 'ITEM' )
7858          IN ('TAX')) THEN
7859       -- invoice has tax line set the global variable
7860       -- to be used in ap_import_invoices_pkg
7861      -- AP_IMPORT_INVOICES_PKG.g_inv_has_tax_line := 'Y'; --bug 15862708
7862      p_invoice_rec.inv_has_tax_line := 'Y';
7863     -- bug 10158760: end
7864 
7865     END IF; -- for ITEM line type lookup
7866 
7867     --------------------------------------------------------
7868     -- Step 10
7869     -- Check for receipt information if match option = 'R'
7870     --------------------------------------------------------
7871     debug_info := '(Check_lines 10) Call v_check_receipt_info';
7872     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7873       AP_IMPORT_UTILITIES_PKG.Print(
7874         AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
7875     END IF;
7876 
7877 --Bug 5225547 added the below condition to call v_check_receipt_info
7878   IF (p_invoice_lines_tab(i).match_option = 'R') Then
7879 
7880     IF (AP_IMPORT_VALIDATION_PKG.v_check_receipt_info (
7881          p_invoice_rec	,			 -- IN
7882          p_invoice_lines_tab(i),                 -- IN
7883          p_default_last_updated_by,              -- IN
7884          p_default_last_update_login,            -- IN
7885          p_temp_line_status           => l_temp_line_status, -- OUT NOCOPY
7886          p_calling_sequence           => current_calling_sequence)
7887          <> TRUE) THEN
7888       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7889         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7890         'v_check_receipt_info<-' ||current_calling_sequence);
7891       END IF;
7892       RAISE check_lines_failure;
7893     END IF;
7894 
7895    END IF;
7896 
7897     --
7898     -- show output values (only if debug_switch = 'Y')
7899     --
7900     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7901       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7902                    '------------------> l_temp_line_status = '||
7903             l_temp_line_status);
7904     END IF;
7905 
7906     -- We need to set the current status to 'N' only if the temp line status
7907     -- returns 'N'. So all temp returns of 'N' will overwrite the current
7908     -- invoice status to 'N' which finally would be returned to the calling
7909     -- function.
7910     IF (l_temp_line_status = 'N') THEN
7911       l_current_invoice_status := l_temp_line_status;
7912     END IF;
7913 
7914 
7915     -----------------------------------------------------------------
7916     -- Step 11
7917     --Validate the purchasing_category information.
7918     -----------------------------------------------------------------
7919     IF (p_invoice_lines_tab(i).purchasing_category_id IS NOT NULL OR
7920          p_invoice_lines_tab(i).purchasing_category IS NOT NULL) THEN
7921 
7922       debug_info := '(Check Purchasing Category Info 11) Check if valid '
7923                     ||'purchasing category information is provided';
7924       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7925         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7926                                       debug_info);
7927       END IF;
7928 
7929       IF (AP_IMPORT_VALIDATION_PKG.v_check_line_purch_category(
7930                 p_invoice_lines_tab(i),
7931                 p_default_last_updated_by,
7932                 p_default_last_update_login,
7933                 p_current_invoice_status => l_temp_line_status,  --IN OUT
7934                 p_calling_sequence  => current_calling_sequence) <> TRUE )THEN
7935 
7936          IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7937            AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7938            'v_check_purchasing_category<-'||current_calling_sequence);
7939          END IF;
7940          RAISE check_lines_failure;
7941 
7942       END IF;
7943 
7944       IF (l_temp_line_status = 'N') THEN
7945         l_current_invoice_status := l_temp_line_status;
7946       END IF;
7947       --
7948       -- show output values (only if debug_switch = 'Y')
7949       --
7950       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7951         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7952           '------------------>
7953           l_temp_invoice_status  = '||l_temp_line_status);
7954       END IF;
7955 
7956     END IF;
7957 
7958 
7959     -----------------------------------------------------------------
7960     -- Step 12
7961     --Validate the Cost_Factor information.
7962     -----------------------------------------------------------------
7963     IF (p_invoice_lines_tab(i).cost_factor_id IS NOT NULL OR
7964          p_invoice_lines_tab(i).cost_factor_name IS NOT NULL) THEN
7965 
7966       debug_info := '(Check Cost Factor Info 12) Check if valid '
7967                     ||'cost factor information is provided';
7968       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7969         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7970                                       debug_info);
7971       END IF;
7972 
7973       IF (AP_IMPORT_VALIDATION_PKG.v_check_line_cost_factor(
7974                 p_invoice_lines_tab(i),
7975                 p_default_last_updated_by,
7976                 p_default_last_update_login,
7977                 p_current_invoice_status => l_temp_line_status,  --IN OUT
7978                 p_calling_sequence  => current_calling_sequence) <> TRUE )THEN
7979 
7980          IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7981            AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7982            'v_check_line_cost_factor<-'||current_calling_sequence);
7983          END IF;
7984          RAISE check_lines_failure;
7985 
7986       END IF;
7987 
7988       IF (l_temp_line_status = 'N') THEN
7989         l_current_invoice_status := l_temp_line_status;
7990       END IF;
7991       --
7992       -- show output values (only if debug_switch = 'Y')
7993       --
7994       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7995         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7996           '------------------>
7997           l_temp_invoice_status  = '||l_temp_line_status);
7998       END IF;
7999 
8000     END IF;
8001 
8002 
8003     -------------------------------------------------------
8004     --bugfix:5565310
8005     --Step 12a
8006     --Populate PO Tax Attributes on the line if it is a po/rct
8007     --matched.
8008     ----------------------------------------------------------
8009     IF(p_invoice_lines_tab(i).po_line_location_id IS NOT NULL) THEN
8010 
8011        IF (v_check_line_get_po_tax_attr(p_invoice_rec  =>  p_invoice_rec,
8012        				      p_invoice_lines_rec =>p_invoice_lines_tab(i),
8013 				      p_calling_sequence => current_calling_sequence)
8014 				      <> TRUE) THEN
8015 
8016             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8017 	            AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8018 		              'v_check_line_populate_po_tax_attr<-' ||current_calling_sequence);
8019             END IF;
8020             RAISE check_lines_failure;
8021 
8022        END IF;
8023 
8024     END IF;
8025     --------------------------------------------------------
8026     -- Step 13
8027     -- check for accounting date Information
8028     ---------------------------------------------------------
8029     debug_info := '(Check_lines 13) Call v_check_line_accounting_date';
8030     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8031       AP_IMPORT_UTILITIES_PKG.Print(
8032         AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
8033     END IF;
8034 
8035     IF (AP_IMPORT_VALIDATION_PKG.v_check_line_accounting_date(
8036          p_invoice_rec,                          -- IN
8037          p_invoice_lines_tab(i),                -- IN OUT NOCOPY
8038          p_gl_date_from_get_info,                -- IN
8039          p_gl_date_from_receipt_flag,            -- IN
8040          p_set_of_books_id,                      -- IN
8041          p_purch_encumbrance_flag,               -- IN
8042          p_default_last_updated_by,              -- IN
8043          p_default_last_update_login,            -- IN
8044          p_current_invoice_status   => l_temp_line_status,-- IN OUT NOCOPY
8045          p_calling_sequence         => current_calling_sequence)
8046          <> TRUE )THEN
8047       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8048         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8049           'v_check_line_accounting_date<-' ||current_calling_sequence);
8050       END IF;
8051       RAISE check_lines_failure;
8052     END IF;
8053 
8054     --
8055     -- show output values (only if debug_switch = 'Y')
8056     --
8057     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8058       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8059       '------------------> l_temp_line_status = '|| l_temp_line_status);
8060     END IF;
8061     --
8062     IF (l_temp_line_status = 'N') THEN
8063       l_current_invoice_status := l_temp_line_status;
8064     END IF;
8065 
8066 
8067     --------------------------------------------------------
8068     -- Step 14
8069     -- check for project information
8070     ---------------------------------------------------------
8071     debug_info := '(Check_lines 14) Call v_check_line_project_info';
8072     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8073       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8074                                     debug_info);
8075     END IF;
8076 
8077     --bugfix:4773191 , added the IF condition to bypass the pa flexbuild
8078     --validation since this is already done in OIE during the creation
8079     --of expense report before populating the records into interface table.
8080     --IF (p_invoice_rec.invoice_type_lookup_code <> 'EXPENSE REPORT') THEN    .. B# 8528132
8081     --bugfix :10356162, doing null check condition on project info
8082    IF (nvl(p_invoice_rec.invoice_type_lookup_code, 'STANDARD') <> 'EXPENSE REPORT'
8083     AND (p_invoice_lines_tab(i).project_id IS NOT NULL OR
8084          p_invoice_lines_tab(i).task_id IS NOT NULL OR
8085          p_invoice_lines_tab(i).expenditure_type IS NOT NULL OR
8086          p_invoice_lines_tab(i).expenditure_item_date IS NOT NULL OR
8087          p_invoice_lines_tab(i).expenditure_organization_id IS NOT NULL))
8088 
8089     THEN    -- B# 8528132
8090        l_pa_built_account := 0;
8091 
8092        IF (AP_IMPORT_VALIDATION_PKG.v_check_line_project_info (
8093          p_invoice_rec,                              -- IN
8094          p_invoice_lines_tab(i),                        -- IN OUT NOCOPY
8095          nvl(p_invoice_lines_tab(i).accounting_date, --  IN p_accounting_date
8096              p_gl_date_from_get_info),
8097          p_pa_installed,                             -- IN
8098          l_employee_id,                              -- IN
8099          p_base_currency_code,                         -- IN
8100          p_set_of_books_id,                           -- IN
8101          p_chart_of_accounts_id,                     -- IN
8102          p_default_last_updated_by,                     -- IN
8103          p_default_last_update_login,                 -- IN
8104          p_pa_built_account         => l_pa_built_account, -- OUT NOCOPY
8105          p_current_invoice_status   => l_temp_line_status, -- IN OUT NOCOPY
8106          p_calling_sequence         => current_calling_sequence)
8107          <> TRUE )THEN
8108          IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8109             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8110               'v_check_line_project_info<-' ||current_calling_sequence);
8111          END IF;
8112          RAISE check_lines_failure;
8113        END IF;
8114 
8115        --
8116        -- show output values (only if debug_switch = 'Y')
8117        --
8118        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8119           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8120              '------------------> l_temp_line_status = '|| l_temp_line_status
8121             ||' dist_code_combination_id = '
8122             || to_char(p_invoice_lines_tab(i).dist_code_combination_id));
8123        END IF;
8124        --
8125        --
8126        IF (l_temp_line_status = 'N') THEN
8127           l_current_invoice_status := l_temp_line_status;
8128        END IF;
8129 
8130     END IF; --bugfix:4773191
8131 
8132     -------------------------------------------------------------------
8133     -- Step 15.0
8134     -- Check for Product Registration in AP_PRODUCT_REGISTRATIONS
8135     -- If source application is registered for DISTRIBUTION_GENERATION
8136     -- then no need to validate lien account info
8137     -------------------------------------------------------------------
8138 
8139     debug_info := '(Check_lines 15.0) Call Is_Product_Registered';
8140     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8141        AP_IMPORT_UTILITIES_PKG.Print(
8142             AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
8143     End if;
8144 
8145     /* bug 5039042. Whether Source Application is registered for
8146        Distribution Generation Via Ap_Product_Registrations */
8147     /* Bug 5448579. Added the IF condition */
8148     IF (p_invoice_lines_tab(i).application_id IS NULL) THEN
8149       l_product_registered := 'N';
8150     ELSE
8151       IF (Ap_Import_Utilities_Pkg.Is_Product_Registered(
8152                 P_application_id => p_invoice_lines_tab(i).application_id,
8153                 X_registration_api    => l_dummy,
8154                 X_registration_view   => l_dummy,
8155                 P_calling_sequence    => current_calling_sequence)) THEN
8156         l_product_registered := 'Y';
8157       ELSE
8158         l_product_registered := 'N';
8159       END IF;
8160     END IF;
8161 
8162    /* bug 5121735 */
8163    debug_info := '(Check_lines 15.1) l_product_registered: '||l_product_registered;
8164    IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8165      AP_IMPORT_UTILITIES_PKG.Print(
8166      AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
8167    End if;
8168 
8169     -------------------------------------------------------------------
8170     -- Step 15
8171     -- check for account Information.
8172     -- Retropricing: The account validation is not needed for PPA
8173     -- as the ccid will be copied from the corrected_invoice_dist or from
8174     -- po/rcv transaction
8175     ------------------------------------------------------------------
8176     /* bug 5039042. If Source Application is registered for
8177        Ditribution Generation Via Ap_Product_Registrations
8178        Then no need to validate the line account info */
8179 
8180     IF (AP_IMPORT_INVOICES_PKG.g_source <> 'PPA') THEN
8181       IF (l_product_registered = 'N') THEN   /* bug 5121735 */
8182         debug_info := '(Check_lines 15) Call v_check_line_account_info';
8183         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8184           AP_IMPORT_UTILITIES_PKG.Print(
8185             AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
8186         End if;
8187 
8188 		--Start of Bug 13082579/13820857 - payables open interface import applying distribution set to freight lines
8189         --Added the IF condition (p_invoice_lines_rec.line_type_lookup_code = 'ITEM')
8190         IF (p_invoice_lines_tab(i).line_type_lookup_code = 'ITEM') THEN
8191 
8192 		/*Start of bug 4386299*/
8193 		--If distribution_set_id is null or accounting information is not there
8194 		--then we would default from vendor-sites
8195 		IF (
8196 		    (p_invoice_lines_tab(i).dist_code_concatenated IS NULL
8197 		    OR p_invoice_lines_tab(i).partial_segments = 'Y')
8198 		AND p_invoice_lines_tab(i).dist_code_combination_id IS NULL
8199 		AND p_invoice_rec.po_number IS NULL                 --default po number
8200 		AND p_invoice_lines_tab(i).po_number IS NULL
8201 		AND p_invoice_lines_tab(i).po_header_id IS NULL
8202 		AND p_invoice_lines_tab(i).distribution_set_id IS NULL
8203 		AND p_invoice_lines_tab(i).distribution_set_name IS NULL
8204 		AND p_invoice_lines_tab(i).receipt_number is null --Added for Bug 13082579/13820857
8205         AND p_invoice_lines_tab(i).rcv_transaction_id is null --Added for Bug 13082579/13820857
8206 		AND (p_invoice_rec.vendor_id IS NOT NULL
8207 		    AND p_invoice_rec.vendor_site_id IS NOT NULL)
8208 		)
8209 		THEN
8210 		  begin
8211 		    select distribution_set_id
8212 		      into p_invoice_lines_tab(i).distribution_set_id
8213 		      from po_vendor_sites
8214 		     where vendor_id=p_invoice_rec.vendor_id
8215 		       and vendor_site_id=p_invoice_rec.vendor_site_id;
8216 		  exception
8217 		   when no_data_found then
8218 		    p_invoice_lines_tab(i).distribution_set_id:=null;
8219 		  end;
8220 		END IF;
8221 		/*End of bug 4386299*/
8222 	  END IF; --(p_invoice_lines_tab(i).line_type_lookup_code = 'ITEM')
8223 
8224           IF (AP_IMPORT_VALIDATION_PKG.v_check_line_account_info (
8225              p_invoice_lines_tab(i),                       -- IN OUT NOCOPY
8226              p_freight_code_combination_id,                -- IN
8227              l_pa_built_account,                        -- IN
8228              nvl(p_invoice_lines_tab(i).accounting_date, -- IN p_accounting_date
8229                  p_gl_date_from_get_info),
8230              p_set_of_books_id,                          -- IN
8231              p_chart_of_accounts_id,                       -- IN
8232              p_default_last_updated_by,                    -- IN
8233              p_default_last_update_login,                -- IN
8234              p_current_invoice_status => l_temp_line_status,-- IN OUT NOCOPY
8235              p_calling_sequence       => current_calling_sequence) <> TRUE
8236              ) THEN
8237           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8238              AP_IMPORT_UTILITIES_PKG.Print(
8239                AP_IMPORT_INVOICES_PKG.g_debug_switch,
8240                  'v_check_line_account_info<-' ||current_calling_sequence);
8241           END IF;
8242           RAISE check_lines_failure;
8243         END IF;
8244         --
8245         -- show output values (only if debug_switch = 'Y')
8246         --
8247         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8248           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8249             '------------------> l_temp_line_status = '||
8250             l_temp_line_status ||'dist_code_combination_id = '
8251             ||to_char(p_invoice_lines_tab(i).dist_code_combination_id));
8252         END IF;
8253         --
8254         IF (l_temp_line_status = 'N') THEN
8255           l_current_invoice_status := l_temp_line_status;
8256         END IF;
8257      END IF;  -- l_product_registered /* bug 5121735 */
8258     END IF;  --source <> PPA
8259 
8260     --------------------------------------------------------------------------
8261     -- Step 16
8262     -- check for deferred accounting Information
8263     -- Retropricing: For PPA Lines deferred_acctg_flag = 'N' and the validation
8264     -- w.r.t deferred accounting is not required.
8265     --------------------------------------------------------------------------
8266     IF AP_IMPORT_INVOICES_PKG.g_source <> 'PPA' THEN
8267 
8268         debug_info := '(Check_lines 16) Call v_check_deferred_accounting';
8269         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8270           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8271                                          debug_info);
8272         END IF;
8273 
8274         IF (AP_IMPORT_VALIDATION_PKG.v_check_deferred_accounting (
8275              p_invoice_lines_tab(i),                     -- IN OUT NOCOPY
8276              p_set_of_books_id,                        -- IN
8277              p_default_last_updated_by,                -- IN
8278              p_default_last_update_login,              -- IN
8279              p_current_invoice_status => l_temp_line_status,-- IN OUT NOCOPY
8280              p_calling_sequence       => current_calling_sequence) <> TRUE )THEN
8281           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8282             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8283             'v_check_deferred_accounting<-' ||current_calling_sequence);
8284           end if;
8285           RAISE check_lines_failure;
8286         END IF;
8287 
8288         --
8289         -- show output values (only if debug_switch = 'Y')
8290         --
8291         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8292           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8293              '------------------> l_temp_line_status = '||
8294             l_temp_line_status);
8295         END IF;
8296         --
8297         IF (l_temp_line_status = 'N') THEN
8298           l_current_invoice_status := l_temp_line_status;
8299         END IF;
8300 
8301     END IF; --source <> PPA
8302     --------------------------------------------------------
8303     -- Step 17
8304     -- check distribution set information
8305     -- Retropricing: For PPA Lines dist set is NULL and the validation
8306     -- w.r.t Dist Set is not required.
8307     ---------------------------------------------------------
8308      IF AP_IMPORT_INVOICES_PKG.g_source <> 'PPA' THEN
8309         --
8310         debug_info := '(Check_lines 17) Call v_check_line_dist_set';
8311         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8312           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8313                                         debug_info);
8314         END IF;
8315         --
8316         IF (nvl(p_invoice_lines_tab(i).line_type_lookup_code, 'ITEM' )
8317              = 'ITEM') THEN
8318           IF  (AP_IMPORT_VALIDATION_PKG.v_check_line_dist_set (
8319                p_invoice_rec,                         -- IN
8320                p_invoice_lines_tab(i),                -- IN OUT NOCOPY
8321                p_base_currency_code,                  -- IN
8322                l_employee_id,                         -- IN
8323                p_gl_date_from_get_info,               -- IN
8324                p_set_of_books_id,                     -- IN
8325                p_chart_of_accounts_id,                -- IN
8326                p_pa_installed,                        -- IN
8327                p_default_last_updated_by,             -- IN
8328                p_default_last_update_login,           -- IN
8329                p_current_invoice_status   => l_temp_line_status,-- IN OUT NOCOPY
8330                p_calling_sequence         => current_calling_sequence)
8331               <> TRUE )THEN
8332             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
8333              AP_IMPORT_UTILITIES_PKG.Print(
8334                           AP_IMPORT_INVOICES_PKG.g_debug_switch,
8335                       'v_check_line_dist_set<-' ||current_calling_sequence);
8336             END IF;
8337             RAISE check_lines_failure;
8338           END IF;
8339           --
8340           -- show output values (only if debug_switch = 'Y')
8341           --
8342           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
8343             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8344              '------------------> l_temp_line_status = '|| l_temp_line_status);
8345           END IF;
8346           --
8347           IF (l_temp_line_status = 'N') THEN
8348         l_current_invoice_status := l_temp_line_status;
8349           END IF;
8350         END IF; -- Check dist set info, only for ITEM type lines.
8351         --
8352     END IF; --source <> PPA
8353 
8354    --------------------------------------------------------
8355    -- Step 18
8356    -- Validate Qty related information for non PO/RCV matched lines
8357    ---------------------------------------------------------
8358    debug_info := '(Check_lines 18) Call v_check_qty_uom_info';
8359    IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8360      AP_IMPORT_UTILITIES_PKG.Print(
8361          AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
8362    END IF;
8363 
8364    -- check for invalid qty related information for non PO/RCV matched lines
8365    IF (AP_IMPORT_VALIDATION_PKG.v_check_qty_uom_non_po (
8366          p_invoice_rec,                     -- IN
8367          p_invoice_lines_tab(i),               -- IN OUT NOCOPY
8368          p_default_last_updated_by,          -- IN
8369          p_default_last_update_login,        -- IN
8370          p_current_invoice_status   => l_temp_line_status,  -- IN OUT NOCOPY
8371          p_calling_sequence         => current_calling_sequence) <> TRUE) THEN
8372      IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8373        AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8374            'v_check_invalid_awt_group<-' ||current_calling_sequence);
8375      END IF;
8376      RAISE check_lines_failure;
8377    END IF;
8378    --
8379    -- show output values (only if debug_switch = 'Y')
8380    --
8381    IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8382      AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8383       '------------------> l_temp_line_status = '|| l_temp_line_status);
8384    END IF;
8385 
8386    --
8387    IF (l_temp_line_status = 'N') THEN
8388      l_current_invoice_status := l_temp_line_status;
8389    END IF;
8390 
8391 
8392    --------------------------------------------------------
8393    -- Step 19
8394    -- check for AWT group
8395    ---------------------------------------------------------
8396    debug_info := '(Check_lines 19) Call v_check_invalid_awt_group';
8397     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8398      AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8399      debug_info);
8400     END IF;
8401 
8402    -- check for invalid AWT group
8403    IF (AP_IMPORT_VALIDATION_PKG.v_check_invalid_line_awt_group(
8404        p_invoice_rec,                              -- IN
8405        p_invoice_lines_tab(i),                     -- IN OUT NOCOPY
8406        p_default_last_updated_by,                -- IN
8407        p_default_last_update_login,               -- IN
8408        p_current_invoice_status    => l_temp_line_status, -- IN OUT NOCOPY
8409        p_calling_sequence          => current_calling_sequence) <> TRUE )THEN
8410      IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8411        AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8412        'v_check_invalid_awt_group<-' ||current_calling_sequence);
8413      END IF;
8414      RAISE check_lines_failure;
8415    END IF;
8416    --
8417    -- show output values (only if debug_switch = 'Y')
8418    --
8419    IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8420      AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8421        '------------------> l_temp_line_status = '|| l_temp_line_status);
8422    END IF;
8423    --
8424    IF (l_temp_line_status = 'N') THEN
8425      l_current_invoice_status := l_temp_line_status;
8426    END IF;
8427 
8428    --bug6639866
8429    --------------------------------------------------------
8430    -- Step 19.1
8431    -- check for pay AWT group
8432    ---------------------------------------------------------
8433    debug_info := '(Check_lines 19) Call v_check_invalid_line_pay_awt_g';
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    -- check for invalid AWT group
8440    IF (AP_IMPORT_VALIDATION_PKG.v_check_invalid_line_pay_awt_g(
8441        p_invoice_rec,                              -- IN
8442        p_invoice_lines_tab(i),                     -- IN OUT NOCOPY
8443        p_default_last_updated_by,                -- IN
8444        p_default_last_update_login,               -- IN
8445        p_current_invoice_status    => l_temp_line_status, -- IN OUT NOCOPY
8446        p_calling_sequence          => current_calling_sequence) <> TRUE )THEN
8447      IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8448        AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8449        'v_check_invalid_pay_awt_group<-' ||current_calling_sequence);
8450      END IF;
8451      RAISE check_lines_failure;
8452    END IF;
8453    --
8454    -- show output values (only if debug_switch = 'Y')
8455    --
8456    IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8457      AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8458        '------------------> l_temp_line_status = '|| l_temp_line_status);
8459    END IF;
8460    --
8461    IF (l_temp_line_status = 'N') THEN
8462      l_current_invoice_status := l_temp_line_status;
8463    END IF;
8464 
8465 
8466 
8467 
8468    --------------------------------------------------------
8469    -- Step 20
8470    -- check for Duplicate Line Num
8471    -- Retropricing: This check is not needed for PPA's
8472    ---------------------------------------------------------
8473    IF AP_IMPORT_INVOICES_PKG.g_source <> 'PPA' THEN
8474        debug_info := '(Check_lines 20) Call v_check_duplicate_line_num';
8475        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8476          AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8477                                        debug_info);
8478        END IF;
8479 
8480        IF (AP_IMPORT_VALIDATION_PKG.v_check_duplicate_line_num(
8481              p_invoice_rec,                          -- IN
8482              p_invoice_lines_tab(i),                 -- IN OUT NOCOPY
8483              p_default_last_updated_by,              -- IN
8484              p_default_last_update_login,            -- IN
8485              p_current_invoice_status     => l_temp_line_status,-- IN OUT
8486              p_calling_sequence           => current_calling_sequence)
8487              <> TRUE )THEN
8488           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8489            AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8490              'v_check_duplicate_line_num<-' ||current_calling_sequence);
8491           END IF;
8492           RAISE check_lines_failure;
8493        END IF;
8494        --
8495        -- show output values (only if debug_switch = 'Y')
8496        --
8497        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8498          AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8499            '------------------> l_temp_line_status = '|| l_temp_line_status);
8500        END IF;
8501        --
8502        IF (l_temp_line_status = 'N') THEN
8503          l_current_invoice_status := l_temp_line_status;
8504        ELSE
8505          IF (p_invoice_lines_tab(i).line_number is NULL) then
8506            p_invoice_lines_tab(i).line_number := l_max_line_number + 1;
8507            l_max_line_number := l_max_line_number + 1;
8508          END IF;
8509        END IF;
8510    END IF;
8511 
8512    --------------------------------------------------------
8513    -- Step 21
8514    -- check Asset Info
8515    ---------------------------------------------------------
8516    debug_info := '(Check_lines 21) Call v_check_asset_info';
8517    IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8518      AP_IMPORT_UTILITIES_PKG.Print(
8519        AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
8520    End if;
8521 
8522    IF (AP_IMPORT_VALIDATION_PKG.v_check_asset_info (
8523        p_invoice_lines_tab(i),                   -- IN OUT NOCOPY
8524        p_set_of_books_id,                   -- IN
8525        P_asset_book_type,                      -- IN  VARCHAR2
8526        p_default_last_updated_by,               -- IN
8527        p_default_last_update_login,             -- IN
8528        p_current_invoice_status   => l_temp_line_status,-- IN OUT NOCOPY
8529        p_calling_sequence         => current_calling_sequence)
8530        <> TRUE) THEN
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        'v_check_misc_line_info<-' ||current_calling_sequence);
8534       END IF;
8535       RAISE check_lines_failure;
8536    END IF;
8537    --
8538    -- show output values (only if debug_switch = 'Y')
8539    --
8540    IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8541      AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8542       '------------------> l_temp_line_status = '|| l_temp_line_status);
8543    END IF;
8544 
8545    --
8546    IF (l_temp_line_status = 'N') THEN
8547      l_current_invoice_status := l_temp_line_status;
8548    END IF;
8549 
8550 
8551    --------------------------------------------------------
8552    -- Step 22
8553    -- check for Misc Line Info
8554    ---------------------------------------------------------
8555    debug_info := '(Check_lines 22) Call v_check_misc_line_info';
8556    IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8557      AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8558                                     debug_info);
8559    END IF;
8560 
8561    IF (AP_IMPORT_VALIDATION_PKG.v_check_misc_line_info(
8562          p_invoice_rec,		            --7599916
8563          p_invoice_lines_tab(i),            -- IN OUT NOCOPY
8564          p_default_last_updated_by,         -- IN
8565          p_default_last_update_login,        -- IN
8566          p_current_invoice_status    => l_temp_line_status, -- IN OUT NOCOPY
8567          p_calling_sequence          => current_calling_sequence)
8568         <> TRUE )THEN
8569       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8570        AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8571          'v_check_misc_line_info<-' ||current_calling_sequence);
8572       END IF;
8573       RAISE check_lines_failure;
8574    END IF;
8575    --
8576    -- show output values (only if debug_switch = 'Y')
8577    --
8578    IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8579      AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8580         '------------------> l_temp_line_status = '||
8581         l_temp_line_status);
8582    END IF;
8583 
8584    --
8585    IF (l_temp_line_status = 'N') THEN
8586      l_current_invoice_status := l_temp_line_status;
8587    END IF;
8588 
8589    --bug 15862708 starts
8590    IF p_invoice_lines_tab(i).ship_to_location_id IS NULL THEN
8591       /* for bug13398814 - start : Set ship_to_location_id from valid location_code if id is null */
8592     IF (p_invoice_lines_tab(i).ship_to_location_code IS NOT NULL) THEN
8593 
8594       debug_info := '(Check Lines 22.5) Checking for ship to location code ';
8595       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8596           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
8597       END IF;
8598 
8599       IF (AP_IMPORT_VALIDATION_PKG.v_check_ship_to_location_code(
8600           p_invoice_rec,
8601           p_invoice_lines_tab(i),
8602           p_default_last_updated_by,
8603           p_default_last_update_login,
8604           p_current_invoice_status => l_temp_line_status, -- IN OUT
8605           p_calling_sequence       => current_calling_sequence) <> TRUE )THEN
8606 
8607         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8608             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8609                                           'v_check_ship_to_location_code<-' ||current_calling_sequence);
8610         END IF;
8611         RAISE check_lines_failure;
8612       END IF;
8613 
8614       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8615           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8616           '------------------> ship_to_location_id = '|| p_invoice_lines_tab(i).ship_to_location_id);
8617           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8618           '------------------> l_temp_line_status = '||l_temp_line_status);
8619       END IF;
8620 
8621 
8622 	  IF (l_temp_line_status = 'N') THEN
8623         l_current_invoice_status := l_temp_line_status;
8624       END IF;
8625 
8626 	ELSE
8627 	  IF lg_ship_to_loc_id_site.EXISTS(p_invoice_rec.vendor_site_id)
8628     THEN
8629 
8630 		  p_invoice_lines_tab(i).ship_to_location_id:= lg_ship_to_loc_id_site(p_invoice_rec.vendor_site_id);
8631 
8632 		  IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
8633               AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8634                 '------------------> p_invoice_lines_tab(i).ship_to_location_id = '
8635                 || p_invoice_lines_tab(i).ship_to_location_id);
8636           END IF;
8637 
8638 	  ELSE
8639          BEGIN
8640      	   SELECT ship_to_location_id
8641 		    INTO lg_ship_to_loc_id_site(p_invoice_rec.vendor_site_id)
8642             FROM ap_supplier_sites_all
8643 		    WHERE vendor_site_id = p_invoice_rec.vendor_site_id;
8644 
8645          p_invoice_lines_tab(i).ship_to_location_id:= lg_ship_to_loc_id_site(p_invoice_rec.vendor_site_id);
8646 
8647          EXCEPTION
8648           WHEN OTHERS THEN
8649                       NULL;
8650 	   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
8651 				    AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8652                     'No ship to location found based on vendor site '||p_invoice_rec.vendor_site_id);
8653            END IF;
8654 
8655          END;
8656 
8657 
8658 
8659 		  IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8660               AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8661                 '------------------> p_invoice_lines_tab(i).ship_to_location_id = '
8662                 || p_invoice_lines_tab(i).ship_to_location_id);
8663           END IF;
8664 
8665 
8666 
8667       END IF;
8668     END IF;
8669     /* end of bug 13398814*/
8670    END IF;
8671    --bug 15862708 ends
8672 
8673 
8674    --------------------------------------------------------------------------
8675    -- Step 23
8676    -- Check for Tax line info.
8677    -- Retropricing: Tax line would be created by Validation or Calculate Tax
8678    -------------------------------------------------------------------------
8679    IF AP_IMPORT_INVOICES_PKG.g_source <> 'PPA' THEN
8680        debug_info := '(Check_lines 23) Call v_check_tax_line_info';
8681        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8682          AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8683                                         debug_info);
8684        END IF;
8685 
8686        IF (AP_IMPORT_VALIDATION_PKG.v_check_tax_line_info(
8687              p_invoice_lines_tab(i),            -- IN OUT NOCOPY
8688              p_default_last_updated_by,         -- IN
8689              p_default_last_update_login,       -- IN
8690              p_current_invoice_status    => l_temp_line_status, -- IN OUT NOCOPY
8691              p_calling_sequence          => current_calling_sequence)
8692             <> TRUE )THEN
8693           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8694            AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8695              'v_check_tax_line_info<-' ||current_calling_sequence);
8696           END IF;
8697           RAISE check_lines_failure;
8698        END IF;
8699 
8700        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8701          AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8702             '------------------> l_temp_line_status = '||
8703                     l_temp_line_status);
8704        END IF;
8705 
8706        --
8707        IF (l_temp_line_status = 'N') THEN
8708          l_current_invoice_status := l_temp_line_status;
8709        END IF;
8710    END IF;
8711 
8712 /* Bug 4014019: Commenting the call to jg_globe_flex_val due to build issues.
8713 
8714    --------------------------------------------------------
8715    -- Step 24
8716    -- check for Invalid Line Global Flexfield
8717    ---------------------------------------------------------
8718    debug_info := '(Check Lines 24) Check for Line Global Flexfield';
8719     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8720      AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8721                                    debug_info);
8722     END IF;
8723    jg_globe_flex_val.check_attr_value(
8724             'APXIIMPT',
8725             p_invoice_lines_tab(i).global_attribute_category,
8726             p_invoice_lines_tab(i).global_attribute1,
8727             p_invoice_lines_tab(i).global_attribute2,
8728             p_invoice_lines_tab(i).global_attribute3,
8729             p_invoice_lines_tab(i).global_attribute4,
8730             p_invoice_lines_tab(i).global_attribute5,
8731             p_invoice_lines_tab(i).global_attribute6,
8732             p_invoice_lines_tab(i).global_attribute7,
8733             p_invoice_lines_tab(i).global_attribute8,
8734             p_invoice_lines_tab(i).global_attribute9,
8735             p_invoice_lines_tab(i).global_attribute10,
8736             p_invoice_lines_tab(i).global_attribute11,
8737             p_invoice_lines_tab(i).global_attribute12,
8738             p_invoice_lines_tab(i).global_attribute13,
8739             p_invoice_lines_tab(i).global_attribute14,
8740             p_invoice_lines_tab(i).global_attribute15,
8741             p_invoice_lines_tab(i).global_attribute16,
8742             p_invoice_lines_tab(i).global_attribute17,
8743             p_invoice_lines_tab(i).global_attribute18,
8744             p_invoice_lines_tab(i).global_attribute19,
8745             p_invoice_lines_tab(i).global_attribute20,
8746             TO_CHAR(p_set_of_books_id),
8747             fnd_date.date_to_canonical(p_invoice_rec.invoice_date),
8748             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,   -- Retropricing: global need to modify
8749             TO_CHAR(p_invoice_lines_tab(i).invoice_line_id),-- the API to handle PPA tables.
8750             TO_CHAR(p_default_last_updated_by),
8751             TO_CHAR(p_default_last_update_login),
8752             current_calling_sequence,
8753             NULL,NULL,
8754             p_invoice_lines_tab(i).line_type_lookup_code,
8755             NULL,NULL,NULL,NULL,NULL,NULL,NULL,NULL,NULL,NULL,
8756             NULL,NULL,NULL,NULL,NULL,NULL,NULL,NULL,NULL,NULL,
8757             p_current_status => l_temp_line_status);
8758 
8759 
8760     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8761       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8762      'Global Flexfield Lines Processed '|| l_temp_line_status);
8763       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8764          '------------------> l_temp_line_status = '||l_temp_line_status);
8765     END IF;
8766 
8767     IF (l_temp_line_status = 'N') THEN
8768       l_current_invoice_status := l_temp_line_status;
8769     END IF;
8770 
8771 */
8772 
8773     --------------------------------------------------------
8774     -- Step 25
8775     -- Check proration information for non item lines
8776     -- Retropricing: The code below won't be executed for PPA
8777     -- Lines as the prorate_across_flag is N  for RETROITEM
8778     ---------------------------------------------------------
8779     debug_info := '(Check Lines 25) Checking the total dist amount to be '
8780                    ||'prorated';
8781     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8782      AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8783                                    debug_info);
8784     END IF;
8785 
8786     IF (nvl(p_invoice_lines_tab(i).line_type_lookup_code,'ITEM') <> 'ITEM' AND
8787         nvl(p_invoice_lines_tab(i).prorate_across_flag,'N') = 'Y')  THEN
8788       IF (AP_IMPORT_VALIDATION_PKG.v_check_prorate_info (
8789              p_invoice_rec,                                 -- IN
8790              p_invoice_lines_tab(i),                        -- IN OUT NOCOPY
8791              p_default_last_updated_by,                     -- IN
8792              p_default_last_update_login,                   -- IN
8793              p_current_invoice_status  =>l_temp_line_status,-- IN OUT NOCOPY
8794              p_calling_sequence        => current_calling_sequence)
8795              <> TRUE )THEN
8796         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8797           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8798           'v_check_prorate_info<-' ||current_calling_sequence);
8799         END IF;
8800         RAISE check_lines_failure;
8801       END IF;
8802       --
8803       -- show output values (only if debug_switch = 'Y')
8804       --
8805       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8806         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8807            '------------------> l_temp_line_status = '||l_temp_line_status);
8808       END IF;
8809 
8810       --
8811       IF (l_temp_line_status = 'N') THEN
8812         l_current_invoice_status := l_temp_line_status;
8813       END IF;
8814 
8815     END IF; -- End for line type <> ITEM and prorate = Y
8816 
8817     --------------------------------------------------------
8818     -- Step 26
8819     -- Check if retainage account is available if the po shipment
8820     -- has retainage.
8821     ---------------------------------------------------------
8822     IF (p_invoice_lines_tab(i).po_line_location_id IS NOT NULL AND
8823         nvl(p_invoice_rec.invoice_type_lookup_code, 'STANDARD') <> 'PREPAYMENT') THEN
8824 
8825 	debug_info := '(Check Lines 26) Checking for retainage account ';
8826 	IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8827 	    AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
8828 	END IF;
8829 
8830 	IF (AP_IMPORT_VALIDATION_PKG.v_check_line_retainage(
8831 		p_invoice_lines_tab(i),				-- IN OUT
8832 		p_retainage_ccid,
8833 		p_default_last_updated_by,
8834 		p_default_last_update_login,
8835 		p_current_invoice_status => l_temp_line_status, -- IN OUT
8836 		p_calling_sequence       => current_calling_sequence) <> TRUE )THEN
8837 
8838 		IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8839 		    AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8840                                                   'v_check_line_retainage<-' ||current_calling_sequence);
8841 		END IF;
8842 		RAISE check_lines_failure;
8843 	END IF;
8844 
8845 	IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8846 	    AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8847 					  '------------------> l_temp_line_status = '|| l_temp_line_status);
8848 	END IF;
8849 
8850 	IF (l_temp_line_status = 'N') THEN
8851 		l_current_invoice_status := l_temp_line_status;
8852 	END IF;
8853     END IF;
8854 
8855 /* Start of bug 13398814 - commenting the below code as it is moved up just before v_check_tax_line_info()
8856     -- bug 6989166 start
8857     --------------------------------------------------------
8858     -- Step 27
8859     -- Check valid ship to location code, when ship to
8860     -- location id is null.
8861     ---------------------------------------------------------
8862     IF (p_invoice_lines_tab(i).ship_to_location_code IS NOT NULL AND
8863 		p_invoice_lines_tab(i).ship_to_location_id IS NULL) THEN
8864 
8865 	debug_info := '(Check Lines 27) Checking for ship to location code ';
8866 	IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8867 	    AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
8868 	END IF;
8869 
8870 	IF (AP_IMPORT_VALIDATION_PKG.v_check_ship_to_location_code(
8871 		p_invoice_rec,
8872 		p_invoice_lines_tab(i),
8873 		p_default_last_updated_by,
8874 		p_default_last_update_login,
8875 		p_current_invoice_status => l_temp_line_status, -- IN OUT
8876 		p_calling_sequence       => current_calling_sequence) <> TRUE )THEN
8877 
8878 		IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8879 		    AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8880                                                   'v_check_ship_to_location_code<-' ||current_calling_sequence);
8881 		END IF;
8882 		RAISE check_lines_failure;
8883 	END IF;
8884 
8885 	IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8886 	    AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8887 					  '------------------> ship_to_location_id = '
8888 					  || p_invoice_lines_tab(i).ship_to_location_id);
8889 	END IF;
8890 
8891 	IF (l_temp_line_status = 'N') THEN
8892 		l_current_invoice_status := l_temp_line_status;
8893 	END IF;
8894 
8895     END IF;
8896 
8897     -- bug 6989166 end
8898     End of Bug 13398814 */
8899 
8900 	-----------------------------------------------------
8901 	-- Update global_context_code with the right
8902 	-- value corresponding to flexfield JG_AP_INVOICES_LINES
8903 	-- Bug 13491024 - R1213ITTHRESH.QA: ISSUES WITH ITEM LINE GDF IN ITALIAN AP QUICK INVOICE
8904 	-----------------------------------------------------
8905 	debug_info := '(Check Lines 28) Update global context code ';
8906 	IF AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' THEN
8907 		AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
8908 	END IF;
8909 
8910 	-- > IN   global context code in interface table
8911 	-- > OUT NOCOPY  global context code in base table
8912 	IF ( jg_globe_flex_val.reassign_context_code(
8913 	    p_invoice_lines_tab(i).global_attribute_category) <> TRUE) THEN
8914 
8915 		jg_globe_flex_val.reject_invalid_context_code(
8916 			'APXIIMPT',
8917 			AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
8918 			p_invoice_lines_tab(i).invoice_line_id,
8919 			p_default_last_updated_by,
8920 			p_default_last_update_login,
8921 			p_invoice_lines_tab(i).global_attribute_category,
8922 			l_temp_line_status,
8923 			current_calling_sequence);
8924 
8925 		IF (l_temp_line_status <>  'Y') THEN
8926 			IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8927 			    AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8928 							  'jg_globe_flex_val.reject_invalid_context_code<-' ||current_calling_sequence);
8929 			END IF;
8930 			RAISE check_lines_failure;
8931 		END IF;
8932 
8933 		IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8934 		    AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8935 						  '------------------> p_invoice_lines_tab('||i||').global_attribute_category = '
8936 						  || p_invoice_lines_tab(i).global_attribute_category);
8937 		END IF;
8938 
8939 		IF (l_temp_line_status = 'N') THEN
8940 			l_current_invoice_status := l_temp_line_status;
8941 		END IF;
8942 	END IF;
8943 	--End Bug 13491024
8944 
8945 	----GTAS Project Bug#13464635 begin
8946   --------------------------------------------------------
8947    -- Step 28  check for Invalid GTAS info
8948   ---------------------------------------------------------
8949   debug_info := '(Check_lines 28) Call V_CHECK_GDF_VALIDATION';
8950   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8951      AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8952                                    debug_info);
8953   END IF;
8954 
8955   IF (AP_IMPORT_VALIDATION_PKG.V_CHECK_GDF_VALIDATION(
8956        p_invoice_lines_tab(i).invoice_line_id,  -- IN
8957        'INVOICE LINE',                          -- IN
8958        p_default_last_updated_by,               -- IN
8959        p_default_last_update_login,             -- IN
8960        p_current_invoice_status    => l_temp_line_status, -- IN OUT NOCOPY
8961        p_calling_sequence          => current_calling_sequence) <> TRUE )THEN
8962 
8963      IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8964        AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8965        'V_CHECK_GDF_VALIDATION<-' ||current_calling_sequence);
8966      END IF;
8967      RAISE check_lines_failure;
8968    END IF;
8969 
8970    IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8971      AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8972        '------------------> l_temp_line_status = '|| l_temp_line_status);
8973    END IF;
8974    --
8975    IF (l_temp_line_status = 'N') THEN
8976      l_current_invoice_status := l_temp_line_status;
8977    END IF;
8978 
8979  --bug 15862708 starts
8980      IF (AP_IMPORT_VALIDATION_PKG.v_populate_lines_misc(
8981        p_invoice_rec,                                  -- IN
8982        p_invoice_lines_tab(i),                          -- IN OUT
8983        p_calling_sequence          => current_calling_sequence) <> TRUE )THEN
8984 
8985      IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8986        AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8987        'v_populate_lines_misc<-' ||current_calling_sequence);
8988      END IF;
8989      RAISE check_lines_failure;
8990    END IF;
8991 --bug 15862708 ends
8992 
8993 
8994       --Below SELECT statment fetches latest/default  GTAS attributes
8995    --into local record, which are populated in interface table
8996    --through FV Validation API
8997 
8998   IF(l_refresh = 'Y')THEN
8999    SELECT Global_Attribute1,  Global_Attribute2,   Global_Attribute3,
9000           Global_Attribute_Category /*Bug#15977829*/
9001    INTO p_invoice_lines_tab(i).Global_Attribute1,  p_invoice_lines_tab(i).Global_Attribute2,
9002        p_invoice_lines_tab(i).Global_Attribute3,
9003        p_invoice_lines_tab(i).Global_Attribute_Category
9004    FROM AP_INVOICE_LINES_INTERFACE
9005    WHERE invoice_line_id = p_invoice_lines_tab(i).invoice_line_id;
9006   END IF;
9007   --End Bug#13464635
9008 
9009   END LOOP; -- for lines
9010 
9011   p_current_invoice_status := l_current_invoice_status;
9012   RETURN (TRUE);
9013 
9014 EXCEPTION
9015   WHEN OTHERS THEN
9016     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
9017      AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
9018                                    debug_info);
9019     END IF;
9020 
9021     IF (SQLCODE < 0) then
9022       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
9023        AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
9024                                      SQLERRM);
9025       END IF;
9026     END IF;
9027 
9028     IF (invoice_lines%ISOPEN) THEN
9029        CLOSE invoice_lines;
9030     END IF;
9031     RETURN (FALSE);
9032 
9033 END v_check_lines_validation;
9034 
9035 -----------------------------------------------------------------------------
9036 -- This function is used to validate the precision of a line amount.
9037 --
9038 FUNCTION v_check_invoice_line_amount (
9039          p_invoice_lines_rec          IN AP_IMPORT_INVOICES_PKG.r_line_info_rec,
9040          p_precision_inv_curr           IN            NUMBER,
9041          p_default_last_updated_by      IN            NUMBER,
9042          p_default_last_update_login    IN            NUMBER,
9043          p_current_invoice_status       IN OUT NOCOPY VARCHAR2,
9044          p_calling_sequence             IN            VARCHAR2) RETURN BOOLEAN
9045 IS
9046 
9047 check_lines_failure        EXCEPTION;
9048 debug_info                 VARCHAR2(250);
9049 current_calling_sequence   VARCHAR2(2000);
9050 l_current_invoice_status   VARCHAR2(1)    :='Y';
9051 
9052 BEGIN
9053 
9054   -- Updating the calling sequence
9055   current_calling_sequence :=
9056      'AP_IMPORT_VALIDATION_PKG.v_check_invoice_line_amount<-'
9057      ||P_calling_sequence;
9058 
9059   IF LENGTH((ABS(p_invoice_lines_rec.amount) -
9060              TRUNC(ABS(p_invoice_lines_rec.amount))))-1  >
9061      NVL(p_precision_inv_curr,0) THEN
9062 
9063     debug_info :=
9064       '(Check Invoice Line Amount 1) Lines amount exceeds precision.';
9065     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
9066       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
9067                                     debug_info);
9068     END IF;
9069 
9070     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
9071           (AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
9072                p_invoice_lines_rec.invoice_line_id,
9073                'LINE AMOUNT EXCEEDS PRECISION',
9074                p_default_last_updated_by,
9075             p_default_last_update_login,
9076             current_calling_sequence) <> TRUE) THEN
9077       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
9078         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
9079           'insert_rejections<-'||current_calling_sequence);
9080       END IF;
9081       RAISE check_lines_failure;
9082     END IF;
9083     l_current_invoice_status :='N';
9084   END IF;
9085 
9086   p_current_invoice_status := l_current_invoice_status;
9087 
9088   RETURN (TRUE);
9089 
9090 EXCEPTION
9091   WHEN OTHERS THEN
9092     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
9093       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
9094                                     debug_info);
9095     END IF;
9096 
9097     IF (SQLCODE < 0) then
9098       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
9099         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
9100                                       SQLERRM);
9101       END IF;
9102     END IF;
9103     RETURN(FALSE);
9104 
9105 END v_check_invoice_line_amount;
9106 
9107 
9108 -----------------------------------------------------------------------------
9109 -- This function is used to validate PO information at line level.
9110 --
9111 FUNCTION v_check_line_po_info (
9112          p_invoice_rec
9113            IN AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
9114          p_invoice_lines_rec
9115            IN OUT NOCOPY AP_IMPORT_INVOICES_PKG.r_line_info_rec,
9116          p_set_of_books_id              IN            NUMBER,
9117          p_positive_price_tolerance     IN            NUMBER,
9118          p_qty_ord_tolerance            IN            NUMBER,
9119 	     p_amt_ord_tolerance		    IN	          NUMBER,
9120          p_max_qty_ord_tolerance        IN            NUMBER,
9121 	     p_max_amt_ord_tolerance    	IN	          NUMBER,
9122          p_default_last_updated_by      IN            NUMBER,
9123          p_default_last_update_login    IN            NUMBER,
9124          p_current_invoice_status       IN OUT NOCOPY VARCHAR2,
9125          p_calling_sequence             IN            VARCHAR2) RETURN BOOLEAN
9126 
9127 
9128 IS
9129 
9130 check_po_failure                   EXCEPTION;
9131 l_po_number                           VARCHAR2(20) := p_invoice_lines_rec.po_number;
9132 l_po_header_id                    NUMBER := p_invoice_lines_rec.po_header_id;
9133 l_po_line_id                    NUMBER := p_invoice_lines_rec.po_line_id;
9134 l_po_release_id                    NUMBER := p_invoice_lines_rec.po_release_id;
9135 l_po_line_location_id            NUMBER := p_invoice_lines_rec.po_line_location_id;
9136 l_po_distribution_id            NUMBER := p_invoice_lines_rec.po_distribution_id;
9137 l_match_option                    VARCHAR2(25);
9138 l_calc_quantity_invoiced        NUMBER;
9139 l_calc_unit_price               NUMBER;
9140 l_po_is_valid_flag              VARCHAR2(1) := 'N';
9141 l_po_is_consistent_flag         VARCHAR2(1) := 'N';
9142 l_po_line_is_valid_flag         VARCHAR2(1) := 'N';
9143 l_po_line_is_consistent_flag    VARCHAR2(1) := 'N';
9144 l_po_release_is_valid_flag      VARCHAR2(1)    := 'N';
9145 l_po_rel_is_consistent_flag     VARCHAR2(1) := 'N';
9146 l_po_shipment_is_valid_flag     VARCHAR2(1)    := 'N';
9147 l_po_shipment_is_consis_flag    VARCHAR2(1) := 'N';
9148 l_po_dist_is_valid_flag         VARCHAR2(1)    := 'N';
9149 l_po_dist_is_consistent_flag    VARCHAR2(1) := 'N';
9150 l_po_inv_curr_is_consis_flag    VARCHAR2(1)    := 'N';
9151 l_current_invoice_status        VARCHAR2(1) := 'Y';
9152 l_po_is_not_blanket             VARCHAR2(1) := 'N';
9153 l_vendor_id                     NUMBER;
9154 l_purchasing_category_id	AP_INVOICE_LINES_ALL.PURCHASING_CATEGORY_ID%TYPE;
9155 current_calling_sequence         VARCHAR2(2000);
9156 debug_info                       VARCHAR2(500);
9157 
9158 -- Contextual Information for XML Gateway
9159 l_po_currency_code              VARCHAR2(15) := '';
9160 l_invoice_vendor_name           po_vendors.vendor_name%TYPE := '';
9161 
9162 l_price_correct_inv_id          NUMBER;
9163 l_pc_inv_valid                  VARCHAR2(1);
9164 l_base_match_amount		    NUMBER;
9165 l_base_match_quantity		NUMBER;
9166 l_correction_amount		    NUMBER;
9167 l_match_basis    		PO_LINE_TYPES.MATCHING_BASIS%TYPE;
9168 l_pc_po_amt_billed              NUMBER;
9169 l_line_amt_calculated           NUMBER;
9170 l_total_amount_invoiced		NUMBER;
9171 l_total_quantity_invoiced	NUMBER;
9172 l_total_amount_billed		NUMBER;
9173 l_total_quantity_billed		NUMBER;
9174 l_correction_dist_amount	NUMBER;
9175 l_shipment_finally_closed	VARCHAR2(1);
9176 l_corrupt_po_distributions      NUMBER;
9177 l_calc_line_amount		        NUMBER;
9178 l_accrue_on_receipt_flag        po_line_locations.accrue_on_receipt_flag%TYPE;
9179 l_temp_match_option             VARCHAR2(25); --Bug5225547
9180 l_item_description              VARCHAR2(240); --Bug8546486
9181 
9182 l_price_cor_po_header_id        NUMBER;  --bug13599126
9183 l_price_cor_po_line_id          NUMBER;  --bug13599126
9184 l_price_cor_po_line_loc_id      NUMBER;  --bug13599126
9185 l_price_cor_po_distribution_id  NUMBER;  --bug13599126
9186 
9187 
9188 BEGIN
9189   -- Update the calling sequence
9190   --
9191   current_calling_sequence :=
9192     'AP_IMPORT_VALIDATION_PKG.v_check_line_po_info<-'
9193     ||P_calling_sequence;
9194 
9195 IF (nvl(p_invoice_lines_rec.line_type_lookup_code, 'ITEM' )
9196          IN ('ITEM','RETROITEM')) THEN
9197   -----------------------------------------------------------
9198   -- Case 1.0,  Default PO Number from Invoice Header if
9199   -- po_header_id and po_number are null
9200   -----------------------------------------------------------
9201   IF ((l_po_header_id IS NULL) and
9202       (p_invoice_lines_rec.po_number IS NULL) and
9203       (p_invoice_rec.po_number is NOT NULL)) THEN
9204     --
9205     debug_info := '(v_check_line_po_info 1) Default PO Number from invoice '
9206                   ||'header and get l_po_header_id';
9207     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
9208       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
9209                                     debug_info);
9210     END IF;
9211     --
9212 
9213     BEGIN
9214       SELECT 'Y', po_header_id
9215         INTO l_po_is_valid_flag, l_po_header_id
9216         FROM po_headers
9217        WHERE segment1 = p_invoice_rec.po_number
9218     AND type_lookup_code in ('BLANKET', 'PLANNED', 'STANDARD')
9219     /* BUG 2902452 added*/
9220     AND nvl(authorization_status,'INCOMPLETE') in ('APPROVED','REQUIRES REAPPROVAL','IN PROCESS');--Bug5687122 --Added In Process condition
9221 
9222     EXCEPTION
9223       WHEN NO_DATA_FOUND THEN
9224         -- po number is invalid
9225         -- set contextual information for XML GATEWAY
9226         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
9227                                (AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
9228                                 p_invoice_lines_rec.invoice_line_id,
9229                                 'INVALID PO NUM',
9230                                 p_default_last_updated_by,
9231                                 p_default_last_update_login,
9232                                 current_calling_sequence,
9233                                 'Y',
9234                                 'PO NUMBER',
9235                                 p_invoice_rec.po_number) <> TRUE) THEN
9236           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
9237             AP_IMPORT_UTILITIES_PKG.Print(
9238             AP_IMPORT_INVOICES_PKG.g_debug_switch,
9239             'insert_rejections<-'||current_calling_sequence);
9240           END IF;
9241           RAISE check_po_failure;
9242 
9243         END IF;
9244         l_current_invoice_status := 'N';
9245     END;
9246 
9247   END IF;
9248 
9249   -----------------------------------------------------------
9250   -- Case 1.1,  Reject if po_header_id is invalid
9251   -----------------------------------------------------------
9252   IF (l_po_header_id IS NOT NULL) THEN
9253       --
9254     BEGIN
9255       debug_info := '(v_check_line_po_info 1) Validate po_header_id';
9256       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
9257         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
9258                                       debug_info);
9259       END IF;
9260       --
9261       SELECT 'Y'
9262         INTO l_po_is_valid_flag
9263         FROM po_headers ph
9264        WHERE ph.po_header_id = l_po_header_id
9265        AND ph.type_lookup_code in ('BLANKET', 'PLANNED', 'STANDARD')
9266       /* BUG 2902452 added */
9267        AND nvl(authorization_status,'INCOMPLETE') in ('APPROVED','REQUIRES REAPPROVAL','IN PROCESS')--Bug5687122 --Added In Process condition
9268        AND NVL(ph.closed_code, 'X') <> 'FINALLY CLOSED'; --Bug#13867905
9269 
9270     EXCEPTION
9271       WHEN NO_DATA_FOUND THEN
9272         -- po header id is invalid
9273         -- set  contextual information for XML GATEWAY
9274         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
9275                                (AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
9276                                 p_invoice_lines_rec.invoice_line_id,
9277                                 'INVALID PO NUM',
9278                                 p_default_last_updated_by,
9279                                 p_default_last_update_login,
9280                                 current_calling_sequence,
9281                                 'Y',
9282                                 'PO NUMBER',
9283                                 p_invoice_lines_rec.po_number) <> TRUE) THEN
9284           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
9285             AP_IMPORT_UTILITIES_PKG.Print(
9286             AP_IMPORT_INVOICES_PKG.g_debug_switch,
9287             'insert_rejections<-'||current_calling_sequence);
9288           END IF;
9289           RAISE check_po_failure;
9290         END IF;
9291 
9292         l_current_invoice_status := 'N';
9293     END;
9294 
9295   END IF;
9296   -----------------------------------------------------------
9297   -- Case 1.2,  Reject if po_number is missing
9298   -- Bug  7366317 Additional Check for XML Gateway Invoices
9299   -- If Doc type is 'PurchaseOrder' and no PO Info is provided
9300   -- Throw the 'Missing PO NUM' Rejection
9301   -----------------------------------------------------------
9302 
9303    IF (p_invoice_rec.SOURCE= 'XML GATEWAY' AND
9304        UPPER(p_invoice_lines_rec.reference_1) = 'PURCHASEORDER' AND
9305        p_invoice_lines_rec.po_number IS NULL) THEN
9306          BEGIN
9307        -- po number is missing
9308        -- set  contextual information for XML GATEWAY
9309        IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
9310             (AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
9311              p_invoice_lines_rec.invoice_line_id,
9312              'MISSING PO NUM',
9313              p_default_last_updated_by,
9314              p_default_last_update_login,
9315              current_calling_sequence,
9316              'Y',
9317              'LINE NUMBER',
9318              p_invoice_lines_rec.line_number) <> TRUE) THEN
9319           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
9320             AP_IMPORT_UTILITIES_PKG.Print(
9321             AP_IMPORT_INVOICES_PKG.g_debug_switch,
9322             'insert_rejections<-'||current_calling_sequence);
9323           END IF;
9324           RAISE check_po_failure;
9325        END IF;
9326        l_current_invoice_status := 'N';
9327      END;
9328    END IF;
9329 
9330   -----------------------------------------------------------
9331   -- Case 2, Reject if po_number is invalid
9332   -----------------------------------------------------------
9333   IF ((p_invoice_lines_rec.po_number IS NOT NULL) AND
9334       (l_po_header_id IS NULL)) THEN
9335       --
9336     BEGIN
9337       debug_info := '(v_check_line_po_info 2) Validate po_number';
9338       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
9339         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
9340                                       debug_info);
9341       END IF;
9342       --
9343       SELECT 'Y', ph.po_header_id
9344         INTO l_po_is_valid_flag, l_po_header_id
9345         FROM po_headers ph
9346        WHERE segment1 = p_invoice_lines_rec.po_number
9347          AND type_lookup_code in ('BLANKET', 'PLANNED', 'STANDARD')
9348       /*BUG 2902452 added*/
9349       AND nvl(authorization_status,'INCOMPLETE') in ('APPROVED','REQUIRES REAPPROVAL','IN PROCESS')--Bug5687122 --Added In Process condition
9350       AND NVL(ph.closed_code, 'X') <> 'FINALLY CLOSED'; --Bug#13867905
9351 
9352     EXCEPTION
9353       WHEN NO_DATA_FOUND THEN
9354         -- po number is invalid
9355         -- set contextual information for XML GATEWAY
9356         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
9357                                (AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
9358                                 p_invoice_lines_rec.invoice_line_id,
9359                                 'INVALID PO NUM',
9360                                 p_default_last_updated_by,
9361                                 p_default_last_update_login,
9362                                 current_calling_sequence,
9363                                 'Y',
9364                                 'PO NUMBER',
9365                                 p_invoice_lines_rec.po_number) <> TRUE) THEN
9366           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
9367             AP_IMPORT_UTILITIES_PKG.Print(
9368             AP_IMPORT_INVOICES_PKG.g_debug_switch,
9369             'insert_rejections<-'||current_calling_sequence);
9370           END IF;
9371           RAISE check_po_failure;
9372         END IF;
9373 
9374         l_current_invoice_status := 'N';
9375     END;
9376 
9377   END IF;
9378 
9379   ---------------------------------------------------------------------------
9380   -- Case 3, Reject if po_header_id and po_number is inconsistent
9381   ---------------------------------------------------------------------------
9382   IF ((l_po_header_id IS NOT NULL) AND
9383       (p_invoice_lines_rec.po_number IS NOT NULL)) THEN
9384     --
9385     BEGIN
9386       debug_info := '(v_check_line_po_info 3) Check inconsistence for '
9387                     ||'po_number and po_header_id';
9388       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
9389         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
9390                                       debug_info);
9391       END IF;
9392       --
9393       SELECT 'Y'
9394         INTO l_po_is_consistent_flag
9395         FROM po_headers ph
9396        WHERE segment1 = p_invoice_lines_rec.po_number
9397          AND po_header_id = l_po_header_id;
9398 
9399     EXCEPTION
9400       WHEN NO_DATA_FOUND THEN
9401         -- po number is inconsistent
9402         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
9403               (AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
9404                p_invoice_lines_rec.invoice_line_id,
9405                'INCONSISTENT PO INFO',
9406                p_default_last_updated_by,
9407                p_default_last_update_login,
9408                current_calling_sequence) <> TRUE) THEN
9409           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
9410             AP_IMPORT_UTILITIES_PKG.Print(
9411             AP_IMPORT_INVOICES_PKG.g_debug_switch,
9412             'insert_rejections<-'||current_calling_sequence);
9413           END IF;
9414          RAISE check_po_failure;
9415         END IF;
9416         --
9417         l_current_invoice_status := 'N';
9418     END;
9419 
9420   END IF;
9421 
9422   -----------------------------------------------------------
9423   -- Case 4,  Reject if po_line_id is invalid
9424   -----------------------------------------------------------
9425   IF (l_po_line_id IS NOT NULL) THEN
9426     --
9427     BEGIN
9428       debug_info := '(v_check_line_po_info 4) Validate po_line_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       SELECT 'Y'
9435         INTO l_po_line_is_valid_flag
9436         FROM po_lines
9437        WHERE po_line_id = l_po_line_id
9438          AND NVL(closed_code, 'X') <> 'FINALLY CLOSED'; --Bug#13867905;
9439 
9440     EXCEPTION
9441       WHEN NO_DATA_FOUND THEN
9442         -- po line id is invalid
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             'INVALID PO LINE NUM',
9447             p_default_last_updated_by,
9448             p_default_last_update_login,
9449             current_calling_sequence) <> TRUE) THEN
9450           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
9451             AP_IMPORT_UTILITIES_PKG.Print(
9452             AP_IMPORT_INVOICES_PKG.g_debug_switch,
9453             'insert_rejections<-'||current_calling_sequence);
9454           END IF;
9455          RAISE check_po_failure;
9456         END IF;
9457         --
9458         l_current_invoice_status := 'N';
9459     END;
9460 
9461   END IF;
9462 
9463   -- Bug 14366428 Begin
9464 --------------------------------------------------------------------
9465   -- Case 4.1 , Reject if p_vendor_item_num is invalid when no other
9466   --      PO information is provided
9467 -----------------------------------------------------------------------
9468   if ((l_po_header_id is NULL) AND (p_invoice_lines_rec.vendor_item_num IS NOT NULL)
9469       AND (l_po_line_id IS NULL) AND (l_po_release_id IS NULL)
9470       and (p_invoice_lines_rec.po_number IS NULL)) -- and (p_default_po_number is NULL))
9471   then
9472 
9473      debug_info := '(v_check_line_po_info 4.1) Validate po_vendor_item_num';
9474      If AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' then
9475        AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
9476      End if;
9477 
9478     AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
9479                                  'p_vendor_item_num<-'||p_invoice_lines_rec.vendor_item_num);
9480 
9481       BEGIN
9482         SELECT pl.po_header_id
9483 	  INTO l_po_header_id
9484  	  FROM po_lines pl
9485         WHERE pl.vendor_product_num = p_invoice_lines_rec.vendor_item_num;
9486      EXCEPTION
9487         WHEN NO_DATA_FOUND Then
9488              IF ( AP_IMPORT_INVOICES_PKG.g_source = 'XML GATEWAY' ) THEN
9489 
9490              -- Added contextual information for XML Gateway
9491 
9492              IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
9493 			AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
9494 			p_invoice_lines_rec.invoice_line_id,
9495 			'INVALID ITEM',
9496 			p_default_last_updated_by,
9497 			p_default_last_update_login,
9498 			current_calling_sequence,
9499                         'Y',
9500                         'SUPPLIER ITEM NUMBER',
9501                         p_invoice_lines_rec.vendor_item_num ) <> TRUE) THEN
9502 		AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
9503                      'insert_rejections<-'||current_calling_sequence);
9504      		RAISE check_po_failure;
9505       	     END IF;
9506 
9507            ELSE
9508 
9509              IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
9510                         AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
9511 			p_invoice_lines_rec.invoice_line_id,
9512 			'INVALID ITEM',
9513 			p_default_last_updated_by,
9514 			p_default_last_update_login,
9515 			current_calling_sequence) <> TRUE) THEN
9516 		AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
9517                      'insert_rejections<-'||current_calling_sequence);
9518      		RAISE check_po_failure;
9519       	     END IF;
9520 
9521             END IF;  -- g_source = 'XML GATEWAY'
9522 
9523            l_current_invoice_status := 'N';
9524 
9525         WHEN TOO_MANY_ROWS Then
9526 
9527              /* IF ((p_po_line_id	IS NULL) AND
9528 	          (p_po_line_number IS NULL) AND
9529 	          (p_po_line_location_id IS NULL) AND
9530 	          (p_po_distribution_id IS NULL)) Then
9531               */
9532 
9533                 IF ( AP_IMPORT_INVOICES_PKG.g_source = 'XML GATEWAY' ) THEN
9534 
9535                 -- Added contextual information for XML Gateway
9536 
9537                   IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
9538                         AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
9539 			p_invoice_lines_rec.invoice_line_id,
9540 			'CAN MATCH TO ONLY 1 LINE',
9541 			p_default_last_updated_by,
9542 			p_default_last_update_login,
9543  			current_calling_sequence,
9544                         'Y',
9545                         'SUPPLIER ITEM NUMBER',
9546                         p_invoice_lines_rec.vendor_item_num ) <> TRUE) THEN
9547          		AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
9548                           'insert_rejections<-'||current_calling_sequence);
9549          		RAISE check_po_failure;
9550         	  END IF;
9551 
9552                 ELSE
9553 
9554                   IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
9555                         AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
9556 			p_invoice_lines_rec.invoice_line_id,
9557 			'CAN MATCH TO ONLY 1 LINE',
9558 			p_default_last_updated_by,
9559 			p_default_last_update_login,
9560  			current_calling_sequence) <> TRUE) THEN
9561          		AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
9562                           'insert_rejections<-'||current_calling_sequence);
9563          		RAISE check_po_failure;
9564         	  END IF;
9565 
9566                 END IF;  -- g_source = 'XML GATEWAY'
9567 
9568                   l_current_invoice_status := 'N';
9569 
9570 
9571      END;
9572 
9573 END IF;
9574 
9575 -- Bug 14366428 End
9576 
9577   ------------------------------------------------------------
9578   -- Case 5, Reject if po_line_number is invalid
9579   ------------------------------------------------------------
9580   IF ((p_invoice_lines_rec.po_line_number IS NOT NULL) AND
9581       (l_po_line_id IS NULL) AND
9582       (l_po_header_id IS NOT NULL)) THEN
9583     --
9584     BEGIN
9585       debug_info := '(v_check_line_po_info 5) Validate po_line_number';
9586       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
9587         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
9588                                       debug_info);
9589       END IF;
9590       --
9591       --
9592       SELECT 'Y', po_line_id
9593         INTO l_po_line_is_valid_flag, l_po_line_id
9594         FROM po_lines
9595        WHERE line_num = p_invoice_lines_rec.po_line_number
9596          AND po_header_id = l_po_header_id
9597  	 AND NVL(closed_code, 'X') <> 'FINALLY CLOSED'; --Bug#13867905;
9598     EXCEPTION
9599       WHEN NO_DATA_FOUND THEN
9600         -- po line number is invalid
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             'INVALID PO LINE NUM',
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 6, Reject if po_line_id and po_line_number is inconsistent
9623   ---------------------------------------------------------------------------
9624   IF ((l_po_line_id IS NOT NULL) AND
9625       (p_invoice_lines_rec.po_line_number IS NOT NULL)) THEN
9626     --
9627     BEGIN
9628       debug_info := '(v_check_line_po_info 6) Check inconsistence for '
9629                     ||'po_line_number and po_line_id';
9630       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
9631         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
9632                                       debug_info);
9633       END IF;
9634       --
9635       SELECT 'Y'
9636         INTO l_po_line_is_consistent_flag
9637         FROM po_lines
9638        WHERE line_num = p_invoice_lines_rec.po_line_number
9639          AND po_line_id = l_po_line_id;
9640     EXCEPTION
9641       WHEN NO_DATA_FOUND THEN
9642         -- po number is inconsistent
9643         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
9644             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
9645             p_invoice_lines_rec.invoice_line_id,
9646             'INCONSISTENT PO LINE INFO',
9647             p_default_last_updated_by,
9648             p_default_last_update_login,
9649             current_calling_sequence) <> TRUE) THEN
9650           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
9651             AP_IMPORT_UTILITIES_PKG.Print(
9652             AP_IMPORT_INVOICES_PKG.g_debug_switch,
9653             'insert_rejections<-'||current_calling_sequence);
9654           END IF;
9655          RAISE check_po_failure;
9656         END IF;
9657         --
9658         l_current_invoice_status := 'N';
9659     END;
9660 
9661   END IF;
9662 
9663   -----------------------------------------------------------
9664   -- Case 7,  Reject if po_release_id is invalid
9665   -----------------------------------------------------------
9666   IF (l_po_release_id IS NOT NULL) THEN
9667     --
9668     BEGIN
9669       debug_info := '(v_check_line_po_info 7) Validate po_release_id';
9670       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
9671         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
9672                                       debug_info);
9673       END IF;
9674       --
9675       --
9676       SELECT 'Y'
9677         INTO l_po_release_is_valid_flag
9678         FROM po_releases
9679        WHERE po_release_id = l_po_release_id
9680        /* For bug 4038403. Added by lgopalsa
9681           Need to validate the lines for matching */
9682        and nvl(authorization_status, 'INCOMPLETE') in ('APPROVED',
9683                                                        'REQUIRES REAPPROVAL','IN PROCESS')--Bug5687122 --Added In Process condition
9684         AND NVL(closed_code, 'X') <> 'FINALLY CLOSED'; --Bug#13867905
9685 
9686     EXCEPTION
9687       WHEN NO_DATA_FOUND THEN
9688          -- po release id is invalid
9689          -- set contextual information for XML GATEWAY
9690          IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
9691                         AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
9692                         p_invoice_lines_rec.invoice_line_id,
9693                         'INVALID PO RELEASE NUM',
9694                         p_default_last_updated_by,
9695                         p_default_last_update_login,
9696                         current_calling_sequence) <> TRUE) THEN
9697            IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
9698              AP_IMPORT_UTILITIES_PKG.Print(
9699                AP_IMPORT_INVOICES_PKG.g_debug_switch,
9700                'insert_rejections<-'||current_calling_sequence);
9701            END IF;
9702            RAISE check_po_failure;
9703          END IF;
9704 
9705          l_current_invoice_status := 'N';
9706     END;
9707 
9708   END IF;
9709 
9710   ------------------------------------------------------------
9711   -- Case 8, Reject if po_release_num is invalid
9712   ------------------------------------------------------------
9713   IF ((p_invoice_lines_rec.release_num IS NOT NULL) AND
9714       (l_po_release_id IS NULL) AND
9715       (l_po_header_id IS NOT NULL)) THEN
9716     --
9717     BEGIN
9718       debug_info := '(v_check_line_po_info 8) Validate po_release_num';
9719       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
9720         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
9721                                       debug_info);
9722       END IF;
9723       --
9724       SELECT 'Y',
9725          po_release_id
9726         INTO l_po_release_is_valid_flag,
9727          l_po_release_id
9728         FROM po_releases
9729        WHERE release_num = p_invoice_lines_rec.release_num
9730          AND po_header_id = l_po_header_id
9731        /* For bug 4038403
9732           Need to validate the lines for matching */
9733        and nvl(authorization_status, 'INCOMPLETE') in ('APPROVED',
9734                                                        'REQUIRES REAPPROVAL','IN PROCESS') --Bug5687122 --Added In Process condition
9735        AND NVL(closed_code, 'X') <> 'FINALLY CLOSED'; --Bug#13867905
9736 
9737     EXCEPTION
9738       WHEN NO_DATA_FOUND THEN
9739         -- po release number is invalid
9740         -- Set contextual information for XML GATEWAY
9741         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
9742                         AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
9743                         p_invoice_lines_rec.invoice_line_id,
9744                         'INVALID PO RELEASE NUM',
9745                         p_default_last_updated_by,
9746                         p_default_last_update_login,
9747                         current_calling_sequence,
9748                         'Y',
9749                         'PO RELEASE NUMBER',
9750                         p_invoice_lines_rec.release_num) <> TRUE) THEN
9751           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
9752             AP_IMPORT_UTILITIES_PKG.Print(
9753             AP_IMPORT_INVOICES_PKG.g_debug_switch,
9754             'insert_rejections<-'||current_calling_sequence);
9755           END IF;
9756           RAISE check_po_failure;
9757         END IF;
9758 
9759         l_current_invoice_status := 'N';
9760     END;
9761 
9762   END IF;
9763 
9764 
9765   ---------------------------------------------------------------------------
9766   -- Case 9, Reject if po_release_id and release_num is inconsistent
9767   ---------------------------------------------------------------------------
9768   IF ((l_po_release_id IS NOT NULL) AND
9769       (p_invoice_lines_rec.release_num IS NOT NULL)) THEN
9770     --
9771     BEGIN
9772       debug_info := '(v_check_line_po_info 9) Check inconsistence for '
9773                     ||'release_num and po_release_id';
9774       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
9775         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
9776                                       debug_info);
9777       END IF;
9778       --
9779       SELECT 'Y'
9780         INTO l_po_rel_is_consistent_flag
9781         FROM po_releases
9782        WHERE release_num = p_invoice_lines_rec.release_num
9783          AND po_release_id = l_po_release_id;
9784     EXCEPTION
9785       WHEN NO_DATA_FOUND THEN
9786         -- po release information is inconsistent
9787         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
9788             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
9789             p_invoice_lines_rec.invoice_line_id,
9790             'INCONSISTENT RELEASE INFO',
9791             p_default_last_updated_by,
9792             p_default_last_update_login,
9793             current_calling_sequence) <> TRUE) THEN
9794           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
9795             AP_IMPORT_UTILITIES_PKG.Print(
9796             AP_IMPORT_INVOICES_PKG.g_debug_switch,
9797             'insert_rejections<-'||current_calling_sequence);
9798           END IF;
9799            RAISE check_po_failure;
9800         END IF;
9801         --
9802         l_current_invoice_status := 'N';
9803     END;
9804   END IF;
9805 
9806   ---------------------------------------------------------------------------
9807   -- Case 10, Reject if po_release_id and po_line_id is inconsistent
9808   ---------------------------------------------------------------------------
9809   IF ((l_po_release_id IS NOT NULL) AND
9810       (l_po_line_id IS NOT NULL)) THEN
9811     --
9812     BEGIN
9813       debug_info := '(v_check_line_po_info 10) Check inconsistence for '
9814                     ||'po_line_id and po_release_id';
9815       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
9816         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
9817                                       debug_info);
9818       END IF;
9819       --
9820       SELECT 'Y'
9821         INTO l_po_rel_is_consistent_flag
9822         FROM po_line_locations
9823        WHERE po_line_id = l_po_line_id
9824          AND po_release_id = l_po_release_id
9825       /*Bug 2787396 we need to validate the shipment level for matching */
9826          AND nvl(approved_flag, 'N' ) = 'Y'
9827          AND rownum <=1;
9828     EXCEPTION
9829       WHEN NO_DATA_FOUND THEN
9830         -- po release/line is inconsistent
9831         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
9832             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
9833             p_invoice_lines_rec.invoice_line_id,
9834             'INCONSISTENT RELEASE INFO',
9835             p_default_last_updated_by,
9836             p_default_last_update_login,
9837             current_calling_sequence) <> TRUE) THEN
9838           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
9839             AP_IMPORT_UTILITIES_PKG.Print(
9840             AP_IMPORT_INVOICES_PKG.g_debug_switch,
9841             'insert_rejections<-'||current_calling_sequence);
9842           END IF;
9843          RAISE check_po_failure;
9844         END IF;
9845         --
9846         l_current_invoice_status := 'N';
9847     END;
9848   END IF;
9849 
9850   ---------------------------------------------------------------------------
9851   -- Case 10.1, Reject if po_release has more than 1 line no line info is given
9852   ---------------------------------------------------------------------------
9853   IF ((l_po_release_id IS NOT NULL) AND
9854       (l_po_line_id IS NULL)) THEN
9855     --
9856     BEGIN
9857       debug_info :=
9858         '(v_check_line_po_info 10.1) Check lines for po_release_id ';
9859       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
9860         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
9861                                       debug_info);
9862       END IF;
9863       --
9864       SELECT DISTINCT po_line_id
9865         INTO l_po_line_id
9866         FROM po_line_locations
9867        WHERE po_release_id = l_po_release_id
9868       /* For bug 4038403
9869          we should check at line location level approved flag
9870          as we can do invoicing for the line/shipment for which
9871          receipt is allowed and the document is already
9872          undergone approval. */
9873          AND approved_flag ='Y'
9874       /* Bug 9853166 no rejection necessary when shipment_num has
9875          been specified and it will differentiate the lines */
9876          AND nvl(shipment_num, -99) = coalesce(p_invoice_lines_rec.po_shipment_num
9877                                           , shipment_num, -99);
9878 
9879 
9880 
9881     EXCEPTION
9882       WHEN NO_DATA_FOUND THEN
9883         -- po release/line is inconsistent
9884         -- set contextual information for XML GATEWAY
9885         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
9886                         AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
9887                         p_invoice_lines_rec.invoice_line_id,
9888                         'INVALID PO RELEASE INFO',
9889                         p_default_last_updated_by,
9890                         p_default_last_update_login,
9891                         current_calling_sequence,
9892                         'Y',
9893                         'PO RELEASE NUMBER',
9894                         p_invoice_lines_rec.release_num,
9895                         'PO SHIPMENT NUMBER',
9896                         p_invoice_lines_rec.po_shipment_num,
9897                         'PO LINE NUMBER',
9898                         p_invoice_lines_rec.po_line_number) <> TRUE) THEN
9899           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
9900             AP_IMPORT_UTILITIES_PKG.Print(
9901             AP_IMPORT_INVOICES_PKG.g_debug_switch,
9902             'insert_rejections<-'||current_calling_sequence);
9903           END IF;
9904           RAISE check_po_failure;
9905         END IF;
9906 
9907         l_current_invoice_status := 'N';
9908 
9909       WHEN TOO_MANY_ROWS THEN
9910         -- po release
9911         IF ((p_invoice_lines_rec.po_line_number IS NULL)      AND
9912             (p_invoice_lines_rec.inventory_item_id IS NULL)   AND
9913             (p_invoice_lines_rec.vendor_item_num IS NULL)     AND
9914             (p_invoice_lines_rec.item_description IS NULL)    AND
9915             (l_po_line_location_id IS NULL) AND
9916             (l_po_distribution_id IS NULL)) THEN
9917 
9918           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
9919             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
9920             p_invoice_lines_rec.invoice_line_id,
9921             'CAN MATCH TO ONLY 1 LINE',
9922             p_default_last_updated_by,
9923             p_default_last_update_login,
9924             current_calling_sequence) <> TRUE) THEN
9925             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
9926               AP_IMPORT_UTILITIES_PKG.Print(
9927               AP_IMPORT_INVOICES_PKG.g_debug_switch,
9928               'insert_rejections<-'||current_calling_sequence);
9929             END IF;
9930             RAISE check_po_failure;
9931           END IF;
9932 
9933           l_current_invoice_status := 'N';
9934         END IF;
9935 
9936     END;
9937 
9938   END IF;
9939 
9940 --case 10.2 added for bug 4525041
9941  ---------------------------------------------------------------------------
9942   -- Case 10.2, Reject if release_num and po_line_number is inconsistent
9943  ---------------------------------------------------------------------------
9944   IF ((p_invoice_lines_rec.release_num IS NOT NULL) AND (p_invoice_lines_rec.po_line_number IS NOT NULL)
9945        AND (l_po_header_id is not null OR p_invoice_lines_rec.po_number is not null)) THEN
9946 
9947       BEGIN
9948       debug_info :=
9949       '(v_check_line_po_info 10.2) Check lines for po_release_id ';
9950       /* For bug 4038403
9951         Removed the 'STANDARD' from the condition  from both
9952          the queries as there is no need to validate the release
9953          details for standard PO */
9954 
9955       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
9956         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
9957                                       debug_info);
9958      End if;
9959 
9960       IF l_po_header_id IS NOT NULL THEN -- Fix for 2809177
9961         SELECT 'Y'
9962           INTO l_po_rel_is_consistent_flag
9963           FROM po_line_locations
9964           WHERE po_line_id = (
9965                 select po_line_id
9966                   from po_lines pol, po_headers poh
9967                 where poh.po_header_id = pol.po_header_id
9968                   -- and poh.po_header_id = nvl(l_po_header_id, poh.po_header_id)
9969                   -- fix for bug 2809177 commented above line and wrote the below one
9970                   and poh.po_header_id = l_po_header_id
9971                   -- Commented below line as a fix for bug 2809177
9972                   -- and poh.segment1 = nvl(p_invoice_lines_rec.po_number, poh.segment1)
9973                   and poh.type_lookup_code in ('BLANKET', 'PLANNED') --, 'STANDARD')
9974                   and pol.po_line_id = nvl(l_po_line_id, pol.po_line_id)
9975                   and pol.line_num = p_invoice_lines_rec.po_line_number )
9976             AND po_release_id = (
9977                 select po_release_id
9978                   from po_releases por, po_headers poh
9979                 where poh.po_header_id = por.po_header_id
9980                   -- and poh.po_header_id = nvl(l_po_header_id, poh.po_header_id)
9981                   -- fix for bug 2809177 commented above line and wrote the below one
9982                   and poh.po_header_id = l_po_header_id
9983                   -- Commented below line as a fix for bug 2809177
9984                   -- and poh.segment1 = nvl(p_invoice_lines_rec.po_number, poh.segment1)
9985                   and poh.type_lookup_code in ('BLANKET', 'PLANNED')--, 'STANDARD')
9986                   and por.po_header_id = l_po_header_id  -- Added as a fix for bug 2809177
9987                   and por.release_num = p_invoice_lines_rec.release_num )
9988             AND rownum <=1;
9989       ELSIF p_invoice_lines_rec.po_number IS NOT NULL THEN
9990         SELECT 'Y'
9991           INTO l_po_rel_is_consistent_flag
9992           FROM po_line_locations
9993           WHERE po_line_id = (
9994                 select po_line_id
9995                   from po_lines pol, po_headers poh
9996                 where poh.po_header_id = pol.po_header_id
9997                   -- and poh.po_header_id = nvl(l_po_header_id, poh.po_header_id)
9998                   -- and poh.segment1 = nvl(p_invoice_lines_rec.po_number, poh.segment1)
9999                   -- fix for bug 2809177 commented above two lines and wrote the below one
10000                   and poh.segment1 = p_invoice_lines_rec.po_number
10001                   and poh.type_lookup_code in ('BLANKET', 'PLANNED', 'STANDARD')
10002                   and pol.po_line_id = nvl(l_po_line_id, pol.po_line_id)
10003                   and pol.line_num = p_invoice_lines_rec.po_line_number )
10004             AND po_release_id = (
10005                 select po_release_id
10006                   from po_releases por, po_headers poh
10007                 where poh.po_header_id = por.po_header_id
10008                   -- and poh.po_header_id = nvl(l_po_header_id, poh.po_header_id)
10009                   -- and poh.segment1 = nvl(p_invoice_lines_rec.po_number, poh.segment1)
10010                   -- fix for bug 2809177 commented above two line and wrote the below one
10011                   and poh.segment1 = p_invoice_lines_rec.po_number
10012                   and poh.type_lookup_code in ('BLANKET', 'PLANNED', 'STANDARD')
10013                   and por.release_num = p_invoice_lines_rec.release_num )
10014             AND rownum <=1;
10015       END IF ;
10016 
10017       EXCEPTION
10018       WHEN NO_DATA_FOUND THEN
10019           -- po release/line is inconsistent
10020         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
10021                         AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
10022                         p_invoice_lines_rec.invoice_line_id,
10023                         'INCONSISTENT RELEASE INFO',
10024                         p_default_last_updated_by,
10025                         p_default_last_update_login,
10026                         current_calling_sequence
10027                         ) <> TRUE) THEN
10028           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
10029             AP_IMPORT_UTILITIES_PKG.Print(
10030             AP_IMPORT_INVOICES_PKG.g_debug_switch,
10031             'insert_rejections<-'||current_calling_sequence);
10032           END IF;
10033           RAISE check_po_failure;
10034 END IF;
10035       END;
10036 END IF;
10037   ------------------------------------------------------------
10038   -- Case 11, Reject if p_inventory_item_id is invalid
10039   ------------------------------------------------------------
10040   IF ((p_invoice_lines_rec.inventory_item_id IS NOT NULL) AND
10041       (l_po_line_id IS NULL) AND
10042       (l_po_release_id IS NULL) AND
10043       (l_po_header_id IS NOT NULL)) THEN
10044     --
10045     BEGIN
10046       debug_info :=
10047         '(v_check_line_po_info 11) Validate p_inventory_item_id';
10048       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
10049         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
10050                                       debug_info);
10051       END IF;
10052       --
10053       SELECT 'Y', po_line_id
10054         INTO l_po_is_valid_flag, l_po_line_id
10055         FROM po_lines
10056        WHERE item_id = p_invoice_lines_rec.inventory_item_id
10057          AND po_header_id = l_po_header_id;
10058     EXCEPTION
10059       WHEN NO_DATA_FOUND THEN
10060         -- po item id is invalid
10061         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
10062             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
10063             p_invoice_lines_rec.invoice_line_id,
10064             'INVALID ITEM',
10065             p_default_last_updated_by,
10066             p_default_last_update_login,
10067             current_calling_sequence) <> TRUE) THEN
10068           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
10069             AP_IMPORT_UTILITIES_PKG.Print(
10070             AP_IMPORT_INVOICES_PKG.g_debug_switch,
10071             'insert_rejections<-'||current_calling_sequence);
10072           END IF;
10073            RAISE check_po_failure;
10074         END IF;
10075         --
10076         l_current_invoice_status := 'N';
10077 
10078       WHEN TOO_MANY_ROWS Then
10079         IF ((l_po_line_id    IS NULL) AND
10080             (p_invoice_lines_rec.po_line_number IS NULL) AND
10081             (l_po_line_location_id IS NULL) AND
10082             (l_po_distribution_id IS NULL)) Then
10083           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
10084                 AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
10085                  p_invoice_lines_rec.invoice_line_id,
10086                 'CAN MATCH TO ONLY 1 LINE',
10087                  p_default_last_updated_by,
10088                  p_default_last_update_login,
10089                  current_calling_sequence) <> TRUE) THEN
10090             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
10091               AP_IMPORT_UTILITIES_PKG.Print(
10092                 AP_IMPORT_INVOICES_PKG.g_debug_switch,
10093                 'insert_rejections<-'||current_calling_sequence);
10094             END IF;
10095             RAISE check_po_failure;
10096           END IF;
10097 
10098           l_current_invoice_status := 'N';
10099 
10100         END IF;
10101     END;
10102   END IF;
10103 
10104   -----------------------------------------------------------------------
10105   -- Case 11.5, Reject if p_vendor_item_num is invalid -- Bug 1873251
10106   -- changed (p_po_line_id is NULL) to (l_po_line_id is NULL) Bug 2642098
10107   -----------------------------------------------------------------------
10108   IF ((p_invoice_lines_rec.vendor_item_num IS NOT NULL) AND
10109       (l_po_line_id IS NULL) AND
10110       (l_po_release_id IS NULL) AND
10111       (l_po_header_id IS NOT NULL)) THEN
10112     --
10113     BEGIN
10114       debug_info := '(v_check_line_po_info 11.5) Validate p_vendor_item_num';
10115       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
10116         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
10117                                       debug_info);
10118       END IF;
10119       --
10120       SELECT 'Y', po_line_id
10121         INTO l_po_is_valid_flag, l_po_line_id
10122         FROM po_lines
10123        WHERE vendor_product_num = p_invoice_lines_rec.vendor_item_num
10124          AND po_header_id = l_po_header_id;
10125     EXCEPTION
10126       WHEN NO_DATA_FOUND THEN
10127         -- po item id is invalid
10128         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
10129                        AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
10130                         p_invoice_lines_rec.invoice_line_id,
10131                         'INVALID ITEM',
10132                         p_default_last_updated_by,
10133                         p_default_last_update_login,
10134                         current_calling_sequence,
10135                         'Y',
10136                         'SUPPLIER ITEM NUMBER',
10137                         p_invoice_lines_rec.vendor_item_num ) <> TRUE) THEN
10138           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
10139             AP_IMPORT_UTILITIES_PKG.Print(
10140               AP_IMPORT_INVOICES_PKG.g_debug_switch,
10141               'insert_rejections<-'||current_calling_sequence);
10142           END IF;
10143           RAISE check_po_failure;
10144         END IF;
10145 
10146         l_current_invoice_status := 'N';
10147 
10148       WHEN TOO_MANY_ROWS THEN
10149         IF ((l_po_line_id    IS NULL)         AND
10150             (p_invoice_lines_rec.po_line_number IS NULL)      AND
10151         (l_po_line_location_id IS NULL) AND
10152             (l_po_distribution_id IS NULL)) THEN
10153 
10154           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
10155                 AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
10156                  p_invoice_lines_rec.invoice_line_id,
10157                  'CAN MATCH TO ONLY 1 LINE',
10158                  p_default_last_updated_by,
10159                  p_default_last_update_login,
10160                   current_calling_sequence,
10161                  'Y',
10162                  'SUPPLIER ITEM NUMBER',
10163                  p_invoice_lines_rec.vendor_item_num ) <> TRUE) THEN
10164             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
10165               AP_IMPORT_UTILITIES_PKG.Print(
10166                 AP_IMPORT_INVOICES_PKG.g_debug_switch,
10167                 'insert_rejections<-'||current_calling_sequence);
10168             END IF;
10169             RAISE check_po_failure;
10170           END IF;
10171 
10172           l_current_invoice_status := 'N';
10173 
10174         END IF;
10175     END;
10176   END IF;
10177 
10178   ---------------------------------------------------------------------------
10179   -- Case 12, Reject if p_item_description is invalid
10180   -- changed (p_po_line_id is NULL) to (l_po_line_id is NULL) Bug 2642098
10181   ---------------------------------------------------------------------------
10182   IF ((p_invoice_lines_rec.item_description IS NOT NULL) AND
10183       (l_po_line_id IS NULL) AND
10184       (l_po_release_id IS NULL) AND
10185       (l_po_header_id IS NOT NULL)) THEN
10186     --
10187     BEGIN
10188       debug_info := '(v_check_line_po_info 12) Validate p_item_description';
10189       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
10190         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
10191                                       debug_info);
10192       END IF;
10193       --
10194       SELECT 'Y', po_line_id
10195         INTO l_po_is_valid_flag, l_po_line_id
10196         FROM po_lines
10197        WHERE item_description like p_invoice_lines_rec.item_description
10198          AND po_header_id = l_po_header_id;
10199     EXCEPTION
10200       WHEN NO_DATA_FOUND THEN
10201         -- po item id is invalid
10202         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
10203             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
10204             p_invoice_lines_rec.invoice_line_id,
10205             'INVALID ITEM',
10206             p_default_last_updated_by,
10207             p_default_last_update_login,
10208             current_calling_sequence) <> TRUE) THEN
10209           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
10210             AP_IMPORT_UTILITIES_PKG.Print(
10211               AP_IMPORT_INVOICES_PKG.g_debug_switch,
10212               'insert_rejections<-'||current_calling_sequence);
10213           END IF;
10214            RAISE check_po_failure;
10215         END IF;
10216         l_current_invoice_status := 'N';
10217 
10218       WHEN TOO_MANY_ROWS Then
10219 
10220         IF ((l_po_line_id    IS NULL)     AND
10221         (p_invoice_lines_rec.po_line_number IS NULL)    AND
10222         (l_po_line_location_id IS NULL) AND
10223         (l_po_distribution_id IS NULL)) THEN
10224 
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                 'CAN MATCH TO ONLY 1 LINE',
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 
10242         END IF;
10243 
10244     END;
10245 
10246   END IF;
10247 
10248   ---------------------------------------------------------------------------
10249   -- Case 13, Reject if po_inventory_item_id, p_vendor_item_num
10250   --                          and po_item_description are inconsistent
10251   --
10252   --  Added consistency check for Supplier Item Number too as part of
10253   --  the effort to support Supplier Item Number in Invoice Import
10254   --                                                         bug 1873251
10255   ---------------------------------------------------------------------------
10256 
10257   IF ((p_invoice_lines_rec.inventory_item_id IS NOT NULL) AND
10258       (p_invoice_lines_rec.vendor_item_num IS NOT NULL) AND
10259       (l_po_header_id IS NOT NULL)) THEN
10260       --
10261      BEGIN
10262       debug_info := '(v_check_line_po_info 13.1) Check inconsistency for '
10263                     ||'po_inventory_item_id and po_vendor_item_num';
10264       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
10265         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
10266                                       debug_info);
10267       END IF;
10268       --
10269       SELECT 'Y'
10270         INTO l_po_line_is_consistent_flag
10271         FROM po_lines
10272        WHERE item_id = p_invoice_lines_rec.inventory_item_id
10273          AND vendor_product_num = p_invoice_lines_rec.vendor_item_num
10274          AND po_header_id = l_po_header_id;
10275      EXCEPTION
10276        WHEN NO_DATA_FOUND THEN
10277         -- po line information is inconsistent
10278         -- bug 2581097 added contextual information for XML GATEWAY
10279          IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
10280                         AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
10281                         p_invoice_lines_rec.invoice_line_id,
10282                         'INCONSISTENT PO LINE INFO',
10283                         p_default_last_updated_by,
10284                         p_default_last_update_login,
10285                         current_calling_sequence,
10286                         'Y',
10287                         'SUPPLIER ITEM NUMBER',
10288                         p_invoice_lines_rec.vendor_item_num ) <> TRUE) THEN
10289            IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
10290              AP_IMPORT_UTILITIES_PKG.Print(
10291                AP_IMPORT_INVOICES_PKG.g_debug_switch,
10292                'insert_rejections<-'||current_calling_sequence);
10293            END IF;
10294            RAISE check_po_failure;
10295          END IF;
10296 
10297          l_current_invoice_status := 'N';
10298 
10299        WHEN TOO_MANY_ROWS Then
10300 
10301               IF ((l_po_line_id    IS NULL)          AND
10302               (p_invoice_lines_rec.po_line_number IS NULL)      AND
10303               (l_po_line_location_id IS NULL) AND
10304               (l_po_distribution_id IS NULL)) THEN
10305 
10306                   -- bug 2581097 added contextual information for XML GATEWAY
10307 
10308                   IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
10309                         AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
10310                         p_invoice_lines_rec.invoice_line_id,
10311                         'CAN MATCH TO ONLY 1 LINE',
10312                         p_default_last_updated_by,
10313                         p_default_last_update_login,
10314                         current_calling_sequence,
10315                         'Y',
10316                         'SUPPLIER ITEM NUMBER',
10317                         p_invoice_lines_rec.vendor_item_num ) <> TRUE) THEN
10318 
10319                     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
10320                 AP_IMPORT_UTILITIES_PKG.Print(
10321                       AP_IMPORT_INVOICES_PKG.g_debug_switch,
10322                   'insert_rejections<-'||current_calling_sequence);
10323                     END IF;
10324                     RAISE check_po_failure;
10325                   END IF;
10326 
10327                 l_current_invoice_status := 'N';
10328 
10329               END IF;
10330      END;
10331 
10332   ELSIF ((p_invoice_lines_rec.inventory_item_id IS NOT NULL) AND
10333          (p_invoice_lines_rec.item_description IS NOT NULL)  AND
10334          (l_po_header_id IS NOT NULL))     THEN
10335       --
10336      BEGIN
10337       debug_info := '(v_check_line_po_info 13.2) Check inconsistency for '
10338                     ||'po_inventory_item_id and po_item_description'||l_po_line_location_id;
10339       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
10340         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
10341                                       debug_info);
10342       END IF;
10343       --
10344       /* Added the code for Bug#10026073 Start */
10345       IF l_po_line_location_id IS NOT NULL
10346       THEN
10347         SELECT 'Y'
10348           INTO l_po_line_is_consistent_flag
10349           FROM po_lines pl
10350              , po_line_locations pll
10351          WHERE pl.item_id = p_invoice_lines_rec.inventory_item_id
10352            AND nvl(pll.description, pl.item_description) like p_invoice_lines_rec.item_description
10353            AND pl.po_header_id      = pll.po_header_id
10354            AND pll.po_header_id     = l_po_header_id
10355            AND pll.line_location_id = l_po_line_location_id;
10356 
10357       ELSE
10358         SELECT 'Y'
10359           INTO l_po_line_is_consistent_flag
10360           FROM po_lines
10361          WHERE item_id = p_invoice_lines_rec.inventory_item_id
10362            AND item_description like p_invoice_lines_rec.item_description
10363            AND po_header_id = l_po_header_id;
10364       END IF;
10365       /* Added the code for Bug#10026073 End */
10366      EXCEPTION
10367        WHEN NO_DATA_FOUND THEN
10368          -- po line information is inconsistent
10369          IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
10370             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
10371             p_invoice_lines_rec.invoice_line_id,
10372             'INCONSISTENT PO LINE INFO',
10373             p_default_last_updated_by,
10374             p_default_last_update_login,
10375             current_calling_sequence) <> TRUE) THEN
10376 
10377        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
10378                AP_IMPORT_UTILITIES_PKG.Print(
10379                  AP_IMPORT_INVOICES_PKG.g_debug_switch,
10380                  'insert_rejections<-'||current_calling_sequence);
10381            END IF;
10382            RAISE check_po_failure;
10383          END IF;
10384          l_current_invoice_status := 'N';
10385 
10386         WHEN TOO_MANY_ROWS Then
10387 
10388           IF ((l_po_line_id    IS NULL) AND
10389               (p_invoice_lines_rec.po_line_number IS NULL) AND
10390           (l_po_line_location_id IS NULL) AND
10391           (l_po_distribution_id IS NULL)) Then
10392 
10393              IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
10394                   AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
10395                        p_invoice_lines_rec.invoice_line_id,
10396                       'CAN MATCH TO ONLY 1 LINE',
10397                        p_default_last_updated_by,
10398                        p_default_last_update_login,
10399                        current_calling_sequence) <> TRUE) THEN
10400 
10401              IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
10402                   AP_IMPORT_UTILITIES_PKG.Print(
10403                            AP_IMPORT_INVOICES_PKG.g_debug_switch,
10404                           'insert_rejections<-'||current_calling_sequence);
10405                 END IF;
10406           RAISE check_po_failure;
10407               END IF;
10408 
10409               l_current_invoice_status := 'N';
10410 
10411             END IF;
10412      END;
10413 
10414   END IF;
10415 
10416   ---------------------------------------------------------------------------
10417   -- Case 14, Reject if po_line_id and p_inventory_item_id are inconsistent
10418   ---------------------------------------------------------------------------
10419 
10420   IF ((l_po_line_id IS NOT NULL) AND
10421       (p_invoice_lines_rec.inventory_item_id IS NOT NULL)) THEN
10422       --
10423      BEGIN
10424        debug_info := '(v_check_line_po_info 14) Check inconsistency for '
10425                      ||'po_line_id and po_inventory_item_id';
10426        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
10427          AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
10428                                       debug_info);
10429        END IF;
10430        --
10431        --
10432        SELECT 'Y'
10433        INTO l_po_line_is_consistent_flag
10434      FROM po_lines
10435         WHERE item_id = p_invoice_lines_rec.inventory_item_id
10436       AND po_line_id = l_po_line_id;
10437      EXCEPTION
10438        WHEN NO_DATA_FOUND THEN
10439          -- po line information is inconsistent
10440          IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
10441             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
10442              p_invoice_lines_rec.invoice_line_id,
10443             'INCONSISTENT PO LINE INFO',
10444              p_default_last_updated_by,
10445              p_default_last_update_login,
10446              current_calling_sequence) <> TRUE) THEN
10447 
10448        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
10449              AP_IMPORT_UTILITIES_PKG.Print(
10450                 AP_IMPORT_INVOICES_PKG.g_debug_switch,
10451                 'insert_rejections<-'||current_calling_sequence);
10452            END IF;
10453            RAISE check_po_failure;
10454          END IF;
10455          --
10456          l_current_invoice_status := 'N';
10457      END;
10458 
10459   END IF;
10460 
10461   ---------------------------------------------------------------------------
10462   -- Case 15, Reject if po_line_id and p_vendor_item_num are inconsistent
10463   --      Support for Supplier Item Number     , bug 1873251
10464   ---------------------------------------------------------------------------
10465 
10466   IF ((l_po_line_id IS NOT NULL) AND
10467       (p_invoice_lines_rec.vendor_item_num IS NOT NULL)) THEN
10468       --
10469      BEGIN
10470        debug_info := '(v_check_line_po_info 15) Check inconsistency for '
10471                      ||'po_line_id and po_vendor_item_num';
10472        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
10473          AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
10474                                       debug_info);
10475        END IF;
10476 
10477        --
10478        SELECT 'Y'
10479            INTO l_po_line_is_consistent_flag
10480          FROM po_lines
10481         WHERE vendor_product_num = p_invoice_lines_rec.vendor_item_num
10482           AND po_line_id = l_po_line_id;
10483      EXCEPTION
10484        WHEN NO_DATA_FOUND THEN
10485          -- po line information is inconsistent
10486          -- bug 2581097 added contextual information for XML GATEWAY
10487          IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
10488                         AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
10489                         p_invoice_lines_rec.invoice_line_id,
10490                         'INCONSISTENT PO LINE INFO',
10491                         p_default_last_updated_by,
10492                         p_default_last_update_login,
10493                         current_calling_sequence,
10494                         'Y',
10495                         'SUPPLIER ITEM NUMBER',
10496                         p_invoice_lines_rec.vendor_item_num ) <> TRUE) THEN
10497            IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
10498              AP_IMPORT_UTILITIES_PKG.Print(
10499                AP_IMPORT_INVOICES_PKG.g_debug_switch,
10500               'insert_rejections<-'||current_calling_sequence);
10501            END IF;
10502            RAISE check_po_failure;
10503          END IF;
10504 
10505          l_current_invoice_status := 'N';
10506      END;
10507 
10508   END IF;
10509 
10510   ---------------------------------------------------------------------------
10511   -- Case 15.1, Reject if po_line_id and vendor_item_num are inconsistent
10512   --      Support for Supplier Item Number
10513   -- Amount Based Matching - Line should be rejected if Supplier item  No is
10514   -- supplied for service order line. However due to complex work project
10515   -- match basis will be moved at po shipment level hence all the matching
10516   -- basis related validation  will moved to shipment level.
10517   ---------------------------------------------------------------------------
10518 
10519   IF ((p_invoice_lines_rec.po_line_number IS NOT NULL) AND
10520       (p_invoice_lines_rec.vendor_item_num IS NOT NULL) AND
10521       (l_po_header_id IS NOT NULL)) THEN
10522       --
10523      BEGIN
10524        debug_info := '(v_check_line_po_info 15.1) Check inconsistency for '
10525                      ||'po_line_number and po_vendor_item_num';
10526        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
10527          AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
10528                                       debug_info);
10529        END IF;
10530 
10531        --
10532        SELECT 'Y'
10533        INTO l_po_line_is_consistent_flag
10534        FROM po_lines pl
10535       WHERE pl.line_num = p_invoice_lines_rec.po_line_number
10536         AND vendor_product_num = p_invoice_lines_rec.vendor_item_num
10537         AND pl.po_header_id = l_po_header_id;
10538      EXCEPTION
10539        WHEN NO_DATA_FOUND THEN
10540          -- po line information is inconsistent
10541          -- bug 2581097 added contextual information for XML GATEWAY
10542          IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
10543                         AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
10544                         p_invoice_lines_rec.invoice_line_id,
10545                         'INCONSISTENT PO LINE INFO',
10546                         p_default_last_updated_by,
10547                         p_default_last_update_login,
10548                         current_calling_sequence,
10549                         'Y',
10550                         'SUPPLIER ITEM NUMBER',
10551                         p_invoice_lines_rec.vendor_item_num ) <> TRUE) THEN
10552            IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
10553              AP_IMPORT_UTILITIES_PKG.Print(
10554                AP_IMPORT_INVOICES_PKG.g_debug_switch,
10555               'insert_rejections<-'||current_calling_sequence);
10556            END IF;
10557            RAISE check_po_failure;
10558          END IF;
10559 
10560          l_current_invoice_status := 'N';
10561      END;
10562 
10563   END IF;
10564 
10565   ---------------------------------------------------------------------------
10566   -- Case 15.2, Reject if po_line_id and vendor_item_num are inconsistent
10567   --      Support for Supplier Item Number
10568   -- Amount Based Matching - Line should be rejected if inventory item  No is
10569   -- supplied for service order line. However due to complex work project
10570   -- match basis will be moved at po shipment level hence all the matching
10571   -- basis related validation  will moved to shipment level.
10572   ---------------------------------------------------------------------------
10573 
10574   IF ((p_invoice_lines_rec.po_line_number IS NOT NULL) AND
10575       (p_invoice_lines_rec.inventory_item_id IS NOT NULL) AND
10576       (l_po_header_id IS NOT NULL)) THEN
10577       --
10578      BEGIN
10579        debug_info := '(v_check_line_po_info 15.1) Check inconsistency for '
10580                      ||'po_line_number and inventory_item_id';
10581        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
10582          AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
10583                                       debug_info);
10584        END IF;
10585 
10586        --
10587        SELECT 'Y'
10588        INTO l_po_line_is_consistent_flag
10589        FROM po_lines pl
10590       WHERE pl.line_num = p_invoice_lines_rec.po_line_number
10591         -- Bug 6734046 changed vendor_product_num to item_id
10592         AND pl.item_id = p_invoice_lines_rec.inventory_item_id
10593         AND pl.po_header_id = l_po_header_id;
10594      EXCEPTION
10595        WHEN NO_DATA_FOUND THEN
10596          -- po line information is inconsistent
10597          -- bug 2581097 added contextual information for XML GATEWAYi
10598          IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
10599             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
10600              p_invoice_lines_rec.invoice_line_id,
10601             'INCONSISTENT PO LINE INFO',
10602              p_default_last_updated_by,
10603              p_default_last_update_login,
10604              current_calling_sequence) <> TRUE) THEN
10605            IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
10606              AP_IMPORT_UTILITIES_PKG.Print(
10607                AP_IMPORT_INVOICES_PKG.g_debug_switch,
10608               'insert_rejections<-'||current_calling_sequence);
10609            END IF;
10610            RAISE check_po_failure;
10611          END IF;
10612 
10613          l_current_invoice_status := 'N';
10614      END;
10615 
10616   END IF;
10617 
10618 /* Start changes for CLM project bug9503239*/
10619  ---------------------------------------------------------
10620  -- Case 15.3, Reject if po_line is only information line
10621  -- for CLM PO's
10622  ----------------------------------------------------------
10623 
10624 IF ((ap_clm_pvt_pkg.is_clm_installed ='Y' ) and (l_po_header_id is not null )) THEN
10625 
10626  IF(ap_clm_pvt_pkg.is_clm_po(p_po_header_id => l_po_header_id) = 'Y')THEN
10627 ---------------------------------------------------------
10628 -- Reject if po_line is only information line for CLM PO's
10629 -- and po_line_num is provided.
10630 ---------------------------------------------------------
10631    IF (p_invoice_lines_rec.po_line_number IS NOT NULL) THEN
10632       BEGIN
10633        debug_info := '(v_check_line_po_info 15.3) Check whether PO line is information line'
10634                          ||p_invoice_lines_rec.po_line_number;
10635            IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
10636                AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
10637            END IF;
10638 
10639            SELECT 'Y'
10640            INTO l_po_line_is_consistent_flag
10641            FROM po_lines_trx_v pltv,
10642                 po_lines pl
10643            WHERE pl.line_num = p_invoice_lines_rec.po_line_number
10644            AND pl.po_line_id = pltv.po_line_id
10645            AND pl.po_header_id = l_po_header_id;
10646       EXCEPTION
10647        WHEN NO_DATA_FOUND THEN
10648          -- po line is information line
10649          IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
10650              AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
10651              p_invoice_lines_rec.invoice_line_id,
10652              'INVALID PO LINE NUM',
10653              p_default_last_updated_by,
10654             p_default_last_update_login,
10655             current_calling_sequence) <> TRUE) THEN
10656 
10657            IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
10658              AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
10659                                         'insert_rejections<-' ||current_calling_sequence);
10660            END IF;
10661           RAISE check_po_failure;
10662         END IF;
10663          l_current_invoice_status := 'N';
10664       END;
10665    END IF;
10666 
10667 ---------------------------------------------------------
10668 -- Reject if po_line is only information line for CLM PO's
10669 -- and po_line_id is provided
10670 ----------------------------------------------------------
10671    IF (l_po_line_id IS NOT NULL ) THEN
10672        BEGIN
10673           debug_info := '(v_check_line_po_info 15.3) Check whether PO line is information line '
10674                                         ||p_invoice_lines_rec.po_line_number;
10675         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
10676            AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
10677         END IF;
10678 
10679            SELECT 'Y'
10680            INTO l_po_line_is_consistent_flag
10681            FROM po_lines_trx_v
10682            WHERE po_line_id = l_po_line_id
10683            AND po_header_id = l_po_header_id;
10684        EXCEPTION
10685        	WHEN NO_DATA_FOUND THEN
10686           -- po line is information line
10687           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
10688                                  AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
10689                                  p_invoice_lines_rec.invoice_line_id,
10690                                  'INVALID PO LINE NUM',
10691                                  p_default_last_updated_by,
10692                                  p_default_last_update_login,
10693                                  current_calling_sequence) <> TRUE) THEN
10694             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
10695                AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
10696                                           'insert_rejections<-'||current_calling_sequence);
10697             END IF;
10698            RAISE check_po_failure;
10699           END IF;
10700        l_current_invoice_status := 'N';
10701        END;
10702       END IF;
10703   END IF;
10704 END IF;
10705 
10706 /* End changes for CLM project bug9503239 */
10707 
10708   -----------------------------------------------------------
10709   -- Case 16,  Reject if po_line_location_id is invalid
10710   -----------------------------------------------------------
10711 
10712   IF (l_po_line_location_id IS NOT NULL ) THEN
10713     --
10714     BEGIN
10715       debug_info := '(v_check_line_po_info 16) Validate po_line_location_id';
10716       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
10717         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
10718                                       debug_info);
10719       END IF;
10720       --
10721       SELECT 'Y'
10722         INTO l_po_shipment_is_valid_flag
10723         FROM po_line_locations
10724        WHERE line_location_id = l_po_line_location_id
10725        /* For bug 4038403
10726              Need to check the validation for
10727              line location approved_flag */
10728          and approved_flag ='Y'
10729 	 and NVL(closed_code, 'X') <> 'FINALLY CLOSED'; --Bug#13867905;
10730 
10731     EXCEPTION
10732       WHEN NO_DATA_FOUND THEN
10733         -- po line location id is invalid
10734         -- bug 2581097 added contextual information for XML GATEWAY
10735         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
10736                  AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
10737                   p_invoice_lines_rec.invoice_line_id,
10738                  'INVALID PO SHIPMENT NUM',
10739                   p_default_last_updated_by,
10740                   p_default_last_update_login,
10741                   current_calling_sequence,
10742                  'Y',
10743                  'PO SHIPMENT NUMBER',
10744                   p_invoice_lines_rec.po_shipment_num) <> TRUE) THEN
10745           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
10746             AP_IMPORT_UTILITIES_PKG.Print(
10747               AP_IMPORT_INVOICES_PKG.g_debug_switch,
10748               'insert_rejections<-'||current_calling_sequence);
10749           END IF;
10750           RAISE check_po_failure;
10751         END IF;
10752 
10753       l_current_invoice_status := 'N';
10754     END;
10755 
10756   END IF;
10757 
10758 
10759   ------------------------------------------------------------
10760   -- Case 17, Reject if po_shipment_num is invalid
10761   ------------------------------------------------------------
10762 
10763   IF ((p_invoice_lines_rec.po_shipment_num IS NOT NULL) AND
10764       (l_po_line_location_id IS NULL) AND
10765       (l_po_header_id IS NOT NULL)    AND
10766       (l_po_line_id IS NOT NULL)      AND
10767       (l_po_release_id IS NULL))     THEN
10768     --
10769     BEGIN
10770       debug_info := '(v_check_line_po_info 17) Validate po_shipment_num';
10771       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
10772         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
10773                                       debug_info);
10774       END IF;
10775       --
10776 
10777       SELECT 'Y', line_location_id
10778          INTO l_po_shipment_is_valid_flag, l_po_line_location_id
10779         FROM po_line_locations
10780        WHERE shipment_num = p_invoice_lines_rec.po_shipment_num
10781          AND po_header_id = l_po_header_id
10782          AND po_line_id = l_po_line_id
10783 	 	 AND NVL(closed_code, 'X') <> 'FINALLY CLOSED'; --Bug#13867905;
10784     EXCEPTION
10785       WHEN NO_DATA_FOUND THEN
10786         -- po shipment number is invalid
10787         -- bug 2581097 added contextual information for XML GATEWAY
10788         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
10789                         AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
10790                         p_invoice_lines_rec.invoice_line_id,
10791                         'INVALID PO SHIPMENT NUM',
10792                         p_default_last_updated_by,
10793                         p_default_last_update_login,
10794                         current_calling_sequence,
10795                         'Y',
10796                         'PO SHIPMENT NUMBER',
10797                         p_invoice_lines_rec.po_shipment_num) <> TRUE) THEN
10798           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
10799             AP_IMPORT_UTILITIES_PKG.Print(
10800               AP_IMPORT_INVOICES_PKG.g_debug_switch,
10801               'insert_rejections<-'||current_calling_sequence);
10802           END IF;
10803           RAISE check_po_failure;
10804         END IF;
10805 
10806         l_current_invoice_status := 'N';
10807       WHEN TOO_MANY_ROWS THEN
10808         -- po release info is required
10809         -- bug 2581097 added contextual information for XML GATEWAY
10810         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
10811                         AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
10812                         p_invoice_lines_rec.invoice_line_id,
10813                         'INVALID PO RELEASE INFO',
10814                         p_default_last_updated_by,
10815                         p_default_last_update_login,
10816                         current_calling_sequence,
10817                         'Y',
10818                         'PO RELEASE NUMBER',
10819                         p_invoice_lines_rec.release_num,
10820                         'PO SHIPMENT NUMBER',
10821                         p_invoice_lines_rec.po_shipment_num,
10822                         'PO LINE NUMBER',
10823                         p_invoice_lines_rec.po_line_number ) <> TRUE) THEN
10824           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
10825              AP_IMPORT_UTILITIES_PKG.Print(
10826                AP_IMPORT_INVOICES_PKG.g_debug_switch,
10827                'insert_rejections<-'||current_calling_sequence);
10828           END IF;
10829           RAISE check_po_failure;
10830         END IF;
10831         l_current_invoice_status := 'N';
10832     END;
10833 
10834   END IF;
10835 
10836 
10837   ------------------------------------------------------------
10838   -- Case 18, Reject if p_ship_to_location_code is invalid
10839   ------------------------------------------------------------
10840 
10841   IF ((p_invoice_lines_rec.ship_to_location_code IS NOT NULL) AND
10842       (l_po_line_location_id IS NULL) AND
10843       (l_po_header_id IS NOT NULL) AND
10844       (l_po_line_id IS NOT NULL) AND
10845       (l_po_release_id IS NULL)) THEN
10846       --
10847     BEGIN
10848      debug_info := '(v_check_line_po_info 18) Validate p_ship_to_location_code';
10849       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
10850         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
10851                                       debug_info);
10852       END IF;
10853       --
10854 
10855       SELECT 'Y', line_location_id
10856          INTO l_po_shipment_is_valid_flag, l_po_line_location_id
10857         FROM po_line_locations pll,
10858              hr_locations hl
10859        WHERE hl.location_code = p_invoice_lines_rec.ship_to_location_code
10860          AND hl.location_id = pll.ship_to_location_id
10861           AND pll.po_header_id = l_po_header_id
10862          AND pll.po_line_id = l_po_line_id;
10863 
10864      EXCEPTION
10865        WHEN NO_DATA_FOUND THEN
10866          -- po shipment number is invalid
10867          IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
10868             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
10869             p_invoice_lines_rec.invoice_line_id,
10870             'INVALID LOCATION CODE',
10871             p_default_last_updated_by,
10872             p_default_last_update_login,
10873             current_calling_sequence) <> TRUE) THEN
10874 
10875        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
10876              AP_IMPORT_UTILITIES_PKG.Print(
10877              AP_IMPORT_INVOICES_PKG.g_debug_switch,
10878                'insert_rejections<-'||current_calling_sequence);
10879            END IF;
10880            RAISE check_po_failure;
10881          END IF;
10882          --
10883          l_current_invoice_status := 'N';
10884 
10885        WHEN TOO_MANY_ROWS THEN
10886          IF (p_invoice_lines_rec.po_shipment_num IS NULL) Then
10887            -- po shipment to Location is not unique for a Line
10888            IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
10889                 AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
10890                  p_invoice_lines_rec.invoice_line_id,
10891                  'NON UNIQUE LOCATION CODE',
10892                  p_default_last_updated_by,
10893                  p_default_last_update_login,
10894                  current_calling_sequence) <> TRUE) THEN
10895 
10896          IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
10897                AP_IMPORT_UTILITIES_PKG.Print(
10898                  AP_IMPORT_INVOICES_PKG.g_debug_switch,
10899                 'insert_rejections<-'||current_calling_sequence);
10900              END IF;
10901              RAISE check_po_failure;
10902              END IF;
10903            --
10904            l_current_invoice_status := 'N';
10905 
10906          END IF;
10907      END;
10908 
10909   END IF;
10910 
10911   ------------------------------------------------------------
10912   -- Case 19, Reject if po_shipment_num is invalid
10913   ------------------------------------------------------------
10914 
10915   IF ((p_invoice_lines_rec.po_shipment_num IS NOT NULL) AND
10916       (l_po_line_location_id IS NULL) AND
10917       (l_po_header_id IS NOT NULL)    AND
10918       (l_po_release_id IS NOT NULL)) THEN
10919     --
10920     BEGIN
10921       debug_info := '(v_check_line_po_info 19) Validate po_shipment_num';
10922       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
10923         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
10924                                       debug_info);
10925       END IF;
10926       --
10927       SELECT 'Y', line_location_id,
10928       	     po_line_id
10929         INTO l_po_shipment_is_valid_flag, l_po_line_location_id,
10930   	     l_po_line_id
10931         FROM po_line_locations
10932        WHERE shipment_num = p_invoice_lines_rec.po_shipment_num
10933          AND po_header_id = l_po_header_id
10934          AND po_release_id = l_po_release_id
10935 	 AND NVL(closed_code, 'X') <> 'FINALLY CLOSED'; --Bug#13867905;
10936     EXCEPTION
10937       WHEN NO_DATA_FOUND THEN
10938         -- po shipment number is invalid
10939         -- bug 2581097 added contextual information for XML GATEWAY
10940         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
10941                        AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
10942                         p_invoice_lines_rec.invoice_line_id,
10943                         'INVALID PO SHIPMENT NUM',
10944                         p_default_last_updated_by,
10945                         p_default_last_update_login,
10946                         current_calling_sequence,
10947                         'Y',
10948                         'PO SHIPMENT NUMBER',
10949                         p_invoice_lines_rec.po_shipment_num) <> TRUE) THEN
10950           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
10951                AP_IMPORT_UTILITIES_PKG.Print(
10952                  AP_IMPORT_INVOICES_PKG.g_debug_switch,
10953                 'insert_rejections<-'||current_calling_sequence);
10954           END IF;
10955           RAISE check_po_failure;
10956         END IF;
10957 
10958         l_current_invoice_status := 'N';
10959     END;
10960 
10961   END IF;
10962 
10963 
10964   ------------------------------------------------------------
10965   -- Case 20, Reject if p_ship_to_location_code is invalid
10966   ------------------------------------------------------------
10967 
10968   IF ((p_invoice_lines_rec.ship_to_location_code IS NOT NULL) AND
10969       (l_po_line_location_id IS NULL) AND
10970       (l_po_header_id IS NOT NULL) AND
10971       (l_po_release_id IS NOT NULL)) THEN
10972       --
10973     BEGIN
10974       debug_info :=
10975         '(v_check_line_po_info 20) Validate p_ship_to_location_code';
10976       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
10977         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
10978                                       debug_info);
10979       END IF;
10980       --
10981       SELECT 'Y', line_location_id,
10982              po_line_id
10983         INTO l_po_shipment_is_valid_flag, l_po_line_location_id,
10984 	     l_po_line_id
10985         FROM po_line_locations pll, hr_locations hl
10986        WHERE hl.location_code = p_invoice_lines_rec.ship_to_location_code
10987          AND hl.location_id = pll.ship_to_location_id
10988           AND pll.po_header_id = l_po_header_id
10989          AND pll.po_release_id = l_po_release_id;
10990 
10991     EXCEPTION
10992       WHEN NO_DATA_FOUND THEN
10993         -- po shipment number is invalid
10994         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
10995            AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
10996             p_invoice_lines_rec.invoice_line_id,
10997             'INVALID LOCATION CODE',
10998             p_default_last_updated_by,
10999             p_default_last_update_login,
11000             current_calling_sequence) <> TRUE) THEN
11001 
11002           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
11003                AP_IMPORT_UTILITIES_PKG.Print(
11004                  AP_IMPORT_INVOICES_PKG.g_debug_switch,
11005                 'insert_rejections<-'||current_calling_sequence);
11006           END IF;
11007           RAISE check_po_failure;
11008         END IF;
11009         --
11010         l_current_invoice_status := 'N';
11011   -- CHANGES FOR BUG - 2772949  ** STARTS **
11012 	WHEN TOO_MANY_ROWS THEN
11013 		NULL;
11014   -- CHANGES FOR BUG - 2772949  ** ENDS   **
11015   END;
11016   END IF;
11017 
11018   ---------------------------------------------------------------------------
11019   -- Case 21, Reject if po_line_location_id and po_shipment_num is inconsistent
11020   ---------------------------------------------------------------------------
11021 
11022   IF ((l_po_line_location_id IS NOT NULL) AND
11023       (p_invoice_lines_rec.po_shipment_num IS NOT NULL))    THEN
11024       --
11025     BEGIN
11026       debug_info := '(v_check_line_po_info 21) Check inconsistence for '
11027                     ||'po_shipment_num and po_line_location_id';
11028       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
11029         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
11030                                       debug_info);
11031       END IF;
11032       --
11033       SELECT 'Y'
11034       INTO l_po_shipment_is_consis_flag
11035     FROM po_line_locations
11036        WHERE shipment_num = p_invoice_lines_rec.po_shipment_num
11037      AND line_location_id = l_po_line_location_id;
11038     EXCEPTION
11039       WHEN NO_DATA_FOUND THEN
11040         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
11041             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
11042             p_invoice_lines_rec.invoice_line_id,
11043             'INCONSISTENT PO SHIPMENT',
11044             p_default_last_updated_by,
11045             p_default_last_update_login,
11046             current_calling_sequence) <> TRUE) THEN
11047           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
11048                AP_IMPORT_UTILITIES_PKG.Print(
11049                  AP_IMPORT_INVOICES_PKG.g_debug_switch,
11050                 'insert_rejections<-'||current_calling_sequence);
11051           END IF;
11052           RAISE check_po_failure;
11053         END IF;
11054         --
11055         l_current_invoice_status := 'N';
11056     END;
11057 
11058   END IF;
11059 
11060   ---------------------------------------------------------------------------
11061   -- Case 22, Reject if po_line_location_id and p_ship_to_location_code is
11062   -- inconsistent
11063   ---------------------------------------------------------------------------
11064   IF ((l_po_line_location_id IS NOT NULL) AND
11065       (p_invoice_lines_rec.ship_to_location_code IS NOT NULL)) THEN
11066     --
11067     BEGIN
11068       debug_info := '(v_check_line_po_info 22) Check inconsistence for '
11069                     ||'p_ship_to_location_code and po_line_location_id';
11070       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
11071         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
11072                                       debug_info);
11073       END IF;
11074       --
11075 
11076       SELECT 'Y'
11077           INTO l_po_shipment_is_consis_flag
11078         FROM po_line_locations pll,
11079              hr_locations hl
11080        WHERE hl.location_code = p_invoice_lines_rec.ship_to_location_code
11081          AND hl.location_id = pll.ship_to_location_id
11082          AND line_location_id = l_po_line_location_id;
11083 
11084     EXCEPTION
11085       WHEN NO_DATA_FOUND THEN
11086         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
11087             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
11088             p_invoice_lines_rec.invoice_line_id,
11089             'INCONSISTENT PO SHIPMENT',
11090             p_default_last_updated_by,
11091             p_default_last_update_login,
11092             current_calling_sequence) <> TRUE) THEN
11093           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
11094                AP_IMPORT_UTILITIES_PKG.Print(
11095                  AP_IMPORT_INVOICES_PKG.g_debug_switch,
11096                 'insert_rejections<-'||current_calling_sequence);
11097           END IF;
11098           RAISE check_po_failure;
11099         END IF;
11100         --
11101         l_current_invoice_status := 'N';
11102     END;
11103 
11104   END IF;
11105 
11106   ---------------------------------------------------------------------------
11107   -- Case 23, Reject if p_po_shipment_num and p_ship_to_location_code is
11108   -- inconsistent
11109   ---------------------------------------------------------------------------
11110   IF ((p_invoice_lines_rec.po_shipment_num IS NOT NULL)       AND
11111       (p_invoice_lines_rec.ship_to_location_code IS NOT NULL) AND
11112       (l_po_header_id IS NOT NULL)                            AND
11113       (l_po_line_id IS NOT NULL)                              AND
11114       (l_po_release_id IS NULL))                             THEN
11115     --
11116     BEGIN
11117       debug_info := '(v_check_line_po_info 23) Check inconsistence for '
11118                     ||'p_ship_to_location_code and p_po_shipment_num';
11119       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
11120         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
11121                                       debug_info);
11122       END IF;
11123       --
11124       SELECT 'Y'
11125         INTO l_po_shipment_is_consis_flag
11126         FROM po_line_locations pll,
11127              hr_locations hl
11128        WHERE hl.location_code = p_invoice_lines_rec.ship_to_location_code
11129          AND hl.location_id = pll.ship_to_location_id
11130          AND po_line_id = l_po_line_id
11131          AND shipment_num = p_invoice_lines_rec.po_shipment_num
11132          AND po_header_id = l_po_header_id;
11133 
11134     EXCEPTION
11135       WHEN NO_DATA_FOUND THEN
11136         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
11137             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
11138                p_invoice_lines_rec.invoice_line_id,
11139             'INCONSISTENT PO SHIPMENT',
11140             p_default_last_updated_by,
11141             p_default_last_update_login,
11142             current_calling_sequence) <> TRUE) THEN
11143           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
11144                AP_IMPORT_UTILITIES_PKG.Print(
11145                  AP_IMPORT_INVOICES_PKG.g_debug_switch,
11146                 'insert_rejections<-'||current_calling_sequence);
11147           END IF;
11148           --
11149           RAISE check_po_failure;
11150           --
11151         END IF;
11152         --
11153         l_current_invoice_status := 'N';
11154     END;
11155     --
11156   END IF;
11157 
11158 
11159 -- 7531219 moving the following code to case 35.1 (before po overlay procedure - step 36)
11160 
11161 /* Bug 4121338*/
11162   ----------------------------------------------------------
11163   -- Case 23.1, Reject if accrue on receipt is on but
11164   -- overlay gl account is provided in line
11165 
11166   ----------------------------------------------------------
11167 /*
11168  IF (p_invoice_lines_rec.dist_code_combination_id IS NOT NULL OR
11169           p_invoice_lines_rec.dist_code_concatenated IS NOT NULL OR
11170               p_invoice_lines_rec.balancing_segment IS NOT NULL OR
11171               p_invoice_lines_rec.account_segment IS NOT NULL OR
11172               p_invoice_lines_rec.cost_center_segment IS NOT NULL) THEN
11173 
11174     IF ((p_invoice_lines_rec.po_shipment_num IS NOT NULL or p_invoice_lines_rec.po_line_location_id IS NOT NULL) AND
11175       (l_po_header_id IS NOT NULL) AND
11176       ((l_po_line_id IS NOT NULL AND l_po_release_id IS NULL) OR
11177        (l_po_release_id IS NOT NULL AND l_po_line_id IS NULL) OR
11178        (l_po_line_id IS NOT NULL AND l_po_release_id IS NOT NULL))) THEN -- Bug 4254606
11179       BEGIN
11180 
11181         debug_info := '(v_check_line_po_info 23.1) Validate po_shipment_num';
11182         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
11183         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
11184                                 debug_info);
11185         END IF;
11186         --
11187         --
11188 
11189         SELECT NVL(accrue_on_receipt_flag, 'N')
11190         INTO l_accrue_on_receipt_flag
11191         FROM po_line_locations
11192         WHERE ((shipment_num = p_invoice_lines_rec.po_shipment_num
11193                 AND p_invoice_lines_rec.po_shipment_num IS NOT NULL
11194                 AND p_invoice_lines_rec.po_line_location_id IS NULL)
11195              OR (line_location_id = p_invoice_lines_rec.po_line_location_id
11196                 AND p_invoice_lines_rec.po_line_location_id IS NOT NULL
11197                 AND p_invoice_lines_rec.po_shipment_num IS NULL)
11198              OR (p_invoice_lines_rec.po_shipment_num IS NOT NULL
11199                 AND p_invoice_lines_rec.po_line_location_id IS NOT NULL
11200                 AND shipment_num = p_invoice_lines_rec.po_shipment_num
11201                 AND  line_location_id = p_invoice_lines_rec.po_line_location_id))
11202         AND po_header_id = l_po_header_id
11203         AND ((po_release_id = l_po_release_id
11204  AND l_po_line_id IS NULL)
11205             OR (po_line_id = l_po_line_id
11206              AND l_po_release_id IS NULL)
11207             OR (po_line_id = l_po_line_id  -- Bug 4254606
11208              AND po_release_id = l_po_release_id));
11209       EXCEPTION
11210         WHEN OTHERS THEN
11211           Null;
11212       END;
11213 
11214       IF l_accrue_on_receipt_flag = 'Y' THEN
11215 
11216  	IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
11217                 AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
11218                 p_invoice_lines_rec.invoice_line_id,
11219                 'ACCRUE ON RECEIPT',  -- Bug 5235675
11220                 p_default_last_updated_by,
11221                 p_default_last_update_login,
11222                 current_calling_sequence) <> TRUE) THEN
11223             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
11224                 AP_IMPORT_UTILITIES_PKG.Print(
11225                 AP_IMPORT_INVOICES_PKG.g_debug_switch,
11226                   'insert_rejections<-'||current_calling_sequence);
11227             END IF;
11228              RAISE check_po_failure;
11229           END IF;
11230 
11231 
11232         l_current_invoice_status := 'N';
11233 
11234       END IF;
11235 
11236     END IF;
11237 
11238   END IF;
11239 
11240   -- End Bug 4121338
11241 */
11242 
11243 
11244   ---------------------------------------------------------------------------
11245   -- Case 23, Reject if p_po_shipment_num and p_ship_to_location_code is
11246   -- inconsistent
11247   ---------------------------------------------------------------------------
11248   IF ((p_invoice_lines_rec.po_shipment_num IS NOT NULL) AND
11249       (p_invoice_lines_rec.ship_to_location_code IS NOT NULL) AND
11250       (l_po_header_id IS NOT NULL) AND
11251       (l_po_release_id IS  NOT NULL)) THEN
11252     --
11253     BEGIN
11254       debug_info := '(v_check_line_po_info 23) Check inconsistence for '
11255                      ||'p_ship_to_location_code and p_po_shipment_num';
11256       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
11257         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
11258                                       debug_info);
11259       END IF;
11260       --
11261       SELECT 'Y'
11262     INTO l_po_shipment_is_consis_flag
11263         FROM po_line_locations pll,
11264              hr_locations hl
11265        WHERE hl.location_code = p_invoice_lines_rec.ship_to_location_code
11266          AND hl.location_id = pll.ship_to_location_id
11267          AND po_release_id = l_po_release_id
11268          AND shipment_num = p_invoice_lines_rec.po_shipment_num
11269          AND po_header_id = l_po_header_id;
11270 
11271     EXCEPTION
11272       WHEN NO_DATA_FOUND THEN
11273         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
11274             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
11275             p_invoice_lines_rec.invoice_line_id,
11276             'INCONSISTENT PO SHIPMENT',
11277             p_default_last_updated_by,
11278             p_default_last_update_login,
11279             current_calling_sequence) <> TRUE) THEN
11280       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
11281                AP_IMPORT_UTILITIES_PKG.Print(
11282                  AP_IMPORT_INVOICES_PKG.g_debug_switch,
11283                 'insert_rejections<-'||current_calling_sequence);
11284           END IF;
11285           RAISE check_po_failure;
11286         END IF;
11287         --
11288         l_current_invoice_status := 'N';
11289       END;
11290 
11291   END IF;
11292 
11293 
11294   -----------------------------------------------------------
11295   -- Case 25,  Reject if invalid p_po_distribution_id
11296   -----------------------------------------------------------
11297 
11298   IF (l_po_distribution_id IS NOT NULL ) THEN
11299      --
11300      BEGIN
11301       debug_info := '(v_check_line_po_info 25) Validate p_po_distribution_id';
11302       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
11303         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
11304                                       debug_info);
11305       END IF;
11306       --
11307       SELECT 'Y'
11308         INTO l_po_dist_is_valid_flag
11309         FROM po_distributions
11310        WHERE po_distribution_id = l_po_distribution_id
11311          AND line_location_id IS NOT NULL; /* BUG 3253594 */
11312      EXCEPTION
11313        WHEN NO_DATA_FOUND THEN
11314          IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
11315             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
11316             p_invoice_lines_rec.invoice_line_id,
11317             'INVALID PO DIST NUM',
11318             p_default_last_updated_by,
11319             p_default_last_update_login,
11320             current_calling_sequence) <> TRUE) THEN
11321        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
11322                AP_IMPORT_UTILITIES_PKG.Print(
11323                  AP_IMPORT_INVOICES_PKG.g_debug_switch,
11324                 'insert_rejections<-'||current_calling_sequence);
11325            END IF;
11326             RAISE check_po_failure;
11327          END IF;
11328          --
11329          l_current_invoice_status := 'N';
11330      END;
11331 
11332   END IF;
11333 
11334   -----------------------------------------------------------
11335   -- Case 26,  Reject if it is invalid p_po_distribution_num
11336   -----------------------------------------------------------
11337 
11338   IF ((l_po_distribution_id IS NULL) and
11339       (p_invoice_lines_rec.po_distribution_num IS NOT NULL) and
11340       (l_po_line_location_id IS NOT NULL) and
11341       (l_po_line_id IS NOT NULL) and
11342       (l_po_release_id IS NULL) and
11343       (l_po_header_id IS NOT NULL)) THEN
11344     --
11345     BEGIN
11346       debug_info := '(v_check_line_po_info 26) Validate p_po_distribution_num';
11347       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
11348         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
11349                                       debug_info);
11350       END IF;
11351       --
11352       SELECT 'Y' , po_distribution_id
11353       INTO l_po_dist_is_valid_flag,
11354              l_po_distribution_id
11355         FROM po_distributions
11356        WHERE distribution_num = p_invoice_lines_rec.po_distribution_num
11357          AND po_line_id = l_po_line_id
11358      AND line_location_id = l_po_line_location_id
11359          AND po_header_id = l_po_header_id;
11360 
11361     EXCEPTION
11362       WHEN NO_DATA_FOUND THEN
11363         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
11364             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
11365             p_invoice_lines_rec.invoice_line_id,
11366             'INVALID PO DIST NUM',
11367             p_default_last_updated_by,
11368             p_default_last_update_login,
11369             current_calling_sequence) <> TRUE) THEN
11370 
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         --
11379         l_current_invoice_status := 'N';
11380     END;
11381 
11382   END IF;
11383 
11384   ----------------------------------------------------------------------------
11385   -- Case 27,  Reject if  is invalid p_po_distribution_num
11386   ----------------------------------------------------------------------------
11387   IF ((l_po_distribution_id IS NULL) and
11388       (p_invoice_lines_rec.po_distribution_num IS NOT NULL) and
11389       (l_po_release_id IS NOT NULL) and
11390       (l_po_line_location_id IS NOT NULL) and
11391       (l_po_header_id IS NOT NULL)) THEN
11392     --
11393     BEGIN
11394       debug_info := '(v_check_line_po_info 27) Validate p_po_distribution_num';
11395       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
11396         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
11397                                       debug_info);
11398       END IF;
11399       --
11400       SELECT 'Y' , po_distribution_id
11401         INTO l_po_dist_is_valid_flag, l_po_distribution_id
11402         FROM po_distributions
11403        WHERE distribution_num = p_invoice_lines_rec.po_distribution_num
11404      AND po_release_id = l_po_release_id
11405      AND line_location_id = l_po_line_location_id
11406      AND po_header_id = l_po_header_id;
11407 
11408     EXCEPTION
11409       WHEN NO_DATA_FOUND THEN
11410         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
11411             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
11412             p_invoice_lines_rec.invoice_line_id,
11413             'INVALID PO DIST NUM',
11414             p_default_last_updated_by,
11415             p_default_last_update_login,
11416             current_calling_sequence) <> TRUE) THEN
11417 
11418       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
11419                AP_IMPORT_UTILITIES_PKG.Print(
11420                  AP_IMPORT_INVOICES_PKG.g_debug_switch,
11421                 'insert_rejections<-'||current_calling_sequence);
11422           END IF;
11423           RAISE check_po_failure;
11424         END IF;
11425         --
11426         l_current_invoice_status := 'N';
11427     END;
11428 
11429   END IF;
11430 
11431   ---------------------------------------------------------------------------
11432   -- Case 28, Reject if p_po_distribution_num and p_po_distribution_id is
11433   -- inconsistent
11434   ---------------------------------------------------------------------------
11435 
11436   IF ((p_invoice_lines_rec.po_distribution_num IS NOT NULL) AND
11437       (l_po_distribution_id IS NOT NULL)) THEN
11438       --
11439      BEGIN
11440       debug_info := '(v_check_line_po_info 28) Check inconsistence for '
11441                     ||'p_po_distribution_num and p_po_distribution_id';
11442       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
11443         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
11444                                       debug_info);
11445       END IF;
11446       --
11447       SELECT 'Y'
11448         INTO l_po_dist_is_consistent_flag
11449         FROM po_distributions
11450        WHERE po_distribution_id = l_po_distribution_id
11451          AND distribution_num = p_invoice_lines_rec.po_distribution_num
11452          AND line_location_id IS NOT NULL; /* BUG 3253594 */
11453      EXCEPTION
11454        WHEN NO_DATA_FOUND THEN
11455          IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
11456             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
11457             p_invoice_lines_rec.invoice_line_id,
11458             'INCONSISTENT PO DIST INFO',
11459             p_default_last_updated_by,
11460             p_default_last_update_login,
11461             current_calling_sequence) <> TRUE) THEN
11462 
11463        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
11464                AP_IMPORT_UTILITIES_PKG.Print(
11465                  AP_IMPORT_INVOICES_PKG.g_debug_switch,
11466                 'insert_rejections<-'||current_calling_sequence);
11467            END IF;
11468            RAISE check_po_failure;
11469          END IF;
11470          --
11471          l_current_invoice_status := 'N';
11472      END;
11473 
11474   END IF;
11475 
11476   --------------------------------------------
11477   -- Get Valid PO Info only if PO information
11478   -- was not rejected so far
11479   --------------------------------------------
11480   IF (l_current_invoice_status = 'Y') Then
11481 
11482     IF (l_po_number IS NULL) THEN
11483 
11484     ------------------------------------------------------------------------
11485     -- PO step 29,Get po number if it's null
11486     ------------------------------------------------------------------------
11487       ------------------------------------------------
11488       -- Case 1, if po_number is null, then we should try to
11489       -- get it from po_header_id first.  Note that po_header_id
11490       -- would be based on po_number from invoice level if po_number
11491       -- was given at invoice header and line information did not
11492       -- contain either po_header_id or po_number
11493       ------------------------------------------------
11494 
11495       IF (l_po_header_id IS NOT NULL) THEN
11496 
11497         BEGIN
11498           debug_info := '(v_check_line_po_info 29.1) Get po number from '
11499                           ||'po_header_id';
11500           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
11501             AP_IMPORT_UTILITIES_PKG.Print(
11502               AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
11503           END IF;
11504 
11505           SELECT segment1
11506             INTO l_po_number
11507             FROM po_headers
11508            WHERE po_header_id = l_po_header_id
11509              AND type_lookup_code in ('BLANKET', 'PLANNED', 'STANDARD');
11510         EXCEPTION
11511       WHEN NO_DATA_FOUND THEN
11512         NULL;
11513         END;
11514 
11515       END IF; -- Step 29 - Case 1: l_po_header_id is not null
11516 
11517       ----------------------------------------------------
11518       -- Case 2, If l_po_number is still null, get both po_number
11519       --         and po_header_id from l_po_line_id if po_release_id
11520       --         is not available.
11521       ----------------------------------------------------
11522       IF (l_po_number is null) THEN
11523 
11524         IF ((l_po_line_id IS NOT NULL) and (l_po_release_id IS NULL)) THEN
11525 
11526           BEGIN
11527             debug_info :=
11528               '(v_check_line_po_info 29.2) Get po number from po_line_id';
11529             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
11530               AP_IMPORT_UTILITIES_PKG.Print(
11531                 AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
11532             END IF;
11533 
11534             SELECT pl.po_header_id,
11535                ph.segment1
11536           INTO l_po_header_id,
11537                l_po_number
11538            FROM po_headers ph,
11539                    po_lines pl
11540              WHERE pl.po_line_id = l_po_line_id
11541                AND pl.po_header_id = ph.po_header_id;
11542 
11543           EXCEPTION
11544         WHEN NO_DATA_FOUND THEN
11545           NULL;
11546       END;
11547 
11548       ----------------------------------------------------
11549       -- Case 3, If l_po_number is still null and po_release_id
11550       --         is not null, get both po_number
11551       --         and po_header_id from l_po_release_id
11552       ----------------------------------------------------
11553 
11554         ELSIF (l_po_release_id IS NOT NULL) Then
11555 
11556           BEGIN
11557             debug_info := '(v_check_line_po_info 29.3) Get po number from'
11558                           ||' po_release_id';
11559             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
11560               AP_IMPORT_UTILITIES_PKG.Print(
11561                 AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
11562             END IF;
11563 
11564         SELECT pr.po_header_id,
11565                ph.segment1
11566           INTO l_po_header_id,
11567                l_po_number
11568            FROM po_headers ph,
11569                po_releases pr
11570              WHERE pr.po_release_id = l_po_release_id
11571                AND pr.po_header_id = ph.po_header_id;
11572           EXCEPTION
11573         WHEN NO_DATA_FOUND THEN
11574           NULL;
11575           END;
11576 
11577         END IF; -- l_po_release_id is null and po_line_id is not null
11578 
11579       END IF; -- Step 29 - Case 2 and 3: l_po_number is null
11580 
11581       ----------------------------------------------------
11582       -- Case 4, If l_po_number is still null, get both po_number
11583       --         and po_header_id from l_po_line_location_id
11584       ----------------------------------------------------
11585       IF (l_po_number is null) THEN
11586         IF (l_po_line_location_id IS NOT NULL) THEN
11587           --
11588           -- get po_header_id and po_number from po_line_location_id
11589           --
11590           BEGIN
11591 
11592             debug_info := '(v_check_line_po_info 29.4) Get po number from '
11593                           ||'po_line_location_id';
11594             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
11595               AP_IMPORT_UTILITIES_PKG.Print(
11596                 AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
11597             END IF;
11598 
11599         SELECT pll.po_header_id,
11600                ph.segment1
11601           INTO l_po_header_id,
11602                l_po_number
11603            FROM po_headers ph,
11604                po_line_locations pll
11605              WHERE pll.line_location_id = l_po_line_location_id
11606                AND pll.po_header_id = ph.po_header_id;
11607           EXCEPTION
11608             WHEN NO_DATA_FOUND THEN
11609           NULL;
11610           END;
11611 
11612         END IF; -- l_po_line_location_id is not null
11613       END IF; -- Step 29 - Case 4: l_po_number is null
11614 
11615       ----------------------------------------------------
11616       -- Case 5, If l_po_number is still null, get both
11617       --         po_number and po_header_id from
11618       --           po_distribution_id
11619       ----------------------------------------------------
11620       IF (l_po_number is null) THEN
11621         IF (l_po_distribution_id IS NOT NULL) THEN
11622           --
11623           -- get po_header_id and po_number from po_distribution_id
11624           --
11625           BEGIN
11626 
11627             debug_info := '(v_check_line_po_info 29.5) Get po number from '
11628                           ||'po_distribution_id';
11629             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
11630               AP_IMPORT_UTILITIES_PKG.Print(
11631                 AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
11632             END IF;
11633 
11634             SELECT pd.po_header_id,
11635                ph.segment1
11636           INTO l_po_header_id,
11637                l_po_number
11638            FROM po_headers ph,
11639                po_distributions pd
11640              WHERE pd.po_distribution_id = l_po_distribution_id
11641                AND pd.po_header_id = ph.po_header_id
11642                AND pd.line_location_id IS NOT NULL; /* BUG 3253594 */
11643           EXCEPTION
11644         WHEN NO_DATA_FOUND THEN
11645           NULL;
11646       END;
11647 
11648         END IF; -- l_po_distribution_id is not NULL
11649       END IF; -- Step 29 - Case 5: l_po_number is null
11650 
11651     END IF;  -- (PO step 29) -- l_po_number is null
11652 
11653     -----------------------------------------------------------------------
11654     -- Step 30
11655     -- Get po_header_id from po_number if still null
11656     -----------------------------------------------------------------------
11657     IF ((l_po_number IS NOT NULL) AND
11658         (l_po_header_id IS NULL)) THEN
11659 
11660       debug_info :=
11661           '(v_check_line_po_info 30) Get po_header_id from po_number';
11662       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
11663         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
11664                                       debug_info);
11665       END IF;
11666       --bug2268553 to differentiate PO from RFQ and Quotation
11667       SELECT po_header_id
11668         INTO l_po_header_id
11669         FROM po_headers
11670        WHERE segment1 = l_po_number
11671          AND type_lookup_code in ('BLANKET', 'PLANNED', 'STANDARD');
11672 
11673     END IF; -- Step 30: po_number is not null but po_header_id is null
11674 
11675     -- Get other po infomation
11676     -- only if l_po_header_id is not null
11677     --
11678 
11679     IF (l_po_header_id IS NOT NULL) THEN
11680       ------------------------------------------------------------------------
11681       -- Step 31
11682       -- Get po_line_id
11683       ------------------------------------------------------------------------
11684       debug_info := '(v_check_line_po_info 31) Get po_line_id';
11685       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
11686          AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
11687                                       debug_info);
11688       END IF;
11689 
11690       -------------------------------------------------------
11691       -- Case 1, If po_line_id is still null, get it from
11692       --  l_po_line_location_id if po_line_location_id is not null
11693       --------------------------------------------------------
11694       IF (l_po_line_id IS NULL) THEN
11695         IF (l_po_line_location_id IS NOT NULL) THEN
11696 
11697       BEGIN
11698 
11699             debug_info := '(v_check_line_po_info 31.1) Get po_line_id from '
11700                           ||'po_line_location_id';
11701             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
11702               AP_IMPORT_UTILITIES_PKG.Print(
11703                 AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
11704             END IF;
11705 
11706         SELECT po_line_id
11707           INTO l_po_line_id
11708           FROM po_line_locations
11709           WHERE line_location_id = l_po_line_location_id;
11710       EXCEPTION
11711         WHEN NO_DATA_FOUND THEN
11712               NULL;
11713       END;
11714 
11715         END IF; --  l_po_line_location_id is not null
11716       END IF; -- Step 31 - Case 1: l_po_line_id is null
11717 
11718       -------------------------------------------------------
11719       -- Case 2, If l_po_line_id is still null, get it from
11720       --  po_distribution_id if po_distribution_id is not null
11721       --------------------------------------------------------
11722       IF (l_po_line_id IS NULL) THEN
11723       IF (l_po_distribution_id IS NOT NULL) THEN
11724 
11725       BEGIN
11726 
11727             debug_info := '(v_check_line_po_info 31.2) Get po_line_id from '
11728                           ||'po_distribution_id';
11729             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
11730               AP_IMPORT_UTILITIES_PKG.Print(
11731                 AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
11732             END IF;
11733 
11734         SELECT po_line_id
11735           INTO l_po_line_id
11736           FROM po_distributions
11737           WHERE po_distribution_id = l_po_distribution_id
11738             AND line_location_id IS NOT NULL; /* BUG 3253594 */
11739       EXCEPTION
11740         WHEN NO_DATA_FOUND THEN
11741               NULL;
11742       END;
11743 
11744     END IF; -- l_po_distribution_id is not null
11745 
11746    END IF; -- Step 31 - Case 2: l_po_line_id is null
11747 
11748       -------------------------------------------------------
11749       -- Case 3, If po_line_id is still null, default to
11750       -- the first line (it should be one line)
11751       -- If more than 1 line then reject NO PO LINE NUM
11752       --------------------------------------------------------
11753    IF (l_po_line_id IS NULL) THEN
11754 
11755         BEGIN
11756 
11757           debug_info := '(v_check_line_po_info 31.3) Default po_line_id from '
11758                         ||'the first line, if only one line';
11759           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
11760             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
11761                                        debug_info);
11762           END IF;
11763 
11764           SELECT po_line_id
11765             INTO l_po_line_id
11766             FROM po_lines
11767            WHERE po_header_id = l_po_header_id;
11768 
11769         EXCEPTION
11770           WHEN NO_DATA_FOUND Then
11771             NULL;
11772 
11773           WHEN TOO_MANY_ROWS Then
11774             debug_info := '(v_check_line_po_info 31.4) Too many po lines';
11775             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
11776               AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
11777                                       debug_info);
11778             END IF;
11779 
11780             -- bug 2581097 added contextual information for XML GATEWAY
11781 
11782             IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
11783                         AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
11784                         p_invoice_lines_rec.invoice_line_id,
11785                         'NO PO LINE NUM',
11786                         p_default_last_updated_by,
11787                         p_default_last_update_login,
11788                         current_calling_sequence,
11789                         'Y',
11790                         'PO NUMBER',
11791                         l_po_number) <> TRUE) THEN
11792               IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
11793                 AP_IMPORT_UTILITIES_PKG.Print(
11794                     AP_IMPORT_INVOICES_PKG.g_debug_switch,
11795                     'insert_rejections<-'||current_calling_sequence);
11796               END IF;
11797               RAISE check_po_failure;
11798             END IF;
11799             --
11800             l_current_invoice_status := 'N';
11801             --
11802         END;
11803 
11804       END IF; -- Step 31 - Case 3: l_po_line_id is null
11805 
11806     END IF; -- Step 31: (l_po_header_id IS NOT NULL - get po_line_id if null)
11807 
11808     -- Bug # 1042447
11809     --
11810     -- Get  po shipment infomation
11811     -- only if p_po_header_id is not null and po_line_id is not null
11812 
11813     IF (l_po_header_id IS NOT NULL) AND (l_po_line_id is not NULL) THEN
11814       -----------------------------------------------------------------------
11815       -- Step 32
11816       -- Get Get po_line_location_id
11817       -----------------------------------------------------------------------
11818       debug_info := '(v_check_line_po_info 32) Get po_line_location_id';
11819       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
11820         AP_IMPORT_UTILITIES_PKG.Print(
11821           AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
11822       END IF;
11823 
11824       -------------------------------------------------------
11825       -- Case 1, If l_po_line_location_id id still null, get it from
11826       --  po_distribution_id
11827       --------------------------------------------------------
11828       IF (l_po_line_location_id IS NULL) THEN
11829         IF (l_po_distribution_id IS NOT NULL) THEN
11830 
11831           BEGIN
11832             --
11833             debug_info := '(v_check_line_po_info 32.1) Get po_line_id from '
11834                            ||'po_distribution_id';
11835             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
11836               AP_IMPORT_UTILITIES_PKG.Print(
11837                 AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
11838             END IF;
11839 
11840             SELECT line_location_id
11841               INTO l_po_line_location_id
11842               FROM po_distributions
11843               WHERE po_distribution_id = l_po_distribution_id
11844                 AND line_location_id IS NOT NULL; /* BUG 3253594 */
11845           EXCEPTION
11846             WHEN NO_DATA_FOUND THEN
11847                   NULL;
11848           END;
11849           --
11850         END IF; -- l_po_distribution_id is not null
11851       END IF; -- l_po_line_location_id is null
11852 
11853       -------------------------------------------------------
11854       -- Case 2, If po_line_location_id id still null, default to
11855       -- the first line (it should be one one line)
11856       -- If more than 1 line then reject NO SHIPMENT LINE NUM
11857       --------------------------------------------------------
11858       IF (l_po_line_location_id IS NULL) THEN
11859 
11860         BEGIN
11861 
11862           debug_info := '(v_check_line_po_info 32.2) Default '
11863                          ||'po_line_location_id from the first line, '
11864                          ||'if only one line';
11865           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
11866             AP_IMPORT_UTILITIES_PKG.Print(
11867                AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
11868           END IF;
11869 
11870 	  /*--------------------------------------------------------------------+
11871 	  | --Contract Payments:						|
11872 	  | 1.For the case of complex works purchase order, if it is a		|
11873 	  |   A)Prepayment Invoice,we should not reject if we can derive        |
11874 	  |     a single shipment of type 'Prepayment' from the PO line		|
11875 	  |    we should not reject it.						|
11876           |   B)Any other invoice (Std, credit,debit, mixed), we should		|
11877 	  |    not reject if we are able to derive a single actual('Standard') 	|
11878 	  |    shipment.							|
11879 	  +---------------------------------------------------------------------*/
11880 
11881             SELECT line_location_id
11882             INTO l_po_line_location_id
11883             FROM po_line_locations pll
11884            WHERE po_header_id = l_po_header_id
11885             AND po_line_id = l_po_line_id
11886 	    AND
11887 	     (
11888 	      (p_invoice_rec.invoice_type_lookup_code = 'PREPAYMENT' and
11889 	       ((pll.payment_type IS NOT NULL and pll.shipment_type = 'PREPAYMENT') or
11890 	        (pll.payment_type IS NULL)
11891                )
11892               ) OR
11893             --(p_invoice_rec.invoice_type_lookup_code <> 'PREPAYMENT' and    .. B# 8528132
11894               (nvl(p_invoice_rec.invoice_type_lookup_code, 'STANDARD') <> 'PREPAYMENT' and    -- B# 8528132
11895 	       ((pll.payment_type IS NOT NULL and pll.shipment_type <> 'PREPAYMENT') or
11896 		(pll.payment_type IS NULL)
11897 	       )
11898               )
11899              );
11900 
11901         EXCEPTION
11902           WHEN NO_DATA_FOUND Then
11903                 NULL;
11904 
11905           WHEN TOO_MANY_ROWS Then
11906 
11907             debug_info :=
11908               '(v_check_line_po_info 32.2) Too many po shipments';
11909             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
11910               AP_IMPORT_UTILITIES_PKG.Print(
11911                    AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
11912             END IF;
11913 
11914             IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
11915                    AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
11916                      p_invoice_lines_rec.invoice_line_id,
11917                 'NO PO SHIPMENT NUM',
11918                  p_default_last_updated_by,
11919                  p_default_last_update_login,
11920                  current_calling_sequence) <> TRUE) THEN
11921                IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
11922                    AP_IMPORT_UTILITIES_PKG.Print(
11923                    AP_IMPORT_INVOICES_PKG.g_debug_switch,
11924                    'insert_rejections<-'||current_calling_sequence);
11925                END IF;
11926                 RAISE check_po_failure;
11927             END IF;
11928             l_current_invoice_status := 'N';
11929 
11930         END;
11931 
11932       END IF; -- step 31 - CASE 2: po_line_location_id IS still null
11933 
11934     END IF; -- Step 31 - po_header_id and po_line_id are not null
11935 
11936 
11937     --Bug#14193044 modified below query.
11938     --Bug#14118812
11939    IF (p_invoice_lines_rec.ship_to_location_id IS NULL AND
11940         p_invoice_lines_rec.ship_to_location_code IS NULL AND
11941         l_po_line_location_id IS NOT NULL)THEN
11942 
11943         SELECT pll.ship_to_location_id
11944         INTO p_invoice_lines_rec.ship_to_location_id
11945         FROM po_line_locations pll
11946         WHERE pll.line_location_id = l_po_line_location_id;
11947 
11948     END IF;
11949     --Bug#14118812
11950 
11951     ---------------------------------------------------------------------------
11952     -- 31.1 - Amount Based Matching
11953     -- If match basis is still null derive it based po_line_location_id
11954     -- if it is not null. Complex Work Project matching basis will be
11955     -- poulated at shipment level.
11956     -- Bug8546486 fetching the Description at line level from PO tables.
11957     ---------------------------------------------------------------------------
11958     IF (l_po_line_location_id IS NOT NULL) THEN
11959       debug_info := '(v_check_line_po_info 31.1) Get Match Basis Based '||
11960                                   'on line_location_id';
11961       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
11962         AP_IMPORT_UTILITIES_PKG.Print(
11963           AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
11964       END IF;
11965 
11966       SELECT pll.matching_basis,pll.description-- Bug8546486
11967         INTO l_match_basis,l_item_description  -- Bug8546486
11968         FROM po_line_locations pll
11969        WHERE pll.line_location_id = l_po_line_location_id;
11970 
11971     END IF;
11972 
11973     /*Bug8546486 fetching the Description if it is not present at
11974           po_line_locations_all table level*/
11975     IF (l_item_description IS NULL and l_po_line_id IS NOT NULL) THEN
11976 
11977       SELECT pl.item_description
11978         INTO l_item_description
11979         FROM po_lines pl
11980        WHERE pl.po_line_id = l_po_line_id;
11981 
11982     END IF;
11983     --End Bug8546486
11984 
11985     ---------------------------------------------------------------------------
11986     -- 31.2: Check for Corrupt PO data - Amount Based Matching
11987     -- Forward Bug 3253594. Po team made the po_line_id, line_location_id,
11988     -- code_combination_id and quantity_ordered fields of the po_distributions
11989     -- table nullable for certain types of PO's (i.e. Blanket Agreements and
11990     -- Global Agreements). These fields must be not not null in the types of
11991     -- PO's that the 'Payables Open Interface Import' concurrent program
11992     -- handles. Thus, if a distribution with any of these fields null is
11993     -- encountered then we can import the invoice because it references
11994     -- corrupt po distributions
11995     -- Complex Work Project. Matching Basis will be derived from po shipment.
11996     ---------------------------------------------------------------------------
11997 
11998     IF (l_po_header_id IS NOT NULL) THEN
11999       debug_info := '(v_check_line_po_info 31.2) Check for corrupt PO data';
12000       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
12001         AP_IMPORT_UTILITIES_PKG.Print(
12002           AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
12003       END IF;
12004 
12005      --start of bug 5292782
12006      declare
12007      l_blanket varchar2(10);
12008      begin
12009      select type_lookup_code, vendor_id  -- Bug 5448579
12010      into   l_blanket, l_vendor_id
12011      from po_headers
12012      where po_header_id=l_po_header_id;
12013      --end of select for 5292782
12014 
12015 IF (l_blanket<>'BLANKET') THEN /* Bug10103888 */
12016 
12017       SELECT COUNT(*)
12018         INTO l_corrupt_po_distributions
12019         FROM po_distributions
12020        WHERE po_header_id = l_po_header_id
12021          AND (line_location_id IS NULL
12022               OR po_line_id IS NULL
12023               OR code_combination_id IS NULL)
12024          AND  rownum = 1;  -- Bug 5448579
12025 
12026       IF (l_corrupt_po_distributions = 0) THEN
12027 
12028         SELECT COUNT(*)
12029           INTO l_corrupt_po_distributions
12030           FROM po_distributions pod,
12031                po_line_locations pll
12032          WHERE pod.po_header_id = l_po_header_id
12033            AND pod.line_location_id = pll.line_location_id
12034            AND ((pll.matching_basis = 'QUANTITY'
12035                 AND pod.quantity_ordered IS NULL)
12036              OR (pll.matching_basis = 'AMOUNT'
12037                 AND pod.amount_ordered IS NULL))
12038            AND rownum = 1; -- Bug 5448579
12039 
12040       END IF;
12041 
12042    /*  IF (l_blanket<>'BLANKET') THEN --bug 5292782  Moved above for bug 10103888 */
12043       IF (l_corrupt_po_distributions > 0) THEN
12044         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
12045                         AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
12046                         p_invoice_lines_rec.invoice_line_id,
12047                         'INVALID PO NUM',
12048                         p_default_last_updated_by,
12049                         p_default_last_update_login,
12050                         current_calling_sequence,
12051                         'Y',
12052                         'CORRUPT PONUMBER',
12053                         l_po_header_id) <> TRUE) THEN
12054           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
12055                 AP_IMPORT_UTILITIES_PKG.Print(
12056                     AP_IMPORT_INVOICES_PKG.g_debug_switch,
12057                     'insert_rejections<-'||current_calling_sequence);
12058           END IF;
12059           RAISE check_po_failure;
12060         END IF;
12061 
12062         l_current_invoice_status := 'N';
12063 
12064       END IF;
12065      END IF;--Bug 5292782
12066      end; --Bug 5292782
12067 
12068     END IF;
12069 
12070     -- Misc Checks Here
12071     -- At this point we should have all the information in
12072     -- terms of id's
12073 
12074     -------------------------------------------------------------------
12075     -- Step 33   Misc Checks
12076     -- 1. Verify there is no vendor mismatch between invoice and PO
12077     -- 2. Verify that if it is a blanket PO, then release information was
12078     --    provided.  Otherwise, reject.
12079     -- 3. Verify that all PO info provided is correct i.e. points to
12080     --    existing PO data.  Otherwise, reject.
12081     -- 4. If no shipment info could be derived (either there is no shipments
12082     --    for the provided po data or too many) reject.
12083     -- 5. Verify if invoice currency is the same as PO currency and
12084     --    reject otherwise.
12085     -------------------------------------------------------------------
12086     IF (l_po_header_id IS NOT NULL) Then
12087 
12088       debug_info := '(v_check_line_po_info 33.1) Find if PO vendor does not '
12089                      ||'match interface vendor:Get PO Vendor';
12090       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
12091           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
12092                                         debug_info);
12093       END IF;
12094      -- Bug 5448579. L_vendor_id is already derived
12095     /*  SELECT vendor_id
12096         INTO l_vendor_id
12097         FROM po_headers
12098        WHERE po_header_id = l_po_header_id; */
12099 
12100       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
12101           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
12102           '------------------> l_vendor_id :per PO = '||
12103           to_char(l_vendor_id));
12104       END IF;
12105       debug_info :=
12106         '(v_check_line_po_info 33.1) Check for Inconsistent PO Vendor.';
12107       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
12108           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
12109                                       debug_info);
12110       END IF;
12111 
12112       IF (l_vendor_id <> nvl(p_invoice_rec.vendor_id, l_vendor_id)) THEN
12113         IF ( AP_IMPORT_INVOICES_PKG.g_source = 'XML GATEWAY' ) THEN
12114            BEGIN
12115 
12116              SELECT vendor_name
12117                INTO l_invoice_vendor_name
12118                FROM po_vendors
12119               WHERE vendor_id = p_invoice_rec.vendor_id;
12120 
12121              IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
12122                          AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
12123                        p_invoice_lines_rec.invoice_line_id,
12124                        'INCONSISTENT PO SUPPLIER',
12125                         p_default_last_updated_by,
12126                         p_default_last_update_login,
12127                        current_calling_sequence,
12128                        'Y',
12129                        'SUPPLIER NAME',
12130                        l_invoice_vendor_name) <> TRUE) THEN
12131 
12132                IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
12133                  AP_IMPORT_UTILITIES_PKG.Print(
12134                       AP_IMPORT_INVOICES_PKG.g_debug_switch,
12135                       'insert_rejections<-'||current_calling_sequence);
12136                END IF;
12137                 RAISE check_po_failure;
12138          END IF;
12139 
12140            EXCEPTION
12141              WHEN NO_DATA_FOUND THEN
12142                NULL;
12143            END;
12144 
12145         ELSE
12146           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
12147                       AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
12148                      p_invoice_lines_rec.invoice_line_id,
12149                     'INCONSISTENT PO SUPPLIER',
12150                     p_default_last_updated_by,
12151                      p_default_last_update_login,
12152                     current_calling_sequence) <> TRUE) THEN
12153 
12154                 IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
12155                    AP_IMPORT_UTILITIES_PKG.Print(
12156                      AP_IMPORT_INVOICES_PKG.g_debug_switch,
12157                      'insert_rejections<-'||current_calling_sequence);
12158                 END IF;
12159                 RAISE check_po_failure;
12160           END IF;
12161 
12162         END IF;  -- g_source = 'XML GATEWAY'
12163 
12164           l_current_invoice_status := 'N';
12165 
12166       END IF; -- vendor_id in po_header is different than in invoice record
12167 
12168       IF ((p_invoice_lines_rec.release_num IS NULL) AND
12169           (l_po_release_id IS NULL)) THEN
12170       DECLARE
12171          l_blanket varchar2(10); --4019310
12172       BEGIN
12173          l_blanket:='BLANKET'; --4019310
12174 
12175          debug_info := '(v_check_line_po_info 33.2) Find if PO is BLANKET';
12176           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
12177             AP_IMPORT_UTILITIES_PKG.Print(
12178              AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
12179           END IF;
12180 
12181           SELECT 'Y'
12182             INTO l_po_is_not_blanket
12183             FROM po_headers
12184            WHERE po_header_id = l_po_header_id
12185              AND type_lookup_code <> l_blanket; --4019310
12186 
12187         EXCEPTION
12188       WHEN NO_DATA_FOUND THEN
12189             -- po header is BLANKET
12190             -- bug 2581097 added contextual information for XML GATEWAY
12191 
12192             IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
12193                         AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
12194                         p_invoice_lines_rec.invoice_line_id,
12195                         'RELEASE MISSING',
12196                         p_default_last_updated_by,
12197                         p_default_last_update_login,
12198                         current_calling_sequence,
12199                         'Y',
12200                         'PO NUMBER',
12201                         l_po_number) <> TRUE) THEN
12202               IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
12203                      AP_IMPORT_UTILITIES_PKG.Print(
12204                        AP_IMPORT_INVOICES_PKG.g_debug_switch,
12205                        'insert_rejections<-'||current_calling_sequence);
12206               END IF;
12207               RAISE check_po_failure;
12208             END IF;
12209             l_current_invoice_status := 'N';
12210         END;
12211 
12212       END IF; -- release info is null
12213 
12214       IF ((l_po_line_id IS NOT NULL) AND
12215           (l_po_release_id IS NOT NULL) AND
12216           (l_po_line_location_id is NOT NULL)) THEN
12217 
12218         BEGIN
12219 
12220           debug_info :=
12221             '(v_check_line_po_info 33.3) Find if PO info is consistent';
12222           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
12223             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
12224                                         debug_info);
12225           END IF;
12226 
12227           SELECT 'X'
12228             INTO l_po_is_not_blanket
12229             FROM po_line_locations pll,
12230              po_releases pr
12231            WHERE pr.po_header_id = l_po_header_id
12232              AND pr.po_release_id = l_po_release_id
12233              AND pll.po_release_id = pr.po_release_id
12234              AND pll.po_line_id = l_po_line_id
12235              AND pll.line_location_id = l_po_line_location_id;
12236 
12237           EXCEPTION
12238           WHEN NO_DATA_FOUND THEN
12239             -- Reject
12240             IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
12241                         AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
12242                         p_invoice_lines_rec.invoice_line_id,
12243                         'INVALID PO INFO',
12244                         p_default_last_updated_by,
12245                         p_default_last_update_login,
12246                         current_calling_sequence,
12247                         'Y',
12248                         'PO RECEIPT NUMBER',
12249                         p_invoice_lines_rec.receipt_number,
12250                         'PO NUMBER',
12251                         p_invoice_lines_rec.po_number,
12252                         'PO LINE NUMBER',
12253                         p_invoice_lines_rec.po_line_number,
12254                         'PO SHIPMENT NUMBER',
12255                         p_invoice_lines_rec.po_shipment_num,
12256                         'PO RELEASE NUMBER',
12257                         p_invoice_lines_rec.release_num ) <> TRUE) THEN
12258               IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
12259                      AP_IMPORT_UTILITIES_PKG.Print(
12260                        AP_IMPORT_INVOICES_PKG.g_debug_switch,
12261                        'insert_rejections<-'||current_calling_sequence);
12262               END IF;
12263               RAISE check_po_failure;
12264 
12265             END IF;
12266 
12267             l_current_invoice_status := 'N';
12268           END;
12269 
12270       END IF; -- po_line_id, po_release_id and po_line_location_id not null
12271 
12272       ---------------------------------------------------------
12273       -- Check if invoice currency is the same as PO currency
12274       ---------------------------------------------------------
12275       BEGIN
12276         debug_info := '(v_check_line_po_info 33.5) Check if inv curr is same is '
12277                       ||'po curr';
12278         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
12279           AP_IMPORT_UTILITIES_PKG.Print(
12280               AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
12281         END IF;
12282 
12283         SELECT 'Y'
12284           INTO l_po_inv_curr_is_consis_flag
12285           FROM po_headers
12286          WHERE po_header_id = l_po_header_id
12287            AND currency_code = p_invoice_rec.invoice_currency_code;
12288       EXCEPTION
12289         WHEN NO_DATA_FOUND THEN
12290         debug_info :=
12291           '(v_check_line_po_info 33.5) Reject: Inconsistent currencies';
12292           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
12293             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
12294                                         debug_info);
12295           END IF;
12296           -- Reject
12297           IF ( AP_IMPORT_INVOICES_PKG.g_source = 'XML GATEWAY') THEN
12298             SELECT currency_code
12299               INTO l_po_currency_code
12300               FROM po_headers
12301              WHERE po_header_id = l_po_header_id ;
12302 
12303             IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
12304                     AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
12305                          p_invoice_lines_rec.invoice_line_id,
12306                          'INCONSISTENT CURR',
12307                          p_default_last_updated_by,
12308                          p_default_last_update_login,
12309                          current_calling_sequence,
12310                         'Y',
12311                         'INVOICE CURRENCY CODE',
12312                          p_invoice_rec.invoice_currency_code,
12313                         'PO CURRENCY CODE',
12314                          l_po_currency_code ) <> TRUE) THEN
12315 
12316               IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
12317                 AP_IMPORT_UTILITIES_PKG.Print(
12318                        AP_IMPORT_INVOICES_PKG.g_debug_switch,
12319                        'insert_rejections<-'||current_calling_sequence);
12320               END IF;
12321                RAISE check_po_failure;
12322                END IF;
12323 
12324           ELSE
12325 
12326             IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
12327                   AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
12328                       p_invoice_lines_rec.invoice_line_id,
12329                     'INCONSISTENT CURR',
12330                      p_default_last_updated_by,
12331                      p_default_last_update_login,
12332                       current_calling_sequence) <> TRUE) THEN
12333 
12334               IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
12335                 AP_IMPORT_UTILITIES_PKG.Print(
12336                        AP_IMPORT_INVOICES_PKG.g_debug_switch,
12337                        'insert_rejections<-'||current_calling_sequence);
12338               END IF;
12339                RAISE check_po_failure;
12340 
12341             END IF;
12342 
12343           END IF; -- g_source = 'XML GATEWAY'
12344 
12345           l_current_invoice_status := 'N';
12346 
12347         END;
12348 
12349     END IF; -- Step 33 - Misc checks: po_header_id is not null
12350 
12351 
12352   --------------------------------------------------------
12353   -- Step 34.1
12354   -- Check price correction information
12355   -- Retropricing: Please Note that the code for Price
12356   -- Corrections should not be executed for source = 'PPA'.
12357   -- For PPA Lines p_invoice_lines_rec.price_correction_flag
12358   -- should be NULL
12359   ---------------------------------------------------------
12360   IF (AP_IMPORT_INVOICES_PKG.g_source <> 'PPA') THEN
12361     IF p_invoice_lines_rec.price_correction_flag = 'Y' then
12362 
12363      debug_info := '(v_check_line_po_info 34.1) Check for price correction information on'||
12364      			' prepayment invoices';
12365      IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
12366        AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
12367                                      debug_info);
12368      END IF;
12369 
12370      IF(p_invoice_rec.invoice_type_lookup_code = 'PREPAYMENT') THEN
12371 
12372          IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
12373             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
12374                 p_invoice_lines_rec.invoice_line_id,
12375                 'CANNOT PRICE CORRECT PREPAY',
12376                 p_default_last_updated_by,
12377                 p_default_last_update_login,
12378                 current_calling_sequence)<> TRUE) THEN
12379 
12380             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
12381                      AP_IMPORT_UTILITIES_PKG.Print(
12382 	                      AP_IMPORT_INVOICES_PKG.g_debug_switch,
12383                                 'insert_rejections<-'||current_calling_sequence);
12384             END IF;
12385 
12386             RAISE check_po_failure;
12387 
12388          END IF;
12389 
12390          l_current_invoice_status := 'N';
12391 
12392       END IF;
12393 
12394       debug_info := '(v_check_line_po_info 34.2) Check price correction information';
12395       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
12396           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
12397                                       debug_info);
12398       END IF;
12399 
12400       IF p_invoice_lines_rec.price_correct_inv_num is null then
12401 
12402         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
12403               AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
12404               p_invoice_lines_rec.invoice_line_id,
12405               'PRICE CORRECT INV NUM REQUIRED',
12406               p_default_last_updated_by,
12407               p_default_last_update_login,
12408               current_calling_sequence)<> TRUE) THEN
12409 
12410           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
12411                AP_IMPORT_UTILITIES_PKG.Print(
12412                  AP_IMPORT_INVOICES_PKG.g_debug_switch,
12413                  'insert_rejections<-'||current_calling_sequence);
12414           END IF;
12415 
12416           RAISE check_po_failure;
12417         END IF;
12418 
12419         l_current_invoice_status := 'N';
12420 
12421       END IF;
12422 
12423 
12424     --Check if price_correct_inv_line_num is NULL, if so reject the invoice.
12425     IF p_invoice_lines_rec.price_correct_inv_line_num is null then
12426 
12427        debug_info := '(v_check_line_po_info 34.3) Check price correction line information';
12428        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
12429           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
12430                                       debug_info);
12431        END IF;
12432 
12433        IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
12434               AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
12435               p_invoice_lines_rec.invoice_line_id,
12436               'INCOMPLETE PO INFO',
12437               p_default_last_updated_by,
12438               p_default_last_update_login,
12439               current_calling_sequence)<> TRUE) THEN
12440 
12441          IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
12442                AP_IMPORT_UTILITIES_PKG.Print(
12443                  AP_IMPORT_INVOICES_PKG.g_debug_switch,
12444                  'insert_rejections<-'||current_calling_sequence);
12445          END IF;
12446          RAISE check_po_failure;
12447        END IF;
12448        l_current_invoice_status := 'N';
12449 
12450     END IF;
12451 
12452     --check if this is a valid invoice and invoice line is provided
12453     --for a price correction
12454     IF (p_invoice_lines_rec.price_correct_inv_num is not null and
12455         p_invoice_lines_rec.price_correct_inv_line_num is not null) THEN
12456      BEGIN
12457 
12458       debug_info := '(v_check_line_po_info 34.4) Check if price correcting invoice line'
12459 		    ||'is valid';
12460       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
12461         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
12462                                       debug_info);
12463       END IF;
12464 
12465       --bug13599126, added price correction invoice po related columns
12466       SELECT DISTINCT ai.invoice_id,
12467                       ail.amount,
12468                       ail.po_header_id,
12469                       ail.po_line_id,
12470                       ail.po_line_location_id,
12471                       ail.po_distribution_id
12472       INTO l_price_correct_inv_id,
12473            l_base_match_amount,
12474            l_price_cor_po_header_id,
12475            l_price_cor_po_line_id,
12476            l_price_cor_po_line_loc_id,
12477            l_price_cor_po_distribution_id
12478       FROM ap_invoices ai, ap_invoice_lines ail, ap_invoice_distributions aid
12479       WHERE ai.invoice_num = p_invoice_lines_rec.price_correct_inv_num
12480       AND ail.invoice_id = ai.invoice_id
12481       AND ail.line_number = p_invoice_lines_rec.price_correct_inv_line_num
12482       AND aid.invoice_id = ail.invoice_id
12483       AND aid.invoice_line_number = ail.line_number
12484       AND aid.po_distribution_id is not null
12485       AND aid.corrected_invoice_dist_id is null
12486       AND nvl(ail.discarded_flag,'N') = 'N'
12487       AND nvl(ail.cancelled_flag,'N') = 'N'
12488       AND ai.vendor_id = p_invoice_rec.vendor_id
12489       AND rownum <= 1;
12490 
12491       --bug13599126, insert rejection if entered PO detail doesnt match with price correction po details:
12492       if (l_po_header_id is not null and l_price_cor_po_header_id  <> l_po_header_id) or
12493          (l_po_line_id is not null and l_price_cor_po_line_id  <> l_po_line_id) or
12494          (l_po_line_location_id is not null and l_price_cor_po_line_loc_id  <> l_po_line_location_id) or
12495          (l_po_distribution_id is not null and l_price_cor_po_distribution_id  <> l_po_distribution_id) then
12496 
12497           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
12498               AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
12499               p_invoice_lines_rec.invoice_line_id,
12500               'INVALID PO INFO',
12501               p_default_last_updated_by,
12502               p_default_last_update_login,
12503               current_calling_sequence)<> TRUE) THEN
12504             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
12505                      AP_IMPORT_UTILITIES_PKG.Print(
12506                        AP_IMPORT_INVOICES_PKG.g_debug_switch,
12507                        'insert_rejections<-'||current_calling_sequence);
12508             END IF;
12509             RAISE check_po_failure;
12510           END IF;
12511           l_current_invoice_status := 'N';
12512 
12513       else
12514          l_po_header_id := l_price_cor_po_header_id;
12515          l_po_line_id := l_price_cor_po_line_id;
12516          l_po_line_location_id := l_price_cor_po_line_loc_id;
12517          l_po_distribution_id := l_price_cor_po_distribution_id;
12518       end if;
12519 
12520 
12521     EXCEPTION
12522       WHEN NO_DATA_FOUND THEN
12523        IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
12524               AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
12525               p_invoice_lines_rec.invoice_line_id,
12526               'INVALID PO INFO',
12527               p_default_last_updated_by,
12528               p_default_last_update_login,
12529               current_calling_sequence)<> TRUE) THEN
12530          IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
12531                      AP_IMPORT_UTILITIES_PKG.Print(
12532                        AP_IMPORT_INVOICES_PKG.g_debug_switch,
12533                        'insert_rejections<-'||current_calling_sequence);
12534          END IF;
12535          RAISE check_po_failure;
12536        END IF;
12537        l_current_invoice_status := 'N';
12538     END;
12539 
12540    END IF;
12541 
12542    --Check match_basis. Amount Based  Matching.
12543    --Match Basis is already dervied in section 31.1
12544    IF (l_price_correct_inv_id IS NOT NULL
12545 	and p_invoice_lines_rec.price_correct_inv_line_num IS NOT NULL) THEN
12546      BEGIN
12547 
12548        debug_info := '(v_check_line_po_info 34.5) Check if price correction line is matched to'
12549 			||' a service order shipment';
12550        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
12551          AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
12552                                        debug_info);
12553        END IF;
12554 
12555 
12556        IF (l_match_basis = 'AMOUNT') THEN
12557 
12558            IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
12559                 AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
12560                 p_invoice_lines_rec.invoice_line_id,
12561                 'INCONSISTENT PO INFO',
12562                 p_default_last_updated_by,
12563                 p_default_last_update_login,
12564                 current_calling_sequence)<> TRUE) THEN
12565 
12566                 IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
12567 
12568                      AP_IMPORT_UTILITIES_PKG.Print(
12569                        AP_IMPORT_INVOICES_PKG.g_debug_switch,
12570                        'insert_rejections<-'||current_calling_sequence);
12571 
12572                 END IF;
12573 
12574                 RAISE check_po_failure;
12575 
12576            END IF;
12577 
12578 	   l_current_invoice_status := 'N';
12579 
12580         END IF;
12581      EXCEPTION WHEN OTHERS THEN
12582        NULL;
12583      END;
12584 
12585    END IF;  /* check match_basis */
12586 
12587 
12588    IF l_po_distribution_id is not null then
12589 
12590       debug_info := '(v_check_line_po_info 34.6) Check pc invoice is matched '
12591                     ||'to po dist';
12592        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
12593         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
12594                                       debug_info);
12595       END IF;
12596 
12597       BEGIN
12598         --the query below will ensure the invoice has at least one base matched
12599         --distribution matched to this po distribution
12600 
12601         SELECT 'Y'
12602         INTO    l_pc_inv_valid
12603         FROM    ap_invoice_distributions
12604         WHERE   invoice_id = l_price_correct_inv_id
12605 	AND     invoice_line_number = p_invoice_lines_rec.price_correct_inv_line_num
12606         AND     po_distribution_id = l_po_distribution_id;
12607 
12608       EXCEPTION
12609         WHEN NO_DATA_FOUND THEN
12610           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
12611               AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
12612               p_invoice_lines_rec.invoice_line_id,
12613               'INVALID PO INFO',
12614               p_default_last_updated_by,
12615               p_default_last_update_login,
12616               current_calling_sequence)<> TRUE) THEN
12617 
12618             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
12619               AP_IMPORT_UTILITIES_PKG.Print(
12620               AP_IMPORT_INVOICES_PKG.g_debug_switch,
12621               'insert_rejections<-'||current_calling_sequence);
12622             END IF;
12623             RAISE check_po_failure;
12624           END IF;
12625           l_current_invoice_status := 'N';
12626         WHEN TOO_MANY_ROWS THEN
12627           NULL;
12628       END;
12629 
12630     END IF;
12631 
12632 
12633     IF (l_po_distribution_id is null and
12634         l_po_line_location_id is not null) THEN
12635 
12636       debug_info := '(v_check_line_po_info 34.7) Check pc invoice is matched'
12637                     ||' to shipment';
12638        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
12639         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
12640                                       debug_info);
12641       END IF;
12642 
12643       BEGIN
12644         --the query below will ensure the invoice has at least one base matched
12645         --distribution matched to one of the po dists for this shipment
12646 
12647         SELECT 'Y'
12648           INTO l_pc_inv_valid
12649           FROM ap_invoice_distributions
12650          WHERE invoice_id = l_price_correct_inv_id
12651            AND invoice_line_number = p_invoice_lines_rec.price_correct_inv_line_num
12652            AND po_distribution_id IN (
12653                  SELECT po_distribution_id
12654                    FROM po_distributions
12655                    WHERE line_location_id = l_po_line_location_id);
12656 
12657       EXCEPTION
12658         WHEN NO_DATA_FOUND THEN
12659           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
12660                AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
12661                 p_invoice_lines_rec.invoice_line_id,
12662                'INVALID PO INFO',
12663                 p_default_last_updated_by,
12664                 p_default_last_update_login,
12665                 current_calling_sequence)<> TRUE) THEN
12666             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
12667                      AP_IMPORT_UTILITIES_PKG.Print(
12668                        AP_IMPORT_INVOICES_PKG.g_debug_switch,
12669                        'insert_rejections<-'||current_calling_sequence);
12670             END IF;
12671             RAISE check_po_failure;
12672           END IF;
12673           l_current_invoice_status := 'N';
12674         WHEN TOO_MANY_ROWS THEN
12675           NULL;
12676       END;
12677 
12678     END IF;
12679 
12680 
12681     --No price corrections should not be performed against finally closed POs.
12682     BEGIN
12683 
12684        debug_info := '(v_check_line_po_info 34.8) Check if po shipment is finally closed';
12685        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
12686          AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
12687                                       debug_info);
12688        END IF;
12689 
12690        SELECT 'Y'
12691        INTO l_shipment_finally_closed
12692        FROM ap_invoice_lines ail, po_line_locations pll
12693        WHERE ail.invoice_id = l_price_correct_inv_id
12694        AND ail.line_number = p_invoice_lines_rec.price_correct_inv_line_num
12695        AND pll.line_location_id = ail.po_line_location_id
12696        AND pll.closed_code = 'FINALLY CLOSED';
12697 
12698        IF (nvl(l_shipment_finally_closed,'N') = 'Y') THEN
12699 
12700 	  IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
12701                 AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
12702                 p_invoice_lines_rec.invoice_line_id,
12703                 'INVALID PO INFO',
12704                 p_default_last_updated_by,
12705                 p_default_last_update_login,
12706                 current_calling_sequence)<> TRUE) THEN
12707 
12708               IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
12709 
12710                      AP_IMPORT_UTILITIES_PKG.Print(
12711                        AP_IMPORT_INVOICES_PKG.g_debug_switch,
12712                        'insert_rejections<-'||current_calling_sequence);
12713 
12714               END IF;
12715               RAISE check_po_failure;
12716 
12717           END IF;
12718 
12719           l_current_invoice_status := 'N';
12720 
12721        END IF;
12722 
12723     EXCEPTION
12724        WHEN OTHERS THEN
12725 	  NULL;
12726 
12727     END ;
12728 
12729 
12730     --Quantity Invoiced must be always be positive or NULL for price corrections regardless of
12731     --the invoice type.
12732     debug_info := '(v_check_line_po_info 34.9) Check if Quantity_Invoiced for the price corrections'
12733 			||'to be either NULL or positive';
12734     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
12735          AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
12736                                       debug_info);
12737     END IF;
12738 
12739     IF (p_invoice_lines_rec.quantity_invoiced IS NOT NULL AND
12740   	p_invoice_lines_rec.quantity_invoiced < 0) THEN
12741 
12742       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
12743                 AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
12744                 p_invoice_lines_rec.invoice_line_id,
12745                 'INVALID PO INFO',
12746                 p_default_last_updated_by,
12747                 p_default_last_update_login,
12748                 current_calling_sequence)<> TRUE) THEN
12749 
12750            IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
12751 
12752                      AP_IMPORT_UTILITIES_PKG.Print(
12753                        AP_IMPORT_INVOICES_PKG.g_debug_switch,
12754                        'insert_rejections<-'||current_calling_sequence);
12755 
12756            END IF;
12757            RAISE check_po_failure;
12758 
12759        END IF;
12760 
12761        l_current_invoice_status := 'N';
12762 
12763     END IF;
12764 
12765 
12766     --Unit Price must be always be positive for STANDARD invoices, and negative
12767     --for CREDIT/DEBIT memos, and postive or negative for MIXED type of invoices.
12768     debug_info := '(v_check_line_po_info 34.10) Check the sign of the unit_price against'
12769 		  ||'the invoice type';
12770     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
12771          AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
12772                                       debug_info);
12773     END IF;
12774 
12775     --Contract Payments: Modified the IF condition to add 'PREPAYMENT'.
12776 
12777     IF ((p_invoice_rec.invoice_type_lookup_code IN ('STANDARD','PREPAYMENT') and
12778          p_invoice_lines_rec.unit_price < 0) OR
12779         (p_invoice_rec.invoice_type_lookup_code IN ('CREDIT','DEBIT') and
12780 	 p_invoice_lines_rec.unit_price > 0)) THEN
12781 
12782       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
12783                 AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
12784                 p_invoice_lines_rec.invoice_line_id,
12785                 'INVALID PO INFO',
12786                 p_default_last_updated_by,
12787                 p_default_last_update_login,
12788                 current_calling_sequence)<> TRUE) THEN
12789 
12790            IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
12791 
12792                      AP_IMPORT_UTILITIES_PKG.Print(
12793                        AP_IMPORT_INVOICES_PKG.g_debug_switch,
12794                        'insert_rejections<-'||current_calling_sequence);
12795 
12796            END IF;
12797            RAISE check_po_failure;
12798 
12799        END IF;
12800 
12801        l_current_invoice_status := 'N';
12802 
12803     END IF;
12804 
12805     BEGIN
12806 
12807       debug_info := '(v_check_line_po_info 34.11) Check if quantity_invoiced for price correction'
12808 		  ||' exceeds the quantity_invoiced on the base match';
12809 
12810       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
12811          AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
12812                                       debug_info);
12813       END IF;
12814 
12815       BEGIN
12816 
12817          SELECT ail.quantity_invoiced
12818          INTO l_base_match_quantity
12819          FROM ap_invoice_lines ail
12820          WHERE ail.invoice_id = l_price_correct_inv_id
12821          AND ail.line_number = p_invoice_lines_rec.price_correct_inv_line_num;
12822 
12823 
12824       --bugfix:5640388
12825        EXCEPTION
12826          WHEN NO_DATA_FOUND THEN
12827             IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
12828        			       AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
12829                        	       p_invoice_lines_rec.invoice_line_id,
12830                                'PRICE CORRECT INV INVALID',
12831 	                       p_default_last_updated_by,
12832 			       p_default_last_update_login,
12833 			       current_calling_sequence)<> TRUE) THEN
12834 	       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
12835 	           AP_IMPORT_UTILITIES_PKG.Print(
12836 	                          AP_IMPORT_INVOICES_PKG.g_debug_switch,
12837 	                          'insert_rejections<-'||current_calling_sequence);
12838 																								                 END IF;
12839 	             RAISE check_po_failure;
12840                END IF;
12841                l_current_invoice_status := 'N';
12842          WHEN TOO_MANY_ROWS THEN
12843            NULL;
12844       END;
12845 
12846       debug_info := '(v_check_line_po_info Debug 1) p_invoice_lines_rec.quantity_invoiced:'
12847 		  ||p_invoice_lines_rec.quantity_invoiced||
12848                   ', l_base_match_quantity:'||l_base_match_quantity||
12849                   ', for l_price_correct_inv_id:'||l_price_correct_inv_id||
12850                   ', and p_invoice_lines_rec.price_correct_inv_line_num:'||p_invoice_lines_rec.price_correct_inv_line_num;
12851       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
12852          AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
12853                                       debug_info);
12854       END IF;
12855 
12856 
12857       IF ( p_invoice_lines_rec.quantity_invoiced > l_base_match_quantity) THEN
12858 
12859          IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
12860                 AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
12861                 p_invoice_lines_rec.invoice_line_id,
12862                 'AMOUNT BILLED BELOW ZERO',
12863                 p_default_last_updated_by,
12864                 p_default_last_update_login,
12865                 current_calling_sequence)<> TRUE) THEN
12866 
12867              IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
12868 
12869                      AP_IMPORT_UTILITIES_PKG.Print(
12870                        AP_IMPORT_INVOICES_PKG.g_debug_switch,
12871                        'insert_rejections<-'||current_calling_sequence);
12872 
12873              END IF;
12874              RAISE check_po_failure;
12875 
12876           END IF;
12877 
12878           l_current_invoice_status := 'N';
12879 
12880       END IF;
12881 
12882      END ;
12883 
12884 
12885     --Amount_Billed against the Purchase Order Shipment should not go below 0 IN
12886     --absolute terms and relative to the base match. The amount billed for the
12887     --base match should be calculated based on quantity being corrected and any
12888     --previous existing price corrections against the base match.
12889     BEGIN
12890 
12891       debug_info := '(v_check_line_po_info 34.12) Check if amount_billed against PO Shipment/Dist'
12892 		  ||'goes below zero due to this price correction relative to the base match';
12893 
12894 
12895       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
12896          AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
12897                                       debug_info);
12898       END IF;
12899 
12900       l_line_amt_calculated :=
12901       nvl(ap_utilities_pkg.ap_round_currency(
12902            p_invoice_lines_rec.unit_price*
12903            p_invoice_lines_rec.quantity_invoiced,
12904            p_invoice_rec.invoice_currency_code)
12905           ,0);
12906 
12907       IF (p_invoice_lines_rec.amount < 0 OR l_line_amt_calculated < 0) THEN
12908 
12909          BEGIN
12910 
12911             SELECT nvl(sum(ail.amount),0)
12912             INTO l_correction_amount
12913             FROM ap_invoice_lines ail
12914             WHERE ail.invoice_id = l_price_correct_inv_id
12915             AND ail.line_number = p_invoice_lines_rec.price_correct_inv_line_num
12916             AND ail.match_type IN ('PRICE_CORRECTION','QTY_CORRECTION');
12917 
12918 	    --bugfix:5640388
12919 	    EXCEPTION
12920 	        WHEN NO_DATA_FOUND THEN
12921 	            IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
12922 	                     AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
12923 	                     p_invoice_lines_rec.invoice_line_id,
12924 	                     'PRICE CORRECT INV INVALID',
12925 	                     p_default_last_updated_by,
12926 	                     p_default_last_update_login,
12927 	                     current_calling_sequence)<> TRUE) THEN
12928 	                  IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
12929 	                        AP_IMPORT_UTILITIES_PKG.Print(
12930 	                                  AP_IMPORT_INVOICES_PKG.g_debug_switch,
12931 	                                  'insert_rejections<-'||current_calling_sequence);
12932 	                  END IF;
12933 	                 RAISE check_po_failure;
12934 		     END IF;
12935 		     l_current_invoice_status := 'N';
12936 	        WHEN TOO_MANY_ROWS THEN
12937 	            NULL;
12938 	END;
12939 
12940         debug_info := '(v_check_line_po_info Debug 2) l_line_amt_calculated:'
12941 		  ||l_line_amt_calculated||
12942                   ', l_base_match_amount:'||l_base_match_amount||
12943                   ', p_invoice_lines_rec.amount:'||p_invoice_lines_rec.amount||
12944                   ', l_correction_amount:'||l_correction_amount||
12945                   ', for l_price_correct_inv_id:'||l_price_correct_inv_id||
12946                   ', and p_invoice_lines_rec.price_correct_inv_line_num:'||p_invoice_lines_rec.price_correct_inv_line_num;
12947         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
12948          AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
12949                                       debug_info);
12950         END IF;
12951 
12952 
12953         IF (abs(nvl(p_invoice_lines_rec.amount,l_line_amt_calculated)) >
12954 	 				(l_base_match_amount + l_correction_amount)) THEN
12955 
12956            IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
12957                 AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
12958                 p_invoice_lines_rec.invoice_line_id,
12959                 'AMOUNT BILLED BELOW ZERO',
12960                 p_default_last_updated_by,
12961                 p_default_last_update_login,
12962                 current_calling_sequence)<> TRUE) THEN
12963 
12964              IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
12965 
12966                      AP_IMPORT_UTILITIES_PKG.Print(
12967                        AP_IMPORT_INVOICES_PKG.g_debug_switch,
12968                        'insert_rejections<-'||current_calling_sequence);
12969 
12970              END IF;
12971              RAISE check_po_failure;
12972 
12973            END IF;
12974 
12975            l_current_invoice_status := 'N';
12976 
12977          END IF;
12978 
12979        END IF; /* p_invoice_lines_rec.line_amount < 0 */
12980 
12981     END ;
12982 
12983 
12984 
12985     --make sure we won't reduce the amount billed below zero on
12986     --the po dists relative to the base match
12987     --this requires we use the proration logic used in the matching code
12988     --which, for price corrections, is to prorate based upon amount if the
12989     --quantity billed on the po is zero, otherwise prorate by quantity billed
12990 
12991     IF  l_po_distribution_id IS NULL AND
12992         l_po_line_location_id IS NOT NULL AND
12993         (nvl(p_invoice_lines_rec.amount,0) < 0 OR
12994         l_line_amt_calculated < 0) THEN
12995 
12996       debug_info := '(v_check_line_po_info 34.13) Ensure amount billed on po '
12997                      ||'distributions wont be reduced below zero for shipment';
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                                       debug_info);
13001       END IF;
13002 
13003       BEGIN
13004 
13005          SELECT amount, quantity_invoiced
13006          INTO l_total_amount_invoiced, l_total_quantity_invoiced
13007          FROM ap_invoice_lines ail
13008          WHERE ail.invoice_id = l_price_correct_inv_id
13009          AND ail.line_number = p_invoice_lines_rec.price_correct_inv_line_num;
13010 
13011          --bugfix:5640388
13012          EXCEPTION
13013 	   WHEN NO_DATA_FOUND THEN
13014 	      IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
13015 	                     AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
13016 	                     p_invoice_lines_rec.invoice_line_id,
13017 	                     'PRICE CORRECT INV INVALID',
13018 	                     p_default_last_updated_by,
13019 	                     p_default_last_update_login,
13020 	                     current_calling_sequence)<> TRUE) THEN
13021 	          IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13022 	               AP_IMPORT_UTILITIES_PKG.Print(
13023 	                       AP_IMPORT_INVOICES_PKG.g_debug_switch,
13024 	                       'insert_rejections<-'||current_calling_sequence);
13025 	          END IF;
13026 	          RAISE check_po_failure;
13027 	      END IF;
13028 	      l_current_invoice_status := 'N';
13029           WHEN TOO_MANY_ROWS THEN
13030              NULL;
13031       END;
13032 
13033         debug_info := '(v_check_line_po_info Debug 3) l_line_amt_calculated:'
13034 		  ||l_line_amt_calculated||
13035                   ', l_total_quantity_invoiced:'||l_total_quantity_invoiced||
13036                   ', p_invoice_lines_rec.amount:'||p_invoice_lines_rec.amount||
13037                   ', l_correction_amount:'||l_correction_amount||
13038                   ', for l_price_correct_inv_id:'||l_price_correct_inv_id||
13039                   ', and p_invoice_lines_rec.price_correct_inv_line_num:'||p_invoice_lines_rec.price_correct_inv_line_num;
13040         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13041          AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
13042                                       debug_info);
13043         END IF;
13044 
13045       IF l_total_quantity_invoiced = 0 THEN
13046         IF (l_total_amount_invoiced + l_correction_amount + nvl(p_invoice_lines_rec.amount,l_line_amt_calculated) < 0) THEN
13047 
13048                IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
13049                     AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
13050                      p_invoice_lines_rec.invoice_line_id,
13051                      'AMOUNT BILLED BELOW ZERO',
13052                      p_default_last_updated_by,
13053                      p_default_last_update_login,
13054                      current_calling_sequence)<> TRUE) THEN
13055 
13056                  IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13057                       AP_IMPORT_UTILITIES_PKG.Print(
13058                           AP_IMPORT_INVOICES_PKG.g_debug_switch,
13059                          'insert_rejections<-'||current_calling_sequence);
13060                  END IF;
13061                  RAISE check_po_failure;
13062                END IF;
13063                l_current_invoice_status := 'N';
13064 
13065          END IF;
13066       END IF;
13067 
13068 
13069       IF l_total_quantity_invoiced > 0 then
13070 
13071         FOR pc_inv_dists IN (SELECT quantity_invoiced, amount, invoice_distribution_id
13072 			    FROM ap_invoice_distributions
13073 			    WHERE invoice_id = l_price_correct_inv_id
13074 			    AND invoice_line_number = p_invoice_lines_rec.price_correct_inv_line_num)
13075 
13076         LOOP
13077 
13078 	  BEGIN
13079 
13080              SELECT sum(aid.amount)
13081              INTO l_correction_dist_amount
13082 	     FROM ap_invoice_distributions aid
13083              WHERE corrected_invoice_dist_id = pc_inv_dists.invoice_distribution_id
13084 	     GROUP BY corrected_invoice_dist_id ;
13085 
13086           EXCEPTION WHEN OTHERS THEN
13087 	     l_correction_dist_amount := 0;
13088           END ;
13089 
13090         debug_info := '(v_check_line_po_info Debug 4) l_line_amt_calculated:'
13091 		  ||l_line_amt_calculated||
13092                   ', l_total_quantity_invoiced:'||l_total_quantity_invoiced||
13093                   ', p_invoice_lines_rec.amount:'||p_invoice_lines_rec.amount||
13094                   ', l_correction_amount:'||l_correction_amount||
13095                   ', pc_inv_dists.amount:'||pc_inv_dists.amount||
13096                   ', for l_price_correct_inv_id:'||l_price_correct_inv_id||
13097                   ', and p_invoice_lines_rec.price_correct_inv_line_num:'||p_invoice_lines_rec.price_correct_inv_line_num;
13098         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13099          AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
13100                                       debug_info);
13101         END IF;
13102 
13103           IF (pc_inv_dists.quantity_invoiced/ l_total_quantity_invoiced *
13104               p_invoice_lines_rec.amount + l_correction_dist_amount + pc_inv_dists.amount) < 0 OR
13105              (pc_inv_dists.quantity_invoiced/ l_total_quantity_invoiced *
13106               l_line_amt_calculated + l_correction_dist_amount + pc_inv_dists.amount) < 0  THEN
13107 
13108              IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
13109                  AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
13110                  p_invoice_lines_rec.invoice_line_id,
13111                  'AMOUNT BILLED BELOW ZERO',
13112                  p_default_last_updated_by,
13113                  p_default_last_update_login,
13114                  current_calling_sequence)<> TRUE)  THEN
13115                IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13116                    AP_IMPORT_UTILITIES_PKG.Print(
13117                    AP_IMPORT_INVOICES_PKG.g_debug_switch,
13118                    'insert_rejections<-'||current_calling_sequence);
13119                END IF;
13120                RAISE check_po_failure;
13121              END IF;
13122              l_current_invoice_status := 'N';
13123 
13124           END IF;
13125 
13126         END LOOP;
13127 
13128        END IF;
13129 
13130      END IF;  --end of checking if the qty billed on the shipment's dists
13131              --will fall below zero relative to the base match distribution's amount_billed
13132 
13133 
13134 
13135     --Make sure we won't reduce the amount billed below zero on the po dist absolutely
13136     IF (l_po_distribution_id IS NOT NULL AND
13137         (nvl(p_invoice_lines_rec.amount,0) < 0 OR
13138          l_line_amt_calculated < 0)) THEN
13139 
13140       debug_info := '(v_check_line_po_info 34.14) Ensure amount billed on po '
13141                     ||'dist wont be reduced below zero, l_po_distribution_id is: '||l_po_distribution_id;
13142       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13143         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
13144                                       debug_info);
13145       END IF;
13146 
13147    BEGIN
13148       BEGIN
13149 	--Contract Payments: Modified the SELECT clause
13150         SELECT decode(distribution_type,'PREPAYMENT',nvl(amount_financed,0),nvl(amount_billed,0))
13151         INTO l_pc_po_amt_billed
13152         FROM po_distributions
13153         WHERE po_distribution_id = l_po_distribution_id
13154           AND line_location_id IS NOT NULL; /* BUG 3253594 */
13155 
13156       --bugfix:5640388
13157       EXCEPTION
13158         WHEN NO_DATA_FOUND THEN
13159            IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
13160                    AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
13161                    p_invoice_lines_rec.invoice_line_id,
13162                    'PRICE CORRECT INV INVALID',
13163                    p_default_last_updated_by,
13164                    p_default_last_update_login,
13165                    current_calling_sequence)<> TRUE) THEN
13166                 IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13167                     AP_IMPORT_UTILITIES_PKG.Print(
13168                               AP_IMPORT_INVOICES_PKG.g_debug_switch,
13169                               'insert_rejections<-'||current_calling_sequence);
13170                 END IF;
13171                 RAISE check_po_failure;
13172            END IF;
13173            l_current_invoice_status := 'N';
13174         WHEN TOO_MANY_ROWS THEN
13175            NULL;
13176         END;
13177 
13178         debug_info := '(v_check_line_po_info Debug 5) l_line_amt_calculated:'
13179 		  ||l_line_amt_calculated||
13180                   ', l_pc_po_amt_billed:'||l_pc_po_amt_billed||
13181                   ', p_invoice_lines_rec.amount:'||p_invoice_lines_rec.amount||
13182                   ', for l_price_correct_inv_id:'||l_price_correct_inv_id||
13183                   ', and p_invoice_lines_rec.price_correct_inv_line_num:'||p_invoice_lines_rec.price_correct_inv_line_num;
13184         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13185          AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
13186                                       debug_info);
13187         END IF;
13188 
13189 
13190         IF (l_pc_po_amt_billed + nvl(p_invoice_lines_rec.amount,0) < 0) or
13191            (l_pc_po_amt_billed + l_line_amt_calculated < 0) then
13192 
13193            IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
13194               AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
13195               p_invoice_lines_rec.invoice_line_id,
13196               'AMOUNT BILLED BELOW ZERO',
13197               p_default_last_updated_by,
13198               p_default_last_update_login,
13199               current_calling_sequence)<> TRUE) THEN
13200              IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13201                AP_IMPORT_UTILITIES_PKG.Print(
13202                    AP_IMPORT_INVOICES_PKG.g_debug_switch,
13203                   'insert_rejections<-'||current_calling_sequence);
13204              END IF;
13205              RAISE check_po_failure;
13206            END IF;
13207            l_current_invoice_status := 'N';
13208         END IF;
13209 
13210       EXCEPTION
13211         WHEN NO_DATA_FOUND THEN
13212           NULL;
13213       END;
13214 
13215     END IF;
13216 
13217 
13218     --make sure we won't reduce the amount billed below zero on the po dists
13219     --this requires we use the proration logic used in the matching code
13220     --which, for price corrections, is to prorate based upon amount if the
13221     --quantity billed on the po is zero, otherwise prorate by quantity billed
13222 
13223     IF  l_po_distribution_id IS NULL AND
13224         l_po_line_location_id IS NOT NULL AND
13225         (nvl(p_invoice_lines_rec.amount,0) < 0 OR
13226         l_line_amt_calculated < 0) THEN
13227 
13228       debug_info := '(v_check_line_po_info 34.15) Ensure amount billed on po '
13229                      ||'distribtuions wont be reduced below zero for shipment';
13230       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13231         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
13232                                       debug_info);
13233       END IF;
13234 
13235 
13236       --Contract Payments: Modified the SELECT clause
13237       BEGIN
13238 
13239         SELECT nvl(SUM(decode(distribution_type,'PREPAYMENT',nvl(amount_financed,0),nvl(amount_billed,0))),0),
13240                nvl(SUM(decode(distribution_type,'PREPAYMENT',nvl(quantity_financed,0),nvl(quantity_billed,0))),0)
13241         INTO l_total_amount_billed, l_total_quantity_billed
13242         FROM po_distributions
13243         WHERE line_location_id = l_po_line_location_id
13244         AND po_distribution_id IN (SELECT po_distribution_id
13245                                  FROM   ap_invoice_distributions
13246                                  WHERE  invoice_id = l_price_correct_inv_id
13247 				 AND    invoice_line_number = p_invoice_lines_rec.price_correct_inv_line_num);
13248 
13249         --bugfix:5640388
13250        EXCEPTION
13251           WHEN NO_DATA_FOUND THEN
13252               IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
13253                       AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
13254                       p_invoice_lines_rec.invoice_line_id,
13255                       'PRICE CORRECT INV INVALID',
13256                       p_default_last_updated_by,
13257                       p_default_last_update_login,
13258                       current_calling_sequence)<> TRUE) THEN
13259                    IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13260                        AP_IMPORT_UTILITIES_PKG.Print(
13261                                 AP_IMPORT_INVOICES_PKG.g_debug_switch,
13262                                     'insert_rejections<-'||current_calling_sequence);
13263                    END IF;
13264                    RAISE check_po_failure;
13265                END IF;
13266                l_current_invoice_status := 'N';
13267           WHEN TOO_MANY_ROWS THEN
13268                NULL;
13269        END;
13270 
13271        debug_info := '(v_check_line_po_info Debug 6) l_line_amt_calculated:'
13272 		  ||l_line_amt_calculated||
13273                   ', l_total_quantity_billed:'||l_total_quantity_billed||
13274                   ', p_invoice_lines_rec.amount:'||p_invoice_lines_rec.amount||
13275                   ', l_total_amount_billed:'||l_total_amount_billed||
13276                   ', for l_price_correct_inv_id:'||l_price_correct_inv_id||
13277                   ', and p_invoice_lines_rec.price_correct_inv_line_num:'||p_invoice_lines_rec.price_correct_inv_line_num;
13278         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13279          AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
13280                                       debug_info);
13281         END IF;
13282 
13283        IF l_total_quantity_billed = 0 THEN
13284         IF (l_total_amount_billed + nvl(p_invoice_lines_rec.amount,0) < 0) OR
13285            (l_total_amount_billed + l_line_amt_calculated < 0) THEN
13286 
13287                IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
13288                     AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
13289                      p_invoice_lines_rec.invoice_line_id,
13290                      'AMOUNT BILLED BELOW ZERO',
13291                      p_default_last_updated_by,
13292                      p_default_last_update_login,
13293                      current_calling_sequence)<> TRUE) THEN
13294 
13295                  IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13296                       AP_IMPORT_UTILITIES_PKG.Print(
13297                           AP_IMPORT_INVOICES_PKG.g_debug_switch,
13298                          'insert_rejections<-'||current_calling_sequence);
13299                  END IF;
13300                  RAISE check_po_failure;
13301                END IF;
13302                l_current_invoice_status := 'N';
13303 
13304          END IF;
13305       END IF;
13306 
13307 
13308       IF l_total_quantity_billed > 0 then
13309 
13310 	--Contract Payments: Modified the SELECT clause
13311         FOR pc_po_dists IN (SELECT decode(pod.distribution_type,'PREPAYMENT',nvl(pod.quantity_financed,0),
13312 					 nvl(pod.quantity_billed,0)) quantity_billed,
13313 				   decode(pod.distribution_type,'PREPAYMENT',nvl(pod.amount_financed,0),
13314 				         nvl(pod.amount_billed,0)) amount_billed
13315                             FROM po_distributions pod
13316                             WHERE pod.line_location_id = l_po_line_location_id
13317                             AND pod.po_distribution_id IN (
13318                                  SELECT aid.po_distribution_id
13319                                  FROM ap_invoice_distributions aid
13320                                  WHERE  aid.invoice_id = l_price_correct_inv_id
13321 			         AND   aid.invoice_line_number = p_invoice_lines_rec.price_correct_inv_line_num))
13322         LOOP
13323 
13324           IF (pc_po_dists.quantity_billed / l_total_quantity_billed *
13325               p_invoice_lines_rec.amount + pc_po_dists.amount_billed) < 0 OR
13326              (pc_po_dists.quantity_billed / l_total_quantity_billed *
13327               l_line_amt_calculated + pc_po_dists.amount_billed) < 0  THEN
13328 
13329                 debug_info := '(v_check_line_po_info Debug 7) l_line_amt_calculated:'
13330                           ||l_line_amt_calculated||
13331                           ', l_total_quantity_billed:'||l_total_quantity_billed||
13332                           ', p_invoice_lines_rec.amount:'||p_invoice_lines_rec.amount||
13333                           ', pc_po_dists.amount_billed:'||pc_po_dists.amount_billed||
13334                           ', pc_po_dists.quantity_billed:'||pc_po_dists.quantity_billed||
13335                           ', for l_price_correct_inv_id:'||l_price_correct_inv_id||
13336                           ', and p_invoice_lines_rec.price_correct_inv_line_num:'||p_invoice_lines_rec.price_correct_inv_line_num;
13337                 IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13338                  AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
13339                                               debug_info);
13340                 END IF;
13341 
13342              IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
13343                  AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
13344                  p_invoice_lines_rec.invoice_line_id,
13345                  'AMOUNT BILLED BELOW ZERO',
13346                  p_default_last_updated_by,
13347                  p_default_last_update_login,
13348                  current_calling_sequence)<> TRUE)  THEN
13349                IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13350                    AP_IMPORT_UTILITIES_PKG.Print(
13351                    AP_IMPORT_INVOICES_PKG.g_debug_switch,
13352                    'insert_rejections<-'||current_calling_sequence);
13353                END IF;
13354                RAISE check_po_failure;
13355              END IF;
13356              l_current_invoice_status := 'N';
13357 
13358           END IF;
13359 
13360         END LOOP;
13361 
13362        END IF;
13363 
13364      END IF;  --end of checking if the qty billed on the shipment's dists
13365              --will fall below zero
13366 
13367    END IF;   -- p_price_correction_flag = 'Y'
13368 
13369  END IF ; /* g_source <> 'PPA' */
13370 
13371 --Bug 5225547 added the following
13372  -------------------------------------------------------------------------
13373   -- Validate Match Option if populated
13374   -------------------------------------------------------------------------
13375   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
13376          BEGIN
13377                 SELECT po_header_id
13378                 INTO l_po_header_id
13379                 FROM po_headers
13380                 WHERE segment1 = l_po_number
13381                 AND type_lookup_code in ('BLANKET', 'PLANNED', 'STANDARD');
13382          EXCEPTION
13383          when NO_DATA_FOUND then
13384          null;
13385          END;
13386 
13387         BEGIN
13388                 SELECT po_line_id
13389                 INTO l_po_line_id
13390                 FROM po_lines
13391                 WHERE po_header_id = l_po_header_id
13392                 AND ROWNUM <= 1;
13393         EXCEPTION
13394         when NO_DATA_FOUND then
13395         null;
13396         END;
13397 
13398          BEGIN
13399                 SELECT line_location_id
13400                 INTO l_po_line_location_id
13401                 FROM po_line_locations
13402                 WHERE po_header_id = l_po_header_id
13403                 AND po_line_id = l_po_line_id
13404                 AND shipment_num = p_invoice_lines_rec.po_shipment_num ;
13405         EXCEPTION
13406          when NO_DATA_FOUND then
13407          null;
13408          END;
13409 
13410   End if;
13411 IF (l_po_line_location_id IS NULL) THEN
13412 
13413      IF (l_po_distribution_id IS NOT NULL) THEN
13414         BEGIN
13415 
13416             SELECT line_location_id
13417             INTO l_po_line_location_id
13418             FROM po_distributions
13419             WHERE po_distribution_id = l_po_distribution_id;
13420 
13421         EXCEPTION
13422         WHEN NO_DATA_FOUND THEN
13423  NULL;
13424   END;
13425 
13426      END IF;
13427  END IF;
13428 
13429   If ( l_po_line_location_id is not null) then
13430 
13431       debug_info := '(v_check_line_po_info) :Get Match Option from po shipment';
13432       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13433         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
13434                                       debug_info);
13435       END IF;
13436 
13437         Select nvl(match_option,'P')
13438         Into l_temp_match_option
13439         From po_line_locations
13440         Where line_location_id = l_po_line_location_id;
13441 
13442     If (l_temp_match_option is not null) then
13443 
13444    --bug 9292033 : modified below condition to allow prepayment invoices with match option as 'P' and 'R' on PO
13445 
13446      /*IF (p_invoice_lines_rec.match_option IS NOT NULL AND
13447               p_invoice_lines_rec.match_option <> l_temp_match_option) THEN*/
13448 
13449         If ( p_invoice_lines_rec.match_option is not null
13450 	     and ((nvl(p_invoice_rec.invoice_type_lookup_code,'STANDARD') = 'PREPAYMENT'
13451 	           AND p_invoice_lines_rec.match_option = 'R'
13452 		   AND l_temp_match_option = 'P')
13453 		OR
13454 		   (nvl(p_invoice_rec.invoice_type_lookup_code,'STANDARD') <> 'PREPAYMENT'
13455                     AND p_invoice_lines_rec.match_option <> l_temp_match_option))) then
13456 
13457           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
13458               AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
13459               p_invoice_lines_rec.invoice_line_id,
13460               'INVALID MATCH OPTION',
13461               p_default_last_updated_by,
13462               p_default_last_update_login,
13463               current_calling_sequence) <> TRUE) THEN
13464 
13465               IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13466                AP_IMPORT_UTILITIES_PKG.Print(
13467                  AP_IMPORT_INVOICES_PKG.g_debug_switch,
13468                  'insert_rejections<-'||current_calling_sequence);
13469                END IF;
13470                 raise check_po_failure;
13471            End if;
13472            l_current_invoice_status := 'N';
13473 
13474         End if;
13475 
13476         p_invoice_lines_rec.match_option := nvl(l_temp_match_option , p_invoice_lines_rec.match_option);
13477 
13478     End if;
13479  End if;
13480 
13481 --End of bug 5225547
13482 
13483 
13484 
13485     --------------------------------------------------------------------
13486     -- Rest of the PO Validation should be done now
13487     --------------------------------------------------------------------
13488  IF (l_current_invoice_status <>'N') THEN
13489 
13490       ---------------------------------------------------------
13491       -- Step 35
13492       -- check for additional PO validation
13493       ---------------------------------------------------------
13494       debug_info := '(v_check_line_po_info 35) Call v_check_line_po_info2';
13495       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13496         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
13497                                       debug_info);
13498       END IF;
13499 
13500       IF (AP_IMPORT_VALIDATION_PKG.v_check_line_po_info2 (
13501          p_invoice_rec,                                             -- IN
13502          p_invoice_lines_rec,                                     -- IN
13503          p_positive_price_tolerance,                               -- IN
13504          p_qty_ord_tolerance,                                     -- IN
13505 	 p_amt_ord_tolerance,					  -- IN
13506          p_max_qty_ord_tolerance,                                 -- IN
13507 	 p_max_amt_ord_tolerance,				  -- IN
13508          p_po_header_id           => l_po_header_id,                -- IN
13509          p_po_line_id            => l_po_line_id,                     -- IN
13510          p_po_line_location_id => l_po_line_location_id,         -- IN
13511          p_po_distribution_id  => l_po_distribution_id,             -- IN
13512          p_match_option           => l_match_option,             -- OUT NOCOPY
13513          p_calc_quantity_invoiced => l_calc_quantity_invoiced,   -- OUT NOCOPY
13514          p_calc_unit_price          => l_calc_unit_price,        -- OUT NOCOPY
13515          p_calc_line_amount         => l_calc_line_amount,       -- OUT NOCOPY /* ABM */
13516          p_default_last_updated_by => p_default_last_updated_by, -- IN
13517          p_default_last_update_login => p_default_last_update_login,  -- IN
13518          p_current_invoice_status   => l_current_invoice_status,      -- IN OUT
13519          p_match_basis             =>  l_match_basis,        -- IN /*Amount Based Matching */
13520              p_calling_sequence         => current_calling_sequence) <> TRUE )THEN
13521         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13522           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
13523            'v_check_po_line_info2<-' ||current_calling_sequence);
13524         END IF;
13525         RAISE check_po_failure;
13526       END IF;
13527 
13528       --
13529       -- show output values (only if debug_switch = 'Y')
13530       --
13531       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13532         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
13533         '------------------> l_current_invoice_status = '||
13534         l_current_invoice_status);
13535       END IF;
13536 
13537       -- 7531219 moved the following code from Case 23.1
13538      /* Bug 4121338*/
13539       ----------------------------------------------------------
13540       -- Case 35.1, Reject if accrue on receipt is on but
13541       -- overlay gl account is provided in line
13542       ----------------------------------------------------------
13543      IF (p_invoice_lines_rec.dist_code_combination_id IS NOT NULL OR
13544               p_invoice_lines_rec.dist_code_concatenated IS NOT NULL OR
13545                   p_invoice_lines_rec.balancing_segment IS NOT NULL OR
13546                   p_invoice_lines_rec.account_segment IS NOT NULL OR
13547                   p_invoice_lines_rec.cost_center_segment IS NOT NULL) THEN
13548 
13549        -- 7531219 replaced p_invoice_lines_rec.po_line_location_id with l_po_line_location_id
13550        IF ((p_invoice_lines_rec.po_shipment_num IS NOT NULL or l_po_line_location_id /*p_invoice_lines_rec.po_line_location_id*/ IS NOT NULL) AND
13551           (l_po_header_id IS NOT NULL) AND
13552           ((l_po_line_id IS NOT NULL AND l_po_release_id IS NULL) OR
13553            (l_po_release_id IS NOT NULL AND l_po_line_id IS NULL) OR
13554            (l_po_line_id IS NOT NULL AND l_po_release_id IS NOT NULL))) THEN /* Bug 4254606 */
13555           BEGIN
13556 
13557             debug_info := '(v_check_line_po_info 35.1) check accrue on receipt but overlay info is provided';
13558             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13559              AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
13560                                     debug_info);
13561             END IF;
13562 
13563             -- 7531219 replaced p_invoice_lines_rec.po_line_location_id with l_po_line_location_id
13564             SELECT NVL(accrue_on_receipt_flag, 'N')
13565             INTO l_accrue_on_receipt_flag
13566             FROM po_line_locations
13567             WHERE ((shipment_num = p_invoice_lines_rec.po_shipment_num
13568                     AND p_invoice_lines_rec.po_shipment_num IS NOT NULL
13569                     AND p_invoice_lines_rec.po_line_location_id IS NULL)
13570                  OR (line_location_id = l_po_line_location_id --p_invoice_lines_rec.po_line_location_id
13571                     and l_po_line_location_id is not null
13572                     --AND p_invoice_lines_rec.po_line_location_id IS NOT NULL
13573                     AND p_invoice_lines_rec.po_shipment_num IS NULL)
13574                  OR (p_invoice_lines_rec.po_shipment_num IS NOT NULL
13575                     AND p_invoice_lines_rec.po_line_location_id IS NOT NULL
13576                     AND shipment_num = p_invoice_lines_rec.po_shipment_num
13577                     AND  line_location_id = l_po_line_location_id /*p_invoice_lines_rec.po_line_location_id*/))
13578             AND po_header_id = l_po_header_id
13579             AND ((po_release_id = l_po_release_id
13580      AND l_po_line_id IS NULL)
13581                 OR (po_line_id = l_po_line_id
13582                  AND l_po_release_id IS NULL)
13583                 OR (po_line_id = l_po_line_id  /* Bug 4254606 */
13584                  AND po_release_id = l_po_release_id));
13585           EXCEPTION
13586             WHEN OTHERS THEN
13587               Null;
13588           END;
13589 
13590           IF l_accrue_on_receipt_flag = 'Y' THEN
13591 
13592       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
13593                     AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
13594                     p_invoice_lines_rec.invoice_line_id,
13595                     'ACCRUE ON RECEIPT',  -- Bug 5235675
13596                     p_default_last_updated_by,
13597                     p_default_last_update_login,
13598                     current_calling_sequence) <> TRUE) THEN
13599                 IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13600                     AP_IMPORT_UTILITIES_PKG.Print(
13601                     AP_IMPORT_INVOICES_PKG.g_debug_switch,
13602                       'insert_rejections<-'||current_calling_sequence);
13603                 END IF;
13604                  RAISE check_po_failure;
13605               END IF;
13606 
13607 
13608             l_current_invoice_status := 'N';
13609 
13610           END IF;
13611 
13612         END IF;
13613 
13614       END IF;
13615 
13616       /* End Bug 4121338 */
13617 
13618       --------------------------------------------------------
13619       -- Step 36
13620       -- PO Overlay.
13621       -- Retropricing: PO Overlay is not needed for PPA's
13622       ---------------------------------------------------------
13623       IF AP_IMPORT_INVOICES_PKG.g_source <> 'PPA' THEN
13624           debug_info := '(v_check_line_po_info 36) Call v_check_po_overlay';
13625           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13626             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
13627                                          debug_info);
13628           END IF;
13629 
13630           IF (AP_IMPORT_VALIDATION_PKG.v_check_po_overlay(
13631 		p_invoice_rec,					   -- IN
13632                 p_invoice_lines_rec,                               -- IN
13633                 NVL(l_po_line_id, p_invoice_lines_rec.po_line_id), -- IN
13634                 NVL(l_po_line_location_id,
13635                     p_invoice_lines_rec.po_line_location_id),      -- IN
13636                 NVL(l_po_distribution_id,
13637                     p_invoice_lines_rec.po_distribution_id),       -- IN
13638                 p_set_of_books_id,                                   -- IN
13639                 p_default_last_updated_by,                         -- IN
13640                 p_default_last_update_login,                       -- IN
13641                 p_current_invoice_status   => l_current_invoice_status, -- IN OUT
13642                 p_calling_sequence         => current_calling_sequence) <> TRUE )THEN
13643             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13644               AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
13645                       'v_check_po_overlay<-' ||current_calling_sequence);
13646             END IF;
13647             RAISE check_po_failure;
13648           END IF;
13649 
13650           --
13651           -- show output values (only if debug_switch = 'Y')
13652           --
13653           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13654             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
13655              '------------------> l_current_invoice_status = '||
13656              l_current_invoice_status);
13657           END IF;
13658       END IF; ---source <> PPA
13659      END IF; -- Step 35 and Step 36: Invoice Status <> 'N'
13660 
13661    END IF; -- Step 29: Invoice Status <> 'N'
13662 
13663 
13664  ELSIF (p_invoice_lines_rec.line_type_lookup_code IN ('FREIGHT','MISCELLANEOUS','TAX')) THEN
13665 
13666    IF(p_invoice_lines_rec.price_correction_flag = 'Y') THEN
13667 
13668 
13669 	debug_info := '(v_check_line_po_info 37) Cannot associate charge lines with price corrections';
13670         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13671           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
13672                                       debug_info);
13673         END IF;
13674 
13675         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
13676               AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
13677               p_invoice_lines_rec.invoice_line_id,
13678               'INVALID PO INFO',
13679               p_default_last_updated_by,
13680               p_default_last_update_login,
13681               current_calling_sequence) <> TRUE) THEN
13682 
13683            IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13684                AP_IMPORT_UTILITIES_PKG.Print(
13685                  AP_IMPORT_INVOICES_PKG.g_debug_switch,
13686                  'insert_rejections<-'||current_calling_sequence);
13687            END IF;
13688 
13689            RAISE check_po_failure;
13690 
13691          END IF;
13692 
13693          l_current_invoice_status := 'N';
13694 
13695     END IF;
13696 
13697  END IF; /*nvl(p_invoice_lines_rec.line_type_lookup_code, 'ITEM'... */
13698   --
13699   -- Return value
13700   p_current_invoice_status := l_current_invoice_status;
13701 
13702   IF (l_po_header_id IS NOT NULL) Then
13703     p_invoice_lines_rec.po_header_id := l_po_header_id;
13704   End IF;
13705 
13706   IF (l_po_release_id IS NOT NULL) then
13707     p_invoice_lines_rec.po_release_id := l_po_release_id;
13708   END IF;
13709 
13710   IF (l_po_line_id IS NOT NULL) then
13711     p_invoice_lines_rec.po_line_id := l_po_line_id;
13712   END IF;
13713 
13714   IF (l_po_line_location_id IS NOT NULL) Then
13715     p_invoice_lines_rec.po_line_location_id := l_po_line_location_id;
13716   END IF;
13717 
13718   IF (l_po_distribution_id IS NOT NULL) THEN
13719     p_invoice_lines_rec.po_distribution_id := l_po_distribution_id;
13720   END IF;
13721 
13722   IF (l_match_option IS NOT NULL AND
13723     p_invoice_lines_rec.match_option IS NULL) THEN
13724     p_invoice_lines_rec.match_option := l_match_option;
13725   END IF;
13726 
13727   IF (l_calc_quantity_invoiced IS NOT NULL AND
13728     p_invoice_lines_rec.quantity_invoiced IS NULL) then
13729     p_invoice_lines_rec.quantity_invoiced := l_calc_quantity_invoiced;
13730   END IF;
13731 
13732   IF (l_calc_unit_price IS NOT NULL AND
13733     p_invoice_lines_rec.unit_price is NULL) then
13734     p_invoice_lines_rec.unit_price := l_calc_unit_price;
13735   END IF;
13736 
13737   /* Amount Based Matching */
13738   IF (l_calc_line_amount IS NOT NULL AND
13739     p_invoice_lines_rec.amount is NULL) then
13740     p_invoice_lines_rec.amount := l_calc_line_amount;
13741   END IF;
13742 
13743   /* Bug 5400087 */
13744   --7045958
13745 --bug 7532498 - added OR Condition.
13746  --Bug9138771 Quantity Billed is null for EDI Invoices imported through
13747         --    the interface for a Receipt matched invoices as the
13748         --    import treats them as PO matched.Hence no debit memo's are created.
13749 
13750   IF(p_invoice_lines_rec.match_option = 'R') THEN   --Bug9138771
13751     IF (l_match_basis = 'AMOUNT') THEN
13752       p_invoice_lines_rec.match_type := 'ITEM_TO_SERVICE_RECEIPT';
13753     ELSE
13754       p_invoice_lines_rec.match_type := 'ITEM_TO_RECEIPT';
13755     END IF;
13756   ELSE
13757     IF (p_invoice_lines_rec.po_line_location_id IS NOT NULL) THEN
13758       IF (l_match_basis = 'AMOUNT') THEN
13759         p_invoice_lines_rec.match_type := 'ITEM_TO_SERVICE_PO';
13760       ELSE
13761         p_invoice_lines_rec.match_type := 'ITEM_TO_PO';
13762       END IF;
13763     END IF;
13764   END IF;
13765 
13766   IF (p_invoice_lines_rec.price_correction_flag = 'Y') THEN
13767     p_invoice_lines_rec.corrected_inv_id := l_price_correct_inv_id;
13768     p_invoice_lines_rec.match_type := 'PRICE_CORRECTION'; /* 5400087 */
13769   END IF;
13770 
13771   /*Bug8546486 Assigning the description fetched from PO to be inserted
13772          into ap_invoice_lines and ap_invoice_distributions*/
13773   IF (l_item_description IS NOT NULL) then
13774     IF (p_invoice_lines_rec.description IS NULL) then  /* B 9569917 ... added IF condition */
13775 	p_invoice_lines_rec.description := l_item_description;
13776     END IF;
13777     p_invoice_lines_rec.item_description := l_item_description;
13778   END IF;
13779   --End Bug8546486
13780 
13781   RETURN (TRUE);
13782 
13783 EXCEPTION
13784 
13785   WHEN OTHERS THEN
13786     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13787       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
13788                                     debug_info);
13789     END IF;
13790 
13791     IF (SQLCODE < 0) then
13792       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13793         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
13794                                       SQLERRM);
13795       END IF;
13796     END IF;
13797     RETURN(FALSE);
13798 
13799 END v_check_line_po_info;
13800 
13801 
13802 -----------------------------------------------------------------------------
13803 -- This function is used to validate PO information at line level.
13804 --
13805 FUNCTION v_check_line_po_info2 (
13806     p_invoice_rec         IN  AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
13807     p_invoice_lines_rec   IN  AP_IMPORT_INVOICES_PKG.r_line_info_rec,
13808     p_positive_price_tolerance     IN             NUMBER,
13809     p_qty_ord_tolerance            IN             NUMBER,
13810     p_amt_ord_tolerance		   IN		  NUMBER,
13811     p_max_qty_ord_tolerance        IN             NUMBER,
13812     p_max_amt_ord_tolerance	   IN		  NUMBER,
13813     p_po_header_id                   IN             NUMBER,
13814     p_po_line_id                   IN                NUMBER,
13815     p_po_line_location_id           IN               NUMBER,
13816     p_po_distribution_id           IN               NUMBER,
13817     p_match_option                       OUT NOCOPY VARCHAR2,
13818     p_calc_quantity_invoiced           OUT NOCOPY NUMBER,
13819     p_calc_unit_price                  OUT NOCOPY NUMBER,
13820     p_calc_line_amount                 OUT NOCOPY NUMBER, /* Amount Based Matching */
13821     p_default_last_updated_by      IN             NUMBER,
13822     p_default_last_update_login    IN             NUMBER,
13823     p_current_invoice_status       IN  OUT NOCOPY  VARCHAR2,
13824     p_match_basis                  IN             VARCHAR2, /* Amount Based matching */
13825     p_calling_sequence             IN             VARCHAR2) RETURN BOOLEAN
13826 IS
13827 
13828 check_po_failure          EXCEPTION;
13829 l_po_header_id              NUMBER := nvl(p_invoice_lines_rec.po_header_id,
13830                                         p_po_header_id);
13831 l_po_line_id              NUMBER := nvl(p_invoice_lines_rec.po_line_id,
13832                                         p_po_line_id);
13833 l_po_line_location_id      NUMBER := nvl(p_invoice_lines_rec.po_line_location_id,
13834                                         p_po_line_location_id);
13835 l_po_distribution_id      NUMBER := nvl(p_invoice_lines_rec.po_distribution_id,
13836                                         p_po_distribution_id);
13837 l_unit_price              NUMBER := p_invoice_lines_rec.unit_price;
13838 l_po_unit_price              NUMBER;
13839 l_dec_unit_price          NUMBER;
13840 l_unit_of_measure          VARCHAR2(25) := 'N';
13841 l_current_invoice_status  VARCHAR2(1)  := p_current_invoice_status;
13842 l_price_break              VARCHAR2(1);
13843 l_calc_line_amount          NUMBER:=0;
13844 l_overbill                  VARCHAR2(1);
13845 l_qty_based_rejection     VARCHAR2(1);
13846 l_amt_based_rejection	  VARCHAR2(1);
13847 l_quantity_invoiced          NUMBER;
13848 l_qty_invoiced              NUMBER;
13849 l_total_qty_billed          NUMBER;
13850 l_quantity_outstanding      NUMBER;
13851 l_quantity_ordered          NUMBER;
13852 l_qty_already_billed      NUMBER;
13853 l_amount_outstanding      NUMBER;
13854 l_amount_ordered          NUMBER;
13855 l_amt_already_billed      NUMBER;
13856 l_outstanding		  NUMBER;
13857 l_ordered		  NUMBER;
13858 l_already_billed	  NUMBER;
13859 l_po_line_matching_basis  PO_LINES_ALL.MATCHING_BASIS%TYPE;
13860 l_invalid_shipment_type      VARCHAR2(1):= '';
13861 l_invalid_shipment_count  NUMBER;
13862 l_positive_price_variance NUMBER;
13863 l_total_match_amount      NUMBER;
13864 l_temp_match_option          VARCHAR2(25);
13865 current_calling_sequence  VARCHAR2(2000);
13866 debug_info                 VARCHAR2(500);
13867 l_line_amount             NUMBER;  /* Amount Based Matching */
13868 l_temp_shipment_type      PO_LINE_LOCATIONS_ALL.SHIPMENT_TYPE%TYPE;
13869 
13870 BEGIN
13871 
13872   -- Update the calling sequence
13873   --
13874   current_calling_sequence:= 'AP_IMPORT_VALIDATION_PKG.v_check_line_po_info2<-'
13875                              ||P_calling_sequence;
13876 
13877   l_qty_based_rejection := 'N';
13878   l_amt_based_rejection := 'N';
13879 
13880   -----------------------------------------------------------
13881   -- Step 1
13882   -- Check for Active PO
13883   -----------------------------------------------------------
13884   IF ((l_po_header_id IS NOT NULL) AND
13885       (l_po_line_id IS NOT NULL)) THEN
13886 
13887      l_quantity_invoiced := NULL;  --Bug 7446306 - For the Fixed Price Service PO the TERV line is not generated as this is not
13888                               -- initialized to NULL.
13889 
13890     IF (l_po_distribution_id IS NOT NULL) Then
13891       debug_info := '(v_check_line_po_info2 1) Check Valid Shipment Type from '
13892                     ||'l_po_distribution_id ';
13893       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13894         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
13895                                 debug_info);
13896       END IF;
13897 
13898       BEGIN
13899 
13900 	--Contract Payments: Modified the WHERE condition so that we check for
13901         --'Prepayment' type shipments for complex work pos for Prepayment invoices and otherwise
13902         --Standard/Blanket/Scheduled shipments are valid for Standard/Credit invoices.
13903         SELECT 'X'
13904             INTO l_invalid_shipment_type
13905           FROM po_distributions pd,
13906                po_line_locations pll
13907          WHERE pd.line_location_id   = pll.line_location_id
13908            AND pd.po_distribution_id = l_po_distribution_id
13909            AND
13910              (
13911               --(p_invoice_rec.invoice_type_lookup_code <> 'PREPAYMENT' and    .. B# 8528132
13912               (nvl(p_invoice_rec.invoice_type_lookup_code, 'STANDARD') <> 'PREPAYMENT' and    -- B# 8528132
13913 	       pll.SHIPMENT_TYPE IN ('STANDARD','BLANKET','SCHEDULED')
13914               ) OR
13915               (p_invoice_rec.invoice_type_lookup_code = 'PREPAYMENT' and
13916                ((pll.payment_type IS NOT NULL and pll.shipment_type = 'PREPAYMENT') or
13917                 (pll.payment_type IS NULL and pll.shipment_type IN ('STANDARD','BLANKET','SCHEDULED'))
13918                )
13919               )
13920              )
13921            AND pll.APPROVED_FLAG     = 'Y'
13922            AND (nvl(pll.CLOSED_CODE, 'OPEN') <> 'FINALLY CLOSED')
13923            AND nvl(pll.consigned_flag,'N')   <> 'Y';
13924       EXCEPTION
13925         WHEN NO_DATA_FOUND Then
13926           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
13927                 AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
13928                 p_invoice_lines_rec.invoice_line_id,
13929                 'INVALID SHIPMENT TYPE',
13930                 p_default_last_updated_by,
13931                 p_default_last_update_login,
13932                 current_calling_sequence) <> TRUE) THEN
13933             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13934                 AP_IMPORT_UTILITIES_PKG.Print(
13935                 AP_IMPORT_INVOICES_PKG.g_debug_switch,
13936                   'insert_rejections<-'||current_calling_sequence);
13937             END IF;
13938              RAISE check_po_failure;
13939           END IF;
13940           --
13941           l_current_invoice_status := 'N';
13942 
13943       END;
13944 
13945     ELSIF (l_po_line_location_id IS NOT NULL) THEN
13946       -- elsif to po_distribution_id is not null
13947 
13948       debug_info := '(v_check_line_po_info2 1) Check Valid Shipment Type from '
13949                     ||'l_po_line_location_id ';
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,debug_info);
13953       END IF;
13954 
13955       --Contract Payments: Modified the WHERE condition so that we check for
13956       --'Prepayment' type shipments for complex work pos for Prepayment invoices and otherwise
13957       --Standard/Blanket/Scheduled shipments are valid for Standard/Credit invoices.
13958       BEGIN
13959         SELECT    'X'
13960           INTO  l_invalid_shipment_type
13961           FROM  po_line_locations pll
13962          WHERE  line_location_id = l_po_line_location_id
13963            AND(
13964                --(p_invoice_rec.invoice_type_lookup_code <> 'PREPAYMENT' and    .. B# 8528132
13965                (nvl(p_invoice_rec.invoice_type_lookup_code, 'STANDARD') <> 'PREPAYMENT' and    -- B# 8528132
13966 	        pll.SHIPMENT_TYPE IN ('STANDARD','BLANKET','SCHEDULED')
13967                ) OR
13968                (p_invoice_rec.invoice_type_lookup_code = 'PREPAYMENT' and
13969                 ((pll.payment_type IS NOT NULL and pll.shipment_type = 'PREPAYMENT') or
13970                  (pll.payment_type IS NULL and pll.shipment_type IN ('STANDARD','BLANKET','SCHEDULED'))
13971                 )
13972                )
13973               )
13974            AND  APPROVED_FLAG    = 'Y'
13975            AND  (nvl(CLOSED_CODE, 'OPEN') <> 'FINALLY CLOSED')
13976            AND  nvl(consigned_flag,'N')   <> 'Y';
13977 
13978       EXCEPTION
13979         WHEN NO_DATA_FOUND Then
13980           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
13981             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
13982             p_invoice_lines_rec.invoice_line_id,
13983             'INVALID SHIPMENT TYPE',
13984             p_default_last_updated_by,
13985             p_default_last_update_login,
13986             current_calling_sequence) <> TRUE) THEN
13987             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13988               AP_IMPORT_UTILITIES_PKG.Print(
13989                 AP_IMPORT_INVOICES_PKG.g_debug_switch,
13990                   'insert_rejections<-'||current_calling_sequence);
13991             END IF;
13992              RAISE check_po_failure;
13993             END IF;
13994           --
13995           l_current_invoice_status := 'N';
13996 
13997       END;
13998 
13999       -------------------------------------------------------------------------
14000       -- Validate Match Option if populated
14001       -------------------------------------------------------------------------
14002       IF ( l_po_line_location_id is not null) THEN
14003         debug_info := '(v_check_line_po_info2) :Get Match Option from po shipment';
14004         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
14005             AP_IMPORT_UTILITIES_PKG.Print(
14006               AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
14007         END IF;
14008 
14009         SELECT nvl(match_option,'P')
14010           INTO l_temp_match_option
14011              FROM po_line_locations
14012          WHERE line_location_id = l_po_line_location_id;
14013 
14014           --bug 9292033 : modified below condition to allow prepayment invoices with match option as 'P' and 'R' on PO
14015 
14016           /*IF (p_invoice_lines_rec.match_option IS NOT NULL AND
14017               p_invoice_lines_rec.match_option <> l_temp_match_option) THEN*/
14018 
14019           IF (p_invoice_lines_rec.match_option IS NOT NULL
14020 	     AND ((nvl(p_invoice_rec.invoice_type_lookup_code,'STANDARD') = 'PREPAYMENT'
14021 	           AND p_invoice_lines_rec.match_option = 'R'
14022 		   AND l_temp_match_option = 'P')
14023 		OR
14024 		   (nvl(p_invoice_rec.invoice_type_lookup_code,'STANDARD') <> 'PREPAYMENT'
14025                     AND p_invoice_lines_rec.match_option <> l_temp_match_option))) THEN
14026 
14027             -- Reject for invalid Match option
14028             IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
14029                 AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
14030                 p_invoice_lines_rec.invoice_line_id,
14031                 'INVALID MATCH OPTION',
14032                 p_default_last_updated_by,
14033                 p_default_last_update_login,
14034                 current_calling_sequence)<> TRUE) Then
14035               IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
14036                 AP_IMPORT_UTILITIES_PKG.Print(
14037                   AP_IMPORT_INVOICES_PKG.g_debug_switch,
14038                  'insert_rejections <-'||current_calling_sequence);
14039               END IF;
14040           RAISE check_po_failure;
14041             END IF;
14042           l_current_invoice_status := 'N';
14043 
14044           END IF;
14045 
14046         -- set the ouput parameter
14047         p_match_option := nvl(l_temp_match_option ,
14048                               p_invoice_lines_rec.match_option);
14049       END IF; -- if l_po_line_location_id is not null
14050 
14051     ELSIF ((l_po_line_id IS NOT NULL) AND
14052            (l_po_line_location_id IS NULL)) Then
14053            -- elsif to po_distribution_id is not null
14054       debug_info := '(v_check_line_po_info2 1) Check Valid Shipment Type from'
14055                     ||' l_po_line_id ';
14056       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
14057         AP_IMPORT_UTILITIES_PKG.Print(
14058           AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
14059       END IF;
14060 
14061       BEGIN
14062         SELECT count(*)
14063           INTO l_invalid_shipment_count
14064           FROM po_line_locations pll
14065          WHERE pll.po_line_id = l_po_line_id
14066           AND(
14067 	      (
14068                --(p_invoice_rec.invoice_type_lookup_code <> 'PREPAYMENT' and    .. B# 8528132
14069                (nvl(p_invoice_rec.invoice_type_lookup_code, 'STANDARD') <> 'PREPAYMENT' and    -- B# 8528132
14070 	        pll.SHIPMENT_TYPE NOT IN ('STANDARD','BLANKET','SCHEDULED')
14071                ) OR
14072                (p_invoice_rec.invoice_type_lookup_code = 'PREPAYMENT' and
14073                 ((pll.payment_type IS NOT NULL and pll.shipment_type <> 'PREPAYMENT') or
14074                  (pll.payment_type IS NULL and pll.shipment_type NOT IN ('STANDARD','BLANKET','SCHEDULED'))
14075                 )
14076                )
14077               )
14078              /* Bug 4038403 removed these two conditions and added the below condition
14079               OR (APPROVED_FLAG <> 'Y')
14080               OR (APPROVED_FLAG IS NULL) */
14081 
14082               OR nvl(APPROVED_FLAG, 'N') <> 'Y'
14083             )
14084             OR (nvl(CLOSED_CODE, 'OPEN') = 'FINALLY CLOSED')
14085             OR (nvl(consigned_flag,'N') = 'Y');
14086 
14087           IF (l_invalid_shipment_count > 0) Then
14088             IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
14089                 AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
14090                 p_invoice_lines_rec.invoice_line_id,
14091                 'INVALID SHIPMENT TYPE',
14092                 p_default_last_updated_by,
14093                 p_default_last_update_login,
14094                 current_calling_sequence) <> TRUE) THEN
14095                IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
14096                   AP_IMPORT_UTILITIES_PKG.Print(
14097                     AP_IMPORT_INVOICES_PKG.g_debug_switch,
14098                     'insert_rejections<-'||current_calling_sequence);
14099                END IF;
14100                 RAISE check_po_failure;
14101             END IF;
14102             --
14103             l_current_invoice_status := 'N';
14104 
14105           END IF;
14106 
14107       EXCEPTION
14108         WHEN NO_DATA_FOUND Then
14109         NULL;
14110       END;
14111 
14112       -- Check for PO line price break
14113       -- Cannot have a line level match if price break is on
14114       -- Retropricing: Don't know what this rejection means???.
14115       -- For PPA's irrespective of the fact if the line has price breaks
14116       -- or not, we should not reject it. Price breaks is a feature in PO
14117       -- and AP does matching at the ship level.
14118       IF (AP_IMPORT_INVOICES_PKG.g_source <> 'PPA') THEN
14119           debug_info := '(v_check_line_po_info2 1) Check Price Break for PO '
14120                         ||'Line(Line Level Match) ';
14121           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
14122               AP_IMPORT_UTILITIES_PKG.Print(
14123                 AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
14124           END IF;
14125           --
14126           BEGIN
14127             SELECT allow_price_override_flag
14128               INTO l_price_break
14129               FROM po_lines
14130              WHERE po_line_id = l_po_line_id;
14131 
14132               IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
14133                   AP_IMPORT_UTILITIES_PKG.Print(
14134                     AP_IMPORT_INVOICES_PKG.g_debug_switch,
14135                     '------------------> l_price_break= '|| l_price_break);
14136               END IF;
14137               --
14138               IF (nvl(l_price_break,'N') ='Y' ) Then
14139                 IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
14140                     AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
14141                     p_invoice_lines_rec.invoice_line_id,
14142                     'LINE HAS PRICE BREAK',
14143                     p_default_last_updated_by,
14144                     p_default_last_update_login,
14145                     current_calling_sequence) <> TRUE) THEN
14146                   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
14147                       AP_IMPORT_UTILITIES_PKG.Print(
14148                        AP_IMPORT_INVOICES_PKG.g_debug_switch,
14149                        'insert_rejections<-'||current_calling_sequence);
14150                   END IF;
14151                     RAISE check_po_failure;
14152                   END IF;
14153                 --
14154                 l_current_invoice_status := 'N';
14155                 --
14156               END IF;
14157 
14158           EXCEPTION
14159             WHEN NO_DATA_FOUND Then
14160             Null;
14161 
14162           END;
14163           --
14164       END IF; -- source <> 'PPA'
14165     END IF; -- if to po_distribution_id is not null
14166 
14167     ---------------------------------------------------------------------------
14168     -- Step 1.1, Reject if po_inventory_item_id, p_vendor_item_num
14169     --                          and po_item_description are inconsistent
14170     --
14171     --  Added consistency check for Supplier Item Number too as part of
14172     --  the effort to support Supplier Item Number in Invoice Import
14173     --                                                         bug 1873251
14174     --  Amount Based Matching. Reject if any of the lines' match basis
14175     --  is Amount. However due to complex work project match basis will be
14176     --  at po shipment level hence all the matching basis related validation
14177     --  has been moved to shipment level.
14178     ---------------------------------------------------------------------------
14179 
14180     IF l_po_line_location_id IS NOT NULL THEN
14181 
14182        Select shipment_type
14183 	 Into l_temp_shipment_type
14184 	 From po_line_locations
14185 	Where line_location_id = l_po_line_location_id;
14186 
14187     END IF;
14188 
14189     IF ((p_invoice_lines_rec.vendor_item_num IS NOT NULL) AND
14190        (p_match_basis = 'AMOUNT') AND
14191        (nvl(l_temp_shipment_type,'X') <> 'PREPAYMENT')) THEN
14192       --
14193       debug_info := '(v_check_line_po_info2 1.1) Check inconsistency for '
14194                     ||'po_vendor_item_num '
14195                     ||'shipment level match basis is AMOUNT';
14196       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
14197         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
14198                                       debug_info);
14199       END IF;
14200       --
14201       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
14202                         AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
14203                         p_invoice_lines_rec.invoice_line_id,
14204                         'INCONSISTENT SHIPMENT INFO',
14205                         p_default_last_updated_by,
14206                         p_default_last_update_login,
14207                         current_calling_sequence,
14208                         'Y',
14209                         'SUPPLIER ITEM NUMBER',
14210                         p_invoice_lines_rec.vendor_item_num ) <> TRUE) THEN
14211         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
14212              AP_IMPORT_UTILITIES_PKG.Print(
14213                AP_IMPORT_INVOICES_PKG.g_debug_switch,
14214                'insert_rejections<-'||current_calling_sequence);
14215         END IF;
14216         RAISE check_po_failure;
14217       END IF;
14218 
14219       l_current_invoice_status := 'N';
14220     --Bug 9279395 Removed item_description is not null clause
14221     ELSIF ((p_invoice_lines_rec.inventory_item_id IS NOT NULL) AND
14222           (p_match_basis = 'AMOUNT') AND
14223 	  (nvl(l_temp_shipment_type,'X') <> 'PREPAYMENT')) THEN
14224       --
14225       debug_info := '(v_check_line_po_info2 1.1) Check inconsistency for '
14226                     ||'po_inventory_item_id and po_item_description '
14227                     ||'shipment level match basis is AMOUNT';
14228       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
14229         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
14230                                       debug_info);
14231       END IF;
14232       --
14233       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
14234                         AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
14235                         p_invoice_lines_rec.invoice_line_id,
14236                         'INCONSISTENT SHIPMENT INFO',
14237                         p_default_last_updated_by,
14238                         p_default_last_update_login,
14239                         current_calling_sequence ) <> TRUE) THEN
14240         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
14241              AP_IMPORT_UTILITIES_PKG.Print(
14242                AP_IMPORT_INVOICES_PKG.g_debug_switch,
14243                'insert_rejections<-'||current_calling_sequence);
14244         END IF;
14245         RAISE check_po_failure;
14246       END IF;
14247 
14248       l_current_invoice_status := 'N';
14249 
14250     END IF;
14251 
14252     ------------------------------------------------------
14253     -- Step 2
14254     -- Check for Invalid Distribution Set with PO
14255     -- Retropricing: Distribution Set is always NULL for PPA's
14256     ------------------------------------------------------
14257     IF ((p_invoice_lines_rec.distribution_set_id is NOT NULL) OR
14258         (p_invoice_lines_rec.distribution_set_name is NOT NULL)) Then
14259         debug_info := '(v_check_line_po_info2 2) Check for Invalid '
14260                     ||'Distribution Set with PO';
14261       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
14262         AP_IMPORT_UTILITIES_PKG.Print(
14263           AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
14264       END IF;
14265 
14266       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
14267                    AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
14268                    p_invoice_lines_rec.invoice_line_id,
14269                    'INVALID DIST SET WITH PO',
14270                    p_default_last_updated_by,
14271                    p_default_last_update_login,
14272                    current_calling_sequence) <> TRUE) THEN
14273         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
14274             AP_IMPORT_UTILITIES_PKG.Print(
14275               AP_IMPORT_INVOICES_PKG.g_debug_switch,
14276                  'insert_rejections<-'||current_calling_sequence);
14277         END IF;
14278         RAISE check_po_failure;
14279       END IF;
14280       l_current_invoice_status := 'N';
14281 
14282     END IF;
14283 
14284     -----------------------------------------------------
14285     -- Step 3
14286     -- Get Unit Price and UOM from PO Lines
14287     ------------------------------------------------------
14288     debug_info :=
14289       '(v_check_line_po_info2 3) Get Unit Price / UOM from PO Lines';
14290     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
14291         AP_IMPORT_UTILITIES_PKG.Print(
14292           AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
14293     END IF;
14294     --
14295     --bug2878889.Commented the following code and added the code below.
14296 /*    IF (l_po_line_location_id IS NOT NULL) THEN
14297       SELECT pll.price_override, pll.unit_meas_lookup_code
14298         INTO l_po_unit_price,l_unit_of_measure
14299         FROM po_line_locations pll
14300         WHERE  pll.line_location_id = l_po_line_location_id;
14301     ELSE
14302       SELECT unit_price,unit_meas_lookup_code
14303         INTO l_po_unit_price,l_unit_of_measure
14304         FROM po_lines
14305        WHERE po_line_id = l_po_line_id;
14306     END IF;*/
14307 
14308     IF (/* Bug 9326135 (p_invoice_lines_rec.quantity_invoiced IS NULL)
14309              AND */ (l_po_unit_price IS NULL)
14310              AND (p_invoice_lines_rec.po_release_id IS NOT NULL) ) THEN
14311 
14312              SELECT NVL(price_override,unit_price),unit_meas_lookup_code
14313              INTO l_po_unit_price,l_unit_of_measure
14314              FROM po_line_locations_release_v
14315              WHERE po_line_id = l_po_line_id
14316 	     -- bug7328060, added the below condition
14317              AND line_location_id = nvl(l_po_line_location_id, line_location_id)
14318              AND po_release_id = p_invoice_lines_rec.po_release_id;
14319 
14320     ELSIF ( (l_po_line_location_id IS NOT NULL)
14321              /* Bug 9326135 AND (p_invoice_lines_rec.quantity_invoiced IS NULL) */
14322              AND (l_po_unit_price IS NULL)
14323              AND (p_invoice_lines_rec.po_release_id IS NULL) ) THEN
14324 
14325              SELECT pll.price_override, pll.unit_meas_lookup_code
14326              INTO l_po_unit_price,l_unit_of_measure
14327              FROM po_line_locations pll
14328              WHERE  pll.line_location_id = l_po_line_location_id;
14329 
14330     ELSIF (  (l_po_line_id IS NOT NULL)
14331               /* Bug 9326135 AND  (p_invoice_lines_rec.quantity_invoiced IS NULL)*/
14332               AND (l_po_unit_price IS NULL)
14333               AND (p_invoice_lines_rec.po_release_id IS NULL) ) THEN
14334 
14335               SELECT unit_price,unit_meas_lookup_code
14336               INTO l_po_unit_price,l_unit_of_measure
14337               FROM po_lines
14338               WHERE po_line_id = l_po_line_id;
14339 
14340     ELSIF (   (p_invoice_lines_rec.quantity_invoiced IS NOT NULL)
14341              AND (l_po_line_id IS NOT NULL)
14342 	     AND (l_po_unit_price is NULL)
14343 	     AND (p_invoice_lines_rec.amount is NOT NULL)) THEN
14344 
14345               IF (p_invoice_lines_rec.quantity_invoiced=0) THEN
14346                  l_po_unit_price :=0;
14347              ELSE
14348   		 l_po_unit_price := ap_utilities_pkg.ap_round_currency (
14349   	        		    p_invoice_lines_rec.amount /
14350 				    p_invoice_lines_rec.quantity_invoiced,
14351 		                    p_invoice_rec.invoice_currency_code);
14352  	     END IF; --Bug6932650
14353 
14354 		SELECT unit_meas_lookup_code
14355 		INTO l_unit_of_measure
14356 		FROM po_lines
14357 		WHERE po_line_id = l_po_line_id;
14358 
14359     END IF;
14360     --bug2878889 ends
14361 
14362     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
14363         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
14364                   '------------------>
14365                         l_po_unit_price = '||to_char(l_po_unit_price)
14366                         ||' l_unit_of_measure = '||l_unit_of_measure);
14367     END IF;
14368     --
14369     -----------------------------------------------------
14370     -- Step 4
14371     -- Check for Invalid Line Quantity
14372     -- For credits we can have -ve qty
14373     -- Amount Based Matching. Line Amount can not be -ve
14374     -- if match basis is 'AMOUNT'
14375     ------------------------------------------------------
14376     --Contract Payments: Modified the IF condition to add 'PREPAYMENT'.
14377 
14378     IF ((p_invoice_lines_rec.quantity_invoiced) <= 0 AND
14379         (p_invoice_rec.invoice_type_lookup_code IN ('STANDARD','PREPAYMENT'))) Then
14380       debug_info :=
14381         '(v_check_line_po_info2 4) Check for Invalid Line Quantity';
14382       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
14383           AP_IMPORT_UTILITIES_PKG.Print(
14384             AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
14385       END IF;
14386 
14387       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
14388             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
14389             p_invoice_lines_rec.invoice_line_id,
14390             'INVALID QUANTITY',
14391             p_default_last_updated_by,
14392             p_default_last_update_login,
14393             current_calling_sequence,
14394             'Y',
14395             'QUANTITY INVOICED',
14396             p_invoice_lines_rec.quantity_invoiced) <> TRUE) THEN
14397         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
14398             AP_IMPORT_UTILITIES_PKG.Print(
14399               AP_IMPORT_INVOICES_PKG.g_debug_switch,
14400                 'insert_rejections<-'||current_calling_sequence);
14401         END IF;
14402         RAISE check_po_failure;
14403       END IF;
14404 
14405       l_current_invoice_status := 'N';
14406 
14407     END IF;
14408 
14409     ELSIF (p_match_basis = 'AMOUNT') THEN
14410       IF ((p_invoice_lines_rec.amount) <= 0 AND
14411         (p_invoice_rec.invoice_type_lookup_code = 'STANDARD')) Then
14412          debug_info :=
14413           '(v_check_line_po_info2 4) Check for Invalid Line Amount';
14414         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
14415            AP_IMPORT_UTILITIES_PKG.Print(
14416             AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
14417         END IF;
14418 
14419         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
14420             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
14421             p_invoice_lines_rec.invoice_line_id,
14422             'INVALID QUANTITY',
14423             p_default_last_updated_by,
14424             p_default_last_update_login,
14425             current_calling_sequence,
14426             'Y',
14427             'QUANTITY INVOICED',
14428             p_invoice_lines_rec.amount) <> TRUE) THEN
14429           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
14430             AP_IMPORT_UTILITIES_PKG.Print(
14431               AP_IMPORT_INVOICES_PKG.g_debug_switch,
14432                 'insert_rejections<-'||current_calling_sequence);
14433           END IF;
14434           RAISE check_po_failure;
14435         END IF;
14436 
14437         l_current_invoice_status := 'N';
14438 
14439       END IF;
14440 
14441     END IF; -- end if match basis
14442 
14443     ------------------------------------------------------
14444     -- Step 5
14445     -- Check for Invalid Unit of Measure against PO Line
14446     -- Amount Based Matching. No need to check for UOM
14447     -- if match basis is 'AMOUNT'
14448     ------------------------------------------------------
14449     IF (p_match_basis = 'QUANTITY') THEN
14450     IF (p_invoice_lines_rec.unit_of_meas_lookup_code <> l_unit_of_measure)
14451         AND (p_match_option = 'P') THEN
14452       debug_info := '(v_check_line_po_info2 5) Check for Unit of Measure'
14453                     ||' against PO';
14454       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
14455           AP_IMPORT_UTILITIES_PKG.Print(
14456             AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
14457       END IF;
14458       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
14459                         AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
14460                         p_invoice_lines_rec.invoice_line_id,
14461                         'UOM DOES NOT MATCH PO',
14462                         p_default_last_updated_by,
14463                         p_default_last_update_login,
14464                         current_calling_sequence) <> TRUE) THEN
14465         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
14466             AP_IMPORT_UTILITIES_PKG.Print(
14467               AP_IMPORT_INVOICES_PKG.g_debug_switch,
14468                  'insert_rejections<-'||current_calling_sequence);
14469         END IF;
14470         RAISE check_po_failure;
14471       END IF;
14472       l_current_invoice_status := 'N';
14473 
14474     END IF;
14475     END IF;  -- Match Basis QUANTITY
14476 
14477     ----------------------------------------------------------------
14478     -- Step 6
14479     -- Check for Valid unit_price, quantity_invoiced and line_amount
14480     -- Amount Based Matching. Nso need to validate line amount based
14481     -- on unit_price and quantity_invoiced, or unit_price based on
14482     -- line_amount and quantity_invoiced, or calculate quantity_inv
14483     -- oiced based on line_amount and unit_price
14484     ----------------------------------------------------------------
14485     IF (p_match_basis = 'QUANTITY') THEN
14486     IF ((p_invoice_lines_rec.quantity_invoiced IS NOT NULL) AND
14487         (p_invoice_lines_rec.unit_price IS NOT NULL) AND
14488         (p_invoice_lines_rec.amount IS NOT NULL)) Then
14489       debug_info := '(v_check_line_po_info2 7) Check for valid unit_price, '
14490                      ||'quantity_invoiced and line_amount';
14491       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
14492           AP_IMPORT_UTILITIES_PKG.Print(
14493             AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
14494       END IF;
14495 
14496       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
14497         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
14498         'quantity_invoiced = '||to_char(p_invoice_lines_rec.quantity_invoiced)||
14499         ' unit_price = '||to_char(p_invoice_lines_rec.unit_price)||
14500         ' amount = '||to_char(p_invoice_lines_rec.amount));
14501       END IF;
14502 
14503       -- The following can have rounding issues so use line_amount
14504       -- for consistency check.
14505       -- l_calculated_unit_price :=
14506       -- p_invoice_lines_rec.amount / p_quantity_invoiced;
14507       l_calc_line_amount := ap_utilities_pkg.ap_round_currency (
14508         p_invoice_lines_rec.unit_price * p_invoice_lines_rec.quantity_invoiced,
14509         p_invoice_rec.invoice_currency_code);
14510       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
14511         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
14512         '------------------>
14513         l_calc_line_amount = '||to_char(l_calc_line_amount));
14514       END IF;
14515 
14516       -- Bug 5469166. Added the g_source <> 'PPA' condition
14517 
14518       IF (l_calc_line_amount <> p_invoice_lines_rec.amount) OR
14519 /*
14520 2830338 : Raise INVALID PRICE/QUANTITY if Amount does not have the
14521                   same sign as Quantity
14522 */
14523       --Bug6836072
14524         ((SIGN(p_invoice_lines_rec.amount) <> SIGN(p_invoice_lines_rec.quantity_invoiced)
14525          AND
14526          (NVL(p_invoice_lines_rec.amount, 0) <> 0))
14527 	 --bug13599126, added condition to skip the sign validation for price correction invoice
14528          and nvl(p_invoice_lines_rec.price_correction_flag, 'N') <> 'Y'
14529         AND AP_IMPORT_INVOICES_PKG.g_source <> 'PPA')
14530         THEN
14531         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
14532                        AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
14533                         p_invoice_lines_rec.invoice_line_id,
14534                         'INVALID PRICE/QUANTITY/AMOUNT',
14535                         p_default_last_updated_by,
14536                         p_default_last_update_login,
14537                         current_calling_sequence,
14538                         'Y',
14539                         'QUANTITY INVOICED',
14540                         p_invoice_lines_rec.quantity_invoiced,
14541                         'UNIT PRICE',
14542                         p_invoice_lines_rec.unit_price,
14543                         'INVOICE LINE AMOUNT',
14544                         p_invoice_lines_rec.amount) <> TRUE) THEN
14545           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
14546               AP_IMPORT_UTILITIES_PKG.Print(
14547                 AP_IMPORT_INVOICES_PKG.g_debug_switch,
14548                   'insert_rejections<-'||current_calling_sequence);
14549           END IF;
14550           RAISE check_po_failure;
14551         END IF;
14552         l_current_invoice_status := 'N';
14553       END IF;
14554     ELSIF ((p_invoice_lines_rec.quantity_invoiced IS NOT NULL) AND
14555            (P_INVOICE_LINES_REC.UNIT_PRICE IS NULL) AND
14556            (p_invoice_lines_rec.amount IS NOT NULL)) Then
14557       debug_info := '(v_check_line_po_info2 7) Get unit_price from '
14558                     ||'quantity_invoiced and line_amount';
14559       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
14560         AP_IMPORT_UTILITIES_PKG.Print(
14561           AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
14562       END IF;
14563       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
14564         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
14565         'inside the else condition ');
14566       END IF;
14567 
14568 /*
14569 2830338 : Raise INVALID PRICE/QUANTITY if Amount does not have the
14570                   same sign as Quantity
14571 */
14572       --Bug6836072
14573       IF ((NVL(p_invoice_lines_rec.amount, 0) <> 0)
14574           AND SIGN(p_invoice_lines_rec.amount) <> SIGN(p_invoice_lines_rec.quantity_invoiced))
14575 	  --bug13599126, added condition to skip the sign validation for price correction invoice
14576           and nvl(p_invoice_lines_rec.price_correction_flag, 'N') <> 'Y'
14577       THEN
14578          IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
14579                        AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
14580                         p_invoice_lines_rec.invoice_line_id,
14581                         'INVALID PRICE/QUANTITY/AMOUNT',
14582                         p_default_last_updated_by,
14583                         p_default_last_update_login,
14584                         current_calling_sequence,
14585                         'Y',
14586                         'QUANTITY INVOICED',
14587                         p_invoice_lines_rec.quantity_invoiced,
14588                         'UNIT PRICE',
14589                         p_invoice_lines_rec.unit_price,
14590                         'INVOICE LINE AMOUNT',
14591                         p_invoice_lines_rec.amount) <> TRUE) THEN
14592          IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
14593               AP_IMPORT_UTILITIES_PKG.Print(
14594                 AP_IMPORT_INVOICES_PKG.g_debug_switch,
14595                   'insert_rejections<-'||current_calling_sequence);
14596           END IF;
14597           RAISE check_po_failure;
14598         END IF;
14599         l_current_invoice_status := 'N';
14600       END IF;
14601 
14602       -- We should calc the unit price instead of using the one from PO
14603       -- Use from PO only if both p_unit_price and p_quantity_invoiced are null
14604       /*Bug 5495483 Added the below IF condition*/
14605       /*l_unit_price := p_invoice_lines_rec.amount /
14606                     p_invoice_lines_rec.quantity_invoiced;*/
14607       IF (p_invoice_lines_rec.quantity_invoiced=0) THEN
14608             l_unit_price :=0;
14609       ELSE
14610             l_unit_price := p_invoice_lines_rec.amount /p_invoice_lines_rec.quantity_invoiced;
14611       END IF;
14612 
14613       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
14614           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
14615           '------------------>
14616           l_unit_price = '||to_char(l_unit_price));
14617       END IF;
14618 
14619     END IF;
14620 
14621   -- Calculate qty invoiced.
14622   -- Retropricing: Qnantity_invoiced will not be calculated
14623   -- for PPA Lines
14624 
14625     -- bug8587322
14626     l_dec_unit_price := nvl(l_unit_price,nvl(l_po_unit_price,1));
14627     IF (p_invoice_lines_rec.quantity_invoiced IS NULL) Then
14628       -- Quantity is not being rounded
14629       --l_dec_unit_price := nvl(l_unit_price,nvl(l_po_unit_price,1));
14630 
14631       IF (l_dec_unit_price = 0) Then
14632          l_quantity_invoiced := p_invoice_lines_rec.amount;
14633       ELSE
14634          l_quantity_invoiced := ROUND(p_invoice_lines_rec.amount/l_dec_unit_price,15) ;
14635       END IF;
14636 
14637       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
14638         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
14639              '------------------>
14640           l_quantity_invoiced = '||to_char(l_quantity_invoiced)
14641       ||' line_amount = '||to_char(p_invoice_lines_rec.amount)
14642       ||' unit_price = '||to_char(l_unit_price));
14643       END IF;
14644 
14645     END IF;
14646 
14647     END IF; -- Match Basis QUANTITY
14648 
14649     ------------------------------------------------------------
14650     -- Step 7
14651     -- Calculate line_amount if unit_price and quantiy_invoiced
14652     -- are provided in case of Amount Based Matching
14653     ------------------------------------------------------------
14654     IF (p_match_basis = 'AMOUNT' AND
14655         p_invoice_lines_rec.amount IS NULL) THEN
14656       IF ((p_invoice_lines_rec.quantity_invoiced IS NOT NULL) AND
14657         (p_invoice_lines_rec.unit_price IS NOT NULL)) THEN
14658         debug_info := '(v_check_line_po_info2 7) Calculate line_amount, '
14659                      ||'in case of match basis is AMOUNT';
14660         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
14661           AP_IMPORT_UTILITIES_PKG.Print(
14662             AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
14663         END IF;
14664 
14665         -- The following can have rounding issues so use line_amount
14666         -- for consistency check.
14667         -- l_calculated_unit_price :=
14668         -- p_invoice_lines_rec.amount / p_quantity_invoiced;
14669         l_calc_line_amount := ap_utilities_pkg.ap_round_currency (
14670           p_invoice_lines_rec.unit_price * p_invoice_lines_rec.quantity_invoiced,
14671           p_invoice_rec.invoice_currency_code);
14672         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
14673           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
14674           '------------------>
14675           l_calc_line_amount = '||to_char(l_calc_line_amount));
14676         END IF;
14677       ELSE
14678         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
14679                        AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
14680                         p_invoice_lines_rec.invoice_line_id,
14681                         'INSUFFICIENT AMOUNT INFO',
14682                         p_default_last_updated_by,
14683                         p_default_last_update_login,
14684                         current_calling_sequence,
14685                         'Y',
14686                         'QUANTITY INVOICED',
14687                         p_invoice_lines_rec.quantity_invoiced,
14688                         'UNIT PRICE',
14689                         p_invoice_lines_rec.unit_price,
14690                         'INVOICE LINE AMOUNT',
14691                         p_invoice_lines_rec.amount) <> TRUE) THEN
14692           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
14693               AP_IMPORT_UTILITIES_PKG.Print(
14694                 AP_IMPORT_INVOICES_PKG.g_debug_switch,
14695                   'insert_rejections<-'||current_calling_sequence);
14696           END IF;
14697           RAISE check_po_failure;
14698         END IF;
14699         l_current_invoice_status := 'N';
14700       END IF;
14701     END IF;
14702 
14703     -------------------------------------------------------------
14704     -- Step 8
14705     -- Check for Invalid Unit Price against PO
14706     -- Retropricing:
14707     -- We assume that PO will not allow to retroprice a PO again
14708     -- if there are pending PO shipment instructions in the
14709     -- AP_INVOICE_LINES_INTERFACE. If the PO's unit price is not
14710     -- equal to the unit price on the PPA, then it should
14711     -- be rejected . Currently UNIT PRC NOT EQUAL TO PO
14712     -- rejection is only meant for EDI-GATEWAY.
14713     -- Thia step should not be executed in context of PPA's.
14714     -- Amount Based Matching. Reject for negative total amount
14715     -- invoiced against given PO
14716     -------------------------------------------------------------
14717     IF AP_IMPORT_INVOICES_PKG.g_source <> 'PPA' THEN
14718         --
14719         IF (l_po_line_location_id IS NOT NULL) THEN
14720           l_qty_invoiced := nvl(p_invoice_lines_rec.quantity_invoiced,
14721                               l_quantity_invoiced);
14722           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
14723             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
14724               '------------------>
14725               Decoded l_qty_invoiced = '||to_char(l_qty_invoiced));
14726           END IF;
14727           --
14728           -- For Invoice import, we should always average out the price for
14729           -- all matched for a given line_location.
14730           -- This will account for all invoices , credit memos as well as positive
14731           -- price corrections.
14732           --Retropricing: PPA'should be excluded from the quantity_invoiced.
14733 
14734           SELECT NVL(SUM(DECODE(L.MATCH_TYPE,
14735                                 'PRICE_CORRECTION', 0,
14736                                 'PO_PRICE_ADJUSTMENT', 0,
14737                                 'ADJUSTMENT_CORRECTION', 0,
14738                                  NVL(L.quantity_invoiced, 0))),0) +
14739                                  NVL(l_qty_invoiced,0),
14740                                  ROUND(NVL(p_invoice_lines_rec.amount +
14741                                  NVL(SUM(NVL(L.amount, 0)),0),0),5)
14742             INTO l_total_qty_billed,
14743                    l_total_match_amount
14744             FROM ap_invoice_lines L
14745            WHERE l.po_line_location_id = l_po_line_location_id;
14746 
14747           -- If total qty billed is below zero
14748           -- we should reject. In invoice workbench the form takes care of this.
14749           -- Amount Based Matching
14750           IF (l_total_qty_billed < 0 AND
14751              p_match_basis = 'QUANTITY') Then
14752             debug_info := '(v_check_line_po_info2 8) Reject for negative total '
14753                           ||'quantity invoiced against given PO ';
14754             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
14755               AP_IMPORT_UTILITIES_PKG.Print(
14756                 AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
14757             END IF;
14758 
14759             IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
14760                AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
14761                p_invoice_lines_rec.invoice_line_id,
14762                'NEGATIVE QUANTITY BILLED', --Bug 5134622
14763                p_default_last_updated_by,
14764                p_default_last_update_login,
14765                current_calling_sequence,
14766                'Y',
14767                'QUANTITY INVOICED',
14768                l_total_qty_billed ) <> TRUE) THEN
14769               IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
14770                  AP_IMPORT_UTILITIES_PKG.Print(
14771                    AP_IMPORT_INVOICES_PKG.g_debug_switch,
14772                    'insert_rejections<-'||current_calling_sequence);
14773               END IF;
14774               RAISE check_po_failure;
14775             END IF;
14776             l_current_invoice_status := 'N';
14777 
14778           END IF; -- total qty billed is less than 0
14779 
14780           -- If total qty billed is zero and total match amount is not equal to zero
14781           -- Case I: total match amount is positive; this will never happen in
14782           -- the above scenario
14783           -- Case II: total match amount is -ve ; essentially we have an extra
14784           -- credit for supplier
14785           -- Discussed with Subir, since the invoice workbench allows this ,
14786           -- we would not reject
14787           IF ((l_total_qty_billed = 0 ) AND
14788               (l_total_match_amount <> 0))Then
14789             debug_info := '(v_check_line_po_info2 9) Extra credit for '||
14790                           'supplier:Negative total match amount against given PO ';
14791             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
14792                 AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
14793                                               debug_info);
14794             END IF;
14795 
14796           END IF;
14797 
14798           IF p_invoice_lines_rec.unit_price >
14799              p_positive_price_tolerance * l_po_unit_price THEN
14800               l_positive_price_variance := 1;
14801           ELSE
14802               l_positive_price_variance :=0;
14803           END IF;
14804 
14805           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
14806               AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
14807               '------------------>
14808               l_positive_price_varaince = '||to_char(l_positive_price_variance)
14809           ||' l_total_qty_billed = '||to_char(l_total_qty_billed));
14810           END IF;
14811 
14812           -- Reject even if tolerance is not set
14813           --
14814           IF (AP_IMPORT_INVOICES_PKG.g_source = 'EDI GATEWAY') THEN
14815             IF (l_positive_price_variance > 0) then --modified for 1939078
14816               debug_info := '(v_check_line_po_info2 9) Check for Invalid Unit '
14817                             ||'Price against PO';
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               IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
14824                            AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
14825                             p_invoice_lines_rec.invoice_line_id,
14826                             'UNIT PRC NOT EQUAL TO PO',
14827                             p_default_last_updated_by,
14828                             p_default_last_update_login,
14829                             current_calling_sequence) <> TRUE) THEN
14830                 IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
14831                     AP_IMPORT_UTILITIES_PKG.Print(
14832                       AP_IMPORT_INVOICES_PKG.g_debug_switch,
14833                        'insert_rejections<-'||current_calling_sequence);
14834                 END IF;
14835                 RAISE check_po_failure;
14836               END IF;
14837               l_current_invoice_status := 'N';
14838 
14839             END IF; -- l_total_price_variance
14840 
14841           END IF; -- g_source
14842 
14843         ELSIF ((l_po_line_location_id IS NULL) AND
14844                (l_po_line_id IS NOT NULL)) THEN
14845                -- else if po line location is not null
14846           l_qty_invoiced := nvl(p_invoice_lines_rec.quantity_invoiced,
14847                                 l_quantity_invoiced);
14848           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
14849               AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
14850                     '------------------>
14851                 l_qty_invoiced = '||to_char(l_qty_invoiced));
14852           END IF;
14853           --
14854           SELECT  NVL(SUM(DECODE(L.MATCH_TYPE, 'PRICE_CORRECTION', 0,
14855                                  'PO_PRICE_ADJUSTMENT', 0,
14856                                  'ADJUSTMENT_CORRECTION', 0,
14857                                   NVL(L.quantity_invoiced, 0))),0) +
14858                   NVL(l_qty_invoiced,0),
14859                   NVL(SUM(NVL(PLL.amount,0)),0) +
14860                   NVL(p_invoice_lines_rec.amount, l_line_amount)
14861             INTO  l_total_qty_billed,
14862                   l_total_match_amount  /* Amount Based Matching */
14863             FROM  ap_invoice_lines L,
14864                   po_line_locations PLL
14865            WHERE  L.po_line_location_id = PLL.line_location_id
14866              AND  PLL.po_line_id = l_po_line_id;
14867 
14868           -- If total qty billed is below zero
14869           -- we should reject. In invoice workbench the form takes care of this.
14870            -- Amount Based Matching
14871           IF (l_total_qty_billed < 0 AND
14872               p_match_basis = 'QUANTITY') Then
14873               debug_info := '(v_check_line_po_info2 8) Reject for negative total '
14874                  ||'quantity invoiced against given PO(for PO Line match) ';
14875             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
14876                 AP_IMPORT_UTILITIES_PKG.Print(
14877                   AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
14878             END IF;
14879 
14880             IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
14881                      AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
14882                      p_invoice_lines_rec.invoice_line_id,
14883                     'NEGATIVE QUANTITY BILLED', --Bug 5134622
14884                      p_default_last_updated_by,
14885                      p_default_last_update_login,
14886                      current_calling_sequence,
14887                      'Y',
14888                      'QUANTITY INVOICED',
14889                      l_total_qty_billed ) <> TRUE) THEN
14890               IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
14891                 AP_IMPORT_UTILITIES_PKG.Print(
14892                   AP_IMPORT_INVOICES_PKG.g_debug_switch,
14893                  'insert_rejections<-'||current_calling_sequence);
14894               END IF;
14895               RAISE check_po_failure;
14896             END IF;
14897             l_current_invoice_status := 'N';
14898 
14899           /* Amount Based Matching */
14900           -- If total amount is billed zero, We should reject.
14901           -- In Invoice workbench form take care of this
14902           ELSIF (l_total_match_amount < 0 AND
14903                  p_match_basis = 'AMOUNT') Then
14904             debug_info := '(v_check_line_po_info2 8) Reject for negative total '
14905                           ||'amount matched against given PO ';
14906             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
14907               AP_IMPORT_UTILITIES_PKG.Print(
14908                 AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
14909           END IF;
14910 
14911             IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
14912                AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
14913                p_invoice_lines_rec.invoice_line_id,
14914                'INVALID LINE AMOUNT',
14915                p_default_last_updated_by,
14916                p_default_last_update_login,
14917                current_calling_sequence,
14918                'Y',
14919                'AMOUNT INVOICED',
14920                l_total_match_amount ) <> TRUE) THEN
14921               IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
14922                  AP_IMPORT_UTILITIES_PKG.Print(
14923                    AP_IMPORT_INVOICES_PKG.g_debug_switch,
14924                    'insert_rejections<-'||current_calling_sequence);
14925               END IF;
14926               RAISE check_po_failure;
14927             END IF;
14928             l_current_invoice_status := 'N';
14929 
14930           END IF; -- total qty billed is less than 0
14931 
14932           IF p_invoice_lines_rec.unit_price >
14933              p_positive_price_tolerance * l_po_unit_price THEN
14934               l_positive_price_variance := 1;
14935           ELSE
14936               l_positive_price_variance :=0;
14937           END IF;
14938 
14939           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
14940               AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
14941                 '------------------>
14942                 l_positive_price_variance = '||to_char(l_positive_price_variance)
14943                 ||' l_total_qty_billed = '||to_char(l_total_qty_billed));
14944           END IF;
14945 
14946           IF (AP_IMPORT_INVOICES_PKG.g_source = 'EDI GATEWAY') Then
14947             IF (l_positive_price_variance > 0) THEN --modified for 1939078
14948               debug_info := '(v_check_line_po_info2 9) Check for Invalid Unit  '
14949                             ||'Price against PO';
14950               IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
14951                 AP_IMPORT_UTILITIES_PKG.Print(
14952                   AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
14953               END IF;
14954 
14955               IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
14956                           AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
14957                           p_invoice_lines_rec.invoice_line_id,
14958                           'UNIT PRC NOT EQUAL TO PO',
14959                           p_default_last_updated_by,
14960                           p_default_last_update_login,
14961                           current_calling_sequence) <> TRUE) THEN
14962                 IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
14963                   AP_IMPORT_UTILITIES_PKG.Print(
14964                     AP_IMPORT_INVOICES_PKG.g_debug_switch,
14965                       'insert_rejections<-'||current_calling_sequence);
14966                 END IF;
14967                 RAISE check_po_failure;
14968               END IF;
14969               l_current_invoice_status := 'N';
14970 
14971             END IF; -- l_total_price_variance
14972 
14973           END IF; -- g_source
14974 
14975         END IF; -- po line location id is not null
14976     END IF; -- source <> PPA
14977     ----------------------------------------------------------------
14978     -- Step 10
14979     -- Check for Overbill, if yes then reject. Only if tolerances are set
14980     -- This is as per Aetna's requirement. This can later be implemented
14981     -- as system options. Discussed this with Subir and Lauren 11/5/97
14982     -- Even here we assume zero for null quantity ordered tolerance
14983     -- Only for EDI GATEWAY source 5/4/98
14984     -- Retropricing:
14985     -- Overbill rejection is meant only for EDI Gateway. The following
14986     -- code should not reject PPA Invoice Lines. Adding the IF condition
14987     -- so that the code is not executed for PPA's.
14988     -----------------------------------------------------------------
14989     IF (AP_IMPORT_INVOICES_PKG.g_source <> 'PPA') THEN
14990 
14991        IF (l_po_line_location_id IS NOT NULL) THEN
14992           debug_info := '(v_check_line_po_info2 10) Check for quantity overbill '
14993                         ||'for PO Shipment';
14994 
14995           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
14996               AP_IMPORT_UTILITIES_PKG.Print(
14997                 AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
14998           END IF;
14999 
15000           IF (AP_IMPORT_UTILITIES_PKG.get_overbill_for_shipment(
15001                 l_po_line_location_id,              -- IN
15002                 NVL(p_invoice_lines_rec.quantity_invoiced,
15003                 l_quantity_invoiced),               -- IN
15004 		p_invoice_lines_rec.amount,         --IN
15005                 l_overbill,                         -- OUT NOCOPY
15006                 l_quantity_outstanding,             -- OUT NOCOPY
15007                 l_quantity_ordered,                 -- OUT NOCOPY
15008                 l_qty_already_billed,               -- OUT NOCOPY
15009 		l_amount_outstanding,		    -- OUT NOCOPY
15010 		l_amount_ordered,		    -- OUT NOCOPY
15011 		l_amt_already_billed,		    -- OUT NOCOPY
15012                 current_calling_sequence) <> TRUE) THEN
15013 
15014             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15015                 AP_IMPORT_UTILITIES_PKG.Print(
15016                   AP_IMPORT_INVOICES_PKG.g_debug_switch,
15017                     'get_overbill_for_shipment<-'||current_calling_sequence);
15018             END IF;
15019             RAISE check_po_failure;
15020           END IF;
15021 
15022           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15023               AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
15024                '------------------> l_overbill = '||l_overbill
15025             ||' l_quantity_outstanding = ' ||to_char(l_quantity_outstanding)
15026             ||' l_quantity_ordered =  '    ||to_char(l_quantity_ordered)
15027             ||' l_qty_already_billed =  '  ||to_char(l_qty_already_billed)
15028 	    ||' l_amount_outstanding = '   ||to_char(l_amount_outstanding)
15029 	    ||' l_amount_ordered =  '      ||to_char(l_amount_ordered)
15030 	    ||' l_amt_already_billed =  '  ||to_char(l_amt_already_billed)
15031             ||' p_max_qty_ord_tolerance = '||to_char(p_max_qty_ord_tolerance)
15032 	    ||' p_max_amt_ord_tolerance = '||to_char(p_max_amt_ord_tolerance)
15033             ||' p_qty_ord_tolerance  = '   ||to_char(p_qty_ord_tolerance)
15034 	    ||' p_amt_ord_tolerance  = '   ||to_char(p_amt_ord_tolerance));
15035 
15036           END IF;
15037 
15038           -- This is as per EDI requirements. We might need to address this later
15039           -- with quick invoices.
15040 
15041           IF (AP_IMPORT_INVOICES_PKG.g_source = 'EDI GATEWAY') Then
15042 
15043             IF(p_match_basis = 'QUANTITY') THEN
15044 
15045 		IF (p_qty_ord_tolerance is not null) then -- Added for bug 9381715
15046 	              IF ((NVL(p_invoice_lines_rec.quantity_invoiced,l_quantity_invoiced) +
15047 		               l_qty_already_billed) >
15048 			    (NVL(p_qty_ord_tolerance,1) * l_quantity_ordered)) THEN
15049 	                    debug_info := '(v_check_line_po_info2 11) Reject for '
15050 		            ||'p_qty_ord_tolerance';
15051 	                 IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15052 			         AP_IMPORT_UTILITIES_PKG.Print(
15053 				AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
15054 	                 END IF;
15055 			l_qty_based_rejection := 'Y';
15056 	              END IF;
15057 		-- Added for bug 9381715
15058 		ELSE
15059 			l_qty_based_rejection := 'N';
15060 		END IF; -- bug 9381715 ends
15061 
15062               IF (p_max_qty_ord_tolerance IS NOT NULL) Then
15063 
15064                  IF ((NVL(p_invoice_lines_rec.quantity_invoiced,l_quantity_invoiced) +
15065                        l_qty_already_billed) >
15066                       (p_max_qty_ord_tolerance + l_quantity_ordered)) THEN
15067                     debug_info := '(v_check_line_po_info2 12) Reject for '
15068                                ||'p_max_qty_ord_tolerance';
15069                     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
15070                       AP_IMPORT_UTILITIES_PKG.Print(
15071                          AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
15072                     END IF;
15073                     l_qty_based_rejection := 'Y';
15074 
15075                  END IF;
15076 
15077               END IF;
15078 
15079               IF (nvl(l_qty_based_rejection,'N') = 'Y') Then
15080                  debug_info := '(v_check_line_po_info2 13) Reject for Quantity '
15081                             ||'overbill for PO Shipment';
15082                  IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
15083                       AP_IMPORT_UTILITIES_PKG.Print(
15084                  	     AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
15085                  END IF;
15086 
15087                  IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
15088                             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
15089                             p_invoice_lines_rec.invoice_line_id,
15090                             'INVALID INVOICE QUANTITY',
15091                             p_default_last_updated_by,
15092                             p_default_last_update_login,
15093                             current_calling_sequence) <> TRUE) THEN
15094 
15095                       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
15096                          AP_IMPORT_UTILITIES_PKG.Print(
15097                             AP_IMPORT_INVOICES_PKG.g_debug_switch,
15098                                'insert_rejections<-'||current_calling_sequence);
15099                       END IF;
15100 
15101                       RAISE check_po_failure;
15102                   END IF;
15103                   l_current_invoice_status := 'N';
15104 
15105                END IF; -- l_qty_based_rejection = 'Y'
15106 
15107 	   ELSIF (p_match_basis = 'AMOUNT') THEN
15108 
15109 	       IF ((p_invoice_lines_rec.amount + l_amt_already_billed) >
15110                    (NVL(p_amt_ord_tolerance,1) * l_amount_ordered)) THEN
15111 
15112                  debug_info := '(v_check_line_po_info2 14) Reject for '
15113                             ||'p_amt_ord_tolerance';
15114                  IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15115                      AP_IMPORT_UTILITIES_PKG.Print(
15116                        AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
15117                  END IF;
15118 
15119                  l_amt_based_rejection := 'Y';
15120 
15121                END IF;
15122 
15123                IF (p_max_amt_ord_tolerance IS NOT NULL) Then
15124 
15125                   IF ((p_invoice_lines_rec.amount + l_amt_already_billed) >
15126                       (p_max_amt_ord_tolerance + l_amount_ordered)) THEN
15127 
15128                       debug_info := '(v_check_line_po_info2 15) Reject for '
15129                                ||'p_max_amt_ord_tolerance';
15130                       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
15131                          AP_IMPORT_UTILITIES_PKG.Print(
15132                             AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
15133                       END IF;
15134                       l_amt_based_rejection := 'Y';
15135 
15136                   END IF;
15137 
15138                END IF;
15139 
15140                IF (nvl(l_amt_based_rejection,'N') = 'Y') Then
15141 
15142                   debug_info := '(v_check_line_po_info2 16) Reject for Amount '
15143                             ||'overbill for PO Shipment';
15144                   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
15145                       AP_IMPORT_UTILITIES_PKG.Print(
15146                           AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
15147                   END IF;
15148 
15149                   IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
15150                             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
15151                             p_invoice_lines_rec.invoice_line_id,
15152                             'LINE AMOUNT EXCEEDED TOLERANCE',
15153                             p_default_last_updated_by,
15154                             p_default_last_update_login,
15155                             current_calling_sequence) <> TRUE) THEN
15156 
15157                       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
15158                            AP_IMPORT_UTILITIES_PKG.Print(
15159                                AP_IMPORT_INVOICES_PKG.g_debug_switch,
15160                                'insert_rejections<-'||current_calling_sequence);
15161                       END IF;
15162 
15163                       RAISE check_po_failure;
15164                   END IF;
15165 
15166                   l_current_invoice_status := 'N';
15167 
15168                END IF; -- nvl(l_amt_based_rejection,'N') = 'Y'
15169 
15170             END IF; --p_match_basis = 'QUANTITY'
15171 
15172           END IF; -- g_source = 'EDI GATEWAY'
15173 
15174        ELSIF ((l_po_line_location_id IS NULL)AND
15175                (l_po_line_id IS NOT NULL)) THEN
15176           -- po line location id is not null
15177           debug_info := '(v_check_line_po_info2 17) Check for quantity overbill '
15178                         ||'for PO Line';
15179           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15180             AP_IMPORT_UTILITIES_PKG.Print(
15181               AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
15182           END IF;
15183 
15184           IF (AP_IMPORT_UTILITIES_PKG.get_overbill_for_po_line(
15185               l_po_line_id,
15186               NVL(p_invoice_lines_rec.quantity_invoiced, l_quantity_invoiced),
15187 	      p_invoice_lines_rec.amount,  --IN
15188               l_overbill,                  -- OUT
15189               l_outstanding,     	   -- OUT
15190               l_ordered,         	   -- OUT
15191               l_already_billed,            -- OUT
15192 	      l_po_line_matching_basis,    -- OUT
15193               current_calling_sequence) <> TRUE) THEN
15194 
15195               IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
15196                 AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
15197                    'get_overbill_for_po_line<-'||current_calling_sequence);
15198               END IF;
15199               RAISE check_po_failure;
15200           END IF;
15201 
15202           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
15203             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
15204                '------------------> l_overbill = '||l_overbill
15205                ||' l_outstanding quantity/amount = '||to_char(l_outstanding)
15206               ||' l_ordered quantity/amount = '||to_char(l_ordered)
15207               ||' l_already_billed quantity/amount = '||to_char(l_already_billed)
15208               ||' p_max_qty_ord_tolerance  = '||to_char(p_max_qty_ord_tolerance)
15209 	      ||' p_max_amt_ord_tolerance = '||to_char(p_max_amt_ord_tolerance)
15210               ||' p_qty_ord_tolerance  = '||to_char(p_qty_ord_tolerance)
15211 	      ||' p_amt_ord_tolerance  = '||to_char(p_amt_ord_tolerance));
15212 
15213           END IF;
15214 
15215           -- This is as per EDI requirements. We might need to address this later
15216           -- with quick invoices.
15217           IF (AP_IMPORT_INVOICES_PKG.g_source = 'EDI GATEWAY') Then
15218 
15219 	     IF (l_po_line_matching_basis = 'QUANTITY') THEN
15220 
15221 		IF (p_qty_ord_tolerance is not null) then -- Added for bug 9381715
15222 			IF ((NVL(p_invoice_lines_rec.quantity_invoiced,l_quantity_invoiced) +
15223                			 l_already_billed) >
15224 	                    (NVL(p_qty_ord_tolerance,1) * l_ordered)) THEN
15225 		             debug_info := '(v_check_line_po_info2 18) Reject for '
15226 				            ||'p_qty_ord_tolerance';
15227 	                   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
15228 	                      AP_IMPORT_UTILITIES_PKG.Print(
15229 		                  AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
15230 			   END IF;
15231 			   l_qty_based_rejection := 'Y';
15232 	                END IF;
15233 		-- Added for bug 9381715
15234 		ELSE
15235 			l_qty_based_rejection := 'N';
15236 		END IF; -- bug 9381715 ends
15237 
15238                 IF (p_max_qty_ord_tolerance IS NOT NULL) Then
15239                    IF ((NVL(p_invoice_lines_rec.quantity_invoiced,l_quantity_invoiced) +
15240                           l_already_billed) >
15241                        (p_max_qty_ord_tolerance + l_ordered)) THEN
15242 
15243                        debug_info := '(v_check_line_po_info2 19) Reject for '
15244                               ||'p_max_qty_ord_tolerance';
15245                         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
15246                   	   AP_IMPORT_UTILITIES_PKG.Print(
15247                     		AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
15248                 	END IF;
15249                 	l_qty_based_rejection := 'Y';
15250                    END IF;
15251                 END IF;
15252 
15253                 IF (nvl(l_qty_based_rejection,'N') = 'Y') THEN
15254                    debug_info := '(v_check_line_po_info2 20) Reject for Quantity '
15255                              ||'overbill for PO Line';
15256                    IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
15257                 	AP_IMPORT_UTILITIES_PKG.Print(
15258                   		AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
15259               	   END IF;
15260 
15261               	   IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
15262                             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
15263                             p_invoice_lines_rec.invoice_line_id,
15264                             'INVALID INVOICE QUANTITY',
15265                             p_default_last_updated_by,
15266                             p_default_last_update_login,
15267                             current_calling_sequence) <> TRUE) THEN
15268                         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
15269                   	   AP_IMPORT_UTILITIES_PKG.Print(
15270                     		AP_IMPORT_INVOICES_PKG.g_debug_switch,
15271                       		'insert_rejections<-'||current_calling_sequence);
15272                 	END IF;
15273                 	RAISE check_po_failure;
15274               	   END IF;
15275 
15276                    l_current_invoice_status := 'N';
15277 
15278                 END IF; /* nvl(l_qty_based_rejection,'N') = 'Y' */
15279 
15280             ELSIF (l_po_line_matching_basis = 'AMOUNT') THEN
15281 
15282                IF ((p_invoice_lines_rec.amount + l_already_billed) >
15283                   (NVL(p_amt_ord_tolerance,1) * l_ordered)) THEN
15284                   debug_info := '(v_check_line_po_info2 21) Reject for '
15285                                  ||'p_amt_ord_tolerance';
15286 
15287                   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
15288                      AP_IMPORT_UTILITIES_PKG.Print(
15289                        AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
15290                   END IF;
15291                   l_amt_based_rejection := 'Y';
15292 
15293                END IF;
15294 
15295                IF (p_max_amt_ord_tolerance IS NOT NULL) Then
15296 
15297                   IF ((p_invoice_lines_rec.amount + l_already_billed) >
15298                      (p_max_amt_ord_tolerance + l_ordered)) THEN
15299 
15300                      debug_info := '(v_check_line_po_info2 22) Reject for '
15301                                   ||'p_max_amt_ord_tolerance';
15302                      IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
15303                         AP_IMPORT_UTILITIES_PKG.Print(
15304                           AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
15305                      END IF;
15306 
15307                      l_amt_based_rejection := 'Y';
15308 
15309                   END IF;
15310 
15311                END IF;
15312 
15313                IF (nvl(l_amt_based_rejection,'N') = 'Y') THEN
15314                   debug_info := '(v_check_line_po_info2 23) Reject for Amount '
15315                                ||'overbill for PO Line';
15316                   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
15317                     AP_IMPORT_UTILITIES_PKG.Print(
15318                       AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
15319                   END IF;
15320 
15321                   IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
15322                             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
15323                             p_invoice_lines_rec.invoice_line_id,
15324                             'LINE AMOUNT EXCEEDED TOLERANCE',
15325                             p_default_last_updated_by,
15326                             p_default_last_update_login,
15327                             current_calling_sequence) <> TRUE) THEN
15328                      IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
15329                        AP_IMPORT_UTILITIES_PKG.Print(
15330                            AP_IMPORT_INVOICES_PKG.g_debug_switch,
15331                            'insert_rejections<-'||current_calling_sequence);
15332                      END IF;
15333                      RAISE check_po_failure;
15334                   END IF;
15335 
15336                   l_current_invoice_status := 'N';
15337 
15338                END IF;
15339 
15340 	    END IF; --l_po_line_matching_basis = 'QUANTITY'
15341 
15342           END IF ; --g_source = 'EDI'...
15343 
15344    --     END IF; -- overbill
15345 
15346       END IF; -- l_po_header_id is NOT NULL
15347 
15348   END IF; --source <> PPA
15349 
15350   p_current_invoice_status := l_current_invoice_status;
15351   p_calc_quantity_invoiced := l_quantity_invoiced;
15352   p_calc_unit_price        := l_dec_unit_price;
15353 
15354   RETURN(TRUE);
15355 
15356 EXCEPTION
15357   WHEN OTHERS THEN
15358     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
15359       AP_IMPORT_UTILITIES_PKG.Print(
15360         AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
15361     END IF;
15362 
15363     IF (SQLCODE < 0) then
15364       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
15365         AP_IMPORT_UTILITIES_PKG.Print(
15366           AP_IMPORT_INVOICES_PKG.g_debug_switch, SQLERRM);
15367       END IF;
15368     END IF;
15369     RETURN(FALSE);
15370 
15371 END v_check_line_po_info2;
15372 
15373 FUNCTION v_check_po_overlay (
15374    p_invoice_rec	       IN  AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
15375    p_invoice_lines_rec         IN  AP_IMPORT_INVOICES_PKG.r_line_info_rec,
15376    p_po_line_id                IN            NUMBER,
15377    p_po_line_location_id       IN            NUMBER,
15378    p_po_distribution_id        IN            NUMBER,
15379    p_set_of_books_id           IN            NUMBER,
15380    p_default_last_updated_by   IN            NUMBER,
15381    p_default_last_update_login IN            NUMBER,
15382    p_current_invoice_status    IN OUT NOCOPY VARCHAR2,
15383    p_calling_sequence          IN            VARCHAR2) RETURN BOOLEAN
15384 IS
15385    check_po_failure              EXCEPTION;
15386    l_po_line_id                NUMBER    := p_po_line_id;
15387    l_po_line_location_id    NUMBER    := p_po_line_location_id;
15388    l_po_distribution_id        NUMBER    := p_po_distribution_id;
15389    l_unbuilt_flex           VARCHAR2(240):='';
15390    l_reason_unbuilt_flex    VARCHAR2(2000):='';
15391    l_code_combination_id    NUMBER;
15392    l_current_invoice_status    VARCHAR2(1) := p_current_invoice_status;
15393    l_dist_code_concatenated    VARCHAR2(2000):='';
15394    current_calling_sequence VARCHAR2(2000);
15395    debug_info               VARCHAR2(500);
15396 
15397 CURSOR    po_distributions_cur IS
15398    SELECT code_combination_id
15399      FROM po_distributions
15400     WHERE line_location_id = l_po_line_location_id
15401     AND nvl(accrue_on_receipt_flag,'N') <> 'Y' --Bug 2667171 added this Condition
15402     ORDER BY distribution_num;
15403 
15404 --Contract Payments: Modified the where clause
15405 CURSOR    po_line_locations_cur IS
15406    SELECT pd.code_combination_id
15407      FROM po_distributions pd,
15408       po_line_locations pll
15409     WHERE pd.line_location_id = pll.line_location_id
15410       AND pll.po_line_id = l_po_line_id
15411       AND(
15412           --(p_invoice_rec.invoice_type_lookup_code <> 'PREPAYMENT' and                  .. B# 8528132
15413           (nvl(p_invoice_rec.invoice_type_lookup_code, 'STANDARD') <> 'PREPAYMENT' and   -- B# 8528132
15414            pll.SHIPMENT_TYPE IN ('STANDARD','BLANKET','SCHEDULED')
15415           ) OR
15416           (p_invoice_rec.invoice_type_lookup_code = 'PREPAYMENT' and
15417            ((pll.payment_type IS NOT NULL and pll.shipment_type = 'PREPAYMENT') or
15418             (pll.payment_type IS NULL and pll.shipment_type IN ('STANDARD','BLANKET','SCHEDULED'))
15419            )
15420           )
15421          )
15422       AND pll.APPROVED_FLAG = 'Y'
15423     ORDER BY pll.shipment_num,pd.distribution_num;
15424 
15425 BEGIN
15426   -- Update the calling sequence
15427   --
15428   current_calling_sequence :=  'v_check_po_overlay<-'||P_calling_sequence;
15429 
15430   ----------------------------------------------------------
15431   -- Check Account Overlay
15432   -- Step 1
15433   ----------------------------------------------------------
15434   IF ((l_current_invoice_status <> 'N') AND
15435       ((p_invoice_lines_rec.dist_code_concatenated IS NOT NULL) OR
15436        (p_invoice_lines_rec.balancing_segment IS NOT NULL) OR
15437        (p_invoice_lines_rec.cost_center_segment IS NOT NULL) OR
15438        (p_invoice_lines_rec.account_segment IS NOT NULL)) ) THEN
15439     IF (p_invoice_lines_rec.dist_code_concatenated IS NOT NULL) THEN
15440       l_dist_code_concatenated := p_invoice_lines_rec.dist_code_concatenated;
15441     END IF;
15442 
15443     IF (l_po_distribution_id IS NOT NULL) THEN
15444       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15445         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
15446            '(v_check_po_overlay 1) Get l_code_combination_id FROM '
15447            ||'l_po_distribution_id ');
15448       END IF;
15449 
15450       SELECT code_combination_id
15451         INTO l_code_combination_id
15452         FROM po_distributions
15453        WHERE po_distribution_id = l_po_distribution_id
15454          AND line_location_id IS NOT NULL; /* BUG 3253594 */
15455       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15456         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
15457           '------------------> l_code_combination_id  = '
15458           || to_char(l_code_combination_id)
15459           ||'balancing_segment ='||p_invoice_lines_rec.balancing_segment
15460           ||'cost_center_segment ='||p_invoice_lines_rec.cost_center_segment
15461           ||'account_segment ='||p_invoice_lines_rec.account_segment
15462           ||'dist_code_concatenated ='
15463           ||p_invoice_lines_rec.dist_code_concatenated);
15464         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
15465         '(v_check_po_overlay 2) Check Overlay Segments fOR '
15466         ||'l_po_distribution_id ');
15467       END IF;
15468 
15469       IF (AP_UTILITIES_PKG.overlay_segments(
15470            p_invoice_lines_rec.balancing_segment,
15471            p_invoice_lines_rec.cost_center_segment,
15472            p_invoice_lines_rec.account_segment,
15473            l_dist_code_concatenated,
15474            l_code_combination_id , -- OUT NOCOPY
15475            p_set_of_books_id ,
15476            'CHECK' , -- Overlay Mode
15477            l_unbuilt_flex , -- OUT NOCOPY
15478            l_reason_unbuilt_flex , -- OUT NOCOPY
15479            FND_GLOBAL.RESP_APPL_ID,
15480            FND_GLOBAL.RESP_ID,
15481            FND_GLOBAL.USER_ID,
15482            current_calling_sequence ,
15483            NULL,
15484            p_invoice_lines_rec.accounting_date) <> TRUE) THEN --7531219
15485         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15486           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
15487             '(v_check_po_overlay 2) Overlay_Segments<-'
15488              ||current_calling_sequence);
15489         END IF;
15490         Raise check_po_failure;
15491       ELSE
15492         -- show output values (only IF debug_switch = 'Y')
15493         --
15494         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15495           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
15496             '------------------> l_unbuilt_flex = '|| l_unbuilt_flex
15497             ||'l_reason_unbuilt_flex = '||l_reason_unbuilt_flex
15498             ||'l_code_combination_id = '|| to_char(l_code_combination_id));
15499         END IF;
15500 
15501         -- 7531219 changed the if condition
15502         IF (l_unbuilt_flex is not null or l_reason_unbuilt_flex is not null /*l_code_combination_id = -1*/) THEN
15503           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15504             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
15505               '(v_check_po_overlay 3) Invalid code_combination_id overlay');
15506           END IF;
15507 
15508           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
15509             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
15510                p_invoice_lines_rec.invoice_line_id,
15511                'INVALID ACCT OVERLAY',
15512                p_default_last_updated_by,
15513                p_default_last_update_login,
15514                current_calling_sequence) <> TRUE) THEN
15515           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15516             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
15517               'insert_rejections<-'||current_calling_sequence);
15518           END IF;
15519           RAISE check_po_failure;
15520         END IF; -- Code combination id is -1
15521         l_current_invoice_status := 'N';
15522         END IF; -- added by iyas for code_combination_id
15523       END IF; -- IF overlay segments is other than TRUE
15524     ELSIF (l_po_line_location_id IS NOT NULL) THEN
15525       -- IF po distribution id is not NULL
15526       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15527         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
15528           '(v_check_po_overlay 1) Get l_code_combination_id FROM '
15529           ||'l_po_line_location_id ');
15530         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
15531           '(v_check_po_overlay 1) Open po_distributions ');
15532       END IF;
15533 
15534       OPEN po_distributions_cur;
15535 
15536       LOOP
15537       --
15538       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15539         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
15540              '(v_check_po_overlay 2) Fetch po_distributions_cur ');
15541       END IF;
15542 
15543       FETCH po_distributions_cur  INTO
15544                 l_code_combination_id;
15545       --
15546       EXIT WHEN po_distributions_cur%NOTFOUND OR
15547                 po_distributions_cur%NOTFOUND IS NULL;
15548 
15549       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15550         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
15551             '------------------> l_code_combination_id  = '
15552          || to_char(l_code_combination_id)
15553          ||'balancing_segment ='||p_invoice_lines_rec.balancing_segment
15554          ||'cost_center_segment ='||p_invoice_lines_rec.cost_center_segment
15555          ||'account_segment ='||p_invoice_lines_rec.account_segment
15556          ||'l_dist_code_concatenated ='||l_dist_code_concatenated);
15557 
15558         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
15559           '(v_check_po_overlay 3) Check Overlay Segments fOR '
15560           ||'l_po_line_location_id ');
15561       END IF;
15562 
15563       IF (AP_UTILITIES_PKG.overlay_segments(
15564              p_invoice_lines_rec.balancing_segment,
15565              p_invoice_lines_rec.cost_center_segment,
15566              p_invoice_lines_rec.account_segment,
15567              l_dist_code_concatenated,
15568              l_code_combination_id ,         -- OUT NOCOPY
15569              p_set_of_books_id ,
15570              'CHECK' ,                 -- Overlay Mode
15571              l_unbuilt_flex ,             -- OUT NOCOPY
15572              l_reason_unbuilt_flex ,         -- OUT NOCOPY
15573              FND_GLOBAL.RESP_APPL_ID,
15574              FND_GLOBAL.RESP_ID,
15575              FND_GLOBAL.USER_ID,
15576              current_calling_sequence,
15577              NULL,
15578              p_invoice_lines_rec.accounting_date ) <> TRUE) THEN --7531219
15579         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15580           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
15581             '(v_check_po_overlay 3) Overlay_Segments<-'
15582              ||current_calling_sequence);
15583         END IF;
15584         CLOSE po_distributions_cur;
15585         RAISE check_po_failure;
15586       ELSE
15587         -- show output values (only IF debug_switch = 'Y')
15588         --
15589         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15590           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
15591             '------------------> l_unbuilt_flex = '||l_unbuilt_flex
15592             ||'l_reason_unbuilt_flex = '||l_reason_unbuilt_flex
15593             ||'l_code_combination_id = '|| to_char(l_code_combination_id));
15594         END IF;
15595 
15596         -- 7531219 changed the if condition
15597         IF (l_unbuilt_flex is not null or l_reason_unbuilt_flex is not null/*l_code_combination_id = -1*/) THEN
15598           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15599             AP_IMPORT_UTILITIES_PKG.Print(
15600              AP_IMPORT_INVOICES_PKG.g_debug_switch,
15601              '(v_check_po_overlay 4) Invalid code_combination_id overlay');
15602           END IF;
15603 
15604           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
15605              AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
15606              p_invoice_lines_rec.invoice_line_id,
15607              'INVALID ACCT OVERLAY',
15608              p_default_last_updated_by,
15609              p_default_last_update_login,
15610              current_calling_sequence) <> TRUE) THEN
15611           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15612               AP_IMPORT_UTILITIES_PKG.Print(
15613                 AP_IMPORT_INVOICES_PKG.g_debug_switch,
15614                   'insert_rejections<-'||current_calling_sequence);
15615           END IF;
15616           CLOSE po_distributions_cur;
15617           RAISE check_po_failure;
15618             --
15619           END IF;
15620           l_current_invoice_status := 'N';
15621         END IF; -- code combination id is -1
15622       END IF; --overlay segments
15623 
15624       END LOOP;
15625       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15626         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
15627           '(v_check_po_overlay 5) Close po_distributions ');
15628       END IF;
15629       CLOSE po_distributions_cur;
15630     ELSIF ((l_po_line_id IS NOT NULL) AND
15631            (l_po_line_location_id IS NULL)) THEN
15632          -- po distribution id is not NULL
15633       -- PO Line Level Matching
15634       --
15635       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15636         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
15637           '(v_check_po_overlay 1) Get l_code_combination_id FROM l_po_line_id ');
15638         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
15639           '(v_check_po_overlay 1) Open po_line_locations ');
15640       END IF;
15641 
15642       OPEN po_line_locations_cur;
15643 
15644       LOOP
15645       --
15646       --
15647       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15648         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
15649           '(v_check_po_overlay 2) Fetch po_line_locations_cur ');
15650       END IF;
15651 
15652       FETCH po_line_locations_cur  INTO l_code_combination_id;
15653       --
15654       EXIT WHEN po_line_locations_cur%NOTFOUND OR
15655                 po_line_locations_cur%NOTFOUND IS NULL;
15656 
15657       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15658         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
15659           '------------------> l_code_combination_id  = '||
15660           to_char(l_code_combination_id)
15661           ||'balancing_segment ='||p_invoice_lines_rec.balancing_segment
15662           ||'cost_center_segment ='||p_invoice_lines_rec.cost_center_segment
15663           ||'account_segment ='||p_invoice_lines_rec.account_segment
15664           ||'l_dist_code_concatenated ='||l_dist_code_concatenated);
15665         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
15666           '(v_check_po_overlay 3) Check Overlay Segments fOR l_po_line_id ');
15667       END IF;
15668 
15669       IF (AP_UTILITIES_PKG.overlay_segments(
15670           p_invoice_lines_rec.balancing_segment,
15671           p_invoice_lines_rec.cost_center_segment,
15672           p_invoice_lines_rec.account_segment,
15673           l_dist_code_concatenated,
15674           l_code_combination_id,             -- OUT NOCOPY
15675           p_set_of_books_id,
15676           'CHECK' ,                 -- Overlay Mode
15677           l_unbuilt_flex ,                 -- OUT NOCOPY
15678           l_reason_unbuilt_flex ,             -- OUT NOCOPY
15679           FND_GLOBAL.RESP_APPL_ID,
15680           FND_GLOBAL.RESP_ID,
15681           FND_GLOBAL.USER_ID,
15682           current_calling_sequence ,
15683           NULL,
15684           p_invoice_lines_rec.accounting_date) <> TRUE) THEN --7531219
15685         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15686           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
15687             '(v_check_po_overlay 3) Overlay_Segments<-'
15688             ||current_calling_sequence);
15689         END IF;
15690         CLOSE po_line_locations_cur;
15691         Raise check_po_failure;
15692       ELSE
15693         -- show output values (only IF debug_switch = 'Y')
15694         --
15695         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15696           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
15697              '------------------>
15698            l_unbuilt_flex = '||l_unbuilt_flex
15699              ||'l_reason_unbuilt_flex = '||l_reason_unbuilt_flex
15700              ||'l_code_combination_id = '|| to_char(l_code_combination_id));
15701         END IF;
15702 
15703         -- 7531219 changed the if condition
15704         IF (l_unbuilt_flex is not null or l_reason_unbuilt_flex is not null/*l_code_combination_id = -1*/) THEN
15705           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15706             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
15707               '(v_check_po_overlay 4) Invalid code_combination_id overlay');
15708           END IF;
15709           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
15710              AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
15711                 p_invoice_lines_rec.invoice_line_id,
15712                 'INVALID ACCT OVERLAY',
15713                 p_default_last_updated_by,
15714                 p_default_last_update_login,
15715                 current_calling_sequence) <> TRUE) THEN
15716             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15717               AP_IMPORT_UTILITIES_PKG.Print(
15718                 AP_IMPORT_INVOICES_PKG.g_debug_switch,
15719                   'insert_rejections<-'||current_calling_sequence);
15720             END IF;
15721             CLOSE po_line_locations_cur;
15722             RAISE check_po_failure;
15723             --
15724           END IF; -- insert rejections
15725           l_current_invoice_status := 'N';
15726         END IF; -- code combination id is -1
15727       END IF;  -- overlay segments
15728 
15729       END LOOP;
15730       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15731         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
15732           '(v_check_po_overlay 5) Close po_line_locations ');
15733       END IF;
15734       CLOSE po_line_locations_cur;
15735     END IF; -- po distribution id is not NULL
15736   ELSE -- invoice status <> 'N'
15737     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15738       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
15739          '(v_check_po_overlay 1) No Overlay Required ');
15740     END IF;
15741 
15742   END IF; -- invoice status <> 'N'
15743 
15744   p_current_invoice_status := l_current_invoice_status;
15745   RETURN (TRUE);
15746 
15747 EXCEPTION
15748   WHEN OTHERS THEN
15749     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15750       AP_IMPORT_UTILITIES_PKG.Print(
15751         AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
15752     END IF;
15753 
15754     IF (SQLCODE < 0) THEN
15755       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15756         AP_IMPORT_UTILITIES_PKG.Print(
15757           AP_IMPORT_INVOICES_PKG.g_debug_switch,SQLERRM);
15758       END IF;
15759     END IF;
15760     RETURN(FALSE);
15761 
15762 END v_check_po_overlay;
15763 
15764 
15765 ------------------------------------------------------------------------------
15766 -- This function is used to validate RCV information.
15767 -- Retropricing:Step 1 and 3 don't execute for PPA's
15768 ------------------------------------------------------------------------------
15769 FUNCTION v_check_receipt_info (
15770    p_invoice_rec	IN    AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
15771    p_invoice_lines_rec  IN OUT NOCOPY AP_IMPORT_INVOICES_PKG.r_line_info_rec,
15772    p_default_last_updated_by      IN            NUMBER,
15773    p_default_last_update_login    IN            NUMBER,
15774    p_temp_line_status                OUT NOCOPY VARCHAR2,
15775    p_calling_sequence             IN            VARCHAR2) RETURN BOOLEAN
15776 IS
15777    check_receipt_failure        EXCEPTION;
15778    l_temp_rcv_txn_id            NUMBER;
15779    l_temp_ship_line_id          NUMBER;     --Bug 7344899 variable added
15780    l_temp_value                    VARCHAR2(1);
15781    l_qty_billed_sum                NUMBER;
15782    l_rcv_uom                    VARCHAR2(30);
15783    l_qty_billed                    NUMBER;
15784    debug_info                    VARCHAR2(2000);
15785    current_calling_sequence        VARCHAR2(2000);
15786    l_cascade_receipts_flag      VARCHAR2(1);
15787    l_price_correct_inv_id	AP_INVOICES.INVOICE_ID%TYPE;
15788 
15789    --Contract Payments
15790    l_shipment_type		PO_LINE_LOCATIONS_ALL.SHIPMENT_TYPE%TYPE;
15791 
15792 BEGIN
15793 
15794   -- Update   the calling sequence
15795   current_calling_sequence :=
15796     'AP_IMPORT_VALIDATION_PKG.v_check_receipt_info <-' ||p_calling_sequence;
15797 
15798   --Contract Payments: Cannot match a Prepayment invoice to receipt.
15799   IF (p_invoice_rec.invoice_type_lookup_code = 'PREPAYMENT' AND
15800       (p_invoice_lines_rec.rcv_transaction_id IS NOT NULL OR
15801        p_invoice_lines_rec.match_option = 'R' OR
15802        p_invoice_lines_rec.receipt_number IS NOT NULL
15803       )
15804      ) THEN
15805 
15806       debug_info := '(Check Receipt Info 1) Check if invoice type is'||
15807       		   ' Prepayment and receipt info is provided';
15808       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15809          AP_IMPORT_UTILITIES_PKG.Print(
15810                  AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
15811       END IF;
15812 
15813       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
15814                    AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
15815                    p_invoice_lines_rec.invoice_line_id,
15816                    'INVALID MATCHING INFO',
15817                    p_default_last_updated_by,
15818                    p_default_last_update_login,
15819                    current_calling_sequence)<> TRUE) THEN
15820           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15821              AP_IMPORT_UTILITIES_PKG.Print(
15822                  AP_IMPORT_INVOICES_PKG.g_debug_switch,
15823                 'insert_rejections <-'||current_calling_sequence);
15824           END IF;
15825           Raise check_receipt_failure;
15826       END IF;
15827 
15828       p_temp_line_status := 'N';
15829 
15830   END IF;
15831 
15832   ---------------------------------------------------------------------------
15833   -- Step 1 : Validate receipt info IF source is EDI GATEWAY AND type = ITEM
15834   ---------------------------------------------------------------------------
15835 
15836   /* Commented for bug#9857975 Start
15837      Uncommented for bug#10175718
15838      We would cascade the receipts of a shipment for EDI GATEWAY invoices
15839      if the receipt information is missing in the interface table.
15840    */
15841   IF (AP_IMPORT_INVOICES_PKG.g_source = 'EDI GATEWAY') AND
15842      (p_invoice_lines_rec.line_type_lookup_code = 'ITEM') AND
15843      (p_invoice_lines_rec.match_option = 'R') THEN
15844 
15845 
15846     -- Case a : receipt_num AND id are NULL
15847     IF (p_invoice_lines_rec.receipt_number is NULL ) AND
15848        (p_invoice_lines_rec.rcv_transaction_id is NULL) AND
15849        (p_invoice_lines_rec.po_line_location_id is not NULL) THEN
15850 
15851        debug_info := '(Check Receipt Info 1) Case a';
15852       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15853           AP_IMPORT_UTILITIES_PKG.Print(
15854             AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
15855       END IF;
15856 
15857       BEGIN
15858        SELECT rcv_transaction_id
15859          INTO l_temp_rcv_txn_id
15860          FROM po_ap_receipt_match_v
15861         WHERE po_line_location_id = p_invoice_lines_rec.po_line_location_id;
15862 
15863       EXCEPTION
15864         When no_data_found THEN
15865            -- reject fOR INSUFFICIENT RECEIPT INFORMATION
15866            IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
15867                 AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
15868                 p_invoice_lines_rec.invoice_line_id,
15869                 'INSUFFICIENT RECEIPT INFO',
15870                 p_default_last_updated_by,
15871                 p_default_last_update_login,
15872                 current_calling_sequence)<> TRUE) THEN
15873              IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15874                AP_IMPORT_UTILITIES_PKG.Print(
15875                  AP_IMPORT_INVOICES_PKG.g_debug_switch,
15876                    'insert_rejections <-'||current_calling_sequence);
15877              END IF;
15878               Raise check_receipt_failure;
15879            END IF;
15880            p_temp_line_status := 'N';
15881         When too_many_rows THEN
15882              l_cascade_receipts_flag := 'Y';
15883              p_invoice_lines_rec.cascade_receipts_flag := 'Y'; /* Setting the cascade_receipts_flag to Y, this interface line needs to cascade the receipts */
15884 			 AP_IMPORT_VALIDATION_PKG.lg_cascade_rept_flag(p_invoice_rec.invoice_id||'-'||p_invoice_lines_rec.line_number) :='Y';
15885           l_temp_rcv_txn_id := NULL;
15886       END;
15887 
15888       -- Case c : receipt num is not NULL, id is NULL
15889     ELSIF (p_invoice_lines_rec.receipt_number is not NULL) AND
15890         (p_invoice_lines_rec.rcv_transaction_id is NULL) THEN
15891       debug_info := '(Check Receipt Info 1) Case c';
15892       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15893         AP_IMPORT_UTILITIES_PKG.Print(
15894           AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
15895       END IF;
15896 
15897       BEGIN
15898        SELECT rcv_transaction_id
15899          INTO l_temp_rcv_txn_id
15900          FROM po_ap_receipt_match_v
15901         WHERE receipt_number = p_invoice_lines_rec.receipt_number
15902           AND po_line_location_id = p_invoice_lines_rec.po_line_location_id;
15903 
15904        Exception
15905          When no_data_found THEN
15906        --reject fOR INVALID RECEIPT INFORMATION
15907        IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
15908             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
15909             p_invoice_lines_rec.invoice_line_id,
15910             'INVALID RECEIPT INFO',
15911             p_default_last_updated_by,
15912             p_default_last_update_login,
15913             current_calling_sequence)<> TRUE) THEN
15914              IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15915                AP_IMPORT_UTILITIES_PKG.Print(
15916                  AP_IMPORT_INVOICES_PKG.g_debug_switch,
15917                    'insert_rejections <-'||current_calling_sequence);
15918              END IF;
15919          Raise check_receipt_failure;
15920        END IF;
15921        p_temp_line_status := 'N';
15922          WHEN too_many_rows THEN
15923            l_cascade_receipts_flag := 'Y';
15924            p_invoice_lines_rec.cascade_receipts_flag := 'Y'; /* Setting the cascade_receipts_flag to Y, this interface line needs to cascade the receipts */
15925 		   AP_IMPORT_VALIDATION_PKG.lg_cascade_rept_flag(p_invoice_rec.invoice_id||'-'||p_invoice_lines_rec.line_number) :='Y';
15926        l_temp_rcv_txn_id := NULL;
15927       END;
15928 
15929     -- Case d : receipt_num is NULL AND id is not NULL
15930     ELSIF (p_invoice_lines_rec.receipt_number is NULL) AND
15931     (p_invoice_lines_rec.rcv_transaction_id is not NULL) THEN
15932       debug_info := '(Check Receipt Info 1) Case d';
15933       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15934          AP_IMPORT_UTILITIES_PKG.Print(
15935            AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
15936       END IF;
15937 
15938       BEGIN
15939        SELECT rcv_transaction_id
15940        INTO l_temp_rcv_txn_id
15941        FROM po_ap_receipt_match_v
15942        WHERE rcv_transaction_id = p_invoice_lines_rec.rcv_transaction_id
15943        AND po_line_location_id = p_invoice_lines_rec.po_line_location_id;
15944 
15945        EXCEPTION
15946          When Others THEN
15947      -- reject fOR INVALID RECEIPT INFORMATION
15948          IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
15949             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
15950             p_invoice_lines_rec.invoice_line_id,
15951             'INVALID RECEIPT INFO',
15952             p_default_last_updated_by,
15953             p_default_last_update_login,
15954             current_calling_sequence)<> TRUE) THEN
15955              IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15956                AP_IMPORT_UTILITIES_PKG.Print(
15957                  AP_IMPORT_INVOICES_PKG.g_debug_switch,
15958             'insert_rejections <-'||current_calling_sequence);
15959              END IF;
15960          Raise check_receipt_failure;
15961        END IF;
15962        p_temp_line_status := 'N';
15963       END;
15964 
15965     -- Case d : receipt num is not NULL AND id is not NULL
15966     ELSIF (p_invoice_lines_rec.receipt_number is not NULL) AND
15967           (p_invoice_lines_rec.rcv_transaction_id is not NULL) THEN
15968       debug_info := '(Check Receipt Info 1) Case e';
15969       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15970         AP_IMPORT_UTILITIES_PKG.Print(
15971           AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
15972       END IF;
15973       BEGIN
15974        SELECT rcv_transaction_id
15975          INTO l_temp_rcv_txn_id
15976          FROM po_ap_receipt_match_v
15977         WHERE rcv_transaction_id = p_invoice_lines_rec.rcv_transaction_id
15978           AND receipt_number = p_invoice_lines_rec.receipt_number
15979           AND po_line_location_id = p_invoice_lines_rec.po_line_location_id;
15980 
15981 
15982       Exception
15983          When Others THEN
15984      -- reject fOR INCONSISTENT RECEIPT INFORMATION
15985          IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
15986             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
15987             p_invoice_lines_rec.invoice_line_id,
15988             'INCONSISTENT RECEIPT INFO',
15989             p_default_last_updated_by,
15990             p_default_last_update_login,
15991             current_calling_sequence)<> TRUE) THEN
15992            IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15993                AP_IMPORT_UTILITIES_PKG.Print(
15994                  AP_IMPORT_INVOICES_PKG.g_debug_switch,
15995                    'insert_rejections <-'||current_calling_sequence);
15996            END IF;
15997        Raise check_receipt_failure;
15998      END IF;
15999      p_temp_line_status := 'N';
16000        END;
16001     END IF; -- Case a receipt number AND id are NULL
16002 
16003 
16004     -------------------------------------------------------------------
16005     -- Step 1.A  Validate UOM AND Quantity IF cascade flag = 'Y'
16006     -- Context: Source = 'EDI GATEWAY', line type = 'ITEM' AND
16007     -- Match Option = 'R'
16008     -------------------------------------------------------------------
16009     IF (nvl(l_cascade_receipts_flag,'N') = 'Y' )THEN
16010       -- Validate UOM
16011       IF (p_invoice_lines_rec.unit_of_meas_lookup_code is not NULL) THEN
16012         debug_info := 'validate the UOM';
16013         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16014           AP_IMPORT_UTILITIES_PKG.Print(
16015             AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
16016         END IF;
16017 
16018         BEGIN
16019         SELECT distinct receipt_uom_lookup_code
16020           INTO l_rcv_uom
16021           FROM po_ap_receipt_match_v
16022          WHERE po_line_location_id = p_invoice_lines_rec.po_line_location_id
16023            AND receipt_number = NVL(p_invoice_lines_rec.receipt_number,
16024                                         receipt_number)
16025            AND rcv_transaction_id = nvl(p_invoice_lines_rec.rcv_transaction_id,
16026                                         rcv_transaction_id);
16027         EXCEPTION
16028         WHEN OTHERS THEN
16029           -- reject with   UOM DOES NOT MATCH RECEIPT
16030           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
16031                 AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
16032                 p_invoice_lines_rec.invoice_line_id,
16033                 'UOM DOES NOT MATCH RECPT',
16034                 p_default_last_updated_by,
16035                 p_default_last_update_login,
16036                 current_calling_sequence)<> TRUE) THEN
16037                 IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16038                   AP_IMPORT_UTILITIES_PKG.Print(
16039                     AP_IMPORT_INVOICES_PKG.g_debug_switch,
16040                 'insert_rejections <-'||current_calling_sequence);
16041                 END IF;
16042             Raise check_receipt_failure;
16043           END IF;
16044          END;
16045 
16046        IF (l_rcv_uom <> p_invoice_lines_rec.unit_of_meas_lookup_code) THEN
16047           -- reject with   UOM DOES NOT MATCH RECEIPT
16048           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
16049                 AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
16050                 p_invoice_lines_rec.invoice_line_id,
16051                 'UOM DOES NOT MATCH RECPT',
16052                 p_default_last_updated_by,
16053                 p_default_last_update_login,
16054                 current_calling_sequence)<> TRUE) THEN
16055                 IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16056                   AP_IMPORT_UTILITIES_PKG.Print(
16057                     AP_IMPORT_INVOICES_PKG.g_debug_switch,
16058                       'insert_rejections <-'||current_calling_sequence);
16059                 END IF;
16060             Raise check_receipt_failure;
16061           END IF;
16062         END IF;
16063 
16064       END IF; -- unit of measure is not NULL
16065 
16066       -- Validate quantity billed does not become less than zero
16067       debug_info := 'Check IF quantity billed will be less than zero';
16068       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16069         AP_IMPORT_UTILITIES_PKG.Print(
16070           AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
16071       END IF;
16072 
16073       BEGIN
16074       --bug 5118518:Removed the view reference
16075           SELECT nvl(sum(nvl(RT.quantity_billed,0)),0)
16076             INTO l_qty_billed_sum
16077             FROM rcv_transactions RT ,
16078                  rcv_shipment_headers SH ,
16079                  po_headers_all PH ,
16080                  po_line_locations_all PS ,
16081                  po_releases_all PR ,
16082                  per_all_people_f BU
16083           WHERE  RT.po_line_location_id = p_invoice_lines_rec.po_line_location_id
16084             AND  SH.receipt_num     = nvl(p_invoice_lines_rec.receipt_number,sh.receipt_num)
16085             AND RT.transaction_id  = nvl(p_invoice_lines_rec.rcv_transaction_id, RT.transaction_id)
16086             AND RT.SHIPMENT_HEADER_ID  = SH.SHIPMENT_HEADER_ID
16087             AND RT.PO_HEADER_ID        = PH.PO_HEADER_ID
16088             AND RT.PO_LINE_LOCATION_ID = PS.LINE_LOCATION_ID
16089             AND RT.PO_RELEASE_ID       = PR.PO_RELEASE_ID(+)
16090             AND PH.AGENT_ID            = BU.PERSON_ID(+)
16091             AND SH.receipt_source_code = 'VENDOR'
16092             AND RT.TRANSACTION_TYPE IN ('RECEIVE', 'MATCH')
16093             AND BU.EFFECTIVE_START_DATE(+) <= TRUNC(SYSDATE)
16094             AND BU.EFFECTIVE_END_DATE(+)   >= TRUNC(SYSDATE)
16095             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 ));
16096 
16097           IF ((p_invoice_lines_rec.quantity_invoiced + l_qty_billed_sum) < 0) THEN
16098           -- reject with   INVALID QUANTITY
16099             IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
16100                  AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
16101                  p_invoice_lines_rec.invoice_line_id,
16102                  'INVALID QUANTITY',
16103                  p_default_last_updated_by,
16104                  p_default_last_update_login,
16105                  current_calling_sequence,
16106                  'Y',
16107                  'QUANTITY INVOICED',
16108                  p_invoice_lines_rec.quantity_invoiced + l_qty_billed_sum )
16109                  <> TRUE) THEN
16110               IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16111                 AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
16112                   'insert_rejections <-'||current_calling_sequence);
16113               END IF;
16114               Raise check_receipt_failure;
16115             END IF;
16116           END IF;
16117       END;
16118     END IF; -- cascade receipts flag = 'Y' --Step 1.A
16119 
16120   -------------------------------------------------------------------------
16121   -- Step 2 : Validate receipt info IF source is not
16122   -- EDI GATEWAY AND type = ITEM
16123   -- Retropricing: Match_option is populated as null for PPA Invoice lines,
16124   -- however the in v_check_line_po_info2, the value of match_option is determined and
16125   -- is assigned to p_invoice_lines_rec.match_option for further validation.
16126   -------------------------------------------------------------------------
16127   ELSIF (AP_IMPORT_INVOICES_PKG.g_source <> 'EDI GATEWAY') AND
16128   /* Commented for bug#9857975 End */
16129      (p_invoice_lines_rec.line_type_lookup_code IN ('ITEM', 'RETROITEM')) AND
16130      (p_invoice_lines_rec.match_option = 'R') THEN
16131 
16132     -- Case a : receipt_num AND id are NULL
16133     IF  (p_invoice_lines_rec.receipt_number is NULL ) AND
16134         (p_invoice_lines_rec.rcv_transaction_id is NULL) AND
16135         (p_invoice_lines_rec.po_line_location_id is not NULL) THEN
16136       debug_info := '(Check Receipt Info 2) Case a';
16137       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16138         AP_IMPORT_UTILITIES_PKG.Print(
16139           AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
16140       END IF;
16141       -- reject fOR INSUFFICIENT RECEIPT INFORMATION
16142       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
16143             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
16144             p_invoice_lines_rec.invoice_line_id,
16145             'INSUFFICIENT RECEIPT INFO',
16146             p_default_last_updated_by,
16147             p_default_last_update_login,
16148             current_calling_sequence)<> TRUE) THEN
16149          IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16150            AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
16151              'insert_rejections <-'||current_calling_sequence);
16152          END IF;
16153          Raise check_receipt_failure;
16154       END IF;
16155       p_temp_line_status := 'N';
16156 
16157       -- Case b : receipt num is not NULL, id is NULL
16158     ELSIF (p_invoice_lines_rec.receipt_number is not NULL) AND
16159            (p_invoice_lines_rec.rcv_transaction_id is NULL) THEN
16160        debug_info := '(Check Receipt Info 2) Case b';
16161        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16162          AP_IMPORT_UTILITIES_PKG.Print(
16163            AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
16164        END IF;
16165        BEGIN
16166         SELECT rcv_transaction_id
16167           INTO l_temp_rcv_txn_id
16168           FROM po_ap_receipt_match_v
16169          WHERE receipt_number = p_invoice_lines_rec.receipt_number
16170            AND po_line_location_id = p_invoice_lines_rec.po_line_location_id;
16171 
16172         Exception
16173           When no_data_found THEN
16174           --reject fOR INVALID RECEIPT INFORMATION
16175           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
16176                 AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
16177                 p_invoice_lines_rec.invoice_line_id,
16178                 'INVALID RECEIPT INFO',
16179                 p_default_last_updated_by,
16180                 p_default_last_update_login,
16181                 current_calling_sequence)<> TRUE) THEN
16182                 IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16183                     AP_IMPORT_UTILITIES_PKG.Print(
16184                       AP_IMPORT_INVOICES_PKG.g_debug_switch,
16185                         'insert_rejections <-'||current_calling_sequence);
16186                 END IF;
16187             Raise check_receipt_failure;
16188           END IF;
16189           p_temp_line_status := 'N';
16190         When too_many_rows THEN
16191             -- reject fOR INSUFFICIENT RECEIPT INFORMATION
16192             IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
16193                     AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
16194                     p_invoice_lines_rec.invoice_line_id,
16195                     'INSUFFICIENT RECEIPT INFO',
16196                     p_default_last_updated_by,
16197                     p_default_last_update_login,
16198                     current_calling_sequence)<> TRUE) THEN
16199               IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16200                 AP_IMPORT_UTILITIES_PKG.Print(
16201                   AP_IMPORT_INVOICES_PKG.g_debug_switch,
16202                     'insert_rejections <-'||current_calling_sequence);
16203               END IF;
16204               Raise check_receipt_failure;
16205             END IF;
16206             p_temp_line_status := 'N';
16207         END;
16208 
16209      -- Case c : receipt_num is NULL AND id is not NULL
16210     ELSIF (p_invoice_lines_rec.receipt_number is NULL) AND
16211        (p_invoice_lines_rec.rcv_transaction_id is not NULL) THEN
16212        debug_info := '(Check Receipt Info 2) Case c';
16213        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16214          AP_IMPORT_UTILITIES_PKG.Print(
16215            AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
16216        END IF;
16217 
16218        BEGIN
16219         SELECT rcv_transaction_id
16220           INTO l_temp_rcv_txn_id
16221           FROM po_ap_receipt_match_v
16222          WHERE rcv_transaction_id = p_invoice_lines_rec.rcv_transaction_id
16223            AND po_line_location_id = p_invoice_lines_rec.po_line_location_id;
16224 
16225        Exception
16226        WHEN Others THEN
16227          -- reject fOR INVALID RECEIPT INFORMATION
16228          IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
16229                 AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
16230                 p_invoice_lines_rec.invoice_line_id,
16231                 'INVALID RECEIPT INFO',
16232                 p_default_last_updated_by,
16233                 p_default_last_update_login,
16234                 current_calling_sequence)<> TRUE) THEN
16235                IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16236                    AP_IMPORT_UTILITIES_PKG.Print(
16237                    AP_IMPORT_INVOICES_PKG.g_debug_switch,
16238                   'insert_rejections <-'||current_calling_sequence);
16239                END IF;
16240            Raise check_receipt_failure;
16241          END IF;
16242          p_temp_line_status := 'N';
16243        END;
16244 
16245      -- Case d : receipt num is not NULL AND id is not NULL
16246     ELSIF (p_invoice_lines_rec.receipt_number is not NULL) AND
16247       (p_invoice_lines_rec.rcv_transaction_id is not NULL) THEN
16248         debug_info := '(Check Receipt Info 2) Case d';
16249         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16250           AP_IMPORT_UTILITIES_PKG.Print(
16251             AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
16252         END IF;
16253 
16254         BEGIN
16255             SELECT rcv_transaction_id
16256               INTO l_temp_rcv_txn_id
16257               FROM po_ap_receipt_match_v
16258              WHERE rcv_transaction_id = p_invoice_lines_rec.rcv_transaction_id
16259                AND receipt_number = p_invoice_lines_rec.receipt_number
16260                AND po_line_location_id = p_invoice_lines_rec.po_line_location_id;
16261 
16262         EXCEPTION
16263         When Others THEN
16264             -- reject fOR INCONSISTENT RECEIPT INFORMATION
16265             IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
16266                     AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
16267                     p_invoice_lines_rec.invoice_line_id,
16268                     'INCONSISTENT RECEIPT INFO',
16269                     p_default_last_updated_by,
16270                     p_default_last_update_login,
16271                     current_calling_sequence)<> TRUE) THEN
16272                 IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16273                    AP_IMPORT_UTILITIES_PKG.Print(
16274                    AP_IMPORT_INVOICES_PKG.g_debug_switch,
16275                    'insert_rejections <-'||current_calling_sequence);
16276                 END IF;
16277                 Raise check_receipt_failure;
16278             END IF;
16279         p_temp_line_status := 'N';
16280         END;
16281      END IF; -- Receipt number AND id are NULL
16282 
16283   -------------------------------------------------------------------------
16284   -- Step 3 : Validate receipt info IF type is not ITEM or RETROITEM AND
16285   -- some receipt info given
16286   -------------------------------------------------------------------------
16287   ELSIF (p_invoice_lines_rec.line_type_lookup_code IN
16288         ('TAX', 'MISCELLANEOUS','FREIGHT') AND
16289         (p_invoice_lines_rec.receipt_number IS NOT NULL OR
16290          p_invoice_lines_rec.rcv_transaction_id IS NOT NULL)) THEN
16291 
16292     -- Case a : receipt_num AND id are NULL
16293     -- ignore matching to receipt
16294 
16295     -- Case b : receipt num is not NULL, id is NULL
16296     IF (p_invoice_lines_rec.receipt_number is not NULL) AND
16297        (p_invoice_lines_rec.rcv_transaction_id is NULL) THEN
16298       debug_info := '(Check Receipt Info 3) Case b';
16299       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16300          AP_IMPORT_UTILITIES_PKG.Print(
16301          AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
16302       END IF;
16303       BEGIN
16304        SELECT rcv_transaction_id
16305          INTO l_temp_rcv_txn_id
16306          FROM po_ap_receipt_match_v
16307          WHERE receipt_number = p_invoice_lines_rec.receipt_number;
16308        Exception
16309        When no_data_found THEN
16310            --reject fOR INVALID RECEIPT INFORMATION
16311            IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
16312                 AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
16313                 p_invoice_lines_rec.invoice_line_id,
16314                 'INVALID RECEIPT INFO',
16315                 p_default_last_updated_by,
16316                 p_default_last_update_login,
16317                 current_calling_sequence)<> TRUE) THEN
16318                  IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16319                    AP_IMPORT_UTILITIES_PKG.Print(
16320                      AP_IMPORT_INVOICES_PKG.g_debug_switch,
16321                        'insert_rejections <-'||current_calling_sequence);
16322                  END IF;
16323              Raise check_receipt_failure;
16324            END IF;
16325            p_temp_line_status := 'N';
16326        When too_many_rows THEN
16327        -- reject fOR INSUFFICIENT RECEIPT INFORMATION
16328            IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
16329                 AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
16330                 p_invoice_lines_rec.invoice_line_id,
16331                 'INSUFFICIENT RECEIPT INFO',
16332                 p_default_last_updated_by,
16333                 p_default_last_update_login,
16334                 current_calling_sequence)<> TRUE) THEN
16335                  IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16336                    AP_IMPORT_UTILITIES_PKG.Print(
16337                      AP_IMPORT_INVOICES_PKG.g_debug_switch,
16338                      'insert_rejections <-'||current_calling_sequence);
16339                  END IF;
16340              Raise check_receipt_failure;
16341            END IF;
16342            p_temp_line_status := 'N';
16343        END;
16344 
16345     -- Case c : receipt_num is NULL AND id is not NULL
16346     ELSIF (p_invoice_lines_rec.receipt_number is NULL) AND
16347           (p_invoice_lines_rec.rcv_transaction_id is not NULL) THEN
16348       debug_info := '(Check Receipt Info 3) Case c';
16349       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16350         AP_IMPORT_UTILITIES_PKG.Print(
16351           AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
16352       END IF;
16353       BEGIN
16354        SELECT rcv_transaction_id
16355          INTO l_temp_rcv_txn_id
16356          FROM po_ap_receipt_match_v
16357         WHERE rcv_transaction_id = p_invoice_lines_rec.rcv_transaction_id;
16358        Exception
16359          When Others THEN
16360            -- reject fOR INVALID RECEIPT INFORMATION
16361            IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
16362             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
16363             p_invoice_lines_rec.invoice_line_id,
16364             'INVALID RECEIPT INFO',
16365             p_default_last_updated_by,
16366             p_default_last_update_login,
16367             current_calling_sequence)<> TRUE) THEN
16368                  IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16369                    AP_IMPORT_UTILITIES_PKG.Print(
16370                      AP_IMPORT_INVOICES_PKG.g_debug_switch,
16371                        'insert_rejections <-'||current_calling_sequence);
16372                  END IF;
16373              Raise check_receipt_failure;
16374            END IF;
16375            p_temp_line_status := 'N';
16376        END;
16377 
16378     -- Case d : receipt num is not NULL AND id is not NULL
16379     ELSIF (p_invoice_lines_rec.receipt_number is not NULL) AND
16380       (p_invoice_lines_rec.rcv_transaction_id is not NULL) THEN
16381       debug_info := '(Check Receipt Info 3) Case d';
16382       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16383          AP_IMPORT_UTILITIES_PKG.Print(
16384            AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
16385       END IF;
16386       BEGIN
16387        SELECT rcv_transaction_id
16388          INTO l_temp_rcv_txn_id
16389          FROM po_ap_receipt_match_v
16390         WHERE rcv_transaction_id = p_invoice_lines_rec.rcv_transaction_id
16391           AND receipt_number = p_invoice_lines_rec.receipt_number;
16392        Exception
16393          When Others THEN
16394              -- reject for inconsistent receipt information
16395              IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
16396                     AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
16397                     p_invoice_lines_rec.invoice_line_id,
16398                     'INCONSISTENT RECEIPT INFO',
16399                     p_default_last_updated_by,
16400                     p_default_last_update_login,
16401                     current_calling_sequence)<> TRUE) THEN
16402                  IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16403                    AP_IMPORT_UTILITIES_PKG.Print(
16404                      AP_IMPORT_INVOICES_PKG.g_debug_switch,
16405                        'insert_rejections <-'||current_calling_sequence);
16406                  END IF;
16407                  Raise check_receipt_failure;
16408              END IF;
16409              p_temp_line_status := 'N';
16410                END;
16411             END IF; -- receipt number AND id are NULL.
16412   END IF; -- Source, line type AND match option (Step 1)
16413 
16414   -- copy l_temp_rcv_txn_id back to rcv_transaction id IF not NULL
16415   p_invoice_lines_rec.rcv_transaction_id :=
16416         nvl(l_temp_rcv_txn_id, p_invoice_lines_rec.rcv_transaction_id);
16417 
16418 	-- Getting the value of rcv_shipment_line_id -- Bug 7344899
16419 
16420    IF (p_invoice_lines_rec.rcv_transaction_id is not NULL)  THEN
16421         debug_info := '(Get the value of rcv_shipment_line_id) ';
16422       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16423          AP_IMPORT_UTILITIES_PKG.Print(
16424          AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
16425       END IF;
16426       BEGIN
16427        SELECT rcv_shipment_line_id
16428        INTO   l_temp_ship_line_id
16429        FROM po_ap_receipt_match_v
16430 	   WHERE rcv_transaction_id = p_invoice_lines_rec.rcv_transaction_id;
16431        Exception
16432        When no_data_found THEN
16433            --reject fOR INVALID RECEIPT INFORMATION
16434            IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
16435                 AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
16436                 p_invoice_lines_rec.invoice_line_id,
16437                 'INVALID RECEIPT INFO',
16438                 p_default_last_updated_by,
16439                 p_default_last_update_login,
16440                 current_calling_sequence)<> TRUE) THEN
16441                  IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16442                    AP_IMPORT_UTILITIES_PKG.Print(
16443                      AP_IMPORT_INVOICES_PKG.g_debug_switch,
16444                        'insert_rejections <-'||current_calling_sequence);
16445                  END IF;
16446              Raise check_receipt_failure;
16447            END IF;
16448            p_temp_line_status := 'N';
16449        When too_many_rows THEN
16450        -- reject fOR INSUFFICIENT RECEIPT INFORMATION
16451            IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
16452                 AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
16453                 p_invoice_lines_rec.invoice_line_id,
16454                 'INSUFFICIENT RECEIPT INFO',
16455                 p_default_last_updated_by,
16456                 p_default_last_update_login,
16457                 current_calling_sequence)<> TRUE) THEN
16458                  IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16459                    AP_IMPORT_UTILITIES_PKG.Print(
16460                      AP_IMPORT_INVOICES_PKG.g_debug_switch,
16461                      'insert_rejections <-'||current_calling_sequence);
16462                  END IF;
16463              Raise check_receipt_failure;
16464            END IF;
16465            p_temp_line_status := 'N';
16466 
16467        END;
16468        END IF;
16469 	   --copy l_temp_ship_line_id back to rcv_shipment_line_id  IF not NULL
16470 
16471 	   p_invoice_lines_rec.rcv_shipment_line_id := l_temp_ship_line_id ; --Bug 7344899
16472 
16473 
16474   ---------------------------------------------------------------------------
16475   -- Step 4:  Validate the final match flag <> 'Y'
16476   ---------------------------------------------------------------------------
16477   debug_info := '(check receipt info 4) : Final Match flag';
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, debug_info);
16481   END IF;
16482 
16483   IF (p_invoice_lines_rec.match_option = 'R') AND
16484      (nvl(p_invoice_lines_rec.final_match_flag,'N') = 'Y' ) THEN
16485     -- reject fOR INVALID FINAL MATCH FLAG
16486     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
16487         AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
16488         p_invoice_lines_rec.invoice_line_id,
16489         'INVALID FINAL MATCH FLAG',
16490         p_default_last_updated_by,
16491         p_default_last_update_login,
16492         current_calling_sequence)<> TRUE) THEN
16493       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16494         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
16495           'insert_rejections <-'||current_calling_sequence);
16496       END IF;
16497       Raise check_receipt_failure;
16498     END IF;
16499     p_temp_line_status := 'N';
16500   END IF;
16501 
16502   ----------------------------------------------------------------------------
16503   -- Step 5 : Validate the UOM  IF rcv_txn_id is not NULL
16504   ----------------------------------------------------------------------------
16505   IF (p_invoice_lines_rec.rcv_transaction_id IS NOT NULL)  AND
16506      (p_invoice_lines_rec.match_option = 'R') AND
16507      (p_invoice_lines_rec.unit_of_meas_lookup_code IS NOT NULL) THEN
16508 
16509     debug_info := '(check receipt info 5) : Validate UOM';
16510     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16511       AP_IMPORT_UTILITIES_PKG.Print(
16512         AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
16513     END IF;
16514     BEGIN
16515       SELECT 'Y'
16516         INTO l_temp_value
16517         FROM po_ap_receipt_match_v
16518        WHERE rcv_transaction_id = p_invoice_lines_rec.rcv_transaction_id
16519          AND receipt_uom_lookup_code =
16520              p_invoice_lines_rec.unit_of_meas_lookup_code;
16521     EXCEPTION
16522       WHEN OTHERS THEN
16523         -- reject for uom does not match receipt
16524         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
16525             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
16526             p_invoice_lines_rec.invoice_line_id,
16527             'UOM DOES NOT MATCH RECPT',
16528             p_default_last_updated_by,
16529             p_default_last_update_login,
16530             current_calling_sequence)<> TRUE) THEN
16531           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16532             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
16533               'insert_rejections <-'||current_calling_sequence);
16534           END IF;
16535       Raise check_receipt_failure;
16536         END IF;
16537         p_temp_line_status := 'N';
16538     END;
16539   END IF;
16540 
16541   ----------------------------------------------------------------------------
16542   -- Step 6 : Validate IF prorate is checked AND receipt info provided
16543   -- for non Item.
16544   -- Retropricing: PPA Invoice Line will not have TAX and there the code
16545   -- below will not get executed.
16546   ----------------------------------------------------------------------------
16547   debug_info := '(check receipt info 6) : Check prorate flag';
16548   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16549     AP_IMPORT_UTILITIES_PKG.Print(
16550       AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
16551   END IF;
16552 
16553   IF (p_invoice_lines_rec.line_type_lookup_code IN
16554      ('MISCELLANEOUS', 'FREIGHT','TAX') AND
16555       NVL(p_invoice_lines_rec.prorate_across_flag,'N') = 'Y' AND
16556       (p_invoice_lines_rec.receipt_number is not NULL OR
16557       p_invoice_lines_rec.rcv_transaction_id is not NULL) ) THEN
16558 
16559     -- reject for inconsistent allocation info
16560     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
16561             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
16562             p_invoice_lines_rec.invoice_line_id,
16563             'INCONSISTENT ALLOC INFO',
16564             p_default_last_updated_by,
16565             p_default_last_update_login,
16566             current_calling_sequence)<> TRUE) THEN
16567       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16568         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
16569           'insert_rejections <-'||current_calling_sequence);
16570       END IF;
16571       Raise check_receipt_failure;
16572     END IF;
16573     p_temp_line_status := 'N';
16574   END IF;
16575 
16576   ---------------------------------------------------------------------------
16577   -- step 7 : Validate quantity billed does not become less than zero ,
16578   --          IF rcv_transaction-id is not NULL AND is valid.
16579   -- Retropricing: Quantity Billed is not affected by Retropricing. This
16580   -- validation should be bypassed for PPA's.
16581   ---------------------------------------------------------------------------
16582   IF AP_IMPORT_INVOICES_PKG.g_source <> 'PPA' THEN
16583       IF (p_invoice_lines_rec.rcv_transaction_id is not NULL) AND
16584          (p_temp_line_status <> 'N') AND
16585          (p_invoice_lines_rec.match_option = 'R') AND
16586          (p_invoice_lines_rec.quantity_invoiced is not NULL) THEN
16587         debug_info := '(Check receipt info 7) : check Quantity billed';
16588         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16589           AP_IMPORT_UTILITIES_PKG.Print(
16590             AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
16591         END IF;
16592 
16593         BEGIN
16594           SELECT nvl(quantity_billed,0)
16595             INTO l_qty_billed
16596             FROM rcv_transactions
16597            WHERE transaction_id = p_invoice_lines_rec.rcv_transaction_id;
16598 
16599           IF (l_qty_billed +  p_invoice_lines_rec.quantity_invoiced ) < 0 THEN
16600             IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
16601                AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
16602                p_invoice_lines_rec.invoice_line_id,
16603                'INVALID QUANTITY',
16604                p_default_last_updated_by,
16605                p_default_last_update_login,
16606                current_calling_sequence,
16607                'Y',
16608                'QUANTITY INVOICED',
16609                l_qty_billed + p_invoice_lines_rec.quantity_invoiced )<> TRUE) THEN
16610               IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16611                 AP_IMPORT_UTILITIES_PKG.Print(
16612                   AP_IMPORT_INVOICES_PKG.g_debug_switch,
16613                     'insert_rejections <-'||current_calling_sequence);
16614               END IF;
16615               Raise check_receipt_failure;
16616             END IF;
16617             p_temp_line_status := 'N';
16618           END IF;
16619         END;
16620       END IF; -- rcv_txn_id not NULL
16621   END IF; --source <> PPA
16622   -- p_temp_line_status has the return value
16623   RETURN (TRUE);
16624 
16625 EXCEPTION
16626   When OTHERS THEN
16627     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16628       AP_IMPORT_UTILITIES_PKG.Print(
16629         AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
16630     END IF;
16631 
16632     IF (SQLCODE < 0) THEN
16633       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16634         AP_IMPORT_UTILITIES_PKG.Print(
16635           AP_IMPORT_INVOICES_PKG.g_debug_switch, SQLERRM);
16636       END IF;
16637     END IF;
16638     Return(FALSE);
16639 
16640 END v_check_receipt_info;
16641 
16642 
16643 
16644 -----------------------------------------------------------------------------
16645 -- This function is used to validate line level accounting date information.
16646 --
16647 FUNCTION v_check_line_accounting_date (
16648    p_invoice_rec        IN
16649     AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
16650    p_invoice_lines_rec  IN OUT NOCOPY AP_IMPORT_INVOICES_PKG.r_line_info_rec,
16651    p_gl_date_from_get_info        IN            DATE,
16652    p_gl_date_from_receipt_flag    IN            VARCHAR2,
16653    p_set_of_books_id              IN            NUMBER,
16654    p_purch_encumbrance_flag       IN            VARCHAR2,
16655    p_default_last_updated_by      IN            NUMBER,
16656    p_default_last_update_login    IN            NUMBER,
16657    p_current_invoice_status       IN OUT NOCOPY VARCHAR2,
16658    p_calling_sequence             IN            VARCHAR2) RETURN BOOLEAN
16659 IS
16660    check_accounting_date_failure  EXCEPTION;
16661    l_period_name                  VARCHAR2(15);
16662    l_dummy                          VARCHAR2(100);
16663    l_key                            VARCHAR2(1000);
16664    l_numof_values                   NUMBER;
16665    l_valueOut                   fnd_plsql_cache.generic_cache_value_type;
16666    l_values                     fnd_plsql_cache.generic_cache_values_type;
16667    l_ret_code                      VARCHAR2(1);
16668    l_exception                     VARCHAR2(10);
16669    l_current_invoice_status         VARCHAR2(1) := 'Y';
16670    l_accounting_date             DATE := p_invoice_lines_rec.accounting_date;
16671    current_calling_sequence       VARCHAR2(2000);
16672    debug_info                    VARCHAR2(500);
16673 
16674 BEGIN
16675   -- Update the calling sequence
16676   --
16677   current_calling_sequence :=
16678      'AP_IMPORT_VALIDATION_PKG.v_check_line_accounting_date<-'
16679      ||P_calling_sequence;
16680 
16681   --------------------------------------------------------------------------
16682   -- IF the accounting date is not specified in the Lines Interface use
16683   -- gl_date_from_invoice, IF null, THEN use gl_date_from_get_info as the
16684   -- acct date. Logic for deriving p_gl_date_from_get_info : Use GL Date
16685   -- from  Report input params
16686   -- IF null ,THEN
16687   --   IF p_gl_date_from_receipt_flag = 'I','N' THEN Invoice Date is
16688   --   used as the Gl Date
16689   --     IF invoice date is null use the sysdate as the invoice date/ GL_Date
16690   --   ElsIF p_gl_date_from_receipt_flag IN 'S','Y'   ,THEN use sydate as
16691   -- the GL Date.
16692   ---------------------------------------------------------------------------
16693 
16694   IF (l_accounting_date IS NULL) AND (p_invoice_rec.gl_date IS NOT NULL) THEN
16695     debug_info := '(Check_line_accounting_date 1) Default '
16696                   ||'line_accounting_date from Invoice gl_date';
16697     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16698       AP_IMPORT_UTILITIES_PKG.Print(
16699         AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
16700     END IF;
16701 
16702     l_accounting_date := p_invoice_rec.gl_date;
16703 
16704   ELSIF (l_accounting_date IS NULL) AND (p_gl_date_from_get_info IS NOT NULL)
16705     THEN
16706     debug_info := '(v_check_line_accounting_date 1) GL Date is Null in '
16707                   ||'Interface, Use gl_date from Get Info';
16708     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16709       AP_IMPORT_UTILITIES_PKG.Print(
16710         AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
16711     END IF;
16712     l_accounting_date := p_gl_date_from_get_info;
16713   END IF;
16714 
16715   IF ((l_accounting_date IS NULL) AND
16716       (p_gl_date_from_receipt_flag IN ('I','N')) AND
16717       (p_invoice_rec.invoice_date is NOT NULL)) THEN
16718     debug_info := '(v_check_line_accounting_date 2) GL Date is Invoice Date';
16719     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16720       AP_IMPORT_UTILITIES_PKG.Print(
16721         AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
16722     END IF;
16723 
16724     /* l_accounting_date := p_invoice_rec.invoice_date; commented for bug#12356854 */
16725     /* Added for bug#12356854 Start */
16726     ap_utilities_pkg.get_gl_date_and_period_1
16727     ( p_invoice_rec.invoice_date,
16728       NULL,
16729       l_period_name,
16730       l_accounting_date,
16731       NULL,
16732       p_invoice_rec.org_id
16733     );
16734     /* Added for bug#12356854 End */
16735   ELSIF((l_accounting_date IS NULL) AND
16736         (p_gl_date_from_receipt_flag IN ('I','N')) AND
16737         (p_invoice_rec.invoice_date is NULL)) THEN
16738     debug_info := '(v_check_line_accounting_date 2) GL Date is sysdate';
16739     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16740       AP_IMPORT_UTILITIES_PKG.Print(
16741         AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
16742     END IF;
16743     l_accounting_date := AP_IMPORT_INVOICES_PKG.g_inv_sysdate;
16744   END IF;
16745 
16746   ------------------------------------------------------------------------
16747   -- Reject IF account_date is not in open period
16748   ------------------------------------------------------------------------
16749   debug_info := '(v_check_line_accounting_date 3) Check IF gl date is not '
16750                 ||'in open period';
16751   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16752     AP_IMPORT_UTILITIES_PKG.Print(
16753       AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
16754   END IF;
16755 
16756   -- bug 2496185 by isartawi .. cache the code_combination_ids
16757   l_key := TO_CHAR(p_set_of_books_id)||' '||
16758            TO_CHAR(NVL(l_accounting_date,
16759                        AP_IMPORT_INVOICES_PKG.g_inv_sysdate),'dd-mm-yyyy');
16760 
16761   fnd_plsql_cache.generic_1tom_get_values(
16762               AP_IMPORT_INVOICES_PKG.lg_many_controller,
16763               AP_IMPORT_INVOICES_PKG.lg_generic_storage,
16764               l_key,
16765               l_numof_values,
16766               l_values,
16767               l_ret_code);
16768 
16769   IF l_ret_code = '1' THEN --  means l_key found in cache
16770     l_period_name := l_values(1).varchar2_1;
16771     l_exception   := l_values(1).varchar2_2;
16772     IF l_exception = 'TRUE' THEN
16773       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
16774           AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
16775           p_invoice_lines_rec.invoice_line_id,
16776           'ACCT DATE NOT IN OPEN PD',
16777           p_default_last_updated_by,
16778           p_default_last_update_login,
16779           current_calling_sequence) <> TRUE) THEN
16780         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16781           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
16782             'insert_rejections<-'||current_calling_sequence);
16783         END IF;
16784         RAISE check_accounting_date_failure;
16785       END IF;
16786 
16787         --Bug3302807 Setting the l_current_invoice_status to 'N' if rejected
16788          l_current_invoice_status := 'N';
16789 
16790    END IF; -- l_exception TRUE
16791   ELSE  -- IF l_key not found in cache(l_ret_code other than 1) .. cache it
16792     BEGIN
16793       SELECT period_name
16794         INTO l_period_name
16795         FROM gl_period_statuses
16796        WHERE application_id = 200
16797          AND set_of_books_id = p_set_of_books_id
16798          AND trunc(nvl(l_accounting_date,AP_IMPORT_INVOICES_PKG.g_inv_sysdate))
16799              between start_date and END_date
16800          AND closing_status in ('O', 'F')
16801          AND NVL(adjustment_period_flag, 'N') = 'N';
16802 
16803       l_exception           := 'FALSE';
16804       l_valueOut.varchar2_1 := l_period_name;
16805       l_valueOut.varchar2_2 := l_exception;
16806       l_values(1)           := l_valueOut;
16807       l_numof_values        := 1;
16808 
16809       fnd_plsql_cache.generic_1tom_put_values(
16810                   AP_IMPORT_INVOICES_PKG.lg_many_controller,
16811                   AP_IMPORT_INVOICES_PKG.lg_generic_storage,
16812                   l_key,
16813                   l_numof_values,
16814                   l_values);
16815     EXCEPTION
16816       WHEN NO_DATA_FOUND THEN
16817         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16818           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
16819             'Accounting date is not in open period');
16820         END IF;
16821 
16822         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
16823             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
16824              p_invoice_lines_rec.invoice_line_id,
16825             'ACCT DATE NOT IN OPEN PD',
16826             p_default_last_updated_by,
16827             p_default_last_update_login,
16828             current_calling_sequence) <> TRUE) THEN
16829           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16830             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
16831               'insert_rejections<-'||current_calling_sequence);
16832           END IF;
16833           RAISE check_accounting_date_failure;
16834         END IF;
16835         l_current_invoice_status := 'N';
16836         l_exception              := 'TRUE';
16837         l_valueOut.varchar2_1    := NULL;
16838         l_valueOut.varchar2_2    := l_exception;
16839         l_values(1)              := l_valueOut;
16840         l_numof_values           := 1;
16841 
16842         fnd_plsql_cache.generic_1tom_put_values(
16843                     AP_IMPORT_INVOICES_PKG.lg_many_controller,
16844                     AP_IMPORT_INVOICES_PKG.lg_generic_storage,
16845                     l_key,
16846                     l_numof_values,
16847                     l_values);
16848     END;
16849   END IF; -- IF ret_code is 1
16850   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16851     AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
16852         '------------------> l_period_name = '|| l_period_name
16853     ||'l_accounting_date = '||to_char(l_accounting_date));
16854   END IF;
16855 
16856   --------------------------------------------------------------------------
16857   -- Reject IF the year of gl date is beyond encumbrance year
16858   -- only IF purch_encumbrance_flag = 'Y'
16859   --------------------------------------------------------------------------
16860   IF (p_purch_encumbrance_flag = 'Y') THEN
16861     BEGIN
16862       debug_info := '(v_check_line_accounting_date 4) Reject IF the year of '
16863                     ||'gl date is beyond encumbrance year';
16864       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16865         AP_IMPORT_UTILITIES_PKG.Print(
16866           AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
16867       END IF;
16868 
16869       SELECT 'The period is NOT beyond latest encumbrance year'
16870         INTO l_DUMMY
16871         FROM GL_PERIOD_STATUSES gps1,
16872              GL_SETS_OF_BOOKS gsob
16873        WHERE gps1.period_year <= gsob.latest_encumbrance_year
16874          AND gsob.SET_OF_BOOKS_ID = p_set_of_books_id
16875          AND gps1.APPLICATION_ID = 200
16876          AND gps1.SET_OF_BOOKS_ID = gsob.SET_OF_BOOKS_ID
16877          AND trunc(nvl(l_accounting_date,AP_IMPORT_INVOICES_PKG.g_inv_sysdate))
16878              BETWEEN gps1.START_DATE AND gps1.END_DATE
16879          AND gps1.closing_status in ('O', 'F')
16880          AND NVL(gps1.adjustment_period_flag, 'N') = 'N';
16881 
16882     EXCEPTION
16883       WHEN NO_DATA_FOUND THEN
16884         --
16885         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16886           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
16887             'Accounting date is beyond encumbrance year');
16888         END IF;
16889 
16890         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
16891            AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
16892             p_invoice_lines_rec.invoice_line_id,
16893             'ACCT DATE BEYOND ENC YEAR',
16894             p_default_last_updated_by,
16895             p_default_last_update_login,
16896             current_calling_sequence) <> TRUE) THEN
16897           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16898             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
16899             'insert_rejections<-'||current_calling_sequence);
16900           END IF;
16901           RAISE check_accounting_date_failure;
16902         END IF;
16903         --
16904         l_current_invoice_status := 'N';
16905     END;
16906   END IF; -- purch encumbrance flag is Y
16907 
16908   IF (l_current_invoice_status = 'Y') THEN
16909     IF (l_accounting_date is not NULL) THEN
16910       p_invoice_lines_rec.accounting_date := l_accounting_date;
16911     END IF;
16912     IF (l_period_name is not NULL) THEN
16913       p_invoice_lines_rec.period_name := l_period_name;
16914     END IF;
16915   END IF;
16916   -- Return value
16917   p_current_invoice_status := l_current_invoice_status;
16918 
16919   RETURN (TRUE);
16920 EXCEPTION
16921   WHEN OTHERS THEN
16922     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16923       AP_IMPORT_UTILITIES_PKG.Print(
16924         AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
16925     END IF;
16926 
16927     IF (SQLCODE < 0) THEN
16928       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16929         AP_IMPORT_UTILITIES_PKG.Print(
16930           AP_IMPORT_INVOICES_PKG.g_debug_switch, SQLERRM);
16931       END IF;
16932     END IF;
16933     RETURN(FALSE);
16934 
16935 END v_check_line_accounting_date;
16936 
16937 ------------------------------------------------------------------------------
16938 -- This function is used to validate line level project information.
16939 -- Retropricing:
16940 -- For the validation of PPA Invoice Lines , we will not be calling the
16941 -- PA Flexbuilder. We only verify if the Project level infomation
16942 -- is correct. Also we will bypass the rejection -- 'INCONSISTENT DIST INFO
16943 -- when both po and pa information co-exist.
16944 ------------------------------------------------------------------------------
16945 
16946 FUNCTION v_check_line_project_info (
16947    p_invoice_rec         IN AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
16948    p_invoice_lines_rec   IN OUT NOCOPY AP_IMPORT_INVOICES_PKG.r_line_info_rec,
16949    p_accounting_date           IN            DATE,
16950    p_pa_installed              IN            VARCHAR2,
16951    p_employee_id               IN            NUMBER,
16952    p_base_currency_code        IN            VARCHAR2,
16953    p_set_of_books_id           IN            NUMBER,
16954    p_chart_of_accounts_id      IN            NUMBER,
16955    p_default_last_updated_by   IN            NUMBER,
16956    p_default_last_update_login IN            NUMBER,
16957    p_pa_built_account             OUT NOCOPY NUMBER,
16958    p_current_invoice_status    IN OUT NOCOPY VARCHAR2,
16959    p_calling_sequence          IN            VARCHAR2) RETURN BOOLEAN
16960 IS
16961 
16962 check_project_failure          EXCEPTION;
16963 l_current_invoice_status      VARCHAR2(1) := 'Y';
16964 l_error_found                  VARCHAR2(1) := 'N';
16965 l_pa_default_dist_ccid          NUMBER;
16966 l_pa_concatenated_segments    VARCHAR2(2000):='';
16967 l_dist_code_combination_id    NUMBER ;
16968 l_award_id                      NUMBER;
16969 l_unbuilt_flex                VARCHAR2(240):='';
16970 l_reason_unbuilt_flex         VARCHAR2(2000):='';
16971 current_calling_sequence      VARCHAR2(2000);
16972 debug_info                     VARCHAR2(500);
16973 l_key                         VARCHAR2(1000);
16974 l_numof_values                NUMBER;
16975 l_valueOut                    fnd_plsql_cache.generic_cache_value_type;
16976 l_values                      fnd_plsql_cache.generic_cache_values_type;
16977 l_ret_code                    VARCHAR2(1);
16978 l_validate_res                VARCHAR2(10);
16979 
16980 BEGIN
16981   -- Update the calling sequence
16982   --
16983   current_calling_sequence :=
16984     'AP_IMPORT_VALIDATION_PKG.v_check_line_project_info<-'
16985     ||P_calling_sequence;
16986 
16987   l_award_id := p_invoice_lines_rec.award_id ;
16988 
16989   debug_info := '(v_check_line_project_info Debug 1) p_invoice_lines_rec.project_id:'
16990         ||p_invoice_lines_rec.project_id||', '||
16991         'p_invoice_lines_rec.task_id:'
16992         ||p_invoice_lines_rec.task_id||', '||
16993         'p_invoice_lines_rec.expenditure_type:'
16994         ||p_invoice_lines_rec.expenditure_type||', '||
16995         'p_invoice_lines_rec.expenditure_item_date:'
16996         ||p_invoice_lines_rec.expenditure_item_date||', '||
16997         'p_invoice_lines_rec.expenditure_organization_id:'
16998         ||p_invoice_lines_rec.expenditure_organization_id||'.';
16999 
17000   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
17001         AP_IMPORT_UTILITIES_PKG.Print(
17002                 AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
17003   END IF;
17004 
17005  /*Bug#10356162 - Project_id Null check removed */
17006   IF (
17007   --p_invoice_lines_rec.project_id IS NOT NULL  AND
17008       AP_IMPORT_INVOICES_PKG.g_source <> 'PPA') THEN
17009 
17010     ---------------------------------------------------------------------
17011     -- Step 1 - Reject IF line has PA info and it is PO matched
17012     -- or contains a default account (conflict of account sources)
17013 
17014     ---------------------------------------------------------------------
17015     debug_info := '(v_check_line_project_info 1) Check IF line has PA Info'
17016                   ||' and other account info as well';
17017     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
17018       AP_IMPORT_UTILITIES_PKG.Print(
17019         AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
17020     END IF;
17021 
17022     IF ( p_invoice_lines_rec.po_number IS NOT NULL    OR
17023          p_invoice_lines_rec.po_header_id IS NOT NULL ) THEN
17024       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
17025         AP_IMPORT_UTILITIES_PKG.Print(
17026           AP_IMPORT_INVOICES_PKG.g_debug_switch,
17027             '(v_check_line_project_info 2) Line with additional account'
17028             ||' info:Reject');
17029       END IF;
17030 
17031 
17032       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
17033           AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
17034            p_invoice_lines_rec.invoice_line_id,
17035              'INCONSISTENT DIST INFO',
17036            p_default_last_updated_by,
17037            p_default_last_update_login,
17038            current_calling_sequence) <> TRUE) THEN
17039         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
17040           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
17041             'insert_rejections<-'||current_calling_sequence);
17042         END IF;
17043         RAISE check_project_failure;
17044       END IF;
17045 
17046       --
17047       l_current_invoice_status := 'N';
17048 
17049     END IF; -- po number or po header id are not null
17050 
17051     --------------------------------------------------------------
17052     -- Do nothing when none of the project info is provided
17053     -- Else Perform the PA/project validation.
17054     -- Refer bug 12904008
17055     --------------------------------------------------------------
17056     IF ((p_invoice_lines_rec.project_id IS NULL) AND
17057         (p_invoice_lines_rec.task_id IS NULL) AND
17058         (p_invoice_lines_rec.expenditure_type IS NULL) AND
17059         (p_invoice_lines_rec.expenditure_item_date IS NULL) AND
17060         (p_invoice_lines_rec.expenditure_organization_id IS NULL)) THEN
17061 
17062         --There is no project info. Do nothing.
17063         NULL;
17064     ELSE
17065         --------------------------------------------------------------
17066         -- Step 2
17067         -- Check for minimum info required for PA Flexbuild
17068         -- Else reject
17069         --------------------------------------------------------------
17070         IF (p_invoice_lines_rec.expenditure_item_date is NULL) then
17071               IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
17072                 AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
17073                 '(v_check_line_project_info 2) Get expenditure item date');
17074               END IF;
17075 
17076                 p_invoice_lines_rec.expenditure_item_date :=
17077                   AP_INVOICES_PKG.get_expenditure_item_date(
17078                     p_invoice_rec.invoice_id,
17079                     p_invoice_rec.invoice_date,
17080                     p_accounting_date,
17081                     NULL,
17082                     NULL,
17083                     l_error_found);
17084 
17085               IF (l_error_found = 'Y') then
17086                 RAISE check_project_failure;
17087               END IF;
17088         END IF; -- Expenditure item date is null
17089 
17090         IF ((p_invoice_lines_rec.project_id IS NULL) OR
17091                 (p_invoice_lines_rec.task_id IS NULL) OR
17092                 (p_invoice_lines_rec.expenditure_type IS NULL) OR
17093                 (p_invoice_lines_rec.expenditure_item_date IS NULL) OR
17094                 (p_invoice_lines_rec.expenditure_organization_id IS NULL)) THEN
17095               IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
17096                 AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
17097                 '(v_check_line_project_info 2) Insufficient PA Info:Reject');
17098               END IF;
17099 
17100               IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
17101                     AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
17102                      p_invoice_lines_rec.invoice_line_id,
17103                     'INSUFFICIENT PA INFO',
17104                      p_default_last_updated_by,
17105                      p_default_last_update_login,
17106                      current_calling_sequence) <> TRUE) THEN
17107                 IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
17108                       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
17109                     'insert_rejections<-'||current_calling_sequence);
17110                 END IF;
17111                 RAISE check_project_failure;
17112               END IF;
17113               --
17114               l_current_invoice_status := 'N';
17115         END IF;
17116     END IF;
17117 
17118     -- We need to call the GMS API only when the current invoice status
17119     -- is 'Y' and l_award_id is not null
17120     -- Else ignore the call.
17121     IF ( l_current_invoice_status = 'Y' AND p_invoice_lines_rec.project_id is not null ) THEN
17122       debug_info := 'AWARD_ID_REQUEST :(v_check_line_award_info 1) Check  '
17123                     ||'GMS Info ';
17124       IF GMS_AP_API.gms_debug_switch(AP_IMPORT_INVOICES_PKG.g_debug_switch) THEN
17125         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
17126           AP_IMPORT_UTILITIES_PKG.Print(
17127             AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
17128         END IF;
17129       END IF;
17130 
17131         /*Bug#10235692 - passing 'APTXNIMP' to p_calling_sequence */
17132       IF    ( GMS_AP_API.v_check_line_award_info (
17133                   p_invoice_lines_rec.invoice_line_id,
17134                   p_invoice_lines_rec.amount,
17135                   p_invoice_lines_rec.base_amount,
17136                   p_invoice_lines_rec.dist_code_concatenated,
17137                   p_invoice_lines_rec.dist_code_combination_id,
17138                   p_invoice_rec.po_number,
17139                   p_invoice_lines_rec.po_number,
17140                   p_invoice_lines_rec.po_header_id,
17141                   p_invoice_lines_rec.distribution_set_id,
17142                   p_invoice_lines_rec.distribution_set_name,
17143                   p_set_of_books_id,
17144                   p_base_currency_code,
17145                   p_invoice_rec.invoice_currency_code,
17146                   p_invoice_rec.exchange_rate,
17147                   p_invoice_rec.exchange_rate_type,
17148                   p_invoice_rec.exchange_date,
17149                   p_invoice_lines_rec.project_id,
17150                   p_invoice_lines_rec.task_id,
17151                   p_invoice_lines_rec.expenditure_type,
17152                   p_invoice_lines_rec.expenditure_item_date,
17153                   p_invoice_lines_rec.expenditure_organization_id,
17154                   NULL, -- project_accounting_context
17155                   p_invoice_lines_rec.pa_addition_flag,
17156                   p_invoice_lines_rec.pa_quantity,
17157                   p_employee_id,
17158                   p_invoice_rec.vendor_id,
17159                   p_chart_of_accounts_id,
17160                   p_pa_installed,
17161                   p_invoice_lines_rec.prorate_across_flag,
17162                   p_invoice_lines_rec.attribute_category,
17163                   p_invoice_lines_rec.attribute1,
17164                   p_invoice_lines_rec.attribute2,
17165                   p_invoice_lines_rec.attribute3,
17166                   p_invoice_lines_rec.attribute4,
17167                   p_invoice_lines_rec.attribute5,
17168                   p_invoice_lines_rec.attribute6,
17169                   p_invoice_lines_rec.attribute7,
17170                   p_invoice_lines_rec.attribute8,
17171                   p_invoice_lines_rec.attribute9,
17172                   p_invoice_lines_rec.attribute10,
17173                   p_invoice_lines_rec.attribute11,
17174                   p_invoice_lines_rec.attribute12,
17175                   p_invoice_lines_rec.attribute13,
17176                   p_invoice_lines_rec.attribute14,
17177                   p_invoice_lines_rec.attribute15,
17178                   p_invoice_rec.attribute_category,
17179                   p_invoice_rec.attribute1,
17180                   p_invoice_rec.attribute2,
17181                   p_invoice_rec.attribute3,
17182                   p_invoice_rec.attribute4,
17183                   p_invoice_rec.attribute5,
17184                   p_invoice_rec.attribute6,
17185                   p_invoice_rec.attribute7,
17186                   p_invoice_rec.attribute8,
17187                   p_invoice_rec.attribute9,
17188                   p_invoice_rec.attribute10,
17189                   p_invoice_rec.attribute11,
17190                   p_invoice_rec.attribute12,
17191                   p_invoice_rec.attribute13,
17192                   p_invoice_rec.attribute14,
17193                   p_invoice_rec.attribute15,
17194                   p_invoice_lines_rec.partial_segments,
17195                   p_default_last_updated_by,
17196                   p_default_last_update_login,
17197                   'APTXNIMP',
17198                   l_award_id,
17199                   'AWARD_SET_ID_REQUEST' ) <> TRUE ) THEN
17200         IF GMS_AP_API.gms_debug_switch(AP_IMPORT_INVOICES_PKG.g_debug_switch)
17201           THEN
17202           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
17203             '(v_check_line_project_info 3) Invalid GMS Info:Reject');
17204         END IF;
17205 
17206         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
17207                 AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
17208                 p_invoice_lines_rec.invoice_line_id,
17209                 'INSUFFICIENT GMS INFO',
17210                 p_default_last_updated_by,
17211                 p_default_last_update_login,
17212                 current_calling_sequence) <> TRUE) THEN
17213           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
17214             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
17215               'insert_rejections<-'||current_calling_sequence);
17216           END IF;
17217           RAISE check_project_failure;
17218         END IF;
17219         --
17220         l_current_invoice_status := 'N';
17221       END IF;
17222     END IF; -- l_current_invoice_status = 'Y' and l_award_id is not null
17223 
17224     ------------------------------------------------------------------------
17225     -- Step 3
17226     -- IF invoice status is Y THEN Flexbuild
17227     ------------------------------------------------------------------------
17228     IF (l_current_invoice_status = 'Y') THEN
17229       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
17230         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
17231           '(v_check_line_project_info 4) Call pa_flexbuild');
17232       END IF;
17233       IF (AP_IMPORT_INVOICES_PKG.g_source <> 'PPA')  THEN
17234           IF (AP_IMPORT_UTILITIES_PKG.pa_flexbuild(
17235                  p_invoice_rec,                      -- IN
17236                  p_invoice_lines_rec,                -- IN OUT NOCOPY
17237                  p_accounting_date,                      -- IN
17238                  p_pa_installed,                     -- IN
17239                  p_employee_id,                     -- IN
17240                  p_base_currency_code,                -- IN
17241                  p_chart_of_accounts_id,             -- IN
17242                  p_default_last_updated_by,          -- IN
17243                  p_default_last_update_login,        -- IN
17244                  p_pa_default_dist_ccid     => l_pa_default_dist_ccid,    -- OUT NOCOPY
17245                  p_pa_concatenated_segments => l_pa_concatenated_segments,-- OUT NOCOPY
17246                  p_current_invoice_status   => l_current_invoice_status,  -- OUT NOCOPY
17247                  p_calling_sequence         => current_calling_sequence) <> TRUE) THEN
17248 
17249 
17250             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
17251               AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
17252                 'insert_rejections<-'||current_calling_sequence);
17253             END IF;
17254             RAISE check_project_failure;
17255           END IF; -- pa flexbuild
17256       END IF; -- source <> PPA
17257 
17258       -- Added following IF condition so that GMS API will be
17259       -- called only when award_id is not null
17260       IF (l_current_invoice_status = 'Y' AND l_award_id is not null) THEN
17261         debug_info := 'AWARD_ID_REMOVE :(v_check_line_award_info 1) Check  GMS Info ';
17262         IF GMS_AP_API.gms_debug_switch(AP_IMPORT_INVOICES_PKG.g_debug_switch)
17263           THEN
17264           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
17265             AP_IMPORT_UTILITIES_PKG.Print(
17266               AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
17267           END IF;
17268         END IF;
17269 
17270         /*Bug#10235692 - passing 'APTXNIMP' to p_calling_sequence */
17271         IF GMS_AP_API.v_check_line_award_info (
17272                     p_invoice_lines_rec.invoice_line_id    ,
17273                     p_invoice_lines_rec.amount,
17274                     p_invoice_lines_rec.base_amount,
17275                     p_invoice_lines_rec.dist_code_concatenated,
17276                     p_invoice_lines_rec.dist_code_combination_id,
17277                     p_invoice_rec.po_number,
17278                     p_invoice_lines_rec.po_number,
17279                     p_invoice_lines_rec.po_header_id,
17280                     p_invoice_lines_rec.distribution_set_id,
17281                     p_invoice_lines_rec.distribution_set_name,
17282                     p_set_of_books_id,
17283                     p_base_currency_code,
17284                     p_invoice_rec.invoice_currency_code,
17285                     p_invoice_rec.exchange_rate,
17286                     p_invoice_rec.exchange_rate_type,
17287                     p_invoice_rec.exchange_date,
17288                     p_invoice_lines_rec.project_id,
17289                     p_invoice_lines_rec.task_id,
17290                     p_invoice_lines_rec.expenditure_type,
17291                     p_invoice_lines_rec.expenditure_item_date,
17292                     p_invoice_lines_rec.expenditure_organization_id,
17293                     NULL, --p_project_accounting_context
17294                     p_invoice_lines_rec.pa_addition_flag,
17295                     p_invoice_lines_rec.pa_quantity,
17296                     p_employee_id,
17297                     p_invoice_rec.vendor_id,
17298                     p_chart_of_accounts_id,
17299                     p_pa_installed,
17300                     p_invoice_lines_rec.prorate_across_flag,
17301                     p_invoice_lines_rec.attribute_category,
17302                     p_invoice_lines_rec.attribute1,
17303                     p_invoice_lines_rec.attribute2,
17304                     p_invoice_lines_rec.attribute3,
17305                     p_invoice_lines_rec.attribute4,
17306                     p_invoice_lines_rec.attribute5,
17307                     p_invoice_lines_rec.attribute6,
17308                     p_invoice_lines_rec.attribute7,
17309                     p_invoice_lines_rec.attribute8,
17310                     p_invoice_lines_rec.attribute9,
17311                     p_invoice_lines_rec.attribute10,
17312                     p_invoice_lines_rec.attribute11,
17313                     p_invoice_lines_rec.attribute12,
17314                     p_invoice_lines_rec.attribute13,
17315                     p_invoice_lines_rec.attribute14,
17316                     p_invoice_lines_rec.attribute15,
17317                     p_invoice_rec.attribute_category,
17318                     p_invoice_rec.attribute1,
17319                     p_invoice_rec.attribute2,
17320                     p_invoice_rec.attribute3,
17321                     p_invoice_rec.attribute4,
17322                     p_invoice_rec.attribute5,
17323                     p_invoice_rec.attribute6,
17324                     p_invoice_rec.attribute7,
17325                     p_invoice_rec.attribute8,
17326                     p_invoice_rec.attribute9,
17327                     p_invoice_rec.attribute10,
17328                     p_invoice_rec.attribute11,
17329                     p_invoice_rec.attribute12,
17330                     p_invoice_rec.attribute13,
17331                     p_invoice_rec.attribute14,
17332                     p_invoice_rec.attribute15,
17333                     p_invoice_lines_rec.partial_segments,
17334                     p_default_last_updated_by,
17335                     p_default_last_update_login,
17336                     'APTXNIMP',
17337                     l_award_id,
17338                     'AWARD_SET_ID_REMOVE' ) <> TRUE  THEN
17339           IF GMS_AP_API.gms_debug_switch(AP_IMPORT_INVOICES_PKG.g_debug_switch)
17340             THEN
17341             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
17342               AP_IMPORT_UTILITIES_PKG.Print(
17343                 AP_IMPORT_INVOICES_PKG.g_debug_switch,
17344                   '(v_check_line_project_info 3) Invalid GMS Info:Reject');
17345             END IF;
17346           END IF;
17347 
17348           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
17349                 AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
17350                  p_invoice_lines_rec.invoice_line_id,
17351                 'INSUFFICIENT GMS INFO',
17352                 p_default_last_updated_by,
17353                 p_default_last_update_login,
17354                 current_calling_sequence) <> TRUE) THEN
17355             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
17356               AP_IMPORT_UTILITIES_PKG.Print(
17357                 AP_IMPORT_INVOICES_PKG.g_debug_switch,
17358                   'insert_rejections<-'||current_calling_sequence);
17359             END IF;
17360              RAISE check_project_failure;
17361           END IF;
17362           --
17363           l_current_invoice_status := 'N';
17364         END IF; -- GMS
17365       END IF; -- l_current_invoice_Status ='Y' AND l_award_id is not null
17366 
17367       --------------------------------------------------------------
17368       -- Step 4
17369       -- IF flexbuild is successful THEN get ccid
17370       --------------------------------------------------------------
17371       -- IF ccid is created THEN fine
17372       -- Else get ccid from concat segments since it is new
17373       IF AP_IMPORT_INVOICES_PKG.g_source <> 'PPA'  THEN
17374           IF (l_current_invoice_status = 'Y') THEN
17375             IF (l_pa_default_dist_ccid = -1) THEN
17376               IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
17377                 AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
17378                   '(v_check_line_project_info 4) Create new ccid from concat segs');
17379               END IF;
17380 
17381               -- Create new ccid
17382               -- IF creation fails THEN reject
17383               -- Bug 1414119 Changed operation from CREATE_COMBINATION to
17384               -- CREATE_COMB_NO_AT at all the places to avoid the autonomous
17385               -- transaction insert for new code combinations when dynamic
17386               -- insert is on.
17387               -- bug 2496185 by isartawi .. cache the code_combination_ids
17388 
17389               l_key := to_char(nvl(p_chart_of_accounts_id,0))||' '
17390                        ||l_pa_concatenated_segments||' '
17391                        ||to_char(AP_IMPORT_INVOICES_PKG.g_inv_sysdate,'dd-mm-yyyy');
17392               fnd_plsql_cache.generic_1tom_get_values(
17393                           AP_IMPORT_INVOICES_PKG.lg_many_controller1,
17394                           AP_IMPORT_INVOICES_PKG.lg_generic_storage1,
17395                           l_key,
17396                           l_numof_values,
17397                           l_values,
17398                           l_ret_code);
17399 
17400               IF l_ret_code = '1' THEN --  means l_key found in cache
17401                 l_dist_code_combination_id := to_number(l_values(1).varchar2_1);
17402                 l_validate_res             := l_values(1).varchar2_2;
17403                 l_reason_unbuilt_flex      := l_values(1).varchar2_3;
17404 
17405               ELSE  -- IF l_key not found in cache .. cache it
17406            -- For BUG 3000219. Changed g_inv_sysdate to p_accounting_date
17407                 IF (fnd_flex_keyval.validate_segs(
17408                    'CREATE_COMB_NO_AT' ,
17409                    'SQLGL',
17410                    'GL#',
17411                    p_chart_of_accounts_id,
17412                    l_pa_concatenated_segments,
17413                    'V',
17414                    p_accounting_date,   --BUG 3000219.Changed from AP_IMPORT_INVOICES_PKG.g_inv_sysdate
17415                    'ALL',
17416                    NULL,
17417                    NULL,
17418                    'GL_global\\nSUMMARY_FLAG\\nI\\nAPPL=SQLAP;NAME=AP_ALL_PARENT_FLEX_NA\\nN',
17419                    NULL,
17420                    FALSE,
17421                    FALSE,
17422                    NULL,
17423                    NULL,
17424                    NULL,
17425                    NULL,
17426                    NULL,
17427                    NULL) <> TRUE) THEN
17428                   l_validate_res := 'FALSE';
17429                 ELSE
17430                   l_validate_res := 'TRUE';
17431                 END IF;
17432 
17433                 l_dist_code_combination_id := fnd_flex_keyval.combination_id;
17434                 l_reason_unbuilt_flex  := fnd_flex_keyval.error_message;
17435 
17436                 l_valueOut.varchar2_1 := to_char(l_dist_code_combination_id);
17437                 l_valueOut.varchar2_2 := l_validate_res;
17438                 l_valueOut.varchar2_3 := l_reason_unbuilt_flex;
17439                 l_values(1) := l_valueOut;
17440                 l_numof_values := 1;
17441 
17442                 fnd_plsql_cache.generic_1tom_put_values(
17443                             AP_IMPORT_INVOICES_PKG.lg_many_controller1,
17444                             AP_IMPORT_INVOICES_PKG.lg_generic_storage1,
17445                             l_key,
17446                             l_numof_values,
17447                             l_values);
17448               END IF;
17449 
17450               IF (l_validate_res <> 'TRUE') THEN
17451                 --Invalid Creation combination
17452                 IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
17453                   AP_IMPORT_UTILITIES_PKG.Print(
17454                     AP_IMPORT_INVOICES_PKG.g_debug_switch,
17455                       '(v_check_line_project_info 4) Invalid ccid:Reject');
17456                 END IF;
17457 
17458                 IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
17459                    AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
17460                     p_invoice_lines_rec.invoice_line_id,
17461                     'INVALID PA ACCT',
17462                     p_default_last_updated_by,
17463                     p_default_last_update_login,
17464                     current_calling_sequence) <> TRUE) THEN
17465                   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
17466                     AP_IMPORT_UTILITIES_PKG.Print(
17467                       AP_IMPORT_INVOICES_PKG.g_debug_switch,
17468                         'insert_rejections<-'||current_calling_sequence);
17469                   END IF;
17470                    RAISE check_project_failure;
17471                 END IF;
17472                 --
17473                 l_current_invoice_status := 'N';
17474                 l_dist_code_combination_id := 0;
17475                 l_unbuilt_flex := l_pa_concatenated_segments;
17476               Else
17477                 IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
17478                   AP_IMPORT_UTILITIES_PKG.Print(
17479                     AP_IMPORT_INVOICES_PKG.g_debug_switch,
17480                   '(v_check_line_project_info 4) Valid ccid created for project');
17481                 END IF;
17482 
17483                 -- Valid Creation Combination
17484                 l_reason_unbuilt_flex := NULL;
17485                 l_unbuilt_flex := NULL;
17486 
17487               END IF; -- Validate res <> TRUE
17488 
17489               --
17490               -- show output values (only IF debug_switch = 'Y')
17491               --
17492               IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
17493                 AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
17494                     '------------------>  l_dist_code_combination_id= '||
17495                 to_char(l_dist_code_combination_id)
17496                 ||' l_reason_unbuilt_flex = '||l_reason_unbuilt_flex
17497                 ||' l_unbuilt_flex = '||l_unbuilt_flex
17498                 ||' l_current_invoice_status = '||l_current_invoice_status);
17499               END IF;
17500 
17501             Else -- pa default ccid is valid
17502               IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
17503                 AP_IMPORT_UTILITIES_PKG.Print(
17504                   AP_IMPORT_INVOICES_PKG.g_debug_switch,
17505                   '(v_check_line_project_info 5) Valid ccid from PA Flexbuild');
17506               END IF;
17507 
17508               l_dist_code_combination_id := l_pa_default_dist_ccid;
17509 
17510             END IF; --pa_default_ccid = -1
17511 
17512             --------------------------------------------------------------
17513             -- Step 5
17514             -- Return PA generated ccid to calling module for evaluation
17515             -- with overlay information.
17516             --------------------------------------------------------------
17517 
17518             -- Overlay will be done in check Account info
17519             --
17520             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
17521               AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
17522              '(v_check_line_project_info 6) Set OUT parameter with PA ccid');
17523             END IF;
17524 
17525             p_pa_built_account := l_dist_code_combination_id;
17526           END IF; -- current_invoice_status(IF before l_pa_default_dist_ccid)
17527       END IF; -- source <> 'PPA'
17528     END IF; -- l_current_invoice_status( IF before pa_flexbuild)
17529 
17530   ELSE
17531     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
17532       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
17533         '(v_check_line_project_info) No Project Id');
17534     END IF;
17535   END IF; -- PA Info
17536 
17537   p_current_invoice_status := l_current_invoice_status;
17538 
17539   RETURN (TRUE);
17540 
17541 EXCEPTION
17542   WHEN OTHERS THEN
17543     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
17544       AP_IMPORT_UTILITIES_PKG.Print(
17545         AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
17546     END IF;
17547 
17548     IF (SQLCODE < 0) THEN
17549       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
17550         AP_IMPORT_UTILITIES_PKG.Print(
17551           AP_IMPORT_INVOICES_PKG.g_debug_switch,SQLERRM);
17552       END IF;
17553     END IF;
17554     RETURN(FALSE);
17555 
17556 END v_check_line_project_info;
17557 
17558 
17559 ------------------------------------------------------------------------------
17560 -- This function is used to validate line level accounting information.
17561 --
17562 ------------------------------------------------------------------------------
17563 FUNCTION v_check_line_account_info (
17564    p_invoice_lines_rec IN OUT NOCOPY AP_IMPORT_INVOICES_PKG.r_line_info_rec,
17565    p_freight_code_combination_id  IN            NUMBER,
17566    p_pa_built_account             IN            NUMBER,
17567    p_accounting_date              IN            DATE,
17568    p_set_of_books_id              IN            NUMBER,
17569    p_chart_of_accounts_id         IN            NUMBER,
17570    p_default_last_updated_by      IN            NUMBER,
17571    p_default_last_update_login    IN            NUMBER,
17572    p_current_invoice_status       IN OUT NOCOPY VARCHAR2,
17573    p_calling_sequence             IN            VARCHAR2) RETURN BOOLEAN
17574 IS
17575    check_account_failure          EXCEPTION;
17576    l_current_invoice_status          VARCHAR2(1) := 'Y';
17577    l_valid_dist_code              VARCHAR(1);
17578    l_dist_code_combination_id      NUMBER;
17579    l_overlayed_ccid               NUMBER;
17580    l_catsegs                      VARCHAR2(200);
17581    l_unbuilt_flex                 VARCHAR2(240):='';
17582    l_reason_unbuilt_flex          VARCHAR2(2000):='';
17583    l_key                          VARCHAR2(1000);
17584    l_numof_values                   NUMBER;
17585    l_valueOut                   fnd_plsql_cache.generic_cache_value_type;
17586    l_values                     fnd_plsql_cache.generic_cache_values_type;
17587    l_ret_code                       VARCHAR2(1);
17588    l_validate_res                 VARCHAR2(10);
17589    current_calling_sequence        VARCHAR2(2000);
17590    debug_info                     VARCHAR2(500);
17591 
17592 BEGIN
17593   -- Update the calling sequence
17594   --
17595   current_calling_sequence :=
17596        'AP_IMPORT_VALIDATION_PKG.v_check_line_account_info<-'
17597        ||P_calling_sequence;
17598 
17599   l_dist_code_combination_id :=
17600     nvl(p_invoice_lines_rec.dist_code_combination_id, p_pa_built_account);
17601 
17602     /* Added debug message for bug 11782001 */
17603   debug_info := 'Before deriving l_dist_code_combination_id is :'||l_dist_code_combination_id;
17604 
17605   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
17606     AP_IMPORT_UTILITIES_PKG.Print(
17607      AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
17608   END IF;
17609   -----------------------------------------------------------
17610   -- Step 1. Initialize account to freight system account if
17611   -- line is of type FREIGHT and no ccid was provided for it
17612   -- either as a default ccid or through projects.
17613   -----------------------------------------------------------
17614   debug_info := '(v_check_line_account_info 1) '||
17615                  'Check IF item line doesnt have account info';
17616 
17617   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
17618     AP_IMPORT_UTILITIES_PKG.Print(
17619      AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
17620   END IF;
17621 
17622   --Assigning system freight account if no freight account is specified
17623   --Change made for bug#2709960
17624   IF (p_invoice_lines_rec.line_type_lookup_code = 'FREIGHT' AND
17625       l_dist_code_combination_id is NULL) THEN
17626     l_dist_code_combination_id := p_freight_code_combination_id;
17627     p_invoice_lines_rec.dist_code_combination_id :=
17628                                   p_freight_code_combination_id;
17629   END IF;
17630 
17631   ---------------------------------------------------------------
17632    -- bug 7531219
17633    -- step 1.1 : validate the overlay balancing segment if entered
17634    --            to avoid importing invalid overlay balancing segment
17635    ---------------------------------------------------------------
17636    IF p_invoice_lines_rec.balancing_segment IS NOT NULL
17637    THEN
17638      IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
17639             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
17640               '(v_check_line_account_info 1.1) '
17641               || 'Check Overlay Balancing Segment if entered');
17642      END IF;
17643 
17644      IF (AP_UTILITIES_PKG.is_balancing_segment_valid(
17645           p_set_of_books_id     => p_set_of_books_id,
17646           p_balancing_segment_value => p_invoice_lines_rec.balancing_segment,
17647           p_date      => p_accounting_date,
17648           p_calling_sequence     => current_calling_sequence) <> TRUE )
17649      THEN
17650         -- Raise check_account_failure;
17651          IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
17652                     AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
17653                     p_invoice_lines_rec.invoice_line_id,
17654                     'INVALID OVERLAY BAL SEGMENT',
17655                      p_default_last_updated_by,
17656                     p_default_last_update_login,
17657                      current_calling_sequence) <> TRUE)
17658          THEN
17659                    IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
17660                       AP_IMPORT_UTILITIES_PKG.Print(
17661                                  AP_IMPORT_INVOICES_PKG.g_debug_switch,
17662                                  'insert_rejections<-'||current_calling_sequence);
17663                    END IF;
17664                    RAISE check_account_failure;
17665          END IF;
17666          l_current_invoice_status := 'N';
17667       END IF;
17668     END IF;
17669 
17670    -------------------------------------------------------------------------
17671     -- bug 7531219
17672     -- Step 1.2:  validate distribution code combination id if entered
17673     --            to avoid importing invalid distribution account
17674     -------------------------------------------------------------------------
17675   IF (l_dist_code_combination_id is NOT NULL and l_dist_code_combination_id <> -1) THEN
17676 
17677      IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
17678             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
17679               '(v_check_line_account_info 1.2) '
17680               || 'Check distribution code combination id if entered');
17681      END IF;
17682 
17683 
17684      -- Validate distribution code combination id information
17685      IF fnd_flex_keyval.validate_ccid(
17686          appl_short_name => 'SQLGL',
17687          key_flex_code => 'GL#',
17688          structure_number => p_chart_of_accounts_id,
17689          combination_id => l_dist_code_combination_id) THEN
17690       l_catsegs := fnd_flex_keyval.concatenated_values;
17691 
17692       IF (fnd_flex_keyval.validate_segs(
17693                         'CHECK_COMBINATION',
17694                         'SQLGL',
17695                         'GL#',
17696                         p_chart_of_accounts_id,
17697                         l_catsegs,
17698                         'V',
17699                         nvl(p_accounting_date, sysdate),
17700                         'ALL',
17701                         NULL,
17702                         '\nSUMMARY_FLAG\nI\nAPPL=SQLGL;' ||
17703                         'NAME=GL_CTAX_SUMMARY_ACCOUNT\nN',
17704                         NULL,
17705                         NULL,
17706                         FALSE,
17707                         FALSE,
17708                         FND_GLOBAL.RESP_APPL_ID,
17709                         FND_GLOBAL.RESP_ID,
17710                         FND_GLOBAL.USER_ID)<>TRUE)  THEN
17711         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
17712              AP_IMPORT_UTILITIES_PKG.Print(
17713              AP_IMPORT_INVOICES_PKG.g_debug_switch,
17714              '(v_check_line_account_info 1.2) Invalid dist_code_combination_id');
17715         END IF;
17716 
17717         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
17718               AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
17719                p_invoice_lines_rec.invoice_line_id,
17720               'INVALID DISTRIBUTION ACCT',
17721                p_default_last_updated_by,
17722                p_default_last_update_login,
17723                current_calling_sequence) <> TRUE) THEN
17724           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
17725             AP_IMPORT_UTILITIES_PKG.Print(
17726           AP_IMPORT_INVOICES_PKG.g_debug_switch,
17727                   'insert_rejections<-'||
17728                   current_calling_sequence);
17729           END IF;
17730           RAISE check_account_failure;
17731         END IF; -- insert rejections
17732         l_current_invoice_status := 'N';
17733       END IF; -- validate segments
17734     ELSE -- Validate ccid
17735       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
17736         AP_IMPORT_UTILITIES_PKG.Print(
17737         AP_IMPORT_INVOICES_PKG.g_debug_switch,
17738                 '((v_check_line_account_info 1.2) - '||
17739                 ' Invalid Code Combination id');
17740       END IF;
17741       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
17742              AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
17743               p_invoice_lines_rec.invoice_line_id,
17744              'INVALID DISTRIBUTION ACCT',
17745               p_default_last_updated_by,
17746               p_default_last_update_login,
17747               current_calling_sequence) <> TRUE) THEN
17748         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
17749              AP_IMPORT_UTILITIES_PKG.Print(
17750              AP_IMPORT_INVOICES_PKG.g_debug_switch,
17751                    'insert_rejections<-'||
17752                    current_calling_sequence);
17753         END IF;
17754         RAISE check_account_failure;
17755       END IF; -- insert rejections
17756       l_current_invoice_status := 'N';
17757     END IF; -- validate ccid
17758 
17759   END IF; -- l_dist_code_combination_id is not null
17760 
17761   ------------------------------------------------------------------------
17762   -- Step 2. Performs several checks if line did not provide distribution
17763   --         set as source.
17764   -- a. Validate account (source of account is line code combination id
17765   --    or pa_built_account) with overlay information if account is not
17766   --    null or concatenated segments on the line are a partial set
17767   --    but only if line is either not project related or projects allows
17768   --    account override.  Do not reject if the account (source of account
17769   --    was line code combination id or pa_built_account) is null and the
17770   --    concatenated segments was a partial set.
17771   -- b. Validate account if concatenated segments is a full set and account
17772   --    was null.  Obtain ccid from cache and validate it.  Also, if other
17773   --    overlay information was provided verify that it generates a valid
17774   --    account.
17775   ------------------------------------------------------------------------
17776   IF ((p_invoice_lines_rec.distribution_set_id is NULL AND
17777        p_invoice_lines_rec.distribution_set_name is null)) THEN
17778 
17779      /*  Overlay lines before we validate in
17780         case the base Code Combination is invalid, but the overlay
17781         Code Combination is not.  */
17782 
17783     -- 7531219 no need to validate in case of po as the validation is already done
17784     IF ((l_dist_code_combination_id IS NOT NULL OR
17785      (p_invoice_lines_rec.dist_code_concatenated IS NOT NULL AND
17786           p_invoice_lines_rec.partial_segments <> 'N'AND
17787            p_invoice_lines_rec.po_number IS NULL AND
17788            p_invoice_lines_rec.po_header_id IS NULL)) AND
17789         (p_invoice_lines_rec.dist_code_concatenated IS NOT NULL  OR
17790          p_invoice_lines_rec.balancing_segment      IS NOT NULL  OR
17791          p_invoice_lines_rec.cost_center_segment    IS NOT NULL  OR
17792          p_invoice_lines_rec.account_segment        IS NOT NULL) AND
17793         (p_invoice_lines_rec.project_id IS NULL OR
17794      (p_invoice_lines_rec.project_id IS NOT NULL AND
17795       AP_IMPORT_INVOICES_PKG.g_pa_allows_overrides = 'Y'))) THEN
17796 
17797           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
17798             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
17799               '(v_check_line_account_info 2) '
17800               || 'Check Overlay Segments for line');
17801           END IF;
17802 
17803           l_overlayed_ccid := l_dist_code_combination_id;
17804 
17805       IF (AP_UTILITIES_PKG.overlay_segments
17806             (p_invoice_lines_rec.balancing_segment,
17807              p_invoice_lines_rec.cost_center_segment,
17808              p_invoice_lines_rec.account_segment,
17809              p_invoice_lines_rec.dist_code_concatenated,
17810              l_overlayed_ccid ,                 -- IN OUT NOCOPY
17811              p_set_of_books_id ,
17812              'CREATE_COMB_NO_AT',    -- Overlay Mode
17813              l_unbuilt_flex ,                           -- OUT NOCOPY
17814              l_reason_unbuilt_flex ,                    -- OUT NOCOPY
17815              FND_GLOBAL.RESP_APPL_ID,
17816              FND_GLOBAL.RESP_ID,
17817              FND_GLOBAL.USER_ID,
17818              current_calling_sequence,
17819              NULL,
17820              p_accounting_date ) <> TRUE) THEN --7531219
17821 
17822         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
17823           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
17824             '(v_check_line_account_info 2) '||
17825             'Overlay_Segments<-'||current_calling_sequence);
17826         END IF;
17827         -- Bug 6124714
17828 		-- Raise check_account_failure;
17829 		IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
17830               AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
17831               p_invoice_lines_rec.invoice_line_id,
17832              'INVALID DISTRIBUTION ACCT',
17833                 p_default_last_updated_by,
17834               p_default_last_update_login,
17835                current_calling_sequence) <> TRUE) THEN
17836 			IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
17837                 AP_IMPORT_UTILITIES_PKG.Print(
17838                 AP_IMPORT_INVOICES_PKG.g_debug_switch,
17839                   'insert_rejections<-'||
17840                    current_calling_sequence);
17841 			END IF;
17842 			RAISE check_account_failure;
17843         END IF; -- insert rejections
17844       ELSE -- overlay segs
17845 
17846         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
17847           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
17848            '------------------> l_unbuilt_flex = '||
17849                   l_unbuilt_flex||'l_reason_unbuilt_flex = '||
17850                   l_reason_unbuilt_flex||'l_overlayed_ccid = '||
17851                   to_char(l_overlayed_ccid));
17852         END IF;
17853 
17854         IF (l_overlayed_ccid = -1 AND
17855         l_dist_code_combination_id IS NOT NULL) THEN
17856           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
17857         AP_IMPORT_UTILITIES_PKG.Print(
17858            AP_IMPORT_INVOICES_PKG.g_debug_switch,
17859                '(v_check_line_account_info 2)' ||
17860                ' Invalid dist_code_combination_id overlay');
17861           END IF;
17862           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
17863                AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
17864                p_invoice_lines_rec.invoice_line_id,
17865                'INVALID ACCT OVERLAY',
17866                p_default_last_updated_by,
17867                p_default_last_update_login,
17868                current_calling_sequence) <> TRUE) THEN
17869             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
17870               AP_IMPORT_UTILITIES_PKG.Print(
17871                 AP_IMPORT_INVOICES_PKG.g_debug_switch,
17872                   'insert_rejections<-'
17873                  || current_calling_sequence);
17874             END IF;
17875             RAISE check_account_failure;
17876              --
17877           END IF; -- insert rejections
17878           l_current_invoice_status := 'N';
17879         ELSE -- overlayed_ccid <> -1
17880           BEGIN
17881             SELECT 'X'
17882               INTO l_valid_dist_code
17883               FROM gl_code_combinations
17884              WHERE code_combination_id = l_overlayed_ccid
17885                AND enabled_flag='Y'
17886                AND NVL(END_date_active, p_accounting_date) --Bug 2923286 Changed gl_inv_sysdate to p_accounting_date
17887                    >= p_accounting_date
17888                AND NVL(start_date_active, p_accounting_date)
17889                    <= p_accounting_date;
17890           EXCEPTION
17891             WHEN NO_DATA_FOUND THEN
17892               IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
17893                 AP_IMPORT_UTILITIES_PKG.Print(
17894                    AP_IMPORT_INVOICES_PKG.g_debug_switch,
17895                    '(v_check_line_account_info 4) '||
17896                    ' Invalid overlayed ccid ');
17897               END IF;
17898 
17899               IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
17900                   AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
17901                     p_invoice_lines_rec.invoice_line_id,
17902                   'INVALID DISTRIBUTION ACCT',
17903                      p_default_last_updated_by,
17904                    p_default_last_update_login,
17905                     current_calling_sequence) <> TRUE) THEN
17906                 IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
17907                   AP_IMPORT_UTILITIES_PKG.Print(
17908                     AP_IMPORT_INVOICES_PKG.g_debug_switch,
17909                     'insert_rejections<-'
17910                    ||current_calling_sequence);
17911                 END IF;
17912                  RAISE check_account_failure;
17913               END IF; -- insert rejections
17914               --
17915               l_current_invoice_status := 'N';
17916           END;
17917 
17918         END IF; -- l_dist_code_combination_id is -1
17919       END IF; --overlay segments
17920 
17921     ELSIF (l_dist_code_combination_id IS NULL AND
17922            p_invoice_lines_rec.dist_code_concatenated IS NOT NULL AND
17923            p_invoice_lines_rec.partial_segments = 'N' AND
17924            p_invoice_lines_rec.po_number IS NULL AND
17925            p_invoice_lines_rec.po_header_id IS NULL) THEN
17926 
17927       -- bug 2496185 by isartawi .. cache the code_combination_ids
17928       l_key := TO_CHAR(NVL(p_chart_of_accounts_id,0))||' '||
17929                p_invoice_lines_rec.dist_code_concatenated||' '||
17930            to_char(p_accounting_date,'dd-mm-yyyy');
17931 
17932       fnd_plsql_cache.generic_1tom_get_values(
17933                AP_IMPORT_INVOICES_PKG.lg_many_controller1,
17934                AP_IMPORT_INVOICES_PKG.lg_generic_storage1,
17935                l_key,
17936                l_numof_values,
17937                l_values,
17938                l_ret_code);
17939       IF l_ret_code = '1' THEN --  means l_key found in cache
17940         l_dist_code_combination_id := to_number(l_values(1).varchar2_1);
17941         l_validate_res             := l_values(1).varchar2_2;
17942          -- Bug 5533471
17943         p_invoice_lines_rec.dist_code_combination_id := l_dist_code_combination_id;
17944 
17945       ELSE  -- IF l_key not found in cache .. cache it
17946         IF (fnd_flex_keyval.validate_segs
17947                 ('CREATE_COMB_NO_AT' ,   --Bug6624362
17948                  'SQLGL',
17949                  'GL#',
17950                  p_chart_of_accounts_id,
17951                  p_invoice_lines_rec.dist_code_concatenated,
17952                  'V',
17953                  p_accounting_date,
17954                  'ALL',
17955                  NULL,
17956                  '\nSUMMARY_FLAG\nI\nAPPL=SQLGL;' ||
17957                  'NAME=GL_CTAX_SUMMARY_ACCOUNT\nN',
17958                  NULL,
17959                  NULL,
17960                  FALSE,
17961                  FALSE,
17962                  FND_GLOBAL.RESP_APPL_ID,
17963                  FND_GLOBAL.RESP_ID,
17964                  FND_GLOBAL.USER_ID) <> TRUE) THEN
17965           l_validate_res := 'FALSE';
17966         ELSE --validate_segs
17967           l_validate_res := 'TRUE';
17968         END IF;
17969         l_dist_code_combination_id := fnd_flex_keyval.combination_id;
17970         p_invoice_lines_rec.dist_code_combination_id := l_dist_code_combination_id; --bug 12987030
17971         l_valueOut.varchar2_1      := to_char(l_dist_code_combination_id);
17972         l_valueOut.varchar2_2      := l_validate_res;
17973         l_values(1)                := l_valueOut;
17974         l_numof_values             := 1;
17975 
17976         fnd_plsql_cache.generic_1tom_put_values(
17977                   AP_IMPORT_INVOICES_PKG.lg_many_controller1,
17978                   AP_IMPORT_INVOICES_PKG.lg_generic_storage1,
17979                   l_key,
17980                   l_numof_values,
17981                   l_values);
17982       END IF; -- l_ret_code='1'
17983 
17984        -- Bug 5533471
17985       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
17986           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
17987             'l_dist_code_combination_id: '|| l_dist_code_combination_id
17988            ||', l_validate_res: '||l_validate_res);
17989       END IF;
17990 
17991       IF (l_validate_res <> 'TRUE')  THEN
17992         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
17993           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
17994             '(v_check_line_account_info 2) '||
17995             'Invalid dist_code_concatenated ');
17996           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
17997             '(v_check_line_account_info 2) '||
17998             'Error create account infomation : '||
17999             FND_FLEX_KEYVAL.error_message);
18000         END IF;
18001 
18002         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
18003               AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
18004               p_invoice_lines_rec.invoice_line_id,
18005              'INVALID DISTRIBUTION ACCT',
18006                 p_default_last_updated_by,
18007               p_default_last_update_login,
18008                current_calling_sequence) <> TRUE) THEN
18009           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
18010                 AP_IMPORT_UTILITIES_PKG.Print(
18011                 AP_IMPORT_INVOICES_PKG.g_debug_switch,
18012                   'insert_rejections<-'||
18013                    current_calling_sequence);
18014           END IF;
18015           RAISE check_account_failure;
18016         END IF; -- insert rejections
18017         --
18018         l_current_invoice_status := 'N';
18019 
18020       ELSE -- validate res is TRUE
18021         IF ((l_current_invoice_status <> 'N') AND
18022             ((p_invoice_lines_rec.balancing_segment IS NOT NULL) OR
18023           (p_invoice_lines_rec.cost_center_segment IS NOT NULL) OR
18024          (p_invoice_lines_rec.account_segment IS NOT NULL))) THEN
18025           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
18026                 AP_IMPORT_UTILITIES_PKG.Print(
18027                   AP_IMPORT_INVOICES_PKG.g_debug_switch,
18028                       '(v_check_line_account_info 2) '||
18029                       'Check Overlay Segments for dist_code_concatenated ');
18030           END IF;
18031 
18032           l_overlayed_ccid := l_dist_code_combination_id;
18033 
18034           IF (AP_UTILITIES_PKG.overlay_segments(
18035                   p_invoice_lines_rec.balancing_segment,
18036                   p_invoice_lines_rec.cost_center_segment,
18037                   p_invoice_lines_rec.account_segment,
18038                   NULL,
18039                   l_overlayed_ccid ,                     -- IN OUT NOCOPY
18040                   p_set_of_books_id ,
18041                   'CREATE_COMB_NO_AT' , -- Overlay Mode
18042                   l_unbuilt_flex ,                       -- OUT NOCOPY
18043                   l_reason_unbuilt_flex ,                -- OUT NOCOPY
18044                   FND_GLOBAL.RESP_APPL_ID,
18045                   FND_GLOBAL.RESP_ID,
18046                   FND_GLOBAL.USER_ID,
18047                   current_calling_sequence,
18048                   Null,
18049                   p_accounting_date ) <> TRUE) THEN --7531219
18050             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
18051                  AP_IMPORT_UTILITIES_PKG.Print(
18052                  AP_IMPORT_INVOICES_PKG.g_debug_switch,
18053                 '(v_check_line_account_info 2) '||
18054                 ' Overlay_Segments<-'||current_calling_sequence);
18055             END IF;
18056             -- Bug 6124714
18057 		    -- Raise check_account_failure;
18058 		IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
18059               AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
18060               p_invoice_lines_rec.invoice_line_id,
18061              'INVALID DISTRIBUTION ACCT',
18062                 p_default_last_updated_by,
18063               p_default_last_update_login,
18064                current_calling_sequence) <> TRUE) THEN
18065 			IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
18066                 AP_IMPORT_UTILITIES_PKG.Print(
18067                 AP_IMPORT_INVOICES_PKG.g_debug_switch,
18068                   'insert_rejections<-'||
18069                    current_calling_sequence);
18070 			END IF;
18071 			RAISE check_account_failure;
18072         END IF; -- insert rejections
18073 
18074           ELSE -- overlay segs
18075             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
18076                   AP_IMPORT_UTILITIES_PKG.Print(
18077                   AP_IMPORT_INVOICES_PKG.g_debug_switch,
18078                   '-----------------> l_unbuilt_flex = '||
18079                   l_unbuilt_flex||' l_reason_unbuilt_flex = '||
18080                   l_reason_unbuilt_flex||'l_overlayed_ccid: '||
18081                   to_char(l_overlayed_ccid));
18082             END IF;
18083 
18084             IF (l_overlayed_ccid = -1) THEN
18085               IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
18086                 AP_IMPORT_UTILITIES_PKG.Print(
18087                  AP_IMPORT_INVOICES_PKG.g_debug_switch,
18088                  '(v_check_line_account_info 4) '||
18089                  'Invalid dist_code_combination_id  overlay');
18090               END IF;
18091 
18092               IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
18093                   AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
18094                    p_invoice_lines_rec.invoice_line_id,
18095                   'INVALID ACCT OVERLAY',
18096                    p_default_last_updated_by,
18097                    p_default_last_update_login,
18098                     current_calling_sequence) <> TRUE) THEN
18099                 IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
18100                   AP_IMPORT_UTILITIES_PKG.Print(
18101                      AP_IMPORT_INVOICES_PKG.g_debug_switch,
18102                        'insert_rejections<-'||
18103                      current_calling_sequence);
18104                 END IF;
18105                 RAISE check_account_failure;
18106               END IF; -- insert rejections
18107               l_current_invoice_status := 'N';
18108             END IF; -- overlayed dist code combination id is -1
18109           END IF; --overlay segments
18110 
18111         -- Bug 5533471
18112         ELSIF  ((l_current_invoice_status <> 'N')
18113                 AND (l_dist_code_combination_id = -1))  THEN
18114 
18115           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
18116                 AP_IMPORT_UTILITIES_PKG.Print(
18117                  AP_IMPORT_INVOICES_PKG.g_debug_switch,
18118                  '(v_check_line_account_info 4.1) '||
18119                  'Invalid dist_code_combination_id  overlay');
18120           END IF;
18121 
18122           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
18123                   AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
18124                    p_invoice_lines_rec.invoice_line_id,
18125                   'INVALID ACCT OVERLAY',
18126                    p_default_last_updated_by,
18127                    p_default_last_update_login,
18128                     current_calling_sequence) <> TRUE) THEN
18129             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
18130                   AP_IMPORT_UTILITIES_PKG.Print(
18131                      AP_IMPORT_INVOICES_PKG.g_debug_switch,
18132                        'insert_rejections<-'||
18133                      current_calling_sequence);
18134             END IF;
18135                 RAISE check_account_failure;
18136           END IF; -- insert rejections
18137           l_current_invoice_status := 'N';
18138 
18139          -- Bug 5533471
18140         ELSIF  ((l_current_invoice_status <> 'N')
18141                 AND (l_dist_code_combination_id <> -1))  THEN
18142 
18143           p_invoice_lines_rec.dist_code_combination_id := l_dist_code_combination_id;
18144 
18145         END IF; -- Invoice Status
18146       END IF; -- Validate res
18147     END IF; -- accounting information exists
18148   END IF; -- distribution set id is null
18149 
18150   ------------------------------------------------------------------
18151   -- Step 3. Validate account information relative to po and receipt
18152   ------------------------------------------------------------------
18153   -- Made changes to the following stmt for receipt matching project
18154   -- We should NOT reject a non-item line IF it has account information,
18155   -- po information and receipt information.
18156   -- But we should Reject IF it has acct info, po info and no receipt info.
18157  -- Bug 7487507
18158  -- Changed the paranthesis in the If condition
18159     IF ((p_invoice_lines_rec.line_type_lookup_code <> 'ITEM' AND
18160        (p_invoice_lines_rec.distribution_set_id IS NOT NULL OR
18161         p_invoice_lines_rec.distribution_set_name IS NOT NULL) AND
18162        (l_dist_code_combination_id IS NOT NULL OR l_overlayed_ccid IS NOT NULL))
18163 OR
18164       ((p_invoice_lines_rec.line_type_lookup_code <> 'ITEM')  AND
18165        ((p_invoice_lines_rec.po_header_id is not null) OR
18166         (p_invoice_lines_rec.po_number is not null)) AND
18167        ((p_invoice_lines_rec.receipt_number is null) AND
18168         (p_invoice_lines_rec.rcv_transaction_id is null)))   OR
18169        (((p_invoice_lines_rec.po_header_id is NOT NULL) OR
18170          (p_invoice_lines_rec.po_number IS NOT NULL)) AND
18171         ((p_invoice_lines_rec.distribution_set_id is NOT NULL) OR
18172          (p_invoice_lines_rec.distribution_set_name is NOT NULL))) ) THEN
18173     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
18174       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
18175         '(v_check_line_account_info 3) '||
18176         'Inconsistent dist Info ');
18177     END IF;
18178 
18179     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
18180         AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
18181         p_invoice_lines_rec.invoice_line_id,
18182         'INCONSISTENT DIST INFO',
18183         p_default_last_updated_by,
18184         p_default_last_update_login,
18185         current_calling_sequence) <> TRUE) THEN
18186       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
18187         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
18188           'insert_rejections<-'||
18189           current_calling_sequence);
18190       END IF;
18191       RAISE check_account_failure;
18192     END IF; -- insert rejections
18193     l_current_invoice_status := 'N';
18194   END IF; -- Step 3
18195 
18196 -- 7531219, commented out following code
18197 -- validation of dist ccid should be done before overlay itself as
18198 -- we need to avoid importing invalid dist ccids
18199 /*
18200   -------------------------------------------------------------------------
18201   -- Step 4. Validate account
18202   -------------------------------------------------------------------------
18203   debug_info := '(v_check_line_account_info 4) calling parent validation ';
18204   IF ((l_dist_code_combination_id is not NULL AND
18205        l_dist_code_combination_id <> -1)          OR
18206       (l_overlayed_ccid IS NOT NULL AND l_overlayed_ccid <> -1))  THEN
18207     debug_info := '(v_check_line_account_info 4) Inside parent validation';
18208     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
18209       AP_IMPORT_UTILITIES_PKG.Print(
18210         AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
18211     END IF;
18212     IF (l_overlayed_ccid IS NULL OR l_overlayed_ccid = -1) THEN
18213       l_overlayed_ccid := l_dist_code_combination_id;
18214     END IF;
18215     IF fnd_flex_keyval.validate_ccid(
18216        appl_short_name => 'SQLGL',
18217        key_flex_code => 'GL#',
18218        structure_number => p_chart_of_accounts_id,
18219        combination_id => l_overlayed_ccid) THEN
18220       l_catsegs := fnd_flex_keyval.concatenated_values;
18221 
18222       IF (fnd_flex_keyval.validate_segs(
18223                         'CHECK_COMBINATION',
18224                         'SQLGL',
18225                         'GL#',
18226                         p_chart_of_accounts_id,
18227                         l_catsegs,
18228                         'V',
18229                         p_accounting_date,
18230                         'ALL',
18231                         NULL,
18232                         '\nSUMMARY_FLAG\nI\nAPPL=SQLGL;' ||
18233                         'NAME=GL_CTAX_SUMMARY_ACCOUNT\nN',
18234                         NULL,
18235                         NULL,
18236                         FALSE,
18237                         FALSE,
18238                         FND_GLOBAL.RESP_APPL_ID,
18239                         FND_GLOBAL.RESP_ID,
18240                         FND_GLOBAL.USER_ID)<>TRUE)  THEN
18241         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
18242               AP_IMPORT_UTILITIES_PKG.Print(
18243               AP_IMPORT_INVOICES_PKG.g_debug_switch,
18244                   '((v_check_line_account_info 4) - '||
18245                   ' Invalid Code Combination id');
18246         END IF;
18247         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
18248               AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
18249                p_invoice_lines_rec.invoice_line_id,
18250               'INVALID DISTRIBUTION ACCT',
18251                p_default_last_updated_by,
18252                p_default_last_update_login,
18253                current_calling_sequence) <> TRUE) THEN
18254           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
18255             AP_IMPORT_UTILITIES_PKG.Print(
18256           AP_IMPORT_INVOICES_PKG.g_debug_switch,
18257                   'insert_rejections<-'||
18258                   current_calling_sequence);
18259           END IF;
18260           RAISE check_account_failure;
18261         END IF; -- insert rejections
18262         l_current_invoice_status := 'N';
18263       END IF; -- validate segments
18264     ELSE -- Validate ccid
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                 '((v_check_line_account_info 4) - '||
18269                 ' Invalid Code Combination id');
18270       END IF;
18271       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
18272              AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
18273               p_invoice_lines_rec.invoice_line_id,
18274              'INVALID DISTRIBUTION ACCT',
18275               p_default_last_updated_by,
18276               p_default_last_update_login,
18277               current_calling_sequence) <> TRUE) THEN
18278         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
18279              AP_IMPORT_UTILITIES_PKG.Print(
18280              AP_IMPORT_INVOICES_PKG.g_debug_switch,
18281                    'insert_rejections<-'||
18282                    current_calling_sequence);
18283         END IF;
18284         RAISE check_account_failure;
18285       END IF; -- insert rejections
18286       l_current_invoice_status := 'N';
18287     END IF; -- Validate ccid
18288   END IF; -- either dist ccid or overlayed ccid are not null
18289 */
18290   -- Return value
18291   p_current_invoice_status := l_current_invoice_status;
18292 
18293   RETURN (TRUE);
18294 
18295 
18296 EXCEPTION
18297   WHEN OTHERS THEN
18298     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
18299       AP_IMPORT_UTILITIES_PKG.Print(
18300         AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
18301     END IF;
18302 
18303     IF (SQLCODE < 0) THEN
18304       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
18305         AP_IMPORT_UTILITIES_PKG.Print(
18306           AP_IMPORT_INVOICES_PKG.g_debug_switch, SQLERRM);
18307       END IF;
18308     END IF;
18309 RETURN(FALSE);
18310 
18311 END v_check_line_account_info;
18312 
18313 
18314 
18315 
18316 -----------------------------------------------------------------------------
18317 -- This function is used to validate line level deferred accounting
18318 -- information.
18319 -----------------------------------------------------------------------------
18320 FUNCTION v_check_deferred_accounting (
18321          p_invoice_lines_rec
18322            IN OUT NOCOPY AP_IMPORT_INVOICES_PKG.r_line_info_rec,
18323          p_set_of_books_id              IN            NUMBER,
18324          p_default_last_updated_by      IN            NUMBER,
18325          p_default_last_update_login    IN            NUMBER,
18326          p_current_invoice_status       IN OUT NOCOPY VARCHAR2,
18327          p_calling_sequence             IN            VARCHAR2) RETURN BOOLEAN
18328 
18329 IS
18330 
18331 check_defer_acctg_failure      EXCEPTION;
18332 l_period_name                  VARCHAR2(15);
18333 l_valid_period_type           VARCHAR2(30);
18334 l_current_invoice_status      VARCHAR2(1) := 'Y';
18335 current_calling_sequence        VARCHAR2(2000);
18336 debug_info                     VARCHAR2(500);
18337 
18338 BEGIN
18339   -- Update the calling sequence
18340   --
18341   current_calling_sequence :=
18342     'AP_IMPORT_VALIDATION_PKG.v_check_deferred_accounting<-'
18343     ||P_calling_sequence;
18344 
18345   ----------------------------------------------------------------------------
18346   --Step 1 - Validate the deferred accounting flag.  Value should be either
18347   -- Null, N or Y.
18348   --
18349   ----------------------------------------------------------------------------
18350   IF (((nvl(p_invoice_lines_rec.deferred_acctg_flag, 'N') <> 'N')  AND
18351        (nvl(p_invoice_lines_rec.deferred_acctg_flag, 'Y') <> 'Y')) OR
18352       ((nvl(p_invoice_lines_rec.deferred_acctg_flag, 'N') = 'N') AND
18353        (p_invoice_lines_rec.def_acctg_start_date IS NOT NULL OR
18354         p_invoice_lines_rec.def_acctg_end_date IS NOT NULL OR
18355         p_invoice_lines_rec.def_acctg_number_of_periods IS NOT NULL OR
18356         p_invoice_lines_rec.def_acctg_period_type IS NOT NULL))) THEN
18357     debug_info := '(Check_deferred_accounting 1)Validate appropriate def data';
18358     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
18359       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
18360                                     debug_info);
18361     END IF;
18362 
18363     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
18364         AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
18365         p_invoice_lines_rec.invoice_line_id,
18366         'INVALID DEFERRED FLAG',
18367         p_default_last_updated_by,
18368         p_default_last_update_login,
18369         current_calling_sequence) <> TRUE) THEN
18370       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
18371         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
18372           'insert_rejections<-'||current_calling_sequence);
18373       END IF;
18374       RAISE check_defer_acctg_failure;
18375     END IF;
18376     l_current_invoice_status := 'N';
18377   END IF;
18378 
18379   ----------------------------------------------------------------------------
18380   -- Step 2 - Validate that mandatory deferred accounting data is populated if
18381   -- deferred accounting is requested.
18382   -- Also validate that if start date is populated it falls in an open period
18383   -- which is the same period as the period for the line.
18384   --
18385   -----------------------------------------------------------------------------
18386   IF (nvl(p_invoice_lines_rec.deferred_acctg_flag, 'N') = 'Y') then
18387     debug_info := '(Check_deferred_accounting 2) Validate start date';
18388     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
18389       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
18390                                     debug_info);
18391     END IF;
18392 
18393     IF (p_invoice_lines_rec.def_acctg_start_date IS NULL OR
18394          p_invoice_lines_rec.def_acctg_end_date IS NULL) THEN
18395 -- Bug 15835723    (p_invoice_lines_rec.def_acctg_number_of_periods IS NULL AND
18396 -- Bug 15835723         p_invoice_lines_rec.def_acctg_end_date IS NULL)) THEN
18397       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
18398             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
18399             p_invoice_lines_rec.invoice_line_id,
18400             'INCOMPLETE DEF ACCTG INFO',
18401             p_default_last_updated_by,
18402             p_default_last_update_login,
18403             current_calling_sequence) <> TRUE) THEN
18404         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
18405           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
18406            'insert_rejections<-'||current_calling_sequence);
18407         END IF;
18408         RAISE check_defer_acctg_failure;
18409       END IF;
18410       l_current_invoice_status := 'N';
18411     END IF;
18412 
18413     IF (p_invoice_lines_rec.def_acctg_start_date IS NOT NULL) THEN
18414 -- Bug 15835723      BEGIN
18415         -- Bug 15835723
18416         l_period_name := Ap_Utilities_Pkg.Get_Current_Gl_Date_No_Cache(
18417                            p_invoice_lines_rec.def_acctg_start_date,
18418                            p_invoice_lines_rec.org_id);
18419 /* Bug 15835723
18420         SELECT period_name
18421           INTO l_period_name
18422           FROM gl_period_statuses
18423          WHERE application_id = 200
18424            AND set_of_books_id = p_set_of_books_id
18425            AND trunc(p_invoice_lines_rec.def_acctg_start_date)
18426                between start_date and end_date
18427            AND closing_status in ('O', 'F')
18428            AND NVL(adjustment_period_flag, 'N') = 'N';
18429 
18430         IF (l_period_name <> p_invoice_lines_rec.period_name) then
18431           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
18432             AP_IMPORT_UTILITIES_PKG.Print(
18433                AP_IMPORT_INVOICES_PKG.g_debug_switch,
18434                'Def Acctg Start Date is not is same period as line');
18435           END IF;
18436 
18437           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
18438                AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
18439                p_invoice_lines_rec.invoice_line_id,
18440                'INVALID DEF START DATE',
18441                p_default_last_updated_by,
18442                p_default_last_update_login,
18443                current_calling_sequence) <> TRUE) THEN
18444             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
18445               AP_IMPORT_UTILITIES_PKG.Print(
18446                 AP_IMPORT_INVOICES_PKG.g_debug_switch,
18447                 'insert_rejections<-'||current_calling_sequence);
18448             END IF;
18449             RAISE check_defer_acctg_failure;
18450           END IF;
18451           l_current_invoice_status := 'N';
18452         END IF; -- period name is other than line period name
18453 
18454       EXCEPTION
18455         WHEN NO_DATA_FOUND then
18456 */ -- Bug 15835723
18457 
18458        IF (l_period_name IS NULL) THEN -- Bug 15835723
18459           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
18460             AP_IMPORT_UTILITIES_PKG.Print(
18461               AP_IMPORT_INVOICES_PKG.g_debug_switch,
18462               'Def Acctg Start Date is not in open period');
18463           END IF;
18464 
18465           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
18466                AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
18467                p_invoice_lines_rec.invoice_line_id,
18468                'INVALID DEF START DATE',
18469                p_default_last_updated_by,
18470                p_default_last_update_login,
18471                current_calling_sequence) <> TRUE) THEN
18472             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
18473               AP_IMPORT_UTILITIES_PKG.Print(
18474                 AP_IMPORT_INVOICES_PKG.g_debug_switch,
18475                   'insert_rejections<-'||current_calling_sequence);
18476             END IF;
18477             RAISE check_defer_acctg_failure;
18478           END IF;
18479           l_current_invoice_status := 'N';
18480       END IF; -- Bug 15835723
18481     END IF; -- def acctg start date is not null
18482 
18483   END IF; -- step 2
18484 
18485   ----------------------------------------------------------------------------
18486   -- Step 3 - Validate that the end date is larger than start date if the
18487   -- deferred flag is Y and the start date is not null.
18488   --
18489   -----------------------------------------------------------------------------
18490   IF (nvl(p_invoice_lines_rec.deferred_acctg_flag, 'N') = 'Y' AND
18491       p_invoice_lines_rec.def_acctg_start_date is not null AND
18492       p_invoice_lines_rec.def_acctg_end_date is not null) then
18493     debug_info := '(Check_deferred_accounting 3) Validate end date';
18494     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
18495       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
18496                                     debug_info);
18497     END IF;
18498 
18499 -- Bug 15835723
18500    IF (p_invoice_lines_rec.def_acctg_end_date IS NOT NULL) THEN
18501 -- Bug 15835723      BEGIN
18502         l_period_name := Ap_Utilities_Pkg.Get_Current_Gl_Date_No_Cache(
18503                            p_invoice_lines_rec.def_acctg_end_date,
18504                            p_invoice_lines_rec.org_id);
18505 -- Bug 15835723
18506 /*      EXCEPTION
18507         WHEN NO_DATA_FOUND then*/
18508       IF (l_period_name IS NULL) THEN
18509           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
18510             AP_IMPORT_UTILITIES_PKG.Print(
18511               AP_IMPORT_INVOICES_PKG.g_debug_switch,
18512               'Def Acctg End Date is not in open period');
18513           END IF;
18514 
18515           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
18516                AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
18517                p_invoice_lines_rec.invoice_line_id,
18518                'INVALID DEF END DATE',
18519                p_default_last_updated_by,
18520                p_default_last_update_login,
18521                current_calling_sequence) <> TRUE) THEN
18522             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
18523               AP_IMPORT_UTILITIES_PKG.Print(
18524                 AP_IMPORT_INVOICES_PKG.g_debug_switch,
18525                   'insert_rejections<-'||current_calling_sequence);
18526             END IF;
18527             RAISE check_defer_acctg_failure;
18528           END IF;
18529           l_current_invoice_status := 'N';
18530       END IF; -- Bug 15835723
18531     END IF; -- def acctg end date is not null
18532 -- Bug 15835723
18533 
18534     IF (trunc(p_invoice_lines_rec.def_acctg_start_date) >
18535         trunc(p_invoice_lines_rec.def_acctg_end_date)) then
18536       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
18537           AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
18538           p_invoice_lines_rec.invoice_line_id,
18539           'INVALID DEF END DATE',
18540           p_default_last_updated_by,
18541           p_default_last_update_login,
18542           current_calling_sequence) <> TRUE) THEN
18543         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
18544             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
18545             'insert_rejections<-'||current_calling_sequence);
18546         END IF;
18547         RAISE check_defer_acctg_failure;
18548       END IF;
18549       l_current_invoice_status := 'N';
18550     END IF;
18551   END IF; -- Deferred flag is Y and both start date and end dates are not null
18552 
18553   ---------------------------------------------------------------------------
18554   -- Step 4 - Validate that Number of periods is a positive integer and
18555   -- Populated if period type is populated but only if deferred flag is Y.
18556   --
18557   ---------------------------------------------------------------------------
18558   IF (nvl(p_invoice_lines_rec.deferred_acctg_flag, 'N') = 'Y' AND
18559       p_invoice_lines_rec.def_acctg_period_type IS NOT NULL) THEN
18560      -- Bug 15835723
18561     debug_info := '(Check_deferred_accounting 4) Make number of periods NULL';
18562     --debug_info := '(Check_deferred_accounting 4) Validate number of periods';
18563     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
18564       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
18565                               debug_info);
18566     END IF;
18567 
18568     -- Bug 15835723
18569     p_invoice_lines_rec.def_acctg_period_type := NULL;
18570 
18571 /* Bug 15835723
18572     IF (p_invoice_lines_rec.def_acctg_number_of_periods is NULL OR
18573         p_invoice_lines_rec.def_acctg_number_of_periods < 0 OR
18574         floor(p_invoice_lines_rec.def_acctg_number_of_periods) <>
18575         ceil(p_invoice_lines_rec.def_acctg_number_of_periods)) THEN
18576       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
18577           AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
18578           p_invoice_lines_rec.invoice_line_id,
18579           'INVALID DEF NUM OF PER',
18580           p_default_last_updated_by,
18581           p_default_last_update_login,
18582           current_calling_sequence) <> TRUE) THEN
18583         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
18584           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
18585           'insert_rejections<-'||current_calling_sequence);
18586         END IF;
18587         RAISE check_defer_acctg_failure;
18588       END IF;
18589       l_current_invoice_status := 'N';
18590 
18591     END IF;
18592 
18593     BEGIN
18594       SELECT 'Valid Period Type'
18595         INTO l_valid_period_type
18596         FROM xla_lookups
18597        WHERE lookup_type = 'XLA_DEFERRED_PERIOD_TYPE'
18598     AND lookup_code = p_invoice_lines_rec.def_acctg_period_type;
18599 
18600     EXCEPTION
18601       When NO_DATA_FOUND THEN
18602         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
18603               AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
18604               p_invoice_lines_rec.invoice_line_id,
18605               'INVALID DEF PER TYPE',
18606               p_default_last_updated_by,
18607               p_default_last_update_login,
18608               current_calling_sequence) <> TRUE) THEN
18609           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
18610         AP_IMPORT_UTILITIES_PKG.Print(
18611            AP_IMPORT_INVOICES_PKG.g_debug_switch,
18612                    'insert_rejections<-'||current_calling_sequence);
18613           END IF;
18614           RAISE check_defer_acctg_failure;
18615         END IF;
18616         l_current_invoice_status := 'N';
18617 
18618     END;
18619 */
18620   END IF; -- Deferred flag is Y and period type is populated.
18621 
18622   ---------------------------------------------------------------------------
18623  -- Step 5 - Validate that Period Type is populated if number of periods is
18624  -- Populated.
18625  -- Bug 12808871: Removing this check - Also validate that it contains a valid type
18626  -- and that it is not simulatneously populated with end date.
18627   --
18628   ---------------------------------------------------------------------------
18629   IF (nvl(p_invoice_lines_rec.deferred_acctg_flag, 'N') = 'Y' AND
18630       p_invoice_lines_rec.def_acctg_number_of_periods IS NOT NULL) THEN
18631     -- Bug 15835723
18632     debug_info := '(Check_deferred_accounting 5) Make period type NULL';
18633     --debug_info := '(Check_deferred_accounting 5) Validate period type';
18634     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
18635       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
18636                                     debug_info);
18637     End if;
18638 
18639     -- Bug 15835723
18640     p_invoice_lines_rec.def_acctg_number_of_periods := NULL;
18641 
18642     /* Bug 12808871 Start - def_acctg_end_date needs to be calculated if def_acctg_period_type
18643         and def_acctg_number_of_periods is not null */
18644 /* Bug 15835723
18645     IF (p_invoice_lines_rec.def_acctg_period_type IS NULL
18646     ** OR (p_invoice_lines_rec.def_acctg_period_type IS NOT NULL AND
18647          p_invoice_lines_rec.def_acctg_end_date IS NOT NULL)
18648          **
18649          ) THEN
18650       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
18651            AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
18652            p_invoice_lines_rec.invoice_line_id,
18653            'INVALID DEF PER TYPE',
18654            p_default_last_updated_by,
18655            p_default_last_update_login,
18656            current_calling_sequence) <> TRUE) THEN
18657         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
18658           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
18659           'insert_rejections<-'||current_calling_sequence);
18660         END IF;
18661         RAISE check_defer_acctg_failure;
18662       END IF;
18663       l_current_invoice_status := 'N';
18664 
18665     ** Bug 12808871 - (re)calculate def_acctg_end_date **
18666     ELSE
18667         IF upper(p_invoice_lines_rec.def_acctg_period_type) = 'DAYS' THEN
18668                 p_invoice_lines_rec.def_acctg_end_date :=
18669                  to_date(p_invoice_lines_rec.def_acctg_start_date,'dd/mm/rrrr') ** bug 13064785 ** +
18670                 to_number(p_invoice_lines_rec.def_acctg_number_of_periods);
18671 
18672         ELSIF upper(p_invoice_lines_rec.def_acctg_period_type) = 'WEEKS' THEN
18673                 p_invoice_lines_rec.def_acctg_end_date :=
18674                  to_date(p_invoice_lines_rec.def_acctg_start_date,'dd/mm/rrrr') ** bug 13064785 **  +
18675                  to_number(p_invoice_lines_rec.def_acctg_number_of_periods)*7;
18676 
18677         ELSIF upper(p_invoice_lines_rec.def_acctg_period_type) = 'MONTHS' THEN
18678                 p_invoice_lines_rec.def_acctg_end_date :=
18679                  ADD_MONTHS(to_date(p_invoice_lines_rec.def_acctg_start_date,'dd/mm/rrrr'), ** bug 13064785 **
18680                   to_number(p_invoice_lines_rec.def_acctg_number_of_periods));
18681 
18682         ELSIF upper(p_invoice_lines_rec.def_acctg_period_type) = 'YEARS' THEN
18683                 p_invoice_lines_rec.def_acctg_end_date :=
18684                  ADD_MONTHS(to_date(p_invoice_lines_rec.def_acctg_start_date,'dd/mm/rrrr'), ** bug 13064785 **
18685                   to_number(p_invoice_lines_rec.def_acctg_number_of_periods)*12);
18686         END IF;
18687 
18688     END IF; -- period type is null
18689 */
18690     /* Bug 12808871 End */
18691 
18692   END IF; -- deferred flag is Y and number of periods is populated
18693 
18694   --
18695   -- Return value
18696   p_current_invoice_status := l_current_invoice_status;
18697   RETURN (TRUE);
18698 
18699 
18700 EXCEPTION
18701   WHEN OTHERS THEN
18702     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
18703       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
18704                                     debug_info);
18705     END IF;
18706 
18707     IF (SQLCODE < 0) then
18708       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
18709         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
18710                                       SQLERRM);
18711       END IF;
18712     END IF;
18713     RETURN(FALSE);
18714 
18715 END v_check_deferred_accounting;
18716 
18717 
18718 ------------------------------------------------------------------------------
18719 -- This function is used to validate distribution set information.
18720 --
18721 ------------------------------------------------------------------------------
18722 FUNCTION v_check_line_dist_set (
18723          p_invoice_rec                  IN
18724          AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
18725          p_invoice_lines_rec            IN OUT NOCOPY
18726          AP_IMPORT_INVOICES_PKG.r_line_info_rec,
18727          p_base_currency_code           IN            VARCHAR2,
18728          p_employee_id                  IN            NUMBER,
18729          p_gl_date_from_get_info        IN            DATE,
18730          p_set_of_books_id              IN            NUMBER,
18731          p_chart_of_accounts_id         IN            NUMBER,
18732          p_pa_installed                 IN            VARCHAR2,
18733          p_default_last_updated_by      IN            NUMBER,
18734          p_default_last_update_login    IN            NUMBER,
18735          p_current_invoice_status       IN OUT NOCOPY VARCHAR2,
18736          p_calling_sequence             IN            VARCHAR2) RETURN BOOLEAN
18737 IS
18738 
18739   dist_set_check_failure      EXCEPTION;
18740   current_calling_sequence    VARCHAR2(2000);
18741   debug_info                  VARCHAR2(500);
18742   l_current_invoice_status    VARCHAR2(1) := 'Y';
18743   l_dist_set_id
18744       NUMBER(15) := p_invoice_lines_rec.distribution_set_id;
18745   l_dist_set_id_per_name      NUMBER(15);
18746   l_inactive_date             DATE;
18747   l_inactive_date_per_name    DATE;
18748   l_total_percent_distribution
18749     AP_DISTRIBUTION_SETS.TOTAL_PERCENT_DISTRIBUTION%TYPE;
18750   l_dset_lines_tab            AP_IMPORT_VALIDATION_PKG.dset_line_tab_type;
18751   l_expd_item_date            ap_invoice_lines.expenditure_item_date%TYPE:= '';
18752   l_error_found               VARCHAR2(1);
18753   i                           BINARY_INTEGER := 0;
18754   l_running_total_amount      NUMBER := 0;
18755   l_running_total_base_amt    NUMBER := 0;
18756   l_max_amount                NUMBER := 0;
18757   l_max_i                     BINARY_INTEGER := 0;
18758   l_running_total_pa_qty      NUMBER := 0;
18759   l_max_pa_quantity           NUMBER := 0;
18760   l_max_i_pa_qty              BINARY_INTEGER := 0;
18761   l_first_pa_qty              BOOLEAN := TRUE;
18762   l_award_set_id              AP_DISTRIBUTION_SET_LINES.award_id%TYPE;
18763   l_award_id                  AP_DISTRIBUTION_SET_LINES.award_id%TYPE;
18764   l_msg_application           VARCHAR2(25);
18765   l_msg_type                  VARCHAR2(25);
18766   l_msg_token1                VARCHAR2(30);
18767   l_msg_token2                VARCHAR2(30);
18768   l_msg_token3                VARCHAR2(30);
18769   l_msg_count                 NUMBER;
18770   l_msg_data                  VARCHAR2(500);
18771   l_billable_flag             VARCHAR2(60) := '';
18772   l_overlayed_ccid            NUMBER;
18773   l_unbuilt_flex              VARCHAR2(240):='';
18774   l_reason_unbuilt_flex       VARCHAR2(2000):='';
18775 
18776 
18777   CURSOR dist_set_lines IS
18778   SELECT DSL.dist_code_combination_id,
18779          DSL.percent_distribution,
18780          DSL.type_1099,
18781          DSL.description,
18782          DSL.distribution_set_line_number,
18783          DSL.attribute_category,
18784          DSL.attribute1,
18785          DSL.attribute2,
18786          DSL.attribute3,
18787          DSL.attribute4,
18788          DSL.attribute5,
18789          DSL.attribute6,
18790          DSL.attribute7,
18791          DSL.attribute8,
18792          DSL.attribute9,
18793          DSL.attribute10,
18794          DSL.attribute11,
18795          DSL.attribute12,
18796          DSL.attribute13,
18797          DSL.attribute14,
18798          DSL.attribute15,
18799          'DIST_SET_LINE',
18800          DSL.project_accounting_context,
18801          DSL.project_id,
18802          DSL.task_id,
18803          DSL.expenditure_organization_id,
18804          DSL.expenditure_type,
18805          NULL, -- pa_quantity
18806          NULL, -- pa_addition_flag
18807          DSL.org_id,
18808          DSL.award_id,
18809          0,    -- amount
18810          0     -- base_amount
18811     FROM ap_distribution_set_lines DSL
18812    WHERE DSL.distribution_set_id = l_dist_set_id
18813    ORDER BY distribution_set_line_number;
18814 
18815    l_sys_link_function varchar2(2); ---bugfix:5725904
18816   BEGIN
18817     -- Update the calling sequence
18818     --
18819     current_calling_sequence :='AP_IMPORT_VALIDATION_PKG.v_check_line_dist_set'
18820                                || '<-' ||P_calling_sequence;
18821 
18822     ------------------------------------------------------------------------
18823     -- Step 1
18824     -- Validate Distribution Set Id
18825     ------------------------------------------------------------------------
18826     debug_info := '(Check Line Dist Set 1) Validate Distribution Set Id';
18827     ------------------------------------------------------------------------
18828     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
18829       AP_IMPORT_UTILITIES_PKG.Print(
18830           AP_IMPORT_INVOICES_PKG.g_debug_switch,
18831           debug_info);
18832     END IF;
18833 
18834     BEGIN
18835       IF (p_invoice_lines_rec.distribution_set_id IS NOT NULL) THEN
18836         SELECT distribution_set_id , inactive_date, total_percent_distribution
18837           INTO l_dist_set_id, l_inactive_date, l_total_percent_distribution
18838           FROM ap_distribution_sets
18839          WHERE distribution_set_id = p_invoice_lines_rec.distribution_set_id;
18840       END IF;
18841 
18842       IF (p_invoice_lines_rec.distribution_set_name IS NOT NULL) THEN
18843         SELECT distribution_set_id , inactive_date, total_percent_distribution
18844           INTO l_dist_set_id_per_name, l_inactive_date_per_name,
18845            l_total_percent_distribution
18846           FROM ap_distribution_sets
18847          WHERE distribution_set_name
18848                = p_invoice_lines_rec.distribution_set_name;
18849       END IF;
18850 
18851     EXCEPTION
18852       WHEN no_data_found THEN
18853         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
18854                 AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
18855                 p_invoice_lines_rec.invoice_line_id,
18856                 'INVALID DISTRIBUTION SET',
18857                 p_default_last_updated_by,
18858                 p_default_last_update_login,
18859                 current_calling_sequence) <> TRUE) THEN
18860           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
18861             AP_IMPORT_UTILITIES_PKG.Print(
18862                 AP_IMPORT_INVOICES_PKG.g_debug_switch,
18863                 'insert_rejections<- '||current_calling_sequence);
18864           END IF;
18865           RAISE dist_set_check_failure;
18866         END IF;
18867 
18868         l_current_invoice_status := 'N';
18869         p_current_invoice_status := l_current_invoice_status;
18870       RETURN (TRUE);
18871     END;
18872 
18873 
18874     IF ((l_dist_set_id is NOT NULL) AND
18875         (l_dist_set_id_per_name is NOT NULL) AND
18876         (l_dist_set_id <> l_dist_set_id_per_name)) Then
18877       -----------------------------------------------------------------------
18878       -- Step 2
18879       -- Check for INCONSISTENT DIST SET
18880       -----------------------------------------------------------------------
18881       debug_info := '(Check Line Dist Set 2) Check for INCONSISTENT DIST SET';
18882       -----------------------------------------------------------------------
18883       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
18884         AP_IMPORT_UTILITIES_PKG.Print(
18885             AP_IMPORT_INVOICES_PKG.g_debug_switch,
18886             debug_info);
18887       End if;
18888 
18889       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
18890               AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
18891               p_invoice_lines_rec.invoice_line_id,
18892               'INCONSISTENT DIST SET',
18893               p_default_last_updated_by,
18894               p_default_last_update_login,
18895               current_calling_sequence) <> TRUE) THEN
18896         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
18897           AP_IMPORT_UTILITIES_PKG.Print(
18898               AP_IMPORT_INVOICES_PKG.g_debug_switch,
18899               'insert_rejections<-' ||current_calling_sequence);
18900         END IF;
18901         RAISE dist_set_check_failure;
18902       END IF;
18903 
18904       l_current_invoice_status := 'N';
18905 
18906     ELSE
18907       ----------------------------------------------------------------------
18908       -- Step 3
18909       -- look for inactive DIST SET
18910       ----------------------------------------------------------------------
18911       debug_info := '(Check Line Dist Set 3.1) Check for inactive DIST SET';
18912       ----------------------------------------------------------------------
18913       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
18914         AP_IMPORT_UTILITIES_PKG.Print(
18915             AP_IMPORT_INVOICES_PKG.g_debug_switch,
18916             debug_info);
18917       END IF;
18918 
18919       IF (( AP_IMPORT_INVOICES_PKG.g_inv_sysdate >=
18920             nvl(trunc(l_inactive_date), AP_IMPORT_INVOICES_PKG.g_inv_sysdate+1))
18921             OR
18922            (AP_IMPORT_INVOICES_PKG.g_inv_sysdate >=
18923             nvl(trunc(l_inactive_date_per_name),
18924                 AP_IMPORT_INVOICES_PKG.g_inv_sysdate+1))) THEN
18925 
18926         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
18927                 AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
18928                 p_invoice_lines_rec.invoice_line_id,
18929                 'INACTIVE DISTRIBUTION SET',
18930                 p_default_last_updated_by,
18931                 p_default_last_update_login,
18932                 current_calling_sequence) <> TRUE) THEN
18933           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
18934             AP_IMPORT_UTILITIES_PKG.Print(
18935                 AP_IMPORT_INVOICES_PKG.g_debug_switch,
18936                 'insert_rejections<- '||current_calling_sequence);
18937           END IF;
18938           RAISE dist_set_check_failure;
18939         END IF; -- end of insert_rejection
18940 
18941         l_current_invoice_status := 'N';
18942       END IF;  -- end of check l_active_date
18943       ----------------------------------------------------------------------
18944       debug_info := '(Check Line Dist Set 3.2) Use dist_set_id_per_name';
18945       ----------------------------------------------------------------------
18946       IF ((l_dist_set_id is Null) AND
18947           (l_dist_set_id_per_name is Not Null)) THEN
18948 
18949         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
18950           AP_IMPORT_UTILITIES_PKG.Print(
18951               AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
18952         END IF;
18953         l_dist_set_id := l_dist_set_id_per_name;
18954       END IF;
18955     END IF; -- end of step 2 and step 3
18956 
18957     ----------------------------------------------------------------------
18958     -- Step 4
18959     -- Validate the info. in distribution set lines before proceeding
18960     -- further. At this point we have validated the basic distribution
18961     -- set information.  Now we need to validate project, task,
18962     -- expenditure details and award for each distribution set lines.
18963     -- Also we need to validate the account and overlayed accounts if any.
18964     ----------------------------------------------------------------------
18965     IF (l_dist_set_id is not null) THEN
18966       --------------------------------------------------------------------
18967       debug_info := '(v_check_line_dist_set 4.1) Get all ' ||
18968                     'the information in the distribution sets';
18969       --------------------------------------------------------------------
18970       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
18971           AP_IMPORT_UTILITIES_PKG.Print(
18972               AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
18973       END IF;
18974       l_dset_lines_tab.DELETE;
18975       OPEN dist_set_lines;
18976       FETCH dist_set_lines BULK COLLECT INTO l_dset_lines_tab;
18977       CLOSE dist_set_lines;
18978 
18979 
18980       ------------------------------------------------------------------
18981       debug_info := '(v_check_line_dist_set 4.2) Loop through read '||
18982                 'dset lines and validate';
18983       ------------------------------------------------------------------
18984       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
18985           AP_IMPORT_UTILITIES_PKG.Print(
18986         AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
18987       END IF;
18988 
18989       FOR i IN l_dset_lines_tab.first..l_dset_lines_tab.last
18990       LOOP
18991 
18992         ----------------------------------------------------------------
18993      debug_info := '(v_check_line_dist_set 4.2.a) Get expenditure '||
18994       'item date if null and dist set line will be project related';
18995     ----------------------------------------------------------------
18996         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
18997           AP_IMPORT_UTILITIES_PKG.Print(
18998               AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
18999         END IF;
19000 
19001         IF (p_invoice_lines_rec.expenditure_item_date IS NULL AND
19002         l_expd_item_date IS NULL AND
19003         (p_invoice_lines_rec.project_id IS NOT NULL OR
19004          l_dset_lines_tab(i).project_id IS NOT NULL)) THEN
19005           l_expd_item_date := AP_INVOICES_PKG.get_expenditure_item_date(
19006                  p_invoice_rec.invoice_id,
19007                  p_invoice_rec.invoice_date,
19008                  nvl(p_invoice_lines_rec.accounting_date,
19009                      p_gl_date_from_get_info),
19010                  NULL,
19011                  NULL,
19012              l_error_found);
19013        IF (l_error_found = 'Y') then
19014              RAISE dist_set_check_failure;
19015            END IF;
19016         ELSIF (p_invoice_lines_rec.expenditure_item_date IS NOT NULL AND
19017            l_expd_item_date IS NULL) THEN
19018           l_expd_item_date := p_invoice_lines_rec.expenditure_item_date;
19019         END IF;
19020 
19021         -----------------------------------------------------------------
19022     debug_info := '(v_check_line_dist_set 4.2.b) Populate amount '||
19023       'and base amount for the distribution into PL/SQL table';
19024     -----------------------------------------------------------------
19025     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
19026           AP_IMPORT_UTILITIES_PKG.Print(
19027               AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
19028         END IF;
19029         IF (l_total_percent_distribution <> 100) THEN
19030           l_dset_lines_tab(i).amount := 0;
19031       l_dset_lines_tab(i).base_amount := 0;
19032     ELSE
19033       l_dset_lines_tab(i).amount := AP_UTILITIES_PKG.Ap_Round_Currency(
19034                               NVL(l_dset_lines_tab(i).percent_distribution,0)
19035                      * NVL(p_invoice_lines_rec.amount,0)/100,
19036                   p_invoice_rec.invoice_currency_code);
19037           l_dset_lines_tab(i).base_amount :=
19038                           AP_UTILITIES_PKG.Ap_Round_Currency(
19039                  NVL(l_dset_lines_tab(i).amount, 0)
19040                  * NVL(p_invoice_rec.exchange_rate, 1),
19041                                  p_base_currency_code);
19042         END IF;
19043 
19044     --
19045     -- Maintain the running totals of the amounts for rounding
19046     l_running_total_amount := l_running_total_amount +
19047       l_dset_lines_tab(i).amount;
19048     l_running_total_base_amt := l_running_total_base_amt +
19049       l_dset_lines_tab(i).base_amount;
19050 
19051     -- Keep track of the particular distribution with the max
19052     -- amount.  That is the distribution that will take the
19053     -- rounding if any.
19054         IF (ABS(l_max_amount) <= ABS(l_dset_lines_tab(i).amount) OR
19055         i = 0) THEN
19056           l_max_amount := l_dset_lines_tab(i).amount;
19057       l_max_i := i;
19058     END IF;
19059 
19060     ----------------------------------------------------------------
19061     debug_info := '(v_check_line_dist_set 4.2.c) Populate project '||
19062       'info if either dist set line has it or invoice line has it';
19063     -------------------------------------------------------------------
19064     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
19065           AP_IMPORT_UTILITIES_PKG.Print(
19066               AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
19067     END IF;
19068 
19069     -- If the distribution set line does not contain project
19070     -- information but the line does, then copy project information
19071     -- from the line.
19072     IF (l_dset_lines_tab(i).project_id IS NULL AND
19073          p_invoice_lines_rec.project_id IS NOT NULL) THEN
19074       l_dset_lines_tab(i).project_source := 'INVOICE_LINE';
19075       l_dset_lines_tab(i).project_accounting_context := 'Yes';
19076           l_dset_lines_tab(i).project_id := p_invoice_lines_rec.project_id;
19077       l_dset_lines_tab(i).task_id := p_invoice_lines_rec.task_id;
19078           l_dset_lines_tab(i).expenditure_type :=
19079         p_invoice_lines_rec.expenditure_type;
19080       l_dset_lines_tab(i).expenditure_organization_id :=
19081         p_invoice_lines_rec.expenditure_organization_id;
19082     END IF;
19083 
19084     -- Regardless of where the project information came from,
19085     -- track the pa quantity but only if this is not a skeleton
19086     -- distribution set and only if the distribution turns out to
19087     -- be project related.
19088     IF (l_dset_lines_tab(i).project_id IS NOT NULL) THEN
19089       IF (l_total_percent_distribution <> 100) THEN
19090         NULL;
19091       ELSE
19092         IF (p_invoice_lines_rec.pa_quantity IS NOT NULL AND
19093             p_invoice_lines_rec.amount <> 0) THEN
19094           l_dset_lines_tab(i).pa_quantity :=
19095       			     p_invoice_lines_rec.pa_quantity
19096                				* l_dset_lines_tab(i).amount /
19097                				p_invoice_lines_rec.amount;
19098         END IF;
19099       END IF;
19100 
19101       -- Keep track of the particular distribution with the max
19102       -- pa quantity.  That is the distribution that will take the
19103       -- rounding if any.
19104       IF (l_first_pa_qty AND
19105           l_dset_lines_tab(i).pa_quantity IS NOT NULL) THEN
19106             l_max_pa_quantity := l_dset_lines_tab(i).pa_quantity;
19107             l_max_i_pa_qty := i;
19108             l_first_pa_qty := FALSE;
19109       ELSIF (l_dset_lines_tab(i).pa_quantity IS NOT NULL AND
19110              NOT l_first_pa_qty ) THEN
19111         IF (ABS(l_max_pa_quantity) <=
19112             ABS(l_dset_lines_tab(i).pa_quantity)) THEN
19113           l_max_pa_quantity := l_dset_lines_tab(i).pa_quantity;
19114           l_max_i_pa_qty := i;
19115         END IF;
19116       END IF;
19117 
19118       l_running_total_pa_qty := Nvl(l_dset_lines_tab(i).pa_quantity,0);
19119       l_dset_lines_tab(i).pa_addition_flag := 'N';
19120 
19121     ELSE
19122       l_dset_lines_tab(i).pa_addition_flag := 'E';
19123 
19124     END IF; -- project id is not null
19125 
19126     -----------------------------------------------------------------
19127     debug_info := '(v_check_line_dist_set 4.2.d) Populate/validate '||
19128       'award information';
19129     -----------------------------------------------------------------
19130     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
19131           AP_IMPORT_UTILITIES_PKG.Print(
19132               AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
19133         END IF;
19134     --
19135     -- Default award id from line if award id is not populated
19136     -- for the distribution set line.
19137     --
19138         IF ( l_current_invoice_status = 'Y') THEN
19139 
19140 	   IF (l_dset_lines_tab(i).award_id IS NOT NULL) THEN
19141 	       l_award_set_id := l_dset_lines_tab(i).award_id;
19142 	   ELSIF (p_invoice_lines_rec.award_id IS NOT NULL) THEN
19143 	      l_dset_lines_tab(i).award_id := p_invoice_lines_rec.award_id;
19144 	      l_award_id := p_invoice_lines_rec.award_id;
19145 	   END IF;
19146 
19147 	   IF (l_award_set_id IS NOT NULL) THEN
19148 	       GMS_AP_API.GET_DIST_SET_AWARD(
19149 		                l_dist_set_id,
19150 		                l_dset_lines_tab(i).distribution_set_line_number,
19151 		                l_award_set_id,
19152 		                l_award_id);
19153 
19154 	      l_dset_lines_tab(i).award_id:= l_award_id ;
19155 	  END IF;
19156 
19157 
19158           debug_info := '(v_check_line_dist_set 4.2.d.1) - ' ||
19159                         'Call GMS API to validate award info->temp award dist';
19160           IF ( AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' ) THEN
19161             AP_IMPORT_UTILITIES_PKG.Print(
19162                 AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
19163           END IF;
19164 
19165           ----------------------------------------------------------------
19166           debug_info := '(v_check_line_dist_set 4.2.d.1) - ' ||
19167                         'Get award id from award set from GMS' ;
19168           ----------------------------------------------------------------
19169           IF ( AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' ) THEN
19170             AP_IMPORT_UTILITIES_PKG.Print(
19171                 AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
19172           END IF;
19173           -- Get the value of award_id from GMS API
19174           -- Note that the award in the distribution set line or interface
19175           -- invoice line record is truly an award set id, we need GMS
19176           -- to derive the actual award id and the same must be stored in
19177           -- the distributions when they are created.
19178           -- The call is commented out because it does not exist in 11.6 yet.
19179           IF (l_award_set_id IS NOT NULL) THEN
19180              GMS_AP_API.GET_DIST_SET_AWARD(
19181                 l_dist_set_id,
19182                 l_dset_lines_tab(i).distribution_set_line_number,
19183                 l_award_set_id,
19184                 l_award_id);
19185           END IF;
19186 
19187           ---------------------------------------------------------------------
19188           debug_info := '(v_check_line_dist_set 4.2.d.2) - ' ||
19189                         'Call GMS API - validate award -l_award_id->' ||
19190                          to_char(l_award_id) ;
19191           ---------------------------------------------------------------------
19192           IF ( AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' ) THEN
19193             AP_IMPORT_UTILITIES_PKG.Print(
19194                 AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
19195           END IF;
19196 
19197           /*Bug#10235692 - passing 'APTXNIMP' to p_calling_sequence */
19198           IF (GMS_AP_API.v_check_line_award_info (
19199               p_invoice_line_id  => p_invoice_lines_rec.invoice_line_id,
19200               p_line_amount      => l_dset_lines_tab(i).amount,
19201               p_base_line_amount => l_dset_lines_tab(i).base_amount,
19202               p_dist_code_concatenated   =>
19203             			          p_invoice_lines_rec.dist_code_concatenated,
19204               p_dist_code_combination_id =>
19205         			          l_dset_lines_tab(i).dist_code_combination_id,
19206               p_default_po_number        => NULL,
19207               p_po_number                => NULL,
19208               p_po_header_id             => NULL,
19209               p_distribution_set_id      => l_dist_set_id,
19210               p_distribution_set_name    =>
19211                 			p_invoice_lines_rec.distribution_set_name ,
19212               p_set_of_books_id          => p_set_of_books_id,
19213               p_base_currency_code       => p_base_currency_code,
19214               p_invoice_currency_code    =>
19215                 			p_invoice_rec.invoice_currency_code ,
19216               p_exchange_rate            => p_invoice_rec.exchange_rate,
19217               p_exchange_rate_type       =>
19218                 			p_invoice_rec.exchange_rate_type,
19219               p_exchange_rate_date       =>
19220                 			p_invoice_rec.exchange_date,
19221               p_project_id               => l_dset_lines_tab(i).project_id,
19222               p_task_id                  => l_dset_lines_tab(i).task_id,
19223               p_expenditure_type         =>
19224             				l_dset_lines_tab(i).expenditure_type,
19225               p_expenditure_item_date    => l_expd_item_date,
19226               p_expenditure_organization_id =>
19227                 			l_dset_lines_tab(i).expenditure_organization_id,
19228               p_project_accounting_context =>
19229             				l_dset_lines_tab(i).project_accounting_context,
19230               p_pa_addition_flag           =>
19231             				l_dset_lines_tab(i).pa_addition_flag,
19232               p_pa_quantity                =>
19233                 			l_dset_lines_tab(i).pa_quantity,
19234               p_employee_id                => p_employee_id,
19235               p_vendor_id                  => p_invoice_rec.vendor_id,
19236               p_chart_of_accounts_id       => p_chart_of_accounts_id,
19237               p_pa_installed               => p_pa_installed,
19238               p_prorate_across_flag        =>
19239                 			NVL(p_invoice_lines_rec.prorate_across_flag, 'N'),
19240               p_lines_attribute_category   =>
19241                 			p_invoice_lines_rec.attribute_category,
19242               p_lines_attribute1   => p_invoice_lines_rec.attribute1,
19243               p_lines_attribute2   => p_invoice_lines_rec.attribute2,
19244               p_lines_attribute3   => p_invoice_lines_rec.attribute3,
19245               p_lines_attribute4   => p_invoice_lines_rec.attribute4,
19246               p_lines_attribute5   => p_invoice_lines_rec.attribute5,
19247               p_lines_attribute6   => p_invoice_lines_rec.attribute6,
19248               p_lines_attribute7   => p_invoice_lines_rec.attribute7,
19249               p_lines_attribute8   => p_invoice_lines_rec.attribute8,
19250               p_lines_attribute9   => p_invoice_lines_rec.attribute9,
19251               p_lines_attribute10  => p_invoice_lines_rec.attribute10,
19252               p_lines_attribute11  => p_invoice_lines_rec.attribute11,
19253               p_lines_attribute12  => p_invoice_lines_rec.attribute12,
19254               p_lines_attribute13  => p_invoice_lines_rec.attribute13,
19255               p_lines_attribute14  => p_invoice_lines_rec.attribute14,
19256               p_lines_attribute15  => p_invoice_lines_rec.attribute15,
19257               p_attribute_category => l_dset_lines_tab(i).attribute_category,
19258               p_attribute1         => l_dset_lines_tab(i).attribute1,
19259               p_attribute2         => l_dset_lines_tab(i).attribute2,
19260               p_attribute3         => l_dset_lines_tab(i).attribute3,
19261               p_attribute4         => l_dset_lines_tab(i).attribute4,
19262               p_attribute5         => l_dset_lines_tab(i).attribute5,
19263               p_attribute6         => l_dset_lines_tab(i).attribute6,
19264               p_attribute7         => l_dset_lines_tab(i).attribute7,
19265               p_attribute8         => l_dset_lines_tab(i).attribute8,
19266               p_attribute9         => l_dset_lines_tab(i).attribute9,
19267               p_attribute10        => l_dset_lines_tab(i).attribute10,
19268               p_attribute11        => l_dset_lines_tab(i).attribute11,
19269               p_attribute12        => l_dset_lines_tab(i).attribute12,
19270               p_attribute13        => l_dset_lines_tab(i).attribute13,
19271               p_attribute14        => l_dset_lines_tab(i).attribute14,
19272               p_attribute15        => l_dset_lines_tab(i).attribute15,
19273               p_partial_segments_flag      =>
19274                                    p_invoice_lines_rec.partial_segments,
19275               p_default_last_updated_by    => p_default_last_updated_by,
19276               p_default_last_update_login  => p_default_last_update_login,
19277               p_calling_sequence   => 'APTXNIMP',
19278               p_award_id           => l_award_id,
19279               p_event              => 'AWARD_SET_ID_REQUEST' ) <> TRUE ) THEN
19280             --------------------------------------------------------------
19281             debug_info := '(v_check_line_dist_set 4.2.d.3) - ' ||
19282                           'After Call GMS API - Invalid GMS Info:Reject';
19283             --------------------------------------------------------------
19284             IF ( AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' ) THEN
19285               AP_IMPORT_UTILITIES_PKG.Print(
19286                  AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
19287             END IF;
19288 
19289             IF ( AP_IMPORT_UTILITIES_PKG.insert_rejections(
19290                      AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
19291                       p_invoice_lines_rec.invoice_line_id,
19292                       'INSUFFICIENT GMS INFO',
19293                       p_default_last_updated_by,
19294                       p_default_last_update_login,
19295                       current_calling_sequence) <> TRUE) THEN
19296               RAISE dist_set_check_failure;
19297             END IF;
19298             l_current_invoice_status := 'N';
19299           END IF; -- End of gms_ap_api.v_check_line_award_info.
19300         END IF; -- end of check l_current_invoice_status
19301 
19302         -----------------------------------------------------------
19303         debug_info := '(v_check_line_dist_set 4.2.e) - ' ||
19304                   'Validate project information';
19305         -----------------------------------------------------------
19306         IF ( AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' ) THEN
19307           AP_IMPORT_UTILITIES_PKG.Print(
19308              AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
19309         END IF;
19310         IF (l_dset_lines_tab(i).project_id is not null AND
19311         l_current_invoice_status = 'Y') THEN
19312 
19313 	  --bugfxi:5725904
19314 	  If (p_invoice_rec.invoice_type_lookup_code ='EXPENSE REPORT') Then
19315 	        l_sys_link_function :='ER' ;
19316 	  Else
19317 	        l_sys_link_function :='VI' ;
19318 	  End if;
19319 
19320           PA_TRANSACTIONS_PUB.VALIDATE_TRANSACTION(
19321             X_PROJECT_ID          => l_dset_lines_tab(i).project_id,
19322             X_TASK_ID             => l_dset_lines_tab(i).task_id,
19323             X_EI_DATE             => l_expd_item_date,
19324             X_EXPENDITURE_TYPE    => l_dset_lines_tab(i).expenditure_type,
19325             X_NON_LABOR_RESOURCE  => null,
19326             X_PERSON_ID           => p_employee_id,
19327             X_QUANTITY            => NVL(l_dset_lines_tab(i).pa_quantity,'1'),
19328             X_denom_currency_code => p_invoice_rec.invoice_currency_code,
19329             X_acct_currency_code  => p_base_currency_code,
19330             X_denom_raw_cost      => l_dset_lines_tab(i).amount,
19331             X_acct_raw_cost       => l_dset_lines_tab(i).base_amount,
19332             X_acct_rate_type      => p_invoice_rec.exchange_rate_type,
19333             X_acct_rate_date      => p_invoice_rec.exchange_date,
19334             X_acct_exchange_rate  => p_invoice_rec.exchange_rate,
19335             X_TRANSFER_EI         => null,
19336             X_INCURRED_BY_ORG_ID  =>
19337           	l_dset_lines_tab(i).expenditure_organization_id,
19338             X_NL_RESOURCE_ORG_ID  => null,
19339             X_TRANSACTION_SOURCE  => l_sys_link_function,--Bug 3487412 --bug:5725904
19340             X_CALLING_MODULE      => 'apiimptb.pls',
19341             X_VENDOR_ID           => p_invoice_rec.vendor_id,
19342             X_ENTERED_BY_USER_ID  => to_number(FND_GLOBAL.USER_ID),
19343             X_ATTRIBUTE_CATEGORY  => l_dset_lines_tab(i).attribute_category,
19344             X_ATTRIBUTE1          => l_dset_lines_tab(i).attribute1,
19345             X_ATTRIBUTE2          => l_dset_lines_tab(i).attribute2,
19346             X_ATTRIBUTE3          => l_dset_lines_tab(i).attribute3,
19347             X_ATTRIBUTE4          => l_dset_lines_tab(i).attribute4,
19348             X_ATTRIBUTE5          => l_dset_lines_tab(i).attribute5,
19349             X_ATTRIBUTE6          => l_dset_lines_tab(i).attribute6,
19350             X_ATTRIBUTE7          => l_dset_lines_tab(i).attribute7,
19351             X_ATTRIBUTE8          => l_dset_lines_tab(i).attribute8,
19352             X_ATTRIBUTE9          => l_dset_lines_tab(i).attribute9,
19353             X_ATTRIBUTE10         => l_dset_lines_tab(i).attribute10,
19354             X_ATTRIBUTE11         => l_dset_lines_tab(i).attribute11,
19355             X_ATTRIBUTE12         => l_dset_lines_tab(i).attribute12,
19356             X_ATTRIBUTE13         => l_dset_lines_tab(i).attribute13,
19357             X_ATTRIBUTE14         => l_dset_lines_tab(i).attribute14,
19358             X_ATTRIBUTE15         => l_dset_lines_tab(i).attribute15,
19359             X_msg_application     => l_msg_application,
19360             X_msg_type            => l_msg_type,
19361             X_msg_token1          => l_msg_token1,
19362             X_msg_token2          => l_msg_token2,
19363             X_msg_token3          => l_msg_token3,
19364             X_msg_count           => l_msg_count,
19365             X_msg_data            => l_msg_data,
19366             X_BILLABLE_FLAG       => l_billable_flag,
19367             P_Document_Type       => p_invoice_rec.invoice_type_lookup_code,
19368             P_Document_Line_Type  => p_invoice_lines_rec.line_type_lookup_code);
19369 
19370           IF (l_msg_data IS NOT NULL) THEN
19371             --------------------------------------------------------------
19372          debug_info := '(v_check_line_dist_set 4.2.e.1) - Project '
19373                       ||'validate '
19374                           ||'PA_TRANSACTIONS_PUB.VALIDATE_TRANSACTION Fails'
19375                           ||'->Insert Rejection';
19376             --------------------------------------------------------------
19377             IF ( AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' ) THEN
19378               AP_IMPORT_UTILITIES_PKG.Print(
19379                   AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
19380             END IF;
19381 
19382              -- Bug 5214592 . Added the debug message.
19383              debug_info := SUBSTR(l_msg_data,1,80);
19384              IF ( AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' ) THEN
19385               AP_IMPORT_UTILITIES_PKG.Print(
19386                   AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
19387               END IF;
19388 
19389 
19390             IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
19391                       AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
19392                       p_invoice_lines_rec.invoice_line_id,
19393                       'PA FLEXBUILD FAILED',
19394                       p_default_last_updated_by,
19395                       p_default_last_update_login,
19396                       current_calling_sequence) <> TRUE) THEN
19397               RAISE dist_set_check_failure;
19398             END IF;
19399 
19400             l_current_invoice_status := 'N';
19401 
19402           END IF; -- end of check l_msg_data is not null
19403         END IF;-- end of l_project_id not null/l_current_invoice_status = 'Y'
19404 
19405         -----------------------------------------------------------------
19406         -- Validate account and account overlay depending on set of
19407     -- available data
19408         --
19409         debug_info := '(v_check_line_dist_set 4.2.f) - ' ||
19410                       'validate account';
19411         -----------------------------------------------------------------
19412         IF ( AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' ) THEN
19413           AP_IMPORT_UTILITIES_PKG.Print(
19414               AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
19415         END IF;
19416 
19417         IF ((l_dset_lines_tab(i).project_id IS NULL AND
19418          p_invoice_lines_rec.dist_code_combination_id IS NULL) OR
19419         (l_dset_lines_tab(i).project_id IS NOT NULL AND
19420          l_dset_lines_tab(i).project_source <> 'INVOICE_LINE')) THEN
19421       --
19422           -- Account source is not at the line. Overlay may happen.
19423           -- We need to avoid redoing the account validations done
19424       -- at the line.  If there is no default account (dist_code
19425       -- combination_id at the line is null) and either there is
19426       -- no project info in this distribution or the project info
19427       -- does not come from the line, then new account sources
19428       -- are considered and we do need to validate.
19429       --
19430           IF (p_invoice_lines_rec.dist_code_combination_id IS NULL AND
19431               p_invoice_lines_rec.dist_code_concatenated is NULL AND
19432               p_invoice_lines_rec.balancing_segment is NULL AND
19433               p_invoice_lines_rec.account_segment is NULL AND
19434               p_invoice_lines_rec.cost_center_segment is NULL) THEN
19435 
19436             -------------------------------------------------------------
19437         	debug_info := '(v_check_line_dist_set 4.2.f.1) - ' ||
19438                   'validate account from dist set line - no overlay';
19439             -------------------------------------------------------------
19440             IF ( AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' ) THEN
19441               AP_IMPORT_UTILITIES_PKG.Print(
19442                 AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
19443             END IF;
19444 
19445             IF ( NOT (AP_UTILITIES_PKG.IS_CCID_VALID(
19446                         l_dset_lines_tab(i).dist_code_combination_id,
19447                 	p_chart_of_accounts_id,
19448             		nvl(p_invoice_lines_rec.accounting_date,
19449                         p_gl_date_from_get_info),
19450                   	current_calling_sequence))) THEN
19451               IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
19452                     AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
19453                     p_invoice_lines_rec.invoice_line_id,
19454                     'INVALID DISTRIBUTION ACCT',
19455                     p_default_last_updated_by,
19456                     p_default_last_update_login,
19457                     current_calling_sequence) <> TRUE) THEN
19458                 RAISE dist_set_check_failure;
19459               END IF;
19460 
19461               l_current_invoice_status := 'N';
19462 
19463             END IF; -- end of call function IS_CCID_VALID
19464 
19465           --
19466       -- Again don't overlay and validate if the concatenated segments
19467       -- is other than partial, since that has already been done at
19468       -- line level and that would completely override the dist set line
19469           -- account so, no new validation would be performed.
19470       --
19471           ELSIF (p_invoice_lines_rec.dist_code_combination_id IS NULL AND
19472          (p_invoice_lines_rec.dist_code_concatenated IS NOT NULL OR
19473           p_invoice_lines_rec.balancing_segment is NOT NULL OR
19474                   p_invoice_lines_rec.account_segment is NOT NULL OR
19475                   p_invoice_lines_rec.cost_center_segment is NOT NULL)) THEN
19476         --
19477             -- Make sure we don't go through the overlay and validation
19478             -- if the concatenated segments was full or if the line is
19479         -- project related and projects does not allow override
19480         --
19481         -- 7531219 need to do overlay and validate even in case of full overlay
19482         -- as we are not doing earlier
19483 
19484             IF (/*(p_invoice_lines_rec.dist_code_concatenated IS NULL OR
19485          (p_invoice_lines_rec.dist_code_concatenated IS NOT NULL AND
19486           p_invoice_lines_rec.partial_segments <> 'N')) AND */
19487         (l_dset_lines_tab(i).project_id IS NULL OR
19488          AP_IMPORT_INVOICES_PKG.g_pa_allows_overrides = 'Y')) THEN
19489           l_overlayed_ccid := l_dset_lines_tab(i).dist_code_combination_id;
19490 
19491           -----------------------------------------------------------
19492           debug_info := '(v_check_line_dist_set 4.2.f.2) - ' ||
19493                  'overlay dist set line account with line overlay data';
19494               -----------------------------------------------------------
19495               IF ( AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' ) THEN
19496                   AP_IMPORT_UTILITIES_PKG.Print(
19497                       AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
19498               END IF;
19499               IF ( NOT (AP_UTILITIES_PKG.OVERLAY_SEGMENTS (
19500                           p_invoice_lines_rec.balancing_segment,
19501                           p_invoice_lines_rec.cost_center_segment,
19502                           p_invoice_lines_rec.account_segment,
19503                           p_invoice_lines_rec.dist_code_concatenated,
19504                           l_overlayed_ccid,
19505                           p_set_of_books_id,
19506                           'CREATE_COMB_NO_AT',
19507                           l_unbuilt_flex,
19508                           l_reason_unbuilt_flex,
19509                           FND_GLOBAL.RESP_APPL_ID,
19510                           FND_GLOBAL.RESP_ID,
19511                           FND_GLOBAL.USER_ID,
19512                           current_calling_sequence,
19513                           NULL,
19514                           p_invoice_lines_rec.accounting_date))) THEN  --7531219
19515         --------------------------------------------------------
19516         debug_info := 'Failure found during overlay';
19517         debug_info := debug_info || '-> l_unbuilt_flex= ' ||
19518                             l_unbuilt_flex ||
19519                             '-> l_dist_ccid=' ||
19520                             to_char(l_overlayed_ccid);
19521                 --------------------------------------------------------
19522                 IF ( AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' ) THEN
19523                   AP_IMPORT_UTILITIES_PKG.Print(
19524                       AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
19525                 END IF;
19526                 RAISE dist_set_check_failure;
19527           ELSE
19528             IF (l_overlayed_ccid = -1) THEN
19529               ----------------------------------------------------------
19530               -- debug_info := 'Overlay return -1';
19531           ----------------------------------------------------------
19532                   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
19533             AP_IMPORT_UTILITIES_PKG.Print(
19534                       AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
19535                   END IF;
19536 
19537                   IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
19538                       AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
19539                        p_invoice_lines_rec.invoice_line_id,
19540                       'INVALID ACCT OVERLAY',
19541                        p_default_last_updated_by,
19542                        p_default_last_update_login,
19543                        current_calling_sequence) <> TRUE) THEN
19544                     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
19545           		    AP_IMPORT_UTILITIES_PKG.Print(
19546              			AP_IMPORT_INVOICES_PKG.g_debug_switch,
19547                          	  'insert_rejections<-'||current_calling_sequence);
19548                     END IF;
19549                     RAISE dist_set_check_failure;
19550 
19551                   END IF;
19552 
19553                   l_current_invoice_status := 'N';
19554 
19555                 END IF; -- Code combination id is -1
19556 
19557               END IF; -- Overlay returned other than TRUE
19558 
19559             END IF; -- Overlay info is available, and we should try overlay
19560 
19561           END IF; -- Overaly info is available
19562 
19563         END IF; -- The distribution may require overlay or at least validation
19564                -- of the account since the account won't come from the line
19565             -- which has already validated its account/overlay.
19566 
19567         -------------------------------------------------------------------
19568         -- Call Grants - Clean up
19569         --
19570         debug_info := '(v_check_line_dist_set 4.2.g) - ' ||
19571                       'AWARD_ID_REMOVE: Check  GMS Info ';
19572         -------------------------------------------------------------------
19573         IF (l_current_invoice_status = 'Y' AND l_award_id is not null) THEN
19574           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
19575             AP_IMPORT_UTILITIES_PKG.Print(
19576               AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
19577           END IF;
19578 
19579 	  GMS_AP_API.validate_transaction
19580               ( x_project_id		=> l_dset_lines_tab(i).project_id,
19581 		x_task_id		=> l_dset_lines_tab(i).task_id,
19582 		x_award_id		=> l_award_id,
19583 		x_expenditure_type	=> l_dset_lines_tab(i).expenditure_type,
19584 		x_expenditure_item_date => l_expd_item_date,
19585 		x_calling_sequence      => 'AWARD_SET_ID', /*Bug12356959: Changed calling sequence to AWARD_SET_ID*/
19586 		x_msg_application       => l_msg_application,
19587 		x_msg_type              => l_msg_type,
19588 		x_msg_count             => l_msg_count,
19589 		x_msg_data              => l_msg_data ) ;
19590 
19591 	  IF (l_msg_data IS NOT NULL) THEN
19592 	      --------------------------------------------------------------
19593 	      debug_info := '(v_check_line_dist_set 4.2.d.3) - ' ||
19594 				'After Call GMS API - Invalid GMS Info:Reject';
19595 	      --------------------------------------------------------------
19596 	      IF ( AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' ) THEN
19597 	           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
19598 	      END IF;
19599 
19600 	      IF ( AP_IMPORT_UTILITIES_PKG.insert_rejections(
19601 	      	      	      AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
19602 	      	      	      p_invoice_lines_rec.invoice_line_id,
19603 	      	      	      'INSUFFICIENT GMS INFO',
19604 	      	      	      p_default_last_updated_by,
19605 	      	      	      p_default_last_update_login,
19606 	      	      	      current_calling_sequence) <> TRUE) THEN
19607 
19608 	      	      RAISE dist_set_check_failure;
19609 	      END IF;
19610 	      l_current_invoice_status := 'N';
19611 	  END IF;
19612 
19613         END IF; -- l_current_invoice_Status ='Y' AND l_award_id is not null
19614 
19615       END LOOP;
19616 
19617       -----------------------------------------------------------------------
19618       -- Step 5 - Re-Validate PA info if it is not a skeleton distribution set
19619       -- and there was rounding in the amount
19620       -----------------------------------------------------------------------
19621 
19622       IF ( l_current_invoice_status = 'Y'  AND
19623            l_total_percent_distribution = 100 AND
19624        (p_invoice_lines_rec.amount <> l_running_total_amount OR
19625         p_invoice_lines_rec.base_amount <> l_running_total_base_amt OR
19626         Nvl(p_invoice_lines_rec.pa_quantity, 0) <>
19627         Nvl(l_running_total_pa_qty,0))) THEN
19628 
19629     --
19630     -- If rounding in the amount for a project related distribution
19631     -- then lump all rounding onto the same distribution.
19632     -- Else, find the distribution for any pa quantity rounding.
19633     --
19634     IF (l_dset_lines_tab(l_max_i).project_id IS NOT NULL) THEN
19635 
19636           l_dset_lines_tab(l_max_i).amount := l_dset_lines_tab(l_max_i).amount
19637         + p_invoice_lines_rec.amount
19638         - l_running_total_amount;
19639       l_dset_lines_tab(l_max_i).base_amount :=
19640         l_dset_lines_tab(l_max_i).base_amount
19641         + p_invoice_lines_rec.base_amount
19642         - l_running_total_base_amt;
19643       IF (l_dset_lines_tab(l_max_i).pa_quantity IS NOT NULL) THEN
19644           l_dset_lines_tab(l_max_i).pa_quantity :=
19645           l_dset_lines_tab(l_max_i).pa_quantity
19646           + p_invoice_lines_rec.pa_quantity
19647           - l_running_total_pa_qty;
19648       END IF;
19649 
19650     ELSIF l_dset_lines_tab.exists(l_max_i_pa_qty) THEN  -- Bug 5713771
19651       IF   (l_dset_lines_tab(l_max_i_pa_qty).project_id IS NOT NULL AND
19652            l_dset_lines_tab(l_max_i_pa_qty).pa_quantity IS NOT NULL) THEN
19653 
19654         l_dset_lines_tab(l_max_i_pa_qty).pa_quantity :=
19655         l_dset_lines_tab(l_max_i_pa_qty).pa_quantity
19656         + p_invoice_lines_rec.pa_quantity
19657         - l_running_total_pa_qty;
19658         l_max_i := l_max_i_pa_qty;
19659       END IF;
19660     END IF;
19661 
19662     IF (l_dset_lines_tab(l_max_i).project_id IS NOT NULL) THEN
19663 
19664           If (p_invoice_rec.invoice_type_lookup_code ='EXPENSE REPORT') Then
19665               l_sys_link_function :='ER' ;
19666           Else
19667 	      l_sys_link_function :='VI' ;
19668 	  End if;
19669 
19670           PA_TRANSACTIONS_PUB.VALIDATE_TRANSACTION(
19671           X_PROJECT_ID          => l_dset_lines_tab(l_max_i).project_id,
19672           X_TASK_ID             => l_dset_lines_tab(l_max_i).task_id,
19673           X_EI_DATE             => l_expd_item_date,
19674           X_EXPENDITURE_TYPE    => l_dset_lines_tab(l_max_i).expenditure_type,
19675           X_NON_LABOR_RESOURCE  => null,
19676           X_PERSON_ID           => p_employee_id,
19677           X_QUANTITY            => Nvl(l_dset_lines_tab(l_max_i).pa_quantity,
19678                                        '1'),
19679           X_denom_currency_code => p_invoice_rec.invoice_currency_code,
19680           X_acct_currency_code  => p_base_currency_code,
19681           X_denom_raw_cost      => l_dset_lines_tab(l_max_i).amount,
19682           X_acct_raw_cost       => l_dset_lines_tab(l_max_i).base_amount,
19683           X_acct_rate_type      => p_invoice_rec.exchange_rate_type,
19684           X_acct_rate_date      => p_invoice_rec.exchange_date,
19685           X_acct_exchange_rate  => p_invoice_rec.exchange_rate,
19686           X_TRANSFER_EI         => null,
19687           X_INCURRED_BY_ORG_ID  =>
19688              l_dset_lines_tab(l_max_i).expenditure_organization_id,
19689           X_NL_RESOURCE_ORG_ID  => null,
19690           X_TRANSACTION_SOURCE  => l_sys_link_function,--Bug 3487412 made the change
19691           X_CALLING_MODULE      => 'apiimptb.pls',
19692           X_VENDOR_ID           => p_invoice_rec.vendor_id,
19693           X_ENTERED_BY_USER_ID  => to_number(FND_GLOBAL.USER_ID),
19694           X_ATTRIBUTE_CATEGORY  =>
19695               l_dset_lines_tab(l_max_i).attribute_category,
19696           X_ATTRIBUTE1          => l_dset_lines_tab(l_max_i).attribute1,
19697           X_ATTRIBUTE2          => l_dset_lines_tab(l_max_i).attribute2,
19698           X_ATTRIBUTE3          => l_dset_lines_tab(l_max_i).attribute3,
19699           X_ATTRIBUTE4          => l_dset_lines_tab(l_max_i).attribute4,
19700           X_ATTRIBUTE5          => l_dset_lines_tab(l_max_i).attribute5,
19701           X_ATTRIBUTE6          => l_dset_lines_tab(l_max_i).attribute6,
19702           X_ATTRIBUTE7          => l_dset_lines_tab(l_max_i).attribute7,
19703           X_ATTRIBUTE8          => l_dset_lines_tab(l_max_i).attribute8,
19704           X_ATTRIBUTE9          => l_dset_lines_tab(l_max_i).attribute9,
19705           X_ATTRIBUTE10         => l_dset_lines_tab(l_max_i).attribute10,
19706           X_ATTRIBUTE11         => l_dset_lines_tab(l_max_i).attribute11,
19707           X_ATTRIBUTE12         => l_dset_lines_tab(l_max_i).attribute12,
19708           X_ATTRIBUTE13         => l_dset_lines_tab(l_max_i).attribute13,
19709           X_ATTRIBUTE14         => l_dset_lines_tab(l_max_i).attribute14,
19710           X_ATTRIBUTE15         => l_dset_lines_tab(l_max_i).attribute15,
19711           X_msg_application     => l_msg_application,
19712           X_msg_type            => l_msg_type,
19713           X_msg_token1          => l_msg_token1,
19714           X_msg_token2          => l_msg_token2,
19715           X_msg_token3          => l_msg_token3,
19716           X_msg_count           => l_msg_count,
19717           X_msg_data            => l_msg_data,
19718           X_BILLABLE_FLAG       => l_billable_flag,
19719           P_Document_Type       => p_invoice_rec.invoice_type_lookup_code,
19720           P_Document_Line_Type  => p_invoice_lines_rec.line_type_lookup_code);
19721           IF (l_msg_data IS NOT NULL) THEN
19722             -----------------------------------------------------------------
19723             debug_info := '(v_check_line_dist_set 5.1) - Project validate '
19724                             || 'PA_TRANSACTIONS_PUB.VALIDATE_TRANSACTION Fails'
19725                             || 'for rounding ->Insert Rejection';
19726             -----------------------------------------------------------------
19727             IF ( AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' ) THEN
19728               AP_IMPORT_UTILITIES_PKG.Print(
19729                     AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
19730             END IF;
19731 
19732             IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
19733                       AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
19734                       p_invoice_lines_rec.invoice_line_id,
19735                       'PA FLEXBUILD FAILED',
19736                       p_default_last_updated_by,
19737                       p_default_last_update_login,
19738                       current_calling_sequence) <> TRUE) THEN
19739               RAISE dist_set_check_failure;
19740             END IF;
19741 
19742             l_current_invoice_status := 'N';
19743 
19744           END IF; -- end of check l_msg_data is not null
19745         END IF; -- end of check l_project_id is not null
19746 
19747       END IF;  -- rounding existed
19748 
19749       l_dset_lines_tab.DELETE;
19750 
19751     END IF; -- end of l_dist_set_id is not null
19752 
19753 
19754     IF  (l_current_invoice_status <> 'N') THEN
19755       IF (l_dist_set_id is not NULL) THEN
19756         p_invoice_lines_rec.distribution_set_id := l_dist_set_id;
19757       END IF;
19758     END IF;
19759 
19760     p_current_invoice_status := l_current_invoice_status;
19761     RETURN (TRUE);
19762 
19763   EXCEPTION
19764     WHEN OTHERS THEN
19765       -- Clean up
19766       IF ( Dist_Set_Lines%ISOPEN ) THEN
19767         CLOSE Dist_Set_Lines;
19768       END IF;
19769       l_dset_lines_tab.DELETE;
19770 
19771       debug_info := '(v_check_line_dist_set ) -> ' ||
19772       'exception occurs ->' ;
19773       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
19774         AP_IMPORT_UTILITIES_PKG.Print(
19775             AP_IMPORT_INVOICES_PKG.g_debug_switch,
19776             debug_info);
19777       END IF;
19778 
19779       IF (SQLCODE < 0) THEN
19780         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
19781             AP_IMPORT_UTILITIES_PKG.Print(
19782                 AP_IMPORT_INVOICES_PKG.g_debug_switch,
19783                 SQLERRM);
19784         END IF;
19785       END IF;
19786       RETURN(FALSE);
19787 END v_check_line_dist_set;
19788 
19789 ------------------------------------------------------------------------------
19790 -- This function is used to validate qty/UOM information for non PO/RCV
19791 -- matched lines
19792 --
19793 ------------------------------------------------------------------------------
19794 FUNCTION v_check_qty_uom_non_po (
19795          p_invoice_rec  IN  AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
19796          p_invoice_lines_rec IN OUT NOCOPY AP_IMPORT_INVOICES_PKG.r_line_info_rec,
19797          p_default_last_updated_by      IN            NUMBER,
19798          p_default_last_update_login    IN            NUMBER,
19799          p_current_invoice_status       IN OUT NOCOPY VARCHAR2,
19800          p_calling_sequence             IN            VARCHAR2) RETURN BOOLEAN
19801 
19802 IS
19803 
19804 qty_uom_check_failure            EXCEPTION;
19805 l_uom_is_valid                       VARCHAR2(30);
19806 l_current_invoice_status         VARCHAR2(1) := 'Y';
19807 current_calling_sequence          VARCHAR2(2000);
19808 debug_info                       VARCHAR2(500);
19809 
19810 BEGIN
19811   -- Update the calling sequence
19812   --
19813   current_calling_sequence :=
19814     'AP_IMPORT_VALIDATION_PKG.v_check_qty_uom_non_po <-'||P_calling_sequence;
19815 
19816   IF (p_invoice_lines_rec.po_header_id is NOT NULL OR
19817       p_invoice_lines_rec.rcv_transaction_id is NOT NULL) THEN
19818     --------------------------------------------------------------------------
19819     -- Step 1
19820     -- Nothing to do since this is PO/RCV matched
19821     --------------------------------------------------------------------------
19822     debug_info := '(Check Qty UOM non PO 1) Nothing to do.';
19823     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
19824       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
19825                                     debug_info);
19826     END IF;
19827 
19828     p_current_invoice_status := l_current_invoice_status;
19829     RETURN (TRUE);
19830 
19831   ELSE
19832     -------------------------------------------------------------------------
19833     -- Step 2
19834     -- Check that if quantity related information was provided the line type
19835     -- is Item
19836     -------------------------------------------------------------------------
19837     debug_info :=
19838       '(Check Qty UOM non PO 2) Check Qty related information vs line type.';
19839     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
19840       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
19841                                     debug_info);
19842     END IF;
19843 
19844     IF (p_invoice_lines_rec.line_type_lookup_code NOT IN ( 'ITEM', 'RETROITEM') AND
19845         (p_invoice_lines_rec.quantity_invoiced IS NOT NULL OR
19846          p_invoice_lines_rec.unit_of_meas_lookup_code IS NOT NULL OR
19847          p_invoice_lines_rec.unit_price IS NOT NULL)) THEN
19848       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
19849          AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
19850           p_invoice_lines_rec.invoice_line_id,
19851          'INVALID QTY INFO',
19852           p_default_last_updated_by,
19853           p_default_last_update_login,
19854           current_calling_sequence) <> TRUE) THEN
19855         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
19856           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
19857             'insert_rejections<-'||current_calling_sequence);
19858         END IF;
19859         RAISE qty_uom_check_failure;
19860       END IF;
19861 
19862       l_current_invoice_status := 'N';
19863 
19864     END IF;
19865     /* Bug 5763126 Checking in step 3 is not required
19866      --The validation is already done in step 2
19867     --------------------------------------------------------------------------
19868     -- Step 3
19869     -- Check that if quantity related information  was provided so was the UOM.
19870     --  Only do this check for Item lines.
19871     -------------------------------------------------------------------------
19872     debug_info := '(Check Qty UOM non PO 3) Check Qty information vs UOM';
19873     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
19874       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
19875                                     debug_info);
19876     END IF;
19877 
19878     IF (p_invoice_lines_rec.line_type_lookup_code  IN ('ITEM', 'RETROITEM') AND
19879         (p_invoice_lines_rec.quantity_invoiced IS NOT NULL OR
19880          p_invoice_lines_rec.unit_price IS NOT NULL) AND
19881         p_invoice_lines_rec.unit_of_meas_lookup_code is NULL) THEN
19882 
19883       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
19884            AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
19885            p_invoice_lines_rec.invoice_line_id,
19886           'INCOMPLETE QTY INFO',
19887             p_default_last_updated_by,
19888             p_default_last_update_login,
19889             current_calling_sequence) <> TRUE) THEN
19890         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
19891           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
19892             'insert_rejections<-'||current_calling_sequence);
19893         END IF;
19894         RAISE qty_uom_check_failure;
19895       END IF;
19896 
19897       l_current_invoice_status := 'N';
19898 
19899     END IF;
19900        */   -- Bug 5763126 End
19901     -------------------------------------------------------------------------
19902     -- Step 4
19903     -- Check that if UOM is provided, then either quantity invoiced is
19904     -- provided or can be derived from amount and unit price.  Only do this
19905     -- check for Item lines. Also derive unit price if possible and verify
19906     -- consistency of unit price, qty and amount for the line.
19907     -------------------------------------------------------------------------
19908     debug_info := '(Check Qty UOM non PO 4) Check Qty information when UOM '
19909                   ||'populated';
19910     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
19911       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
19912                                    debug_info);
19913     END IF;
19914 
19915     IF (p_invoice_lines_rec.line_type_lookup_code IN  ('ITEM', 'RETROITEM') AND
19916         p_invoice_lines_rec.unit_of_meas_lookup_code IS NOT NULL) THEN
19917       -----------------------------------------------------------------------
19918       -- Step 4a
19919       -- If quantity invoiced is null and unit price and line amount are not,
19920       -- derive the quantity invoiced.
19921       -----------------------------------------------------------------------
19922       IF (p_invoice_lines_rec.quantity_invoiced is NULL) THEN
19923         debug_info := '(Check Qty UOM non PO 4a) Qty invoiced is null.  Try '
19924                        ||'to derive it';
19925         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
19926           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
19927                                         debug_info);
19928         END IF;
19929 
19930         IF (p_invoice_lines_rec.amount IS NOT NULL AND
19931             p_invoice_lines_rec.unit_price IS NOT NULL) THEN
19932          IF (p_invoice_lines_rec.unit_price = 0) THEN
19933             p_invoice_lines_rec.quantity_invoiced :=
19934               p_invoice_lines_rec.amount;
19935           ELSE
19936             p_invoice_lines_rec.quantity_invoiced :=
19937               p_invoice_lines_rec.amount / p_invoice_lines_rec.unit_price;
19938           END IF;
19939 
19940         ELSE -- We dont have enough data to get quantity invoiced
19941           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
19942               AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
19943               p_invoice_lines_rec.invoice_line_id,
19944              'INCOMPLETE QTY INFO',
19945               p_default_last_updated_by,
19946               p_default_last_update_login,
19947               current_calling_sequence) <> TRUE) THEN
19948             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
19949               AP_IMPORT_UTILITIES_PKG.Print(
19950                 AP_IMPORT_INVOICES_PKG.g_debug_switch,
19951                'insert_rejections<-'||current_calling_sequence);
19952             END IF;
19953             RAISE qty_uom_check_failure;
19954           END IF;
19955           l_current_invoice_status := 'N';
19956         END IF; -- amount and unit price are not null
19957       END IF; -- quantity invoiced is null
19958 
19959       -----------------------------------------------------------------------
19960       -- Step 4b
19961       -- If quantity invoiced provided, verify that it is non 0
19962       --
19963       -----------------------------------------------------------------------
19964       IF (p_invoice_lines_rec.quantity_invoiced is NOT NULL AND
19965           p_invoice_lines_rec.quantity_invoiced = 0) THEN
19966         debug_info := '(Check Qty UOM non PO 4b) Verify qty invoice is non 0';
19967         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
19968           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
19969                                         debug_info);
19970         END IF;
19971 
19972         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
19973             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
19974             p_invoice_lines_rec.invoice_line_id,
19975             'INVALID QTY INFO',
19976              p_default_last_updated_by,
19977              p_default_last_update_login,
19978              current_calling_sequence) <> TRUE) THEN
19979           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
19980             AP_IMPORT_UTILITIES_PKG.Print(
19981                  AP_IMPORT_INVOICES_PKG.g_debug_switch,
19982             'insert_rejections<-'||current_calling_sequence);
19983           END IF;
19984           RAISE qty_uom_check_failure;
19985         END IF;
19986       END IF;
19987 
19988       ------------------------------------------------------------------------
19989       -- Step 4c
19990       -- If quantity invoiced and line amount are not null but unit price is
19991       -- null, derive unit price.
19992       ------------------------------------------------------------------------
19993       IF (p_invoice_lines_rec.quantity_invoiced is NOT NULL AND
19994           p_invoice_lines_rec.amount is NOT NULL AND
19995           p_invoice_lines_rec.unit_price is NULL) THEN
19996         debug_info :=
19997           '(Check Qty UOM non PO 4c) Unit price is null.  Try to derive it';
19998         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
19999           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
20000             debug_info);
20001         END IF;
20002         IF (p_invoice_lines_rec.quantity_invoiced <> 0) THEN
20003           p_invoice_lines_rec.unit_price := p_invoice_lines_rec.amount/
20004                                  p_invoice_lines_rec.quantity_invoiced;
20005         END IF;
20006       END IF;
20007 
20008       -----------------------------------------------------------------------
20009       -- Step 4d
20010       -- If quantity invoiced, unit_price and line amount are populated,
20011       -- verify consistency.
20012       ------------------------------------------------------------------------
20013       IF (p_invoice_lines_rec.quantity_invoiced is NOT NULL AND
20014           p_invoice_lines_rec.unit_price is NOT NULL AND
20015           p_invoice_lines_rec.amount is NOT NULL AND
20016           p_invoice_lines_rec.amount <> ap_utilities_pkg.ap_round_currency(
20017                  p_invoice_lines_rec.quantity_invoiced *
20018                  p_invoice_lines_rec.unit_price,
20019                  p_invoice_rec.invoice_currency_code)) THEN
20020         debug_info :=
20021           '(Check Qty UOM non PO 4d) Verify consistency in qty information';
20022         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
20023           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
20024                                         debug_info);
20025         End if;
20026         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
20027                 AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
20028                 p_invoice_lines_rec.invoice_line_id,
20029                'INCONSISTENT QTY RELATED INFO',
20030                 p_default_last_updated_by,
20031                 p_default_last_update_login,
20032                 current_calling_sequence) <> TRUE) THEN
20033           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
20034             AP_IMPORT_UTILITIES_PKG.Print(
20035               AP_IMPORT_INVOICES_PKG.g_debug_switch,
20036               'insert_rejections<-'||current_calling_sequence);
20037           END IF;
20038           RAISE qty_uom_check_failure;
20039         END IF;
20040         l_current_invoice_status := 'N';
20041       END IF;
20042 
20043       ------------------------------------------------------------------------
20044       -- Step 4e
20045       -- Verify unit of measure provided is valid.
20046       --
20047       ------------------------------------------------------------------------
20048       debug_info :=
20049         '(Check Qty UOM non PO 4e) Verify unit of measure is valid';
20050       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
20051         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
20052                                       debug_info);
20053       END IF;
20054       BEGIN
20055         SELECT 'Valid UOM'
20056           INTO l_uom_is_valid
20057           FROM mtl_units_of_measure
20058          WHERE unit_of_measure = p_invoice_lines_rec.unit_of_meas_lookup_code
20059            AND AP_IMPORT_INVOICES_PKG.g_inv_sysdate
20060             < nvl(disable_date, AP_IMPORT_INVOICES_PKG.g_inv_sysdate + 1) ;
20061       EXCEPTION
20062         WHEN no_data_found THEN
20063           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
20064               AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
20065               p_invoice_lines_rec.invoice_line_id,
20066               'INVALID UOM',
20067                p_default_last_updated_by,
20068                p_default_last_update_login,
20069                current_calling_sequence) <> TRUE) THEN
20070             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
20071               AP_IMPORT_UTILITIES_PKG.Print(
20072                 AP_IMPORT_INVOICES_PKG.g_debug_switch,
20073                'insert_rejections<-'||current_calling_sequence);
20074             END IF;
20075             RAISE qty_uom_check_failure;
20076           END IF;
20077           l_current_invoice_status := 'N';
20078       END;
20079 
20080     END IF; -- line type is ITEM and unit of measure is not null
20081   END IF; -- po header id or rcv transaction id are not null
20082 
20083   p_current_invoice_status := l_current_invoice_status;
20084   RETURN (TRUE);
20085 
20086 EXCEPTION
20087   WHEN OTHERS THEN
20088     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
20089       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
20090                                     debug_info);
20091     END IF;
20092 
20093     IF (SQLCODE < 0) then
20094       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
20095         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
20096                                       SQLERRM);
20097       END IF;
20098     END IF;
20099     RETURN(FALSE);
20100 
20101 END v_check_qty_uom_non_po;
20102 
20103 
20104 -----------------------------------------------------------------------------
20105 -- This function is used to validate line level awt group information.
20106 -----------------------------------------------------------------------------
20107 FUNCTION v_check_invalid_line_awt_group (
20108    p_invoice_rec          IN     AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
20109    p_invoice_lines_rec    IN OUT NOCOPY AP_IMPORT_INVOICES_PKG.r_line_info_rec,
20110    p_default_last_updated_by     IN            NUMBER,
20111    p_default_last_update_login   IN            NUMBER,
20112    p_current_invoice_status      IN OUT NOCOPY VARCHAR2,
20113    p_calling_sequence            IN            VARCHAR2) RETURN BOOLEAN
20114 IS
20115    awt_group_check_failure       EXCEPTION;
20116    l_current_invoice_status      VARCHAR2(1) := 'Y';
20117    l_awt_group_id                NUMBER;
20118    l_awt_group_id_per_name       NUMBER;
20119    l_inactive_date               DATE;
20120    l_inactive_date_per_name      DATE;
20121    l_awt_include_tax_amt         VARCHAR2(1) := 'Y'; --Bug11728066
20122    current_calling_sequence      VARCHAR2(2000);
20123    debug_info                    VARCHAR2(500);
20124 
20125 
20126 BEGIN
20127   -- Update the calling sequence
20128   --
20129   current_calling_sequence :=
20130       'AP_IMPORT_VALIDATION_PKG.v_check_invalid_line_awt_group<-'
20131       ||P_calling_sequence;
20132 
20133   --Bug12612189
20134  select awt_include_tax_amt into l_awt_include_tax_amt
20135  from ap_system_parameters_all
20136  where ORG_ID=P_INVOICE_REC.ORG_ID;
20137 
20138  --bug12612189, start comment
20139  /*
20140  IF p_invoice_lines_rec.line_type_lookup_code ='TAX' --l_awt_include_tax_amt check
20141    and nvl(l_awt_include_tax_amt ,'N') <> 'Y' THEN
20142    p_invoice_lines_rec.awt_group_id := NULL;
20143  ELSE
20144  */ --bug12612189, end comment
20145 
20146   IF p_invoice_lines_rec.awt_group_id is not null THEN
20147     --validate awt_group_id
20148     SELECT group_id, inactive_date
20149       INTO l_awt_group_id, l_inactive_date
20150       FROM ap_awt_groups
20151      WHERE group_id = p_invoice_lines_rec.awt_group_id;
20152   END IF;
20153 
20154   IF (p_invoice_lines_rec.awt_group_name is NOT NULL) THEN
20155     --validate awt group name and retrieve awt group id
20156     SELECT group_id, inactive_date
20157       INTO l_awt_group_id_per_name, l_inactive_date_per_name
20158       FROM ap_awt_groups
20159      WHERE name = p_invoice_lines_rec.awt_group_name;
20160   END IF;
20161 
20162   IF (l_awt_group_id is NOT NULL) AND
20163      (l_awt_group_id_per_name is NOT NULL) AND
20164      (l_awt_group_id <> l_awt_group_id_per_name) THEN
20165 
20166     --------------------------------------------------------------------------
20167     -- Step 1
20168     -- Check for AWT Group Id and Group Name Inconsistency.
20169     --------------------------------------------------------------------------
20170     debug_info := '(Check AWT Group 1) Check for AWT Group Id and Group Name '
20171                   ||'Inconsistency.';
20172     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
20173       AP_IMPORT_UTILITIES_PKG.Print(
20174         AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
20175     END IF;
20176 
20177     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
20178         AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
20179          p_invoice_lines_rec.invoice_line_id,
20180         'INCONSISTENT AWT GROUP',
20181          p_default_last_updated_by,
20182          p_default_last_update_login,
20183          current_calling_sequence) <> TRUE) THEN
20184       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
20185         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
20186           'insert_rejections<-'||current_calling_sequence);
20187       END IF;
20188       RAISE awt_group_check_failure;
20189     END IF;
20190     l_current_invoice_status := 'N';
20191   ELSE
20192     --------------------------------------------------------------------------
20193     -- Step 2
20194     -- Check for Inactive AWT Group
20195     --------------------------------------------------------------------------
20196     debug_info := '(Check AWT Group 2) Check for Inactive AWT Group';
20197     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
20198       AP_IMPORT_UTILITIES_PKG.Print(
20199         AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
20200     END IF;
20201 
20202     IF ((l_awt_group_id IS NOT NULL AND
20203          l_awt_group_id_per_name IS NOT NULL) OR
20204         (l_awt_group_id IS NOT NULL AND
20205          l_awt_group_id_per_name IS NULL)) THEN
20206       IF AP_IMPORT_INVOICES_PKG.g_inv_sysdate >=
20207        NVL(l_inactive_date,
20208            AP_IMPORT_INVOICES_PKG.g_inv_sysdate+1) THEN
20209     --------------------------------------------------------------
20210         -- inactive AWT group (as per id)
20211         --------------------------------------------------------------
20212         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
20213              AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
20214               p_invoice_lines_rec.invoice_line_id,
20215              'INACTIVE AWT GROUP',
20216               p_default_last_updated_by,
20217               p_default_last_update_login,
20218               current_calling_sequence) <> TRUE) THEN
20219           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
20220             AP_IMPORT_UTILITIES_PKG.Print(
20221               AP_IMPORT_INVOICES_PKG.g_debug_switch,
20222               'insert_rejections<-'||current_calling_sequence);
20223           END IF;
20224           RAISE awt_group_check_failure;
20225         END IF;
20226         l_current_invoice_status := 'N';
20227       END IF;
20228     ELSIF ((l_awt_group_id is NULL) AND
20229            (l_awt_group_id_per_name is NOT NULL)) THEN
20230       IF AP_IMPORT_INVOICES_PKG.g_inv_sysdate >=
20231             nvl(l_inactive_date_per_name,
20232                 AP_IMPORT_INVOICES_PKG.g_inv_sysdate+1) THEN
20233         ---------------------------------------------------------------
20234         -- inactive AWT group (per name)
20235         --
20236         ---------------------------------------------------------------
20237         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
20238              AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
20239               p_invoice_lines_rec.invoice_line_id,
20240              'INACTIVE AWT GROUP',
20241               p_default_last_updated_by,
20242               p_default_last_update_login,
20243               current_calling_sequence) <> TRUE) THEN
20244           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
20245             AP_IMPORT_UTILITIES_PKG.Print(
20246               AP_IMPORT_INVOICES_PKG.g_debug_switch,
20247               'insert_rejections<-'||current_calling_sequence);
20248           END IF;
20249           RAISE awt_group_check_failure;
20250         END IF;
20251         l_current_invoice_status := 'N';
20252       END IF;
20253     END IF;
20254   END IF; -- inconsistent awt group
20255 
20256   IF (l_current_invoice_status <> 'N' AND
20257       p_invoice_lines_rec.awt_group_id IS NULL) THEN
20258     IF (l_awt_group_id_per_name is not null) THEN
20259       p_invoice_lines_rec.awt_group_id := l_awt_group_id_per_name;
20260     ELSIF (p_invoice_rec.awt_group_id is not null)
20261     AND not (nvl(l_awt_include_tax_amt ,'N') <> 'Y' and p_invoice_lines_rec.line_type_lookup_code ='TAX') THEN--bug12612189, added this line
20262       p_invoice_lines_rec.awt_group_id := p_invoice_rec.awt_group_id;
20263     END IF;
20264   END IF;
20265 
20266   --bug12612189, commented below line
20267   --END IF; --Bug11728066
20268 
20269   p_current_invoice_status := l_current_invoice_status;
20270   RETURN (TRUE);
20271 
20272 
20273 EXCEPTION
20274   WHEN no_data_found THEN
20275     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
20276        AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
20277         p_invoice_lines_rec.invoice_line_id,
20278        'INVALID AWT GROUP',
20279         p_default_last_updated_by,
20280         p_default_last_update_login,
20281         current_calling_sequence) <> TRUE) THEN
20282       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
20283         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
20284           'insert_rejections<-'||current_calling_sequence);
20285       END IF;
20286       RAISE awt_group_check_failure;
20287     END IF;
20288     l_current_invoice_status := 'N';
20289     p_current_invoice_status := l_current_invoice_status;
20290     RETURN (TRUE);
20291 
20292   WHEN OTHERS THEN
20293     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
20294       AP_IMPORT_UTILITIES_PKG.Print(
20295         AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
20296     END IF;
20297 
20298     IF (SQLCODE < 0) THEN
20299       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
20300         AP_IMPORT_UTILITIES_PKG.Print(
20301           AP_IMPORT_INVOICES_PKG.g_debug_switch, SQLERRM);
20302       END IF;
20303     END IF;
20304     RETURN(FALSE);
20305 
20306 END v_check_invalid_line_awt_group;
20307 
20308     --bug6639866
20309 ----------------------------------------------------------------------------
20310 -- This function is used to validate line level pay awt group information.
20311 -----------------------------------------------------------------------------
20312 FUNCTION v_check_invalid_line_pay_awt_g (
20313    p_invoice_rec          IN     AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
20314    p_invoice_lines_rec    IN OUT NOCOPY AP_IMPORT_INVOICES_PKG.r_line_info_rec,
20315    p_default_last_updated_by     IN            NUMBER,
20316    p_default_last_update_login   IN            NUMBER,
20317    p_current_invoice_status      IN OUT NOCOPY VARCHAR2,
20318    p_calling_sequence            IN            VARCHAR2) RETURN BOOLEAN
20319 IS
20320    pay_awt_group_check_failure       EXCEPTION;
20321    l_current_invoice_status      VARCHAR2(1) := 'Y';
20322    l_pay_awt_group_id                NUMBER;
20323    l_pay_awt_group_id_per_name       NUMBER;
20324    l_inactive_date               DATE;
20325    l_inactive_date_per_name      DATE;
20326    l_awt_include_tax_amt         VARCHAR2(1) := 'Y'; --11728066
20327    current_calling_sequence      VARCHAR2(2000);
20328    debug_info                    VARCHAR2(500);
20329 
20330 BEGIN
20331   -- Update the calling sequence
20332   --
20333   current_calling_sequence :=
20334       'AP_IMPORT_VALIDATION_PKG.v_check_invalid_line_pay_awt_g<-'
20335       ||P_calling_sequence;
20336 --Bug11728066
20337  select awt_include_tax_amt into l_awt_include_tax_amt
20338  from ap_system_parameters_all
20339  where org_id=p_invoice_rec.org_id;
20340 
20341  IF p_invoice_lines_rec.line_type_lookup_code ='TAX' --l_awt_include_tax_amt check
20342  and nvl(l_awt_include_tax_amt ,'N') <> 'Y' THEN
20343  p_invoice_lines_rec.pay_awt_group_id := NULL;
20344 ELSE
20345 
20346   IF p_invoice_lines_rec.pay_awt_group_id is not null THEN
20347     --validate pay_awt_group_id
20348     SELECT group_id, inactive_date
20349       INTO l_pay_awt_group_id, l_inactive_date
20350       FROM ap_awt_groups
20351      WHERE group_id = p_invoice_lines_rec.pay_awt_group_id;
20352   END IF;
20353 
20354   IF (p_invoice_lines_rec.pay_awt_group_name is NOT NULL) THEN
20355  --validate pay awt group name and retrieve pay awt group id
20356     SELECT group_id, inactive_date
20357       INTO l_pay_awt_group_id_per_name, l_inactive_date_per_name
20358       FROM ap_awt_groups
20359      WHERE name = p_invoice_lines_rec.pay_awt_group_name;
20360   END IF;
20361 
20362   IF (l_pay_awt_group_id is NOT NULL) AND
20363      (l_pay_awt_group_id_per_name is NOT NULL) AND
20364      (l_pay_awt_group_id <> l_pay_awt_group_id_per_name) THEN
20365 
20366     --------------------------------------------------------------------------
20367     -- Step 1
20368     -- Check for Pay AWT Group Id and Pay Group Name Inconsistency.
20369     --------------------------------------------------------------------------
20370     debug_info := '(Check Pay AWT Group 1) Check for Pay AWT Group Id and Pay Group Name '
20371                   ||'Inconsistency.';
20372     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
20373       AP_IMPORT_UTILITIES_PKG.Print(
20374         AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
20375     END IF;
20376 
20377     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
20378         AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
20379          p_invoice_lines_rec.invoice_line_id,
20380         'INCONSISTENT PAY AWT GROUP',
20381          p_default_last_updated_by,
20382          p_default_last_update_login,
20383          current_calling_sequence) <> TRUE) THEN
20384       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
20385         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
20386           'insert_rejections<-'||current_calling_sequence);
20387       END IF;
20388       RAISE pay_awt_group_check_failure;
20389     END IF;
20390  l_current_invoice_status := 'N';
20391   ELSE
20392     --------------------------------------------------------------------------
20393     -- Step 2
20394     -- Check for Inactive Pay AWT Group
20395     --------------------------------------------------------------------------
20396     debug_info := '(Check Pay AWT Group 2) Check for Inactive Pay AWT Group';
20397     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
20398       AP_IMPORT_UTILITIES_PKG.Print(
20399         AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
20400     END IF;
20401 
20402     IF ((l_pay_awt_group_id IS NOT NULL AND
20403          l_pay_awt_group_id_per_name IS NOT NULL) OR
20404         (l_pay_awt_group_id IS NOT NULL AND
20405          l_pay_awt_group_id_per_name IS NULL)) THEN
20406       IF AP_IMPORT_INVOICES_PKG.g_inv_sysdate >=
20407        NVL(l_inactive_date,
20408            AP_IMPORT_INVOICES_PKG.g_inv_sysdate+1) THEN
20409         --------------------------------------------------------------
20410         -- inactive pay AWT group (as per id)
20411         --------------------------------------------------------------
20412         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
20413              AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
20414               p_invoice_lines_rec.invoice_line_id,
20415              'INACTIVE PAY AWT GROUP',
20416               p_default_last_updated_by,
20417               p_default_last_update_login,
20418               current_calling_sequence) <> TRUE) THEN
20419           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
20420             AP_IMPORT_UTILITIES_PKG.Print(
20421               AP_IMPORT_INVOICES_PKG.g_debug_switch,
20422               'insert_rejections<-'||current_calling_sequence);
20423           END IF;
20424           RAISE pay_awt_group_check_failure;
20425         END IF;
20426         l_current_invoice_status := 'N';
20427       END IF;
20428     ELSIF ((l_pay_awt_group_id is NULL) AND
20429            (l_pay_awt_group_id_per_name is NOT NULL)) THEN
20430       IF AP_IMPORT_INVOICES_PKG.g_inv_sysdate >=
20431             nvl(l_inactive_date_per_name,
20432                 AP_IMPORT_INVOICES_PKG.g_inv_sysdate+1) THEN
20433         ---------------------------------------------------------------
20434         -- inactive pay AWT group (per name)
20435         --
20436         ---------------------------------------------------------------
20437         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
20438              AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
20439               p_invoice_lines_rec.invoice_line_id,
20440              'INACTIVE PAY AWT GROUP',
20441               p_default_last_updated_by,
20442               p_default_last_update_login,
20443               current_calling_sequence) <> TRUE) THEN
20444           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
20445             AP_IMPORT_UTILITIES_PKG.Print(
20446               AP_IMPORT_INVOICES_PKG.g_debug_switch,
20447               'insert_rejections<-'||current_calling_sequence);
20448           END IF;
20449           RAISE pay_awt_group_check_failure;
20450         END IF;
20451         l_current_invoice_status := 'N';
20452       END IF;
20453     END IF;
20454   END IF; -- inconsistent pay awt group
20455 
20456   IF (l_current_invoice_status <> 'N' AND
20457       p_invoice_lines_rec.pay_awt_group_id IS NULL) THEN
20458     IF (l_pay_awt_group_id_per_name is not null) THEN
20459       p_invoice_lines_rec.pay_awt_group_id := l_pay_awt_group_id_per_name;
20460  ELSIF (p_invoice_rec.pay_awt_group_id is not null) THEN
20461       p_invoice_lines_rec.pay_awt_group_id := p_invoice_rec.pay_awt_group_id;
20462     END IF;
20463   END IF;
20464   END IF;--Bug11728066
20465   p_current_invoice_status := l_current_invoice_status;
20466   RETURN (TRUE);
20467 
20468 
20469 EXCEPTION
20470   WHEN no_data_found THEN
20471     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
20472        AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
20473         p_invoice_lines_rec.invoice_line_id,
20474        'INVALID PAY AWT GROUP',
20475         p_default_last_updated_by,
20476         p_default_last_update_login,
20477         current_calling_sequence) <> TRUE) THEN
20478       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
20479         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
20480           'insert_rejections<-'||current_calling_sequence);
20481       END IF;
20482       RAISE pay_awt_group_check_failure;
20483     END IF;
20484     l_current_invoice_status := 'N';
20485     p_current_invoice_status := l_current_invoice_status;
20486     RETURN (TRUE);
20487 
20488   WHEN OTHERS THEN
20489     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
20490       AP_IMPORT_UTILITIES_PKG.Print(
20491         AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
20492     END IF;
20493 
20494     IF (SQLCODE < 0) THEN
20495       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
20496           AP_IMPORT_UTILITIES_PKG.Print(
20497           AP_IMPORT_INVOICES_PKG.g_debug_switch, SQLERRM);
20498       END IF;
20499     END IF;
20500     RETURN(FALSE);
20501 
20502 END v_check_invalid_line_pay_awt_g;
20503 
20504 
20505 -----------------------------------------------------------------------------
20506 -- This function is used to validate that there is no duplicate line number
20507 -----------------------------------------------------------------------------
20508 FUNCTION v_check_duplicate_line_num (
20509    p_invoice_rec     IN            AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
20510    p_invoice_lines_rec  IN OUT NOCOPY AP_IMPORT_INVOICES_PKG.r_line_info_rec,
20511    p_default_last_updated_by      IN            NUMBER,
20512    p_default_last_update_login    IN            NUMBER,
20513    p_current_invoice_status       IN OUT NOCOPY VARCHAR2,
20514    p_calling_sequence             IN            VARCHAR2) RETURN BOOLEAN
20515 IS
20516 
20517 line_num_check_failure        EXCEPTION;
20518 l_line_count                   NUMBER;
20519 l_current_invoice_status    VARCHAR2(1) := 'Y';
20520 current_calling_sequence    VARCHAR2(2000);
20521 debug_info                  VARCHAR2(500);
20522 
20523 BEGIN
20524   -- Update the calling sequence
20525   --
20526   current_calling_sequence :=
20527       'AP_IMPORT_VALIDATION_PKG.v_check_duplicate_line_num<-'
20528      ||P_calling_sequence;
20529 
20530   IF (p_invoice_lines_rec.line_number is NOT NULL) THEN
20531 
20532     --------------------------------------------------------------------------
20533     -- Step 1
20534     -- Check for Duplicate Line NUMBER.
20535     --------------------------------------------------------------------------
20536     debug_info := '(Check Duplicate Line Number 1) Check for Duplicate '
20537                   ||'Line Number.';
20538     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
20539       AP_IMPORT_UTILITIES_PKG.Print(
20540         AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
20541     END IF;
20542 
20543     SELECT count(*)
20544       INTO l_line_count
20545       FROM ap_invoice_lines_interface
20546      WHERE invoice_id = p_invoice_rec.invoice_id
20547        AND line_number = p_invoice_lines_rec.line_number;
20548 
20549     IF (l_line_count > 1) THEN
20550       debug_info := '(Check Duplicate Line Number 2) Duplicate Line '
20551                     ||'Number Found.';
20552       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
20553         AP_IMPORT_UTILITIES_PKG.Print(
20554           AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
20555       END IF;
20556 
20557       -- bug 2581097 added context for XML GATEWAY
20558       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
20559         AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
20560            p_invoice_lines_rec.invoice_line_id,
20561            'DUPLICATE LINE NUMBER',
20562            p_default_last_updated_by,
20563            p_default_last_update_login,
20564            current_calling_sequence,
20565            'Y',
20566            'INVOICE LINE NUMBER',
20567            p_invoice_lines_rec.line_number) <> TRUE) THEN
20568         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
20569           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
20570             'insert_rejections<-'||current_calling_sequence);
20571         END IF;
20572         RAISE line_num_check_failure;
20573       END IF;
20574       l_current_invoice_status := 'N';
20575     END IF;
20576   END IF;
20577 
20578   p_current_invoice_status := l_current_invoice_status;
20579   RETURN (TRUE);
20580 EXCEPTION
20581   WHEN OTHERS THEN
20582     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
20583       AP_IMPORT_UTILITIES_PKG.Print(
20584         AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
20585     END IF;
20586 
20587     IF (SQLCODE < 0) THEN
20588       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
20589         AP_IMPORT_UTILITIES_PKG.Print(
20590           AP_IMPORT_INVOICES_PKG.g_debug_switch,SQLERRM);
20591       END IF;
20592     END IF;
20593     RETURN(FALSE);
20594 
20595 END v_check_duplicate_line_num;
20596 
20597 
20598 -----------------------------------------------------------------------------
20599 -- This function is used to validate that miscellaneous line level information
20600 -----------------------------------------------------------------------------
20601 FUNCTION v_check_misc_line_info (
20602    p_invoice_rec          		  IN
20603 						AP_IMPORT_INVOICES_PKG.r_invoice_info_rec, --bug 7599916
20604    p_invoice_lines_rec   IN OUT NOCOPY AP_IMPORT_INVOICES_PKG.r_line_info_rec,
20605    p_default_last_updated_by      IN            NUMBER,
20606    p_default_last_update_login    IN            NUMBER,
20607    p_current_invoice_status       IN OUT NOCOPY VARCHAR2,
20608    p_calling_sequence             IN            VARCHAR2) RETURN BOOLEAN
20609 
20610 IS
20611 
20612 misc_line_info_failure        EXCEPTION;
20613 l_valid_info                VARCHAR2(1);
20614 l_current_invoice_status    VARCHAR2(1) := 'Y';
20615 current_calling_sequence    VARCHAR2(2000);
20616 debug_info                  VARCHAR2(500);
20617 -- Bug 5572876. Caching Income Tax Type and Income Tax Region
20618 l_key                            VARCHAR2(1000);
20619 l_numof_values                   NUMBER;
20620 l_valueOut                   fnd_plsql_cache.generic_cache_value_type;
20621 l_values                     fnd_plsql_cache.generic_cache_values_type;
20622 l_ret_code                      VARCHAR2(1);
20623 l_exception                     VARCHAR2(10);
20624 l_key1                          VARCHAR2(1000);
20625 l_numof_values1                 NUMBER;
20626 l_valueOut1                  fnd_plsql_cache.generic_cache_value_type;
20627 l_values1                    fnd_plsql_cache.generic_cache_values_type;
20628 l_ret_code1                  VARCHAR2(1);
20629 l_exception1                    VARCHAR2(10);
20630 l_income_tax_type               ap_income_tax_types.income_tax_type%TYPE;
20631 l_income_tax_region             ap_income_tax_regions.region_short_name%TYPE;
20632 
20633 -- Bug 9189995
20634 l_income_tax_region_flag        ap_system_parameters_all.income_tax_region_flag%TYPE;
20635 
20636         -- Bug 7599916
20637 	Cursor c_type_1099(c_vendor_id NUMBER) Is
20638 	Select pov.type_1099
20639 	From   po_vendors 		   pov
20640 	Where  pov.vendor_id    = c_vendor_id;
20641 	-- Bug 7599916
20642 
20643 BEGIN
20644   -- Update the calling sequence
20645   --
20646   current_calling_sequence :=
20647     'AP_IMPORT_VALIDATION_PKG.v_check_misc_line_info<-'
20648     ||P_calling_sequence;
20649 
20650   --Retropricing
20651   IF (nvl(p_invoice_lines_rec.line_type_lookup_code,'DUMMY')
20652      NOT IN ('FREIGHT','ITEM','MISCELLANEOUS','TAX','AWT', 'RETROITEM', 'RETROTAX')) THEN
20653 
20654     --------------------------------------------------------------------------
20655     -- Step 1
20656     -- Check for Invalid Line type lookup code.
20657     --------------------------------------------------------------------------
20658     debug_info :=
20659        '(Check Misc Line Info 1) Check for Invalid Line type lookup code.';
20660     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
20661       AP_IMPORT_UTILITIES_PKG.Print(
20662         AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
20663     END IF;
20664 
20665     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
20666       AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
20667          p_invoice_lines_rec.invoice_line_id,
20668          'INVALID LINE TYPE LOOKUP',
20669          p_default_last_updated_by,
20670          p_default_last_update_login,
20671          current_calling_sequence) <> TRUE) THEN
20672       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
20673         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
20674           'insert_rejections<-' ||current_calling_sequence);
20675       END IF;
20676       RAISE misc_line_info_failure;
20677     END IF;
20678 
20679     l_current_invoice_status := 'N';
20680 
20681   ELSIF (p_invoice_lines_rec.line_type_lookup_code ='AWT') THEN
20682 
20683     ----------------------------------------------------------------------
20684     -- Step 2
20685     -- Line type lookup code cannot be AWT
20686     ----------------------------------------------------------------------
20687     debug_info := '(Check Misc Line Info 2) Line type lookup code '
20688                   ||'cannot be AWT';
20689     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
20690       AP_IMPORT_UTILITIES_PKG.Print(
20691         AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
20692     END IF;
20693 
20694     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
20695       AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
20696        p_invoice_lines_rec.invoice_line_id,
20697        'LINE TYPE CANNOT BE AWT',
20698        p_default_last_updated_by,
20699        p_default_last_update_login,
20700        current_calling_sequence) <> TRUE) THEN
20701       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
20702         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
20703           'insert_rejections<-' ||current_calling_sequence);
20704       END IF;
20705       RAISE misc_line_info_failure;
20706     END IF;
20707     l_current_invoice_status := 'N';
20708   END IF; -- line type
20709 
20710     -- Bug 7599916
20711 	IF (p_invoice_lines_rec.type_1099 is NULL) THEN
20712 	--------------------------------------------------------------------------
20713     -- Step 3.1
20714     -- defaulting type_1099 from supplier if null in interface table
20715     --------------------------------------------------------------------------
20716 
20717 	debug_info := '(Check Misc Line Info 3) Defaulting type 1099 from
20718 	supplier';
20719     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
20720       AP_IMPORT_UTILITIES_PKG.Print(
20721         AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
20722     END IF;
20723 
20724 	Open  c_type_1099(p_invoice_rec.vendor_id);
20725 	Fetch c_type_1099 Into p_invoice_lines_rec.type_1099;
20726 	Close c_type_1099;
20727 
20728 	END IF;
20729 	-- Bug 7599916
20730 
20731    IF (p_invoice_lines_rec.type_1099 is NOT NULL) THEN
20732      -- Bug 9727834.
20733      -- Added 'NA' validation for type_1099.
20734      -- Setting type_1099 to null if 'NA'.
20735 
20736      IF (p_invoice_lines_rec.type_1099 = 'NA') THEN
20737         debug_info := '(Check Misc Line Info 3) Check Type 1099. ' ||
20738                        'Type 1099 is NA. Setting type 1099 to null.';
20739         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
20740            AP_IMPORT_UTILITIES_PKG.Print(
20741            AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
20742         END IF;
20743 
20744         p_invoice_lines_rec.type_1099 := null ;
20745      ELSE
20746 
20747     --------------------------------------------------------------------------
20748     -- Step 3.2
20749     -- Invalid type_1099
20750     --------------------------------------------------------------------------
20751     debug_info := '(Check Misc Line Info 3) Check Type 1099';
20752     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
20753       AP_IMPORT_UTILITIES_PKG.Print(
20754         AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
20755     END IF;
20756 
20757     -- Invalid Info
20758 
20759     l_key := p_invoice_lines_rec.type_1099;
20760 
20761     fnd_plsql_cache.generic_1tom_get_values(
20762               AP_IMPORT_INVOICES_PKG.lg_incometax_controller,
20763               AP_IMPORT_INVOICES_PKG.lg_incometax_storage,
20764               l_key,
20765               l_numof_values,
20766               l_values,
20767               l_ret_code);
20768 
20769     IF l_ret_code = '1' THEN --  means l_key found in cache
20770       l_income_tax_type := l_values(1).varchar2_1;
20771       l_exception   := l_values(1).varchar2_2;
20772       IF l_exception = 'TRUE' THEN
20773         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
20774           AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
20775            p_invoice_lines_rec.invoice_line_id,
20776           'INVALID TYPE 1099',
20777            p_default_last_updated_by,
20778            p_default_last_update_login,
20779            current_calling_sequence) <> TRUE) THEN
20780           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
20781             AP_IMPORT_UTILITIES_PKG.Print(
20782                AP_IMPORT_INVOICES_PKG.g_debug_switch,
20783               'insert_rejections<-' ||current_calling_sequence);
20784           END IF;
20785            RAISE misc_line_info_failure;
20786         END IF;
20787 
20788         l_current_invoice_status := 'N';
20789       END IF;
20790 
20791     ELSE -- IF l_key not found in cache(l_ret_code other than 1) .. cache it
20792       debug_info := '(Check Misc Line Info 3.1) Check Type 1099 in Else';
20793       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
20794         AP_IMPORT_UTILITIES_PKG.Print(
20795           AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
20796       END IF;
20797 
20798        BEGIN
20799         SELECT income_tax_type
20800         INTO l_income_tax_type
20801         FROM ap_income_tax_types
20802         WHERE income_tax_type = p_invoice_lines_rec.type_1099
20803          AND AP_IMPORT_INVOICES_PKG.g_inv_sysdate
20804            < NVL(inactive_date, AP_IMPORT_INVOICES_PKG.g_inv_sysdate+1) ;
20805 
20806         l_exception           := 'FALSE';
20807         l_valueOut.varchar2_1 := l_income_tax_type;
20808         l_valueOut.varchar2_2 := l_exception;
20809         l_values(1)           := l_valueOut;
20810         l_numof_values        := 1;
20811 
20812         fnd_plsql_cache.generic_1tom_put_values(
20813                   AP_IMPORT_INVOICES_PKG.lg_incometax_controller,
20814                   AP_IMPORT_INVOICES_PKG.lg_incometax_storage,
20815                   l_key,
20816                   l_numof_values,
20817                   l_values);
20818 
20819       EXCEPTION
20820         WHEN NO_DATA_FOUND THEN
20821           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
20822             AP_IMPORT_UTILITIES_PKG.Print(
20823             AP_IMPORT_INVOICES_PKG.g_debug_switch,
20824               '(v_check_misc_line_info 3) Invalid Type 1099');
20825           END IF;
20826 
20827           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
20828             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
20829             p_invoice_lines_rec.invoice_line_id,
20830            'INVALID TYPE 1099',
20831             p_default_last_updated_by,
20832             p_default_last_update_login,
20833             current_calling_sequence) <> TRUE) THEN
20834             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
20835               AP_IMPORT_UTILITIES_PKG.Print(
20836                AP_IMPORT_INVOICES_PKG.g_debug_switch,
20837               'insert_rejections<-' ||current_calling_sequence);
20838             END IF;
20839             RAISE misc_line_info_failure;
20840           END IF;
20841           --
20842           l_current_invoice_status := 'N';
20843           l_exception              := 'TRUE';
20844           l_valueOut.varchar2_1    := NULL;
20845           l_valueOut.varchar2_2    := l_exception;
20846           l_values(1)              := l_valueOut;
20847           l_numof_values           := 1;
20848 
20849             fnd_plsql_cache.generic_1tom_put_values(
20850                     AP_IMPORT_INVOICES_PKG.lg_incometax_controller,
20851                     AP_IMPORT_INVOICES_PKG.lg_incometax_storage,
20852                     l_key,
20853                     l_numof_values,
20854                     l_values);
20855 
20856       END;
20857 
20858     END IF;
20859    END IF; -- type 1099 is NOT 'NA'.
20860   END IF; -- type 1099 is not null
20861 
20862   -- Bug 9189995 - Defaulting logic for Income Tax Region Added
20863   IF ((p_invoice_lines_rec.income_tax_region is NULL) AND
20864       (p_invoice_lines_rec.type_1099 is NOT NULL)         ) THEN
20865 
20866     --------------------------------------------------------------------------
20867     -- Step 4.1
20868     -- Default income_tax_region if null in interface table
20869     -- we default only if type_1099 is not null
20870     --------------------------------------------------------------------------
20871       begin
20872         select asp.income_tax_region,
20873                NVL(asp.income_tax_region_flag, 'N')
20874         into   l_income_tax_region,
20875                l_income_tax_region_flag
20876         from   ap_system_parameters asp
20877         where  asp.org_id = p_invoice_rec.org_id;
20878 
20879        if (l_income_tax_region_flag = 'Y') then
20880          select pvs.state
20881          into   l_income_tax_region
20882          from   po_vendor_sites pvs
20883          where  pvs.vendor_id = p_invoice_rec.vendor_id
20884          and    pvs.vendor_site_id = p_invoice_rec.vendor_site_id;
20885        end if;
20886        p_invoice_lines_rec.income_tax_region := l_income_tax_region;
20887       exception
20888          when others then
20889             debug_info := '(step 4.1 default the income_tax_region';
20890             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
20891               AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
20892                                             debug_info);
20893             END IF;
20894       end;
20895 
20896   END IF; --p_invoice_lines_rec.income_tax_region is NULL
20897 
20898   IF (p_invoice_lines_rec.income_tax_region is NOT NULL) THEN
20899 
20900     --------------------------------------------------------------------------
20901     -- Step 4.2
20902     -- Invalid income_tax_region
20903     --------------------------------------------------------------------------
20904     debug_info := '(Check Misc Line Info 4) Check income_tax_region';
20905     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
20906       AP_IMPORT_UTILITIES_PKG.Print(
20907         AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
20908     END IF;
20909 
20910     -- Invalid Info
20911     l_key1 := p_invoice_lines_rec.income_tax_region;
20912 
20913     fnd_plsql_cache.generic_1tom_get_values(
20914               AP_IMPORT_INVOICES_PKG.lg_incometaxr_controller,
20915               AP_IMPORT_INVOICES_PKG.lg_incometaxr_storage,
20916               l_key1,
20917               l_numof_values1,
20918               l_values1,
20919               l_ret_code1);
20920 
20921     IF l_ret_code1 = '1' THEN --  means l_key found in cache
20922       l_income_tax_region := l_values1(1).varchar2_1;
20923       l_exception1   := l_values1(1).varchar2_2;
20924       IF l_exception1 = 'TRUE' THEN
20925         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
20926           AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
20927            p_invoice_lines_rec.invoice_line_id,
20928           'INVALID TAX REGION',
20929            p_default_last_updated_by,
20930            p_default_last_update_login,
20931            current_calling_sequence) <> TRUE) THEN
20932           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
20933             AP_IMPORT_UTILITIES_PKG.Print(
20934                AP_IMPORT_INVOICES_PKG.g_debug_switch,
20935               'insert_rejections<-' ||current_calling_sequence);
20936           END IF;
20937           RAISE misc_line_info_failure;
20938         END IF;
20939 
20940         l_current_invoice_status := 'N';
20941       END IF;
20942 
20943     ELSE
20944       debug_info := '(Check Misc Line Info 4.1) Check income_tax_region in Else';
20945       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
20946         AP_IMPORT_UTILITIES_PKG.Print(
20947           AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
20948       END IF;
20949 
20950       BEGIN
20951         SELECT region_short_name
20952         INTO l_income_tax_region
20953         FROM ap_income_tax_regions
20954         WHERE region_short_name = p_invoice_lines_rec.income_tax_region
20955          AND AP_IMPORT_INVOICES_PKG.g_inv_sysdate
20956         BETWEEN NVL(active_date, AP_IMPORT_INVOICES_PKG.g_inv_sysdate) AND
20957         NVL(inactive_date, AP_IMPORT_INVOICES_PKG.g_inv_sysdate);
20958 
20959         l_exception1           := 'FALSE';
20960         l_valueOut1.varchar2_1 := l_income_tax_region;
20961         l_valueOut1.varchar2_2 := l_exception1;
20962         l_values1(1)           := l_valueOut1;
20963         l_numof_values1        := 1;
20964 
20965         fnd_plsql_cache.generic_1tom_put_values(
20966                   AP_IMPORT_INVOICES_PKG.lg_incometaxr_controller,
20967                   AP_IMPORT_INVOICES_PKG.lg_incometaxr_storage,
20968                   l_key1,
20969                   l_numof_values1,
20970                   l_values1);
20971 
20972       EXCEPTION
20973         WHEN NO_DATA_FOUND 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             '(v_check_misc_line_info 4) Invalid income tax region');
20977           END IF;
20978           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
20979             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
20980              p_invoice_lines_rec.invoice_line_id,
20981             'INVALID TAX REGION',
20982              p_default_last_updated_by,
20983              p_default_last_update_login,
20984              current_calling_sequence) <> TRUE) THEN
20985             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
20986               AP_IMPORT_UTILITIES_PKG.Print(
20987               AP_IMPORT_INVOICES_PKG.g_debug_switch,
20988                 'insert_rejections<-' ||current_calling_sequence);
20989             END IF;
20990             RAISE misc_line_info_failure;
20991           END IF;
20992           l_current_invoice_status := 'N';
20993           l_exception1             := 'TRUE';
20994           l_valueOut1.varchar2_1   := NULL;
20995           l_valueOut1.varchar2_2   := l_exception1;
20996           l_values1(1)             := l_valueOut1;
20997           l_numof_values1          := 1;
20998 
20999           fnd_plsql_cache.generic_1tom_put_values(
21000                     AP_IMPORT_INVOICES_PKG.lg_incometaxr_controller,
21001                     AP_IMPORT_INVOICES_PKG.lg_incometaxr_storage,
21002                     l_key1,
21003                     l_numof_values1,
21004                     l_values1);
21005 
21006       END;
21007 
21008     END IF;
21009 
21010   END IF;
21011 
21012   p_current_invoice_status := l_current_invoice_status;
21013   RETURN (TRUE);
21014 
21015 EXCEPTION
21016   WHEN OTHERS THEN
21017     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
21018       AP_IMPORT_UTILITIES_PKG.Print(
21019         AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
21020     END IF;
21021 
21022     IF (SQLCODE < 0) THEN
21023       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
21024         AP_IMPORT_UTILITIES_PKG.Print(
21025           AP_IMPORT_INVOICES_PKG.g_debug_switch, SQLERRM);
21026       END IF;
21027     END IF;
21028     RETURN(FALSE);
21029 
21030 END v_check_misc_line_info;
21031 
21032 ---------------------------------------------------------------------------------
21033 -- This function verifies proration of non item lines
21034 --
21035 FUNCTION v_check_prorate_info (
21036    p_invoice_rec                  IN
21037      AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
21038    p_invoice_lines_rec   IN OUT NOCOPY AP_IMPORT_INVOICES_PKG.r_line_info_rec,
21039    p_default_last_updated_by      IN            NUMBER,
21040    p_default_last_update_login    IN            NUMBER,
21041    p_current_invoice_status       IN OUT NOCOPY VARCHAR2,
21042    p_calling_sequence             IN            VARCHAR2) RETURN BOOLEAN
21043 
21044 IS
21045 
21046 prorate_line_info_failure       EXCEPTION;
21047 l_item_line_total               NUMBER;
21048 l_count_non_item_lines          NUMBER := 0;
21049 l_count_item_lines		NUMBER := 0; -- Bug 9700233
21050 l_current_invoice_status    VARCHAR2(1) := 'Y';
21051 current_calling_sequence      VARCHAR2(2000);
21052 debug_info                   VARCHAR2(500);
21053 
21054 BEGIN
21055   -- Update the calling sequence
21056   --
21057   current_calling_sequence :=
21058     'AP_IMPORT_VALIDATION_PKG.v_check_prorate_info<-' ||P_calling_sequence;
21059 
21060   ---------------------------------------------------------------------------
21061   -- Step 1
21062   -- Sum of lines to prorate against cannot be 0
21063   ---------------------------------------------------------------------------
21064   debug_info := '(Check Prorate Info 1) Checking the total dist amount to be '
21065                ||'prorated';
21066   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
21067    AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
21068                                  debug_info);
21069   END IF;
21070 
21071   SELECT   SUM(nvl(AIL.amount,0))
21072     INTO   l_item_line_total
21073     FROM   ap_invoice_lines_interface AIL
21074    WHERE   AIL.invoice_id = p_invoice_rec.invoice_id
21075      AND   ((line_group_number = p_invoice_lines_rec.line_group_number AND
21076              p_invoice_lines_rec.line_group_number IS NOT NULL)         OR
21077             p_invoice_lines_rec.line_group_number is NULL)
21078      AND    line_type_lookup_code = 'ITEM';
21079 
21080   IF (l_item_line_total = 0 ) THEN
21081     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
21082        AP_IMPORT_INVOICES_PKG.g_invoice_lines_table, /* BUG10339648 */
21083      p_invoice_lines_rec.invoice_line_id,
21084         'CANNOT PRORATE TO ZERO',
21085      p_default_last_updated_by,
21086      p_default_last_update_login,
21087      current_calling_sequence) <> TRUE ) THEN
21088       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
21089         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
21090            'insert_rejections<- '||current_calling_sequence);
21091       END IF;
21092       RAISE prorate_line_info_failure;
21093     END IF;
21094     l_current_invoice_status := 'N';
21095   END IF; -- Total of amount for item lines to prorate across is 0
21096 
21097   ---------------------------------------------------------------------------
21098   -- Step 2
21099   -- Prorating across non-item lines is not allowed
21100   ---------------------------------------------------------------------------
21101   debug_info := '(Check Prorate Info 2) Checking lines to prorate across.';
21102   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
21103    AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
21104                                  debug_info);
21105   END IF;
21106 
21107   IF (p_invoice_lines_rec.line_group_number IS NOT NULL) THEN
21108 
21109 	-- Added for bug 9700233
21110 	-- There should be atleast one ITEM line for the line group number
21111 	-- which belongs to other than ITEM line
21112 	-- For TAX line, prorate_across_flag should be Y
21113 
21114 	SELECT COUNT(*)
21115 	INTO   l_count_item_lines
21116 	FROM   ap_invoice_lines_interface AIL
21117 	WHERE   AIL.invoice_id = p_invoice_rec.invoice_id
21118 	AND   line_group_number = p_invoice_lines_rec.line_group_number
21119 	AND   (line_type_lookup_code = 'ITEM'
21120 	       OR (line_type_lookup_code = 'TAX' AND prorate_across_flag = 'Y'));
21121 
21122 	IF (l_count_item_lines = 0) THEN
21123 	      IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
21124 	          AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
21125 			p_invoice_lines_rec.invoice_line_id,
21126 			'CANNOT PRORATE TO NON ITEM',
21127 			p_default_last_updated_by,
21128 			p_default_last_update_login,
21129 			current_calling_sequence) <> TRUE ) THEN
21130 		IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
21131 	          AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
21132 		     'insert_rejections<- '||current_calling_sequence);
21133 	        END IF;
21134 		l_current_invoice_status := 'N';
21135 		RAISE prorate_line_info_failure;
21136 	      END IF;
21137 	      l_current_invoice_status := 'N';
21138 	 END IF; -- count of item line equal to 0
21139 
21140 /* Commented for bug 9700233
21141     SELECT   COUNT(*)
21142       INTO   l_count_non_item_lines
21143       FROM   ap_invoice_lines_interface AIL
21144      WHERE   AIL.invoice_id = p_invoice_rec.invoice_id
21145        AND   line_group_number = p_invoice_lines_rec.line_group_number
21146        AND   line_type_lookup_code <> 'ITEM';
21147 
21148     -- If number of lines other than Item is more than 1 (1 is itself)
21149     -- raise rejection
21150     IF (l_count_non_item_lines > 1) THEN
21151       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
21152           AP_IMPORT_INVOICES_PKG.g_invoices_table,
21153        p_invoice_lines_rec.invoice_line_id,
21154           'CANNOT PRORATE TO NON ITEM',
21155        p_default_last_updated_by,
21156        p_default_last_update_login,
21157            current_calling_sequence) <> TRUE ) THEN
21158         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
21159           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
21160              'insert_rejections<- '||current_calling_sequence);
21161         END IF;
21162         RAISE prorate_line_info_failure;
21163       END IF;
21164     END IF; -- count of non item lines is > 1
21165 */
21166 
21167   END IF; -- line group number is not null
21168 
21169   p_current_invoice_status := l_current_invoice_status;
21170   RETURN (TRUE);
21171 
21172 EXCEPTION
21173   WHEN OTHERS THEN
21174     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
21175       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
21176                                     debug_info);
21177     END IF;
21178 
21179     IF (SQLCODE < 0) THEN
21180       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
21181         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
21182                                       SQLERRM);
21183       END IF;
21184     END IF;
21185     RETURN(FALSE);
21186 
21187 END v_check_prorate_info;
21188 
21189 -----------------------------------------------------------------------------
21190 -- This function verifies and populates asset information
21191 --
21192 FUNCTION v_check_asset_info (
21193          p_invoice_lines_rec
21194            IN OUT NOCOPY AP_IMPORT_INVOICES_PKG.r_line_info_rec,
21195          p_set_of_books_id              IN            NUMBER,
21196          p_asset_book_type              IN            VARCHAR2, -- 5448579
21197          p_default_last_updated_by      IN            NUMBER,
21198          p_default_last_update_login    IN            NUMBER,
21199          p_current_invoice_status       IN OUT NOCOPY VARCHAR2,
21200          p_calling_sequence             IN            VARCHAR2) RETURN BOOLEAN
21201 IS
21202 
21203 asset_line_info_failure         EXCEPTION;
21204 l_valid_asset_book             VARCHAR2(30);
21205 l_asset_book_count             NUMBER;
21206 l_valid_asset_category         VARCHAR2(30);
21207 l_current_invoice_status        VARCHAR2(1) := 'Y';
21208 current_calling_sequence       VARCHAR2(2000);
21209 debug_info                    VARCHAR2(500);
21210 
21211 BEGIN
21212   -- Update the calling sequence
21213   --
21214   current_calling_sequence := 'AP_IMPORT_UTILITIES_PKG.v_check_asset_ifno<-'
21215                               ||P_calling_sequence;
21216 
21217   -------------------------------------------------------------------------------
21218   -- Step 1 - If line type is other than item and any of the asset fields is
21219   -- populated, reject appropriately.
21220   --
21221   ----------------------------------------------------------------------------
21222   debug_info := '(Check Asset Book 1) Verify asset info not on non-item line';
21223   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
21224     AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
21225                                   debug_info);
21226   END IF;
21227 
21228   --Retropricing
21229   IF (p_invoice_lines_rec.line_type_lookup_code NOT IN ('ITEM', 'RETROITEM')) THEN
21230     IF (p_invoice_lines_rec.serial_number IS NOT NULL) THEN
21231       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
21232           AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
21233            p_invoice_lines_rec.invoice_line_id,
21234            'INVALID SERIAL NUMBER INFO',
21235            p_default_last_updated_by,
21236            p_default_last_update_login,
21237            current_calling_sequence) <> TRUE ) THEN
21238         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
21239           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
21240              'insert_rejections<- '||current_calling_sequence);
21241         END IF;
21242         RAISE asset_line_info_failure;
21243       END IF;
21244       l_current_invoice_status := 'N';
21245     END IF; -- Serial number is not null
21246 
21247     IF (p_invoice_lines_rec.manufacturer IS NOT NULL) THEN
21248       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
21249           AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
21250            p_invoice_lines_rec.invoice_line_id,
21251            'INVALID MANUFACTURER INFO',
21252            p_default_last_updated_by,
21253            p_default_last_update_login,
21254            current_calling_sequence) <> TRUE ) THEN
21255         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
21256           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
21257             'insert_rejections<- '||current_calling_sequence);
21258         END IF;
21259         RAISE asset_line_info_failure;
21260       END IF;
21261       l_current_invoice_status := 'N';
21262     END IF; -- Manufacturer is not null
21263 
21264     IF (p_invoice_lines_rec.model_number IS NOT NULL) THEN
21265       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
21266           AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
21267            p_invoice_lines_rec.invoice_line_id,
21268            'INVALID MODEL NUMBER INFO',
21269            p_default_last_updated_by,
21270            p_default_last_update_login,
21271            current_calling_sequence) <> TRUE ) Then
21272         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
21273           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
21274            'insert_rejections<- '||current_calling_sequence);
21275         END IF;
21276         RAISE asset_line_info_failure;
21277       END IF;
21278       l_current_invoice_status := 'N';
21279     END IF; -- Model Number is not null
21280 
21281     IF (p_invoice_lines_rec.warranty_number is not null) then
21282      IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
21283           AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
21284            p_invoice_lines_rec.invoice_line_id,
21285            'INVALID WARRANTY NUM INFO',
21286            p_default_last_updated_by,
21287            p_default_last_update_login,
21288            current_calling_sequence) <> TRUE ) Then
21289         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
21290          AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
21291            'insert_rejections<- '||current_calling_sequence);
21292         END IF;
21293         RAISE asset_line_info_failure;
21294       END IF;
21295       l_current_invoice_status := 'N';
21296     END IF; -- Warranty Number is not null
21297 
21298   END IF; -- Line type is other than ITEM, RETROITEM
21299 
21300   ----------------------------------------------------------------------------
21301  -- Step 2 - If asset book type code is populated verify that it is correct.
21302  -- If it is not populated, populate based on set of books if a single asset
21303  -- book is found.
21304  --
21305   ----------------------------------------------------------------------------
21306   debug_info := '(Check Asset Book 2) Verify asset book if not null';
21307   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
21308     AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
21309                                   debug_info);
21310   END IF;
21311 
21312   IF (p_invoice_lines_rec.asset_book_type_code IS NOT NULL) THEN
21313     debug_info := 'Verify Asset Book since it is not null';
21314     BEGIN
21315       SELECT 'Asset Book Found'
21316         INTO l_valid_asset_book
21317         FROM fa_book_controls bc
21318        WHERE bc.set_of_books_id = p_set_of_books_id
21319          AND bc.book_type_code = p_invoice_lines_rec.asset_book_type_code
21320          AND bc.date_ineffective IS NULL;
21321 
21322     EXCEPTION
21323       WHEN no_data_found then
21324        IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
21325           AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
21326            p_invoice_lines_rec.invoice_line_id,
21327            'INVALID ASSET BOOK CODE',
21328            p_default_last_updated_by,
21329            p_default_last_update_login,
21330            current_calling_sequence) <> TRUE ) Then
21331           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
21332             AP_IMPORT_UTILITIES_PKG.Print(
21333               AP_IMPORT_INVOICES_PKG.g_debug_switch,
21334                'insert_rejections<- '||current_calling_sequence);
21335           END IF;
21336           RAISE asset_line_info_failure;
21337        END IF;
21338        l_current_invoice_status := 'N';
21339       WHEN OTHERS THEN
21340         RAISE asset_line_info_failure;
21341     END;
21342 
21343   ELSE -- Asset book is null
21344     debug_info := 'Get asset book if null and a single one exists for sob';
21345     -- Bug 5448579
21346     p_invoice_lines_rec.asset_book_type_code  := p_asset_book_type;
21347 
21348   END IF; -- Asset book type code is not null
21349 
21350   ----------------------------------------------------------------------------
21351   -- Step 3 - If asset category is populated, verify that it is appropriate
21352   --
21353   ----------------------------------------------------------------------------
21354   debug_info := '(Check Asset Book 3) Verify asset category if not null';
21355   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
21356     AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
21357                                   debug_info);
21358   End if;
21359 
21360   If (p_invoice_lines_rec.asset_category_id is not null) then
21361     debug_info := 'Verify Asset Category since it is not null';
21362     BEGIN
21363       SELECT 'Asset Category found'
21364         INTO l_valid_asset_category
21365         FROM fa_categories
21366        WHERE category_id = p_invoice_lines_rec.asset_category_id;
21367 
21368     EXCEPTION
21369       WHEN no_data_found then
21370        If (AP_IMPORT_UTILITIES_PKG.insert_rejections(
21371            AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
21372            p_invoice_lines_rec.invoice_line_id,
21373            'INVALID ASSET CATEGORY ID',
21374            p_default_last_updated_by,
21375            p_default_last_update_login,
21376            current_calling_sequence) <> TRUE ) Then
21377           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
21378            AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
21379              'insert_rejections<- '||current_calling_sequence);
21380           END IF;
21381           RAISE asset_line_info_failure;
21382        END IF;
21383        l_current_invoice_status := 'N';
21384       WHEN OTHERS THEN
21385         RAISE asset_line_info_failure;
21386     END;
21387 
21388   END IF; -- Asset category is not null
21389 
21390   p_current_invoice_status := l_current_invoice_status;
21391   RETURN (TRUE);
21392 EXCEPTION
21393   WHEN OTHERS THEN
21394     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
21395       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
21396                                     debug_info);
21397     END IF;
21398 
21399     IF (SQLCODE < 0) then
21400       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
21401         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
21402                                       SQLERRM);
21403       END IF;
21404     END IF;
21405     RETURN(FALSE);
21406 
21407 END v_check_asset_info;
21408 
21409 /*=============================================================================
21410  |  FUNCTION - V_Check_Tax_Info()
21411  |
21412  |  DESCRIPTION
21413  |      This function will validate the following fields included in the
21414  |      ap_invoices_interface table as part of the eTax Uptake project:
21415  |        control_amount
21416  |        tax_related_invoice_id
21417  |        calc_tax_during_import_flag
21418  |
21419  |      The other tax fields will be validated by the eTax API.  See DLD for
21420  |      details.
21421  |
21422  |  PARAMETERS
21423  |    p_invoice_rec - record for invoice header
21424  |    p_default_last_updated_by - default last updated by
21425  |    p_default_last_update_login - default last update login
21426  |    p_current_invoice_status - return the status of the invoice after the
21427  |                               validation
21428  |    P_calling_sequence -  Calling sequence
21429  |
21430  |  MODIFICATION HISTORY
21431  |    DATE          Author         Action
21432  |    20-JAN-2004   SYIDNER        Created
21433  |
21434  *============================================================================*/
21435 
21436 FUNCTION v_check_tax_info(
21437      p_invoice_rec               IN AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
21438      p_default_last_updated_by   IN            NUMBER,
21439      p_default_last_update_login IN            NUMBER,
21440      p_current_invoice_status    IN OUT NOCOPY VARCHAR2,
21441      p_calling_sequence          IN            VARCHAR2) RETURN BOOLEAN
21442 IS
21443 
21444   l_current_invoice_status        VARCHAR2(1);
21445   l_reject_code                   VARCHAR2(30);
21446   current_calling_sequence        VARCHAR2(2000);
21447 
21448   debug_info                      VARCHAR2(500);
21449   check_tax_failure               EXCEPTION;
21450 
21451   l_related_inv_id                ap_invoices_all.invoice_id%TYPE;
21452   l_exist_tax_line                ap_invoices_all.invoice_id%TYPE;
21453   l_alloc_not_provided            VARCHAR2(1);
21454   l_tax_lines_cannot_coexist      VARCHAR2(1);
21455   l_tax_found_in_nontax_line      VARCHAR2(1);
21456 
21457 BEGIN
21458 
21459   current_calling_sequence :=  'AP_IMPORT_VALIDATION_PKG.v_check_tax_info<-'
21460                                 ||P_calling_sequence;
21461 
21462   -------------------------------------------------------------------------
21463   debug_info := '(Check tax info 1) Check for control_amount';
21464   -------------------------------------------------------------------------
21465   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
21466       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
21467                                     debug_info);
21468   END IF;
21469 
21470   --bug 9326733
21471   l_current_invoice_status := p_current_invoice_status;
21472 
21473   --Contract Payments: Modified the IF condition to add 'PREPAYMENT'.
21474 
21475   IF ( (p_invoice_rec.invoice_type_lookup_code IN ('STANDARD','PREPAYMENT') and
21476         NVL(p_invoice_rec.control_amount, 0) > NVL(p_invoice_rec.invoice_amount, 0)) OR
21477        (p_invoice_rec.invoice_type_lookup_code IN ('CREDIT', 'DEBIT') and -- bug 7299826
21478         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)
21479      ) THEN
21480 
21481     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
21482       (AP_IMPORT_INVOICES_PKG.g_invoices_table,
21483        p_invoice_rec.invoice_id,
21484        'INVALID CONTROL AMOUNT',
21485        p_default_last_updated_by,
21486        p_default_last_update_login,
21487        current_calling_sequence) <> TRUE) THEN
21488 
21489        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
21490           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
21491           'insert_rejections<-'||current_calling_sequence);
21492        END IF;
21493        RAISE check_tax_failure;
21494 
21495     END IF;
21496     l_current_invoice_status := 'N';
21497   END IF;
21498 
21499   -------------------------------------------------------------------------
21500   debug_info := '(Check tax info 2) Check for tax_related_invoice_id';
21501   -------------------------------------------------------------------------
21502   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
21503       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
21504                                     debug_info);
21505   END IF;
21506 
21507   IF ( p_invoice_rec.tax_related_invoice_id IS NOT NULL) THEN
21508 
21509     BEGIN
21510       SELECT invoice_id
21511         INTO l_related_inv_id
21512         FROM ap_invoices_all
21513        WHERE invoice_id = p_invoice_rec.tax_related_invoice_id
21514          AND vendor_id = p_invoice_rec.vendor_id
21515          AND vendor_site_id = p_invoice_rec.vendor_site_id
21516          AND cancelled_date IS NULL
21517          AND cancelled_by IS NULL;
21518 
21519     EXCEPTION
21520       WHEN no_data_found THEN
21521 
21522         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
21523           (AP_IMPORT_INVOICES_PKG.g_invoices_table,
21524            p_invoice_rec.invoice_id,
21525            'INVALID TAX RELATED INVOICE ID',
21526            p_default_last_updated_by,
21527            p_default_last_update_login,
21528            current_calling_sequence) <> TRUE) THEN
21529 
21530            IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
21531               AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
21532               'insert_rejections<-'||current_calling_sequence);
21533            END IF;
21534            RAISE check_tax_failure;
21535 
21536         END IF;
21537         l_current_invoice_status := 'N';
21538     END;
21539   END IF;  -- Validate only if tax_related_invoice_id is populated
21540 
21541   -------------------------------------------------------------------------
21542   debug_info := '(Check tax info 3) Check for calc_tax_during_import_flag';
21543   -------------------------------------------------------------------------
21544   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
21545       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
21546                                     debug_info);
21547   END IF;
21548 
21549   IF ( p_invoice_rec.calc_tax_during_import_flag = 'Y') THEN
21550 
21551     BEGIN
21552       SELECT invoice_id
21553         INTO l_exist_tax_line
21554         FROM ap_invoice_lines_interface
21555        WHERE invoice_id = p_invoice_rec.invoice_id
21556          AND line_type_lookup_code = 'TAX'
21557          AND ROWNUM =1;
21558 
21559     EXCEPTION
21560       WHEN no_data_found THEN
21561         NULL;
21562     END;
21563 
21564     IF (l_exist_tax_line IS NOT NULL) THEN
21565 
21566       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
21567         (AP_IMPORT_INVOICES_PKG.g_invoices_table,
21568          p_invoice_rec.invoice_id,
21569          'CANNOT CONTAIN TAX LINES',
21570          p_default_last_updated_by,
21571          p_default_last_update_login,
21572          current_calling_sequence) <> TRUE) THEN
21573           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
21574             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
21575             'insert_rejections<-'||current_calling_sequence);
21576          END IF;
21577          RAISE check_tax_failure;
21578        END IF;
21579       l_current_invoice_status := 'N';
21580 
21581     END IF;
21582   END IF;  -- Validate calc_tax_during_import_flag
21583 
21584   -------------------------------------------------------------------------
21585   debug_info := '(Check tax info 4) Validate if allocation structure is '||
21586                 'provided for inclusive lines when the invoice has more than '||
21587                 'one item line.';
21588   -------------------------------------------------------------------------
21589   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
21590       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
21591                                     debug_info);
21592   END IF;
21593 
21594   BEGIN
21595     SELECT 'Y'
21596       INTO l_alloc_not_provided
21597       FROM ap_invoices_interface aii
21598      WHERE aii.invoice_id = p_invoice_rec.invoice_id
21599        AND 1 < (SELECT COUNT(*)
21600                   FROM ap_invoice_lines_interface aili
21601                  WHERE aili.line_type_lookup_code <> 'TAX'
21602                    AND aili.invoice_id = aii.invoice_id)
21603        AND EXISTS (SELECT 'Y'
21604                     FROM ap_invoice_lines_interface ail2
21605                    WHERE ail2.invoice_id = aii.invoice_id
21606                      AND ail2.line_type_lookup_code = 'TAX'
21607                      AND ail2.line_group_number IS NULL
21608                      AND NVL(ail2.incl_in_taxable_line_flag, 'N') = 'Y');
21609   EXCEPTION
21610     WHEN NO_DATA_FOUND THEN
21611       l_alloc_not_provided := 'N';
21612 
21613   END;
21614 
21615   IF (l_alloc_not_provided = 'Y') THEN
21616     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
21617        (AP_IMPORT_INVOICES_PKG.g_invoices_table,
21618        p_invoice_rec.invoice_id,
21619        'NO ALLOCATION RULES FOUND',
21620        p_default_last_updated_by,
21621        p_default_last_update_login,
21622        current_calling_sequence) <> TRUE) THEN
21623        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
21624           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
21625             'insert_rejections<-'||current_calling_sequence);
21626        END IF;
21627        RAISE check_tax_failure;
21628     END IF;
21629 
21630     l_current_invoice_status := 'N';
21631   END IF; -- end of validation if inclusive and alloc structure is not provided
21632 
21633   -------------------------------------------------------------------------
21634   debug_info := '(Check tax info 5) Check if any non-tax line has tax information';
21635   -------------------------------------------------------------------------
21636   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
21637       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
21638                                   debug_info);
21639   END IF;
21640 
21641   BEGIN
21642     SELECT 'Y'
21643       INTO l_tax_found_in_nontax_line
21644       FROM ap_invoices_interface aii
21645      WHERE aii.invoice_id = p_invoice_rec.invoice_id
21646        AND EXISTS (SELECT 'Y'
21647                      FROM ap_invoice_lines_interface ail2
21648                     WHERE ail2.invoice_id = aii.invoice_id
21649                       AND ail2.line_type_lookup_code <> 'TAX'
21650                       AND (ail2.tax_regime_code IS NOT NULL OR
21651                            ail2.tax IS NOT NULL OR
21652                            ail2.tax_jurisdiction_code IS NOT NULL OR
21653                            ail2.tax_status_code IS NOT NULL OR
21654                            ail2.tax_rate_id IS NOT NULL OR
21655                            ail2.tax_rate_code IS NOT NULL OR
21656                            ail2.tax_rate IS NOT NULL OR
21657                            ail2.incl_in_taxable_line_flag IS NOT NULL));
21658   EXCEPTION
21659     WHEN NO_DATA_FOUND THEN
21660       l_tax_found_in_nontax_line := 'N';
21661 
21662   END;
21663 
21664   IF (l_tax_found_in_nontax_line = 'Y') THEN
21665     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
21666        (AP_IMPORT_INVOICES_PKG.g_invoices_table,
21667        p_invoice_rec.invoice_id,
21668        'TAX DATA FOUND ON NONTAX LINES',
21669        p_default_last_updated_by,
21670        p_default_last_update_login,
21671        current_calling_sequence) <> TRUE) THEN
21672        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
21673           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
21674             'insert_rejections<-'||current_calling_sequence);
21675        END IF;
21676        RAISE check_tax_failure;
21677     END IF;
21678 
21679     l_current_invoice_status := 'N';
21680   END IF; -- end of validation if nont-tax lines have tax information
21681 
21682   -------------------------------------------------------------------------
21683   debug_info := '(Check tax info 6) Check if an invoice has a tax line '||
21684                 'matched to receipt and another allocated to item lines';
21685   -------------------------------------------------------------------------
21686   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
21687       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
21688                                   debug_info);
21689   END IF;
21690 
21691   -- Validation:  A tax-only invoice should not have a tax line matched to receipt and
21692   -- a tax line allocated to an item line
21693   -- This validation is only for tax-only invoices since if the invoice has a
21694   -- tax line matched to receipt in an invoice with item lines the rcv info is
21695   -- not taken into consideration.
21696   IF (NVL(p_invoice_rec.tax_only_flag, 'N') = 'Y') THEN
21697     BEGIN
21698       SELECT 'Y'
21699         INTO l_tax_lines_cannot_coexist
21700         FROM ap_invoices_interface aii
21701        WHERE aii.invoice_id = p_invoice_rec.invoice_id
21702          AND EXISTS (SELECT 'Y'
21703                        FROM ap_invoice_lines_interface ail2
21704                       WHERE ail2.invoice_id = aii.invoice_id
21705                         AND ail2.line_type_lookup_code = 'TAX'
21706                         AND ail2.rcv_transaction_id IS NOT NULL)
21707          AND EXISTS (SELECT 'Y'
21708                        FROM ap_invoice_lines_interface ail3
21709                       WHERE ail3.invoice_id = aii.invoice_id
21710                         AND ail3.line_type_lookup_code = 'TAX'
21711                         AND ail3.rcv_transaction_id IS NULL);
21712     EXCEPTION
21713       WHEN NO_DATA_FOUND THEN
21714         l_tax_lines_cannot_coexist := 'N';
21715 
21716     END;
21717 
21718     IF (l_tax_lines_cannot_coexist = 'Y') THEN
21719       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
21720          (AP_IMPORT_INVOICES_PKG.g_invoices_table,
21721          p_invoice_rec.invoice_id,
21722          'TAX LINE TYPES CANNOT COEXIST',
21723          p_default_last_updated_by,
21724          p_default_last_update_login,
21725          current_calling_sequence) <> TRUE) THEN
21726          IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
21727             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
21728               'insert_rejections<-'||current_calling_sequence);
21729          END IF;
21730          RAISE check_tax_failure;
21731       END IF;
21732 
21733       l_current_invoice_status := 'N';
21734     END IF; -- end of validation for tax lines matched to receipts and allocated
21735             -- to item lines
21736   END IF;  -- Is invoice tax-only?
21737 
21738   p_current_invoice_status := l_current_invoice_status;
21739 
21740   RETURN(TRUE);
21741 
21742 EXCEPTION
21743   WHEN OTHERS THEN
21744     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
21745       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
21746                                     debug_info);
21747     END IF;
21748 
21749     IF (SQLCODE < 0) then
21750       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
21751         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
21752                                       SQLERRM);
21753       END IF;
21754     END IF;
21755     RETURN(FALSE);
21756 
21757 END v_check_tax_info;
21758 
21759 /*=============================================================================
21760  |  FUNCTION - V_Check_Tax_Line_Info()
21761  |
21762  |  DESCRIPTION
21763  |      This function will validate the following fields included in the
21764  |      ap_invoice_lines_interface table as part of the eTax Uptake project:
21765  |        control_amount
21766  |        assessable_value
21767  |        incl_in_taxable_line_flag
21768  |
21769  |      The other tax fields will be validated by the eTax API.  See DLD for
21770  |      details.
21771  |
21772  |  PARAMETERS
21773  |    p_invoice_rec - record for invoice header
21774  |    p_default_last_updated_by - default last updated by
21775  |    p_default_last_update_login - default last update login
21776  |    p_current_invoice_status - return the status of the invoice after the
21777  |                               validation
21778  |    P_calling_sequence -  Calling sequence
21779  |
21780  |  MODIFICATION HISTORY
21781  |    DATE          Author         Action
21782  |    20-JAN-2004   SYIDNER        Created
21783  |
21784  *============================================================================*/
21785   FUNCTION v_check_tax_line_info (
21786      p_invoice_lines_rec   IN OUT NOCOPY AP_IMPORT_INVOICES_PKG.r_line_info_rec,
21787      p_default_last_updated_by      IN            NUMBER,
21788      p_default_last_update_login    IN            NUMBER,
21789      p_current_invoice_status       IN OUT NOCOPY VARCHAR2,
21790      p_calling_sequence             IN            VARCHAR2) RETURN BOOLEAN
21791 
21792   IS
21793 
21794     tax_line_info_failure      EXCEPTION;
21795     l_valid_info                VARCHAR2(1);
21796     l_current_invoice_status    VARCHAR2(1) := 'Y';
21797     current_calling_sequence    VARCHAR2(2000);
21798     debug_info                  VARCHAR2(500);
21799 
21800     --6412397
21801     l_po_line_location_id      ap_invoice_lines_interface.po_line_location_id%TYPE;
21802     l_location_id              zx_transaction_lines_gt.ship_from_location_id%type;
21803     l_ship_to_location_id      ap_supplier_sites_all.ship_to_location_id%type;
21804     l_bill_to_location_id      zx_transaction_lines_gt.bill_to_location_id%TYPE;
21805     l_fob_point                po_vendor_sites_all.fob_lookup_code%TYPE;
21806 
21807     l_dflt_tax_class_code      zx_transaction_lines_gt.input_tax_classification_code%type;
21808     l_allow_tax_code_override  varchar2(10);
21809     l_dummy                    number;
21810     -- Purchase Order Info
21811     l_ref_doc_application_id   zx_transaction_lines_gt.ref_doc_application_id%TYPE;
21812     l_ref_doc_entity_code      zx_transaction_lines_gt.ref_doc_entity_code%TYPE;
21813     l_ref_doc_event_class_code zx_transaction_lines_gt.ref_doc_event_class_code%TYPE;
21814     l_ref_doc_line_quantity    zx_transaction_lines_gt.ref_doc_line_quantity%TYPE;
21815     l_ref_doc_trx_level_type   zx_transaction_lines_gt.ref_doc_trx_level_type%TYPE;
21816     l_ref_doc_trx_id           zx_transaction_lines_gt.ref_doc_trx_id%TYPE;
21817     l_product_org_id           zx_transaction_lines_gt.product_org_id%TYPE;
21818 
21819     l_po_header_curr_conv_rate po_headers_all.rate%TYPE;
21820     l_uom_code                 mtl_units_of_measure.uom_code%TYPE;
21821 
21822     l_error_code               VARCHAR2(500);
21823     l_inv_hdr_org_id           ap_invoices_interface.org_id%TYPE;
21824     l_inv_hdr_vendor_id        ap_invoices_interface.vendor_id%TYPE;
21825     l_inv_hdr_vendor_site_id   ap_invoices_interface.vendor_site_id%TYPE;
21826     l_inv_hdr_inv_type         ap_invoices_interface.invoice_type_lookup_code%TYPE;
21827 
21828     l_event_class_code           zx_trx_headers_gt.event_class_code%TYPE;
21829     --6412397
21830 
21831     l_code_combination_id         NUMBER ; -- Bug 10050094
21832 
21833   BEGIN
21834     -- Update the calling sequence
21835     --
21836     current_calling_sequence := 'AP_IMPORT_VALIDATION_PKG.v_check_tax_line_info<-'
21837       ||P_calling_sequence;
21838 
21839 /* Bug 5206170: Removed the check for assessable value
21840     --------------------------------------------------------------------------
21841     debug_info := '(Check Tax Line Info 1) Check for Invalid sign in the '||
21842                   'assessable value';
21843     --------------------------------------------------------------------------
21844     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
21845         AP_IMPORT_UTILITIES_PKG.Print(
21846         AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
21847     END IF;
21848 
21849     IF (NVL(p_invoice_lines_rec.assessable_value, 0) <> 0) THEN
21850       IF (SIGN(p_invoice_lines_rec.assessable_value) <>
21851           SIGN(p_invoice_lines_rec.amount)) THEN
21852         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
21853           AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
21854              p_invoice_lines_rec.invoice_line_id,
21855              'INVALID SIGN ASSESSABLE VALUE',
21856              p_default_last_updated_by,
21857              p_default_last_update_login,
21858              current_calling_sequence) <> TRUE) THEN
21859           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
21860             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
21861               'insert_rejections<-' ||current_calling_sequence);
21862           END IF;
21863           RAISE tax_line_info_failure;
21864         END IF;
21865 
21866         l_current_invoice_status := 'N';
21867 
21868       END IF;
21869     END IF;  -- end of validation for assessable value
21870 */
21871 
21872     --------------------------------------------------------------------------
21873     debug_info := '(Check Tax Line Info 2) Check for control_amount greater '||
21874                    'than line amount';
21875     --------------------------------------------------------------------------
21876     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
21877         AP_IMPORT_UTILITIES_PKG.Print(
21878         AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
21879     END IF;
21880 
21881     IF (NVL(p_invoice_lines_rec.control_amount, 0) <> 0) THEN
21882 
21883       /*  --Bug 6925674 (Base bug6905106) Starts
21884         BEGIN
21885 	        SELECT aii.invoice_type_lookup_code
21886 	        INTO   l_inv_hdr_inv_type
21887 	        FROM   ap_invoices_interface aii,
21888 	               ap_invoice_lines_interface aili
21889 	        WHERE  aii.invoice_id = aili.invoice_id
21890 	        AND    aili.ROWID = p_invoice_lines_rec.row_id;
21891 
21892             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
21893                AP_IMPORT_UTILITIES_PKG.Print(
21894                AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
21895             END IF;
21896         EXCEPTION
21897         WHEN OTHERS THEN
21898             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
21899                AP_IMPORT_UTILITIES_PKG.Print(
21900                AP_IMPORT_INVOICES_PKG.g_debug_switch, SQLERRM);
21901             END IF;
21902         END;  Commented for Bug9852580 */
21903 
21904         IF((sign(NVL(p_invoice_lines_rec.control_amount,0)))= (sign(NVL(p_invoice_lines_rec.amount,0))) AND /* Added for Bug9852580 */
21905         /*(l_inv_hdr_inv_type IN ('CREDIT', 'DEBIT') AND --Bug 7299826  Added DEBIT , Commented for Bug9852580 */
21906           (abs(p_invoice_lines_rec.control_amount) >
21907            abs(p_invoice_lines_rec.amount))) THEN
21908 
21909            IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
21910              AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
21911              p_invoice_lines_rec.invoice_line_id,
21912              'INVALID CONTROL AMOUNT ',
21913              p_default_last_updated_by,
21914              p_default_last_update_login,
21915              current_calling_sequence) <> TRUE) THEN
21916 
21917              IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
21918                  AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
21919                  'insert_rejections<-' ||current_calling_sequence);
21920              END IF;
21921 
21922              RAISE tax_line_info_failure;
21923 
21924           END IF;
21925           l_current_invoice_status := 'N';
21926           --Bug 6925674 (Base bug6905106) Ends
21927         ELSIF ((sign(NVL(p_invoice_lines_rec.control_amount,0))<> sign(NVL(p_invoice_lines_rec.amount,0))) AND /* Added for Bug9852580 */
21928        /*( (l_inv_hdr_inv_type NOT IN ('CREDIT', 'DEBIT') and    --bug 7299826 Commented for Bug9852580 */
21929         (p_invoice_lines_rec.control_amount > p_invoice_lines_rec.amount)) THEN
21930           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
21931              AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
21932              p_invoice_lines_rec.invoice_line_id,
21933              'INVALID CONTROL AMOUNT ',
21934              p_default_last_updated_by,
21935              p_default_last_update_login,
21936              current_calling_sequence) <> TRUE) THEN
21937              IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
21938                AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
21939                'insert_rejections<-' ||current_calling_sequence);
21940              END IF;
21941 
21942 	     RAISE tax_line_info_failure;
21943           END IF;
21944 
21945           l_current_invoice_status := 'N';
21946 
21947         END IF;
21948     END IF;  -- end of validation for control amount
21949 
21950     --------------------------------------------------------------------------
21951     debug_info := '(Check Tax Line Info 3) Tax should not be inclusive if '||
21952                   'tax line is PO matched';
21953     --------------------------------------------------------------------------
21954     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
21955         AP_IMPORT_UTILITIES_PKG.Print(
21956         AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
21957     END IF;
21958 
21959     IF (p_invoice_lines_rec.line_type_lookup_code = 'TAX'
21960         AND NVL(p_invoice_lines_rec.incl_in_taxable_line_flag, 'N') = 'Y'
21961         AND (p_invoice_lines_rec.po_header_id IS NOT NULL OR
21962              p_invoice_lines_rec.po_number IS NOT NULL OR
21963              p_invoice_lines_rec.po_line_id IS NOT NULL OR
21964              p_invoice_lines_rec.po_line_number IS NOT NULL OR
21965              p_invoice_lines_rec.po_line_location_id IS NOT NULL OR
21966              p_invoice_lines_rec.po_shipment_num IS NOT NULL OR
21967              p_invoice_lines_rec.po_distribution_id IS NOT NULL OR
21968              p_invoice_lines_rec.po_distribution_num IS NOT NULL)) THEN
21969 
21970       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
21971        AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
21972           p_invoice_lines_rec.invoice_line_id,
21973            'TAX CANNOT BE INCLUDED',
21974            p_default_last_updated_by,
21975            p_default_last_update_login,
21976            current_calling_sequence) <> TRUE) THEN
21977         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
21978           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
21979             'insert_rejections<-' ||current_calling_sequence);
21980         END IF;
21981         RAISE tax_line_info_failure;
21982       END IF;
21983 
21984       l_current_invoice_status := 'N';
21985 
21986     END IF;  -- end of validation for incl_in_taxable_line_flag
21987 
21988     --Bug 6412397
21989     --------------------------------------------------------------------------
21990     debug_info := '(Check Tax Line Info 4) Tax_regime_code and tax are '||
21991                   'required in tax lines to be imported';
21992     --------------------------------------------------------------------------
21993     IF (p_invoice_lines_rec.line_type_lookup_code = 'TAX' AND
21994         p_invoice_lines_rec.tax_classification_code IS NULL AND
21995         p_invoice_lines_rec.tax_rate_code IS NULL) THEN
21996 
21997     --
21998     --  Fetch header vendor_id, vendor_site_id, invoice type
21999     --
22000 
22001     BEGIN
22002         SELECT NVL(p_invoice_lines_rec.org_id, aii.org_id),
22003                aii.vendor_id,
22004                aii.vendor_site_id,
22005                aii.invoice_type_lookup_code
22006         INTO   l_inv_hdr_org_id,
22007                l_inv_hdr_vendor_id,
22008                l_inv_hdr_vendor_site_id,
22009                l_inv_hdr_inv_type
22010         FROM   ap_invoices_interface aii,
22011                ap_invoice_lines_interface aili
22012         WHERE  aii.invoice_id = aili.invoice_id
22013         AND    aili.ROWID = p_invoice_lines_rec.row_id;
22014 
22015         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
22016             AP_IMPORT_UTILITIES_PKG.Print(
22017             AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
22018         END IF;
22019     EXCEPTION
22020     WHEN OTHERS THEN
22021         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
22022           AP_IMPORT_UTILITIES_PKG.Print(
22023             AP_IMPORT_INVOICES_PKG.g_debug_switch, SQLERRM);
22024         END IF;
22025     END;
22026     ----------------------------------------------------------------------
22027     debug_info := 'Step 4.1: Get location_id for vendor site';
22028     ----------------------------------------------------------------------
22029         BEGIN
22030           SELECT location_id,   ship_to_location_id,   fob_lookup_code
22031             INTO l_location_id, l_ship_to_location_id, l_fob_point
22032             FROM ap_supplier_sites_all
22033            WHERE vendor_site_id = l_inv_hdr_vendor_site_id;
22034 
22035         EXCEPTION
22036           WHEN no_data_found THEN
22037             l_location_id           := null;
22038             l_ship_to_location_id   := null;
22039             l_fob_point            := null;
22040         END;
22041     ----------------------------------------------------------------------
22042     debug_info := 'Step 4.2: Get location_id for org_id';
22043     ----------------------------------------------------------------------
22044         BEGIN
22045           SELECT location_id
22046             INTO l_bill_to_location_id
22047             FROM hr_all_organization_units
22048            WHERE organization_id = l_inv_hdr_org_id;
22049 
22050         EXCEPTION
22051           WHEN no_data_found THEN
22052              l_bill_to_location_id := null;
22053         END;
22054 
22055     -------------------------------------------------------------------
22056     debug_info := 'Step 4.5: Get Additional PO matched  info ';
22057     -------------------------------------------------------------------
22058         IF ( p_invoice_lines_rec.po_line_location_id IS NOT NULL) THEN
22059 
22060           -- this assignment is required since the p_po_line_location_id
22061           -- parameter is IN/OUT.  However, in this case it will not be
22062           -- modified because the po_distribution_id is not provided
22063 
22064         l_po_line_location_id := p_invoice_lines_rec.po_line_location_id;
22065 
22066         IF NOT (AP_ETAX_UTILITY_PKG.Get_PO_Info(
22067            P_Po_Line_Location_Id         => l_po_line_location_id,
22068            P_PO_Distribution_Id          => null,
22069            P_Application_Id              => l_ref_doc_application_id,
22070            P_Entity_code                 => l_ref_doc_entity_code,
22071            P_Event_Class_Code            => l_ref_doc_event_class_code,
22072            P_PO_Quantity                 => l_ref_doc_line_quantity,
22073            P_Product_Org_Id              => l_product_org_id,
22074            P_Po_Header_Id                => l_ref_doc_trx_id,
22075            P_Po_Header_curr_conv_rate    => l_po_header_curr_conv_rate,
22076            P_Uom_Code                   => l_uom_code,
22077            P_Dist_Qty                    => l_dummy,
22078            P_Ship_Price                  => l_dummy,
22079            P_Error_Code                  => l_error_code,
22080            P_Calling_Sequence            => current_calling_sequence)) THEN
22081 
22082            debug_info := 'Step 4.5: Get Additional PO matched info failed: '||
22083 l_error_code;
22084         END IF;
22085 
22086         l_ref_doc_trx_level_type := 'SHIPMENT';
22087 
22088         ELSE
22089          l_ref_doc_application_id     := Null;
22090          l_ref_doc_entity_code        := Null;
22091          l_ref_doc_event_class_code   := Null;
22092          l_ref_doc_line_quantity      := Null;
22093          l_product_org_id             := Null;
22094          l_ref_doc_trx_id             := Null;
22095          l_ref_doc_trx_level_type     := Null;
22096         END IF;
22097 
22098     -------------------------------------------------------------------
22099     debug_info := 'Step 4.6: Get event class code';
22100     -------------------------------------------------------------------
22101 
22102         IF NOT(AP_ETAX_UTILITY_PKG.Get_Event_Class_Code(
22103           P_Invoice_Type_Lookup_Code => l_inv_hdr_inv_type,
22104           P_Event_Class_Code         => l_event_class_code,
22105           P_error_code               => l_error_code,
22106           P_calling_sequence         => current_calling_sequence)) THEN
22107 
22108           debug_info := 'Step 4.6: Get event class code failed: '||
22109 l_error_code;
22110 
22111         END IF;
22112 
22113     -------------------------------------------------------------------
22114     debug_info := 'Step 4.6.1: Get default CCID for Tax call';
22115     -------------------------------------------------------------------
22116     -- Bug 10050094
22117     AP_ETAX_UTILITY_PKG.Get_Default_CCID( p_default_dist_ccid     => p_invoice_lines_rec.default_dist_ccid,
22118                                           p_match_type 	          => p_invoice_lines_rec.match_type,
22119 			                  p_po_line_location_id   => p_invoice_lines_rec.po_line_location_id,
22120 			                  p_po_distribution_id    => p_invoice_lines_rec.po_distribution_id,
22121 			                  p_rcv_transaction_id    => p_invoice_lines_rec.rcv_transaction_id,
22122 			                  p_line_type_lookup_code => p_invoice_lines_rec.line_type_lookup_code,
22123 			                  p_reference_key1        => p_invoice_lines_rec.reference_key1,
22124 			                  p_reference_key2        => p_invoice_lines_rec.reference_key2,
22125 					  p_invoice_line_number   => p_invoice_lines_rec.line_number,
22126 					  p_distribution_set_id   => p_invoice_lines_rec.distribution_set_id,
22127                                           p_calling_sequence      => current_calling_sequence,
22128                                           x_derived_ccid          => l_code_combination_id ) ;
22129 
22130     -------------------------------------------------------------------
22131     debug_info := 'Step 4.7: Call tax classification code defaulting api';
22132     -------------------------------------------------------------------
22133 
22134         ZX_AP_TAX_CLASSIFICATN_DEF_PKG.get_default_tax_classification
22135         (p_ref_doc_application_id           => l_ref_doc_application_id,
22136          p_ref_doc_entity_code              => l_ref_doc_entity_code,
22137          p_ref_doc_event_class_code         => l_ref_doc_event_class_code,
22138          p_ref_doc_trx_id                   => l_ref_doc_trx_id,
22139          p_ref_doc_line_id                  =>
22140 p_invoice_lines_rec.po_line_location_id,
22141          p_ref_doc_trx_level_type           => l_ref_doc_trx_level_type,
22142 --'SHIPMENT',
22143          p_vendor_id                        => l_inv_hdr_vendor_id,
22144          p_vendor_site_id                   => l_inv_hdr_vendor_site_id,
22145          p_code_combination_id              => l_code_combination_id, -- Bug 10050094   p_invoice_lines_rec.default_dist_ccid,
22146          p_concatenated_segments            => null,
22147          p_templ_tax_classification_cd      => null,
22148          p_ship_to_location_id              =>
22149 nvl(p_invoice_lines_rec.ship_to_location_id,
22150                                                    l_ship_to_location_id),
22151          p_ship_to_loc_org_id               => null,
22152          p_inventory_item_id                =>
22153 p_invoice_lines_rec.inventory_item_id,
22154          p_item_org_id                      => l_product_org_id,
22155          p_tax_classification_code          => l_dflt_tax_class_code,
22156          p_allow_tax_code_override_flag     => l_allow_tax_code_override,
22157          APPL_SHORT_NAME                    => 'SQLAP',
22158          FUNC_SHORT_NAME                    => 'NONE',
22159          p_calling_sequence                 => current_calling_sequence,
22160 --'AP_ETAX_SERVICES_PKG',
22161          p_event_class_code                 => NULL, --p_event_class_code,
22162          p_entity_code                      => 'AP_INVOICES',
22163          p_application_id                   => 200,
22164          p_internal_organization_id         => l_inv_hdr_org_id );
22165 
22166 
22167          p_invoice_lines_rec.tax_classification_code := l_dflt_tax_class_code;
22168     END IF;
22169     -- After validation check again
22170     -- End Bug 6412397
22171 
22172     --------------------------------------------------------------------------
22173     debug_info := '(Check Tax Line Info 4.8) Tax_regime_code and tax are '||
22174                   'required in tax lines to be imported'; -- Bug 6412397
22175     --------------------------------------------------------------------------
22176     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
22177         AP_IMPORT_UTILITIES_PKG.Print(
22178         AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
22179     END IF;
22180 
22181     IF (p_invoice_lines_rec.line_type_lookup_code = 'TAX' AND
22182         p_invoice_lines_rec.tax_classification_code is null --6255826
22183           and p_invoice_lines_rec.TAX_RATE_CODE is null   --6255826
22184         )  THEN
22185 
22186       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
22187        AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
22188           p_invoice_lines_rec.invoice_line_id,
22189            'INSUFFICIENT TAX INFO', --bug6255826 Replaced TAX INFO REQUIRED
22190            p_default_last_updated_by,
22191            p_default_last_update_login,
22192            current_calling_sequence) <> TRUE) THEN
22193         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
22194           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
22195             'insert_rejections<-' ||current_calling_sequence);
22196         END IF;
22197         RAISE tax_line_info_failure;
22198       END IF;
22199 
22200       l_current_invoice_status := 'N';
22201 
22202     END IF;  -- end of validation tax_Regime_code and tax column in tax lines
22203 
22204   p_current_invoice_status := l_current_invoice_status;
22205   RETURN (TRUE);
22206 
22207   EXCEPTION
22208     WHEN OTHERS THEN
22209       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
22210         AP_IMPORT_UTILITIES_PKG.Print(
22211           AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
22212       END IF;
22213 
22214       IF (SQLCODE < 0) THEN
22215         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
22216           AP_IMPORT_UTILITIES_PKG.Print(
22217             AP_IMPORT_INVOICES_PKG.g_debug_switch, SQLERRM);
22218         END IF;
22219       END IF;
22220       RETURN(FALSE);
22221 
22222   END v_check_tax_line_info;
22223 
22224 
22225  FUNCTION v_check_line_purch_category(
22226 	p_invoice_lines_rec   IN OUT NOCOPY AP_IMPORT_INVOICES_PKG.r_line_info_rec,
22227         p_default_last_updated_by      IN            NUMBER,
22228         p_default_last_update_login    IN            NUMBER,
22229         p_current_invoice_status       IN OUT NOCOPY VARCHAR2,
22230         p_calling_sequence             IN            VARCHAR2) RETURN BOOLEAN
22231 
22232   IS
22233     purch_category_check_failure EXCEPTION;
22234     l_purchasing_category_id	AP_INVOICE_LINES_ALL.PURCHASING_CATEGORY_ID%TYPE;
22235     l_current_invoice_status    VARCHAR2(1) := 'Y';
22236     current_calling_sequence    VARCHAR2(2000);
22237     debug_info                  VARCHAR2(500);
22238 
22239   BEGIN
22240 
22241     -- Update the calling sequence
22242     --
22243     current_calling_sequence := 'AP_IMPORT_VALIDATION_PKG.v_check_line_purch_category<-'
22244       ||P_calling_sequence;
22245 
22246     --------------------------------------------------------------------------
22247     debug_info := '(Check Line Purchasing_Category Info 1) If purchasing_category_id and '||
22248 		   'concatenated segments are provided'||
22249 		   ' then cross validate the info from concatenated segments';
22250     --------------------------------------------------------------------------
22251     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
22252         AP_IMPORT_UTILITIES_PKG.Print(
22253         AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
22254     END IF;
22255 
22256     -- Bug 5448579
22257     IF AP_IMPORT_INVOICES_PKG.g_structure_id IS NULL THEN
22258       p_invoice_lines_rec.purchasing_category_id := NULL;
22259       p_invoice_lines_rec.purchasing_category := NULL;
22260     END IF;
22261 
22262     IF (p_invoice_lines_rec.line_type_lookup_code <> 'ITEM') THEN
22263 
22264           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
22265                AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
22266                p_invoice_lines_rec.invoice_line_id,
22267                'INCONSISTENT CATEGORY',
22268                p_default_last_updated_by,
22269                p_default_last_update_login,
22270                current_calling_sequence,
22271                'Y',
22272                'INVOICE LINE NUMBER',
22273                p_invoice_lines_rec.line_number) <> TRUE) THEN
22274 
22275                IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
22276                  AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
22277                 'insert_rejections<-'||current_calling_sequence);
22278                END IF;
22279 
22280                RAISE purch_category_check_failure;
22281 
22282           END IF;
22283 
22284           l_current_invoice_status := 'N';
22285 
22286     END IF;
22287 
22288     IF (p_invoice_lines_rec.purchasing_category_id IS NOT NULL AND
22289         p_invoice_lines_rec.purchasing_category IS NOT NULL) THEN
22290 
22291           l_purchasing_category_id := FND_FLEX_EXT.GET_CCID('INV', 'MCAT',
22292            AP_IMPORT_INVOICES_PKG.g_structure_id,
22293            to_char(sysdate,'YYYY/MM/DD HH24:MI:SS'),p_invoice_lines_rec.purchasing_category);
22294 
22295           IF (l_purchasing_category_id <> p_invoice_lines_rec.purchasing_category_id) THEN
22296 
22297 	     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
22298                AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
22299                p_invoice_lines_rec.invoice_line_id,
22300                'INCONSISTENT CATEGORY',
22301                p_default_last_updated_by,
22302                p_default_last_update_login,
22303                current_calling_sequence,
22304                'Y',
22305                'INVOICE LINE NUMBER',
22306                p_invoice_lines_rec.line_number) <> TRUE) THEN
22307 
22308                IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
22309                  AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
22310                 'insert_rejections<-'||current_calling_sequence);
22311                END IF;
22312 
22313                RAISE purch_category_check_failure;
22314 
22315              END IF;
22316 
22317              l_current_invoice_status := 'N';
22318 
22319           END IF;
22320 
22321     ELSIF (p_invoice_lines_rec.purchasing_category IS NOT NULL) THEN
22322 
22323        --------------------------------------------------------------------------
22324        debug_info := '(Check Line purchasing_Category Info 2) If just concatenated segments'||
22325 		     'are provided then derive the purchasing_category_id from that info';
22326        --------------------------------------------------------------------------
22327        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
22328          AP_IMPORT_UTILITIES_PKG.Print(
22329          AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
22330        END IF;
22331 
22332        l_purchasing_category_id := FND_FLEX_EXT.GET_CCID('INV', 'MCAT',
22333           AP_IMPORT_INVOICES_PKG.g_structure_id,
22334           to_char(sysdate,'YYYY/MM/DD HH24:MI:SS'),p_invoice_lines_rec.purchasing_category);
22335 
22336        IF ((l_purchasing_category_id is not null) and (l_purchasing_category_id <> 0 )) THEN
22337           p_invoice_lines_rec.purchasing_category_id := l_purchasing_category_id;
22338 
22339        ELSE
22340 
22341           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
22342                AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
22343                p_invoice_lines_rec.invoice_line_id,
22344                'INVALID CATEGORY',
22345                p_default_last_updated_by,
22346                p_default_last_update_login,
22347                current_calling_sequence,
22348                'Y',
22349                'INVOICE LINE NUMBER',
22350                p_invoice_lines_rec.line_number) <> TRUE) THEN
22351 
22352                IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
22353                  AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
22354                 'insert_rejections<-'||current_calling_sequence);
22355                END IF;
22356 
22357                RAISE purch_category_check_failure;
22358 
22359              END IF;
22360 
22361              l_current_invoice_status := 'N';
22362 
22363        END IF;
22364 
22365     END IF;
22366 
22367     --------------------------------------------------------
22368       -- Validate Item Category Information
22369       -- If both Purchasing_Category and PO Information is provided
22370       -- then validate the Purchasing_Category info provided in interface
22371       -- against the one on the PO_Line.
22372     --------------------------------------------------------
22373     IF (l_current_invoice_status = 'Y' AND
22374 	 p_invoice_lines_rec.purchasing_category_id IS NOT NULL AND
22375           (p_invoice_lines_rec.po_line_id is not null or
22376 	   p_invoice_lines_rec.po_line_location_id is not null)) THEN
22377 
22378        BEGIN
22379 
22380 	  IF (p_invoice_lines_rec.po_line_id IS NOT NULL) THEN
22381    	     SELECT category_id
22382 	     INTO l_purchasing_category_id
22383 	     FROM po_lines_all
22384 	     WHERE po_line_id = p_invoice_lines_rec.po_line_id;
22385 
22386 	  ELSE
22387 	     SELECT pl.category_id
22388 	     INTO l_purchasing_category_id
22389 	     FROM po_lines_all pl, po_line_locations_all pll
22390 	     WHERE pll.line_location_id = p_invoice_lines_rec.po_line_location_id
22391 	     AND pl.po_line_id = pll.po_line_id;
22392 
22393 	  END IF;
22394 
22395 	  IF (l_purchasing_category_id <> p_invoice_lines_rec.purchasing_category_id) THEN
22396 
22397              IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
22398                  AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
22399                  p_invoice_lines_rec.invoice_line_id,
22400                  'INCONSISTENT CATEGORY',
22401                  p_default_last_updated_by,
22402                  p_default_last_update_login,
22403                  current_calling_sequence,
22404                  'Y',
22405                  'INVOICE LINE NUMBER',
22406                  p_invoice_lines_rec.line_number) <> TRUE) THEN
22407 
22408                IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
22409                  AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
22410                 'insert_rejections<-'||current_calling_sequence);
22411                END IF;
22412 
22413                RAISE purch_category_check_failure;
22414 
22415              END IF;
22416 
22417              l_current_invoice_status := 'N';
22418 
22419           /* if the information provided and the information on the PO Line is the same
22420 	   then we do not REJECT, but ignore the value provided by the user, since we will
22421 	   not be denormalizing the purchasing category info of the PO Line onto the
22422 	   invoice lines for matched cases */
22423 
22424           ELSE
22425 
22426 	     p_invoice_lines_rec.purchasing_category_id := NULL;
22427 
22428           END IF;
22429 
22430         END;
22431 
22432      END IF;
22433 
22434      p_current_invoice_status := l_current_invoice_status;
22435 
22436      RETURN (TRUE);
22437 
22438  END v_check_line_purch_category;
22439 
22440 
22441  FUNCTION v_check_line_cost_factor(
22442 	p_invoice_lines_rec   IN OUT NOCOPY AP_IMPORT_INVOICES_PKG.r_line_info_rec,
22443         p_default_last_updated_by      IN            NUMBER,
22444         p_default_last_update_login    IN            NUMBER,
22445         p_current_invoice_status       IN OUT NOCOPY VARCHAR2,
22446         p_calling_sequence             IN            VARCHAR2) RETURN BOOLEAN
22447 
22448   IS
22449     cost_factor_check_failure EXCEPTION;
22450     l_cost_factor_id	AP_INVOICE_LINES_ALL.COST_FACTOR_ID%TYPE;
22451     l_valid_cost_factor VARCHAR2(1);
22452     l_current_invoice_status    VARCHAR2(1) := 'Y';
22453     current_calling_sequence    VARCHAR2(2000);
22454     debug_info                  VARCHAR2(500);
22455 
22456   BEGIN
22457     -- Update the calling sequence
22458     --
22459     current_calling_sequence := 'AP_IMPORT_VALIDATION_PKG.v_check_line_cost_factor<-'
22460       ||P_calling_sequence;
22461 
22462     --------------------------------------------------------------------------
22463     debug_info := '(Check Line Cost_Factor Info 1) If cost_factor_id and '||
22464 		   'cost_factor_name provided'||
22465 		   ' then cross validate the info';
22466     --------------------------------------------------------------------------
22467     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
22468         AP_IMPORT_UTILITIES_PKG.Print(
22469         AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
22470     END IF;
22471 
22472     IF (p_invoice_lines_rec.line_type_lookup_code IN ('TAX','FREIGHT','MISCELLANEOUS')) THEN
22473 
22474       IF (p_invoice_lines_rec.cost_factor_name IS NOT NULL) THEN
22475  	debug_info := '(Check Line Cost_Factor Info 2) Check if cost_factor_name is provided'
22476 		   ||' then derive cost_factor_id';
22477         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
22478            AP_IMPORT_UTILITIES_PKG.Print(
22479            AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
22480         END IF;
22481 
22482         BEGIN
22483 
22484    	  SELECT price_element_type_id
22485 	  INTO l_cost_factor_id
22486 	  FROM pon_price_element_types_vl
22487 	  WHERE name = p_invoice_lines_rec.cost_factor_name;
22488 
22489     	  EXCEPTION WHEN OTHERS THEN
22490 
22491   	     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
22492                  AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
22493                  p_invoice_lines_rec.invoice_line_id,
22494                  'INVALID COST FACTOR INFO',
22495                  p_default_last_updated_by,
22496                  p_default_last_update_login,
22497                  current_calling_sequence,
22498                  'Y',
22499                  'INVOICE LINE NUMBER',
22500                  p_invoice_lines_rec.line_number) <> TRUE) THEN
22501 
22502                IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
22503                  AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
22504                 'insert_rejections<-'||current_calling_sequence);
22505                END IF;
22506 
22507                RAISE cost_factor_check_failure;
22508 
22509              END IF;
22510 
22511              l_current_invoice_status := 'N';
22512         END;
22513 
22514       END IF;  /* IF p_invoice_lines_rec.cost_factor_name IS NOT NULL */
22515 
22516 
22517       IF (l_current_invoice_status = 'Y') THEN
22518 
22519         IF (p_invoice_lines_rec.cost_factor_id IS NOT NULL and
22520 	  p_invoice_lines_rec.cost_factor_name IS NOT NULL) THEN
22521 
22522  	  debug_info := '(Check Line Cost_Factor Info 2) Cross validate '||
22523 			'cost_factor_name and cost_factor_id information';
22524           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
22525              AP_IMPORT_UTILITIES_PKG.Print(
22526              AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
22527           END IF;
22528 
22529 	  IF (l_cost_factor_id <> p_invoice_lines_rec.cost_factor_id) THEN
22530 
22531     	     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
22532                  AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
22533                  p_invoice_lines_rec.invoice_line_id,
22534                  'INVALID COST FACTOR INFO',
22535                  p_default_last_updated_by,
22536                  p_default_last_update_login,
22537                  current_calling_sequence,
22538                  'Y',
22539                  'INVOICE LINE NUMBER',
22540                  p_invoice_lines_rec.line_number) <> TRUE) THEN
22541 
22542                 IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
22543                   AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
22544                  'insert_rejections<-'||current_calling_sequence);
22545                 END IF;
22546 
22547                 RAISE cost_factor_check_failure;
22548 
22549               END IF;
22550 
22551               l_current_invoice_status := 'N';
22552 
22553   	   END IF;
22554 
22555          ELSIF (p_invoice_lines_rec.cost_factor_id IS NULL) THEN
22556 
22557   	   debug_info := '(Check Line Cost_Factor Info 4) If cost_factor_id is null and '||
22558 		   'cost_factor_name is provided, then assign the derived cost_factor_id'
22559 		   ||' then derive cost_factor_id';
22560            IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
22561              AP_IMPORT_UTILITIES_PKG.Print(
22562              AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
22563            END IF;
22564 
22565            p_invoice_lines_rec.cost_factor_id := l_cost_factor_id;
22566 
22567          ELSIF (p_invoice_lines_rec.cost_factor_id IS NOT NULL) THEN
22568 
22569 	   debug_info := '(Check Line Cost Factor Info 5) If cost_factor_id is'||
22570 	   		' not null , then validate it against the valid set of'||
22571 			' cost factors';
22572 	   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
22573              AP_IMPORT_UTILITIES_PKG.Print(
22574              AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
22575            END IF;
22576 
22577            BEGIN
22578 	      SELECT 'Y'
22579 	      INTO l_valid_cost_factor
22580 	      FROM pon_price_element_types_vl
22581 	      WHERE price_element_type_id = p_invoice_lines_rec.cost_factor_id;
22582 
22583       	    EXCEPTION WHEN OTHERS THEN
22584 
22585   	     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
22586                  AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
22587                  p_invoice_lines_rec.invoice_line_id,
22588                  'INVALID COST FACTOR INFO',
22589                  p_default_last_updated_by,
22590                  p_default_last_update_login,
22591                  current_calling_sequence,
22592                  'Y',
22593                  'INVOICE LINE NUMBER',
22594                  p_invoice_lines_rec.line_number) <> TRUE) THEN
22595 
22596                IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
22597                  AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
22598                 'insert_rejections<-'||current_calling_sequence);
22599                END IF;
22600 
22601                RAISE cost_factor_check_failure;
22602 
22603              END IF;
22604 
22605              l_current_invoice_status := 'N';
22606 
22607            END;
22608 
22609          END IF;
22610 
22611       END IF; /* l_current_invoice_status = 'Y' */
22612 
22613     --if cost_factor information is provided on non-charge lines, then do not
22614     --perform any validation, just ignore the value in this fields, and make sure
22615     --to not insert the values onto the non-charge lines.
22616     ELSE
22617 
22618       p_invoice_lines_rec.cost_factor_id := NULL;
22619       p_invoice_lines_rec.cost_factor_name := NULL;
22620 
22621     END IF ;  /* IF p_invoice_lines_rec.line_type_lookup_code ... */
22622 
22623     p_current_invoice_status := l_current_invoice_status;
22624 
22625     RETURN (TRUE);
22626 
22627   END v_check_line_cost_factor;
22628 
22629   FUNCTION v_check_line_retainage(
22630         p_invoice_lines_rec		IN OUT NOCOPY AP_IMPORT_INVOICES_PKG.r_line_info_rec,
22631 	p_retainage_ccid		IN            NUMBER,
22632 	p_default_last_updated_by	IN            NUMBER,
22633 	p_default_last_update_login	IN            NUMBER,
22634 	p_current_invoice_status	IN OUT NOCOPY VARCHAR2,
22635 	p_calling_sequence		IN            VARCHAR2) RETURN BOOLEAN IS
22636 
22637 	l_ret_status          Varchar2(100);
22638 	l_msg_data            Varchar2(4000);
22639 
22640 	l_retained_amount     Number;
22641 
22642 	retainage_check_failure     EXCEPTION;
22643 	l_current_invoice_status    VARCHAR2(1) := 'Y';
22644 	current_calling_sequence    VARCHAR2(2000);
22645 	debug_info                  VARCHAR2(500);
22646 
22647   Begin
22648 	-- Update the calling sequence
22649 	--
22650 	current_calling_sequence := 'AP_IMPORT_VALIDATION_PKG.v_check_line_retainage<-'
22651 					||P_calling_sequence;
22652 
22653 	--------------------------------------------------------------------------
22654 	debug_info := '(Check Retainage 1) Get retained amount based on po shipment and line amount';
22655 	--------------------------------------------------------------------------
22656 	IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
22657             AP_IMPORT_UTILITIES_PKG.Print(
22658             AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
22659         END IF;
22660 
22661 	l_retained_amount := ap_invoice_lines_utility_pkg.get_retained_amount
22662 					(p_invoice_lines_rec.po_line_location_id,
22663 					 p_invoice_lines_rec.amount);
22664 
22665 	--------------------------------------------------------------------------
22666 	debug_info := '(Check Retainage 2) Check for retainage account';
22667 	--------------------------------------------------------------------------
22668 	IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
22669             AP_IMPORT_UTILITIES_PKG.Print(
22670             AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
22671         END IF;
22672 
22673 	If l_retained_amount IS NOT NULL Then
22674 
22675 	   If p_retainage_ccid IS NULL Then
22676 
22677 		If (AP_IMPORT_UTILITIES_PKG.insert_rejections(
22678 				AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
22679 				p_invoice_lines_rec.invoice_line_id,
22680 				'RETAINAGE ACCT REQD',
22681 				p_default_last_updated_by,
22682 				p_default_last_update_login,
22683 				current_calling_sequence,
22684 				'Y',
22685 				'INVOICE LINE NUMBER',
22686 				p_invoice_lines_rec.line_number) <> TRUE) Then
22687 
22688 			If (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') Then
22689 			    AP_IMPORT_UTILITIES_PKG.Print
22690 				(AP_IMPORT_INVOICES_PKG.g_debug_switch, 'insert_rejections<-'||current_calling_sequence);
22691 			End If;
22692 
22693 			RAISE retainage_check_failure;
22694 		End If;
22695 
22696                 l_current_invoice_status := 'N';
22697 	   Else
22698 
22699 		p_invoice_lines_rec.retained_amount := l_retained_amount;
22700 
22701 	   End If;
22702 	End If;
22703 
22704 	p_current_invoice_status := l_current_invoice_status;
22705 	RETURN (TRUE);
22706 
22707   EXCEPTION
22708 	WHEN OTHERS THEN
22709 		IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
22710 			AP_IMPORT_UTILITIES_PKG.Print(
22711 				AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
22712 		END IF;
22713 
22714 		IF (SQLCODE < 0) THEN
22715 			IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
22716 				AP_IMPORT_UTILITIES_PKG.Print(
22717 					AP_IMPORT_INVOICES_PKG.g_debug_switch, SQLERRM);
22718 			END IF;
22719 		END IF;
22720 		RETURN(FALSE);
22721 
22722   End v_check_line_retainage;
22723 
22724 
22725 
22726 
22727   FUNCTION v_check_payment_defaults(
22728     p_invoice_rec               IN OUT NOCOPY AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
22729     p_current_invoice_status	IN OUT NOCOPY VARCHAR2,
22730     p_calling_sequence          IN            VARCHAR2,
22731     p_default_last_updated_by   IN            NUMBER,
22732     p_default_last_update_login IN            NUMBER) return boolean is
22733 
22734 
22735   debug_info                  VARCHAR2(500);
22736   l_current_invoice_status    VARCHAR2(1) := 'Y';
22737   current_calling_sequence    VARCHAR2(2000);
22738   l_dummy                     varchar2(1);
22739   pmt_attr_validation_failure exception;
22740   l_IBY_PAYMENT_METHOD        varchar2(80);
22741   l_PAYMENT_REASON            varchar2(80);
22742   l_BANK_CHARGE_BEARER_DSP    varchar2(80);
22743   l_DELIVERY_CHANNEL          varchar2(80);
22744   l_SETTLEMENT_PRIORITY_DSP   varchar2(80);
22745   l_bank_account_num          varchar2(100);
22746   l_bank_account_name         varchar2(80);
22747   l_bank_branch_name          varchar2(360);
22748   l_bank_branch_num           varchar2(30);
22749   l_bank_name                 varchar2(360);
22750   l_bank_number               varchar2(30);
22751 
22752 
22753 
22754 
22755   l_PAYMENT_METHOD_CODE       varchar2(30);
22756   l_PAYMENT_REASON_CODE       varchar2(30);
22757   l_BANK_CHARGE_BEARER        varchar2(30);
22758   l_DELIVERY_CHANNEL_CODE     varchar2(30);
22759   l_SETTLEMENT_PRIORITY       varchar2(30);
22760   l_PAY_ALONE                 varchar2(30);
22761   l_external_bank_account_id  number;
22762   l_exclusive_payment_flag    varchar2(1);
22763   l_payment_reason_comments   varchar2(240); --4874927
22764   -- Bug 5448579
22765   l_valid_payment_method      IBY_PAYMENT_METHODS_VL.Payment_Method_Code%TYPE;
22766 
22767   --Bug 8213679
22768   l_remit_party_id	AP_INVOICES_ALL.PARTY_ID%TYPE;
22769   l_remit_party_site_id	AP_INVOICES_ALL.PARTY_SITE_ID%TYPE;
22770   --Bug 8213679
22771 
22772 
22773   begin
22774 
22775 
22776     current_calling_sequence := 'AP_IMPORT_VALIDATION_PKG.v_check_payment_defaults<-'
22777 					||P_calling_sequence;
22778 
22779     debug_info := 'Check the payment reason';
22780 
22781     if p_invoice_rec.payment_reason_code is not null then
22782 
22783       begin
22784         select 'x'
22785         into l_dummy
22786         from iby_payment_reasons_vl
22787         where payment_reason_code = p_invoice_rec.payment_reason_code
22788         and rownum = 1;
22789 
22790       exception
22791         when no_data_found then
22792           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
22793                (AP_IMPORT_INVOICES_PKG.g_invoices_table,
22794                 p_invoice_rec.invoice_id,
22795                 'INVALID PAYMENT REASON',
22796                 p_default_last_updated_by,
22797                 p_default_last_update_login,
22798                 current_calling_sequence) <> TRUE) THEN
22799             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
22800               AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
22801                                             'insert_rejections<-'
22802                                             ||current_calling_sequence);
22803             END IF;
22804             RAISE pmt_attr_validation_failure;
22805           END IF;
22806 
22807           l_current_invoice_status := 'N';
22808 
22809        end;
22810     end if;
22811 
22812 
22813 
22814     debug_info := 'Check the bank charge bearer';
22815 
22816     if p_invoice_rec.bank_charge_bearer is not null then
22817 
22818       begin
22819         select 'x'
22820         into l_dummy
22821         from fnd_lookups
22822         where lookup_type = 'IBY_BANK_CHARGE_BEARER'
22823         and lookup_code = p_invoice_rec.bank_charge_bearer
22824         and rownum = 1;
22825 
22826       exception
22827         when no_data_found then
22828           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
22829                (AP_IMPORT_INVOICES_PKG.g_invoices_table,
22830                 p_invoice_rec.invoice_id,
22831                 'INVALID BANK CHARGE BEARER',
22832                 p_default_last_updated_by,
22833                 p_default_last_update_login,
22834                 current_calling_sequence) <> TRUE) THEN
22835             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
22836               AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
22837                                             'insert_rejections<-'
22838                                             ||current_calling_sequence);
22839             END IF;
22840             RAISE pmt_attr_validation_failure;
22841           END IF;
22842 
22843           l_current_invoice_status := 'N';
22844 
22845        end;
22846     end if;
22847 
22848 
22849 
22850     debug_info := 'Check the delivery channel code';
22851 
22852     if p_invoice_rec.delivery_channel_code is not null then
22853 
22854       begin
22855         select 'x'
22856         into l_dummy
22857         from iby_delivery_channels_vl
22858         where delivery_channel_code = p_invoice_rec.delivery_channel_code
22859         and rownum = 1;
22860 
22861       exception
22862         when no_data_found then
22863           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
22864                (AP_IMPORT_INVOICES_PKG.g_invoices_table,
22865                 p_invoice_rec.invoice_id,
22866                 'INVALID DELIVERY CHANNEL CODE',
22867                 p_default_last_updated_by,
22868                 p_default_last_update_login,
22869                 current_calling_sequence) <> TRUE) THEN
22870             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
22871               AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
22872                                             'insert_rejections<-'
22873                                             ||current_calling_sequence);
22874             END IF;
22875             RAISE pmt_attr_validation_failure;
22876           END IF;
22877 
22878           l_current_invoice_status := 'N';
22879 
22880        end;
22881     end if;
22882 
22883 
22884 
22885 
22886 
22887     debug_info := 'Check the settlement priority';
22888 
22889     if p_invoice_rec.settlement_priority is not null then
22890 
22891       begin
22892         select 'x'
22893         into l_dummy
22894         from fnd_lookups
22895         where lookup_type = 'IBY_SETTLEMENT_PRIORITY'
22896         and lookup_code = p_invoice_rec.settlement_priority
22897         and rownum = 1;
22898 
22899       exception
22900         when no_data_found then
22901           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
22902                (AP_IMPORT_INVOICES_PKG.g_invoices_table,
22903                 p_invoice_rec.invoice_id,
22904                 'INVALID SETTLEMENT PRIORITY',
22905                 p_default_last_updated_by,
22906                 p_default_last_update_login,
22907                 current_calling_sequence) <> TRUE) THEN
22908             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
22909               AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
22910                                             'insert_rejections<-'
22911                                             ||current_calling_sequence);
22912             END IF;
22913             RAISE pmt_attr_validation_failure;
22914           END IF;
22915 
22916           l_current_invoice_status := 'N';
22917 
22918        end;
22919     end if;
22920 
22921 
22922 
22923 
22924 
22925 
22926     debug_info := 'Check the external bank account id is defined';
22927 
22928     if p_invoice_rec.external_bank_account_id is not null then
22929 
22930       begin
22931         select 'x'
22932         into l_dummy
22933         from iby_ext_bank_accounts_v
22934         where ext_bank_account_id = p_invoice_rec.external_bank_account_id
22935         and rownum = 1;
22936 
22937       exception
22938         when no_data_found then
22939           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
22940                (AP_IMPORT_INVOICES_PKG.g_invoices_table,
22941                 p_invoice_rec.invoice_id,
22942                 'INVALID EXTERNAL BANK ACCT ID',
22943                 p_default_last_updated_by,
22944                 p_default_last_update_login,
22945                 current_calling_sequence) <> TRUE) THEN
22946             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
22947               AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
22948                                             'insert_rejections<-'
22949                                             ||current_calling_sequence);
22950             END IF;
22951             RAISE pmt_attr_validation_failure;
22952           END IF;
22953 
22954           l_current_invoice_status := 'N';
22955 
22956        end;
22957     end if;
22958 
22959 
22960     debug_info := 'Check the paymemt_method_code is defined';
22961 
22962     if p_invoice_rec.payment_method_code is not null then
22963        -- Bug 5448579
22964       FOR i IN AP_IMPORT_INVOICES_PKG.g_payment_method_tab.First.. AP_IMPORT_INVOICES_PKG.g_payment_method_tab.Last
22965       LOOP
22966         IF  AP_IMPORT_INVOICES_PKG.g_payment_method_tab(i).payment_method = p_invoice_rec.payment_method_code THEN
22967           l_valid_payment_method  :=  AP_IMPORT_INVOICES_PKG.g_payment_method_tab(i).payment_method;
22968           EXIT;
22969         END IF;
22970       END LOOP;
22971 
22972       debug_info := 'l_valid_payment_method: '||l_valid_payment_method;
22973       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
22974         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
22975                                     debug_info);
22976       END IF;
22977 
22978       IF l_valid_payment_method IS NULL THEN
22979 
22980         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
22981                (AP_IMPORT_INVOICES_PKG.g_invoices_table,
22982                 p_invoice_rec.invoice_id,
22983                 'INVALID PAY METHOD',
22984                 p_default_last_updated_by,
22985                 p_default_last_update_login,
22986                 current_calling_sequence) <> TRUE) THEN
22987           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
22988               AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
22989                                             'insert_rejections<-'
22990                                             ||current_calling_sequence);
22991           END IF;
22992           RAISE pmt_attr_validation_failure;
22993         END IF;
22994 
22995         l_current_invoice_status := 'N';
22996 
22997       END IF;
22998 
22999     end if;
23000 
23001     /*  begin
23002         select 'x'
23003         into l_dummy
23004         from iby_payment_methods_vl --4393358
23005         where payment_method_code = p_invoice_rec.payment_method_code
23006         and rownum = 1;
23007 
23008       exception
23009         when no_data_found then
23010           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
23011                (AP_IMPORT_INVOICES_PKG.g_invoices_table,
23012                 p_invoice_rec.invoice_id,
23013                 'INVALID PAY METHOD',
23014                 p_default_last_updated_by,
23015                 p_default_last_update_login,
23016                 current_calling_sequence) <> TRUE) THEN
23017             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
23018               AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
23019                                             'insert_rejections<-'
23020                                             ||current_calling_sequence);
23021             END IF;
23022             RAISE pmt_attr_validation_failure;
23023           END IF;
23024 
23025           l_current_invoice_status := 'N';
23026 
23027        end; */
23028 
23029 
23030 
23031 
23032     --iby's api requires the pay proc trxn type and payment function, so we
23033     --need to determine them for AP if not populated
23034 
23035     -- As per the discussion with Omar/Jayanta, we will only
23036     -- have payables payment function and no more employee expenses
23037     -- payment function.
23038 
23039     if p_invoice_rec.invoice_type_lookup_code is not null and
23040        p_invoice_rec.payment_function is null then
23041         p_invoice_rec.payment_function := 'PAYABLES_DISB';
23042     end if;
23043 
23044     /* bug 5115632 */
23045     if p_invoice_rec.invoice_type_lookup_code = 'EXPENSE REPORT'
23046       and p_invoice_rec.pay_proc_trxn_type_code is null then
23047       p_invoice_rec.pay_proc_trxn_type_code := 'EMPLOYEE_EXP';
23048     end if;
23049 
23050     if p_invoice_rec.invoice_type_lookup_code  <> 'EXPENSE REPORT'
23051       and  p_invoice_rec.pay_proc_trxn_type_code is null then
23052       if p_invoice_rec.payment_function = 'AR_CUSTOMER_REFUNDS' then
23053         p_invoice_rec.pay_proc_trxn_type_code := 'AR_CUSTOMER_REFUND';
23054       elsif p_invoice_rec.payment_function = 'LOANS_PAYMENTS' then
23055         p_invoice_rec.pay_proc_trxn_type_code := 'LOAN_PAYMENT';
23056       else
23057         p_invoice_rec.pay_proc_trxn_type_code := 'PAYABLES_DOC';
23058       end if;
23059     end if;
23060 
23061 
23062 
23063     --now get defaults...
23064     -- modified below if condition as part of bug 8345877
23065     if p_invoice_rec.legal_entity_id is not null and
23066        p_invoice_rec.org_id is not null and
23067        p_invoice_rec.party_id is not null and
23068        --Bug8488565: OR condition for party_site_id and vendor_site_id
23069        (p_invoice_rec.party_site_id is not null or
23070        p_invoice_rec.vendor_site_id is not null ) and
23071        p_invoice_rec.payment_currency_code is not null and
23072        p_invoice_rec.invoice_amount is not null and
23073        p_invoice_rec.payment_function is not null and
23074        p_invoice_rec.pay_proc_trxn_type_code is not null then
23075 
23076 
23077 
23078       debug_info := 'Get iby defaults';
23079 
23080       --Bug 8245830
23081       IF (p_invoice_rec.invoice_type_lookup_code  <> 'PAYMENT REQUEST'  AND
23082 		(p_invoice_rec.remit_to_supplier_id is not null AND
23083 		p_invoice_rec.remit_to_supplier_site_id is not null)
23084 	)THEN
23085         --Bug 8213679
23086         select party_id
23087         into l_remit_party_id
23088         from ap_suppliers
23089         where vendor_id = p_invoice_rec.remit_to_supplier_id;
23090 
23091         select party_site_id
23092         into l_remit_party_site_id
23093         from ap_supplier_sites_all
23094         where vendor_site_id = p_invoice_rec.remit_to_supplier_site_id
23095         and org_id = p_invoice_rec.org_id;
23096         --Bug 8213679
23097       ELSE
23098 	  -- modified below code as part of bug 8345877
23099           --l_remit_party_id      := p_invoice_rec.party_id;
23100 	  --l_remit_party_site_id := p_invoice_rec.party_site_id;
23101           l_remit_party_id      := null;
23102 	 --Bug 9133220 handle expense reports with null party site id.
23103 	 IF p_invoice_rec.party_site_id is null
23104 	    AND p_invoice_rec.invoice_type_lookup_code  <> 'PAYMENT REQUEST'
23105 	    AND nvl(p_invoice_rec.vendor_site_id, -1) > 0 THEN
23106 		select party_site_id
23107 		into l_remit_party_site_id
23108 		from ap_supplier_sites_all
23109 		where vendor_site_id = p_invoice_rec.vendor_site_id
23110 		and org_id = p_invoice_rec.org_id;
23111 	 ELSE
23112 	     l_remit_party_site_id := null;
23113 	 END If;
23114 	 --end Bug 9133220
23115       END IF;
23116 
23117 
23118       ap_invoices_pkg.get_payment_attributes(
23119         p_le_id                     =>p_invoice_rec.legal_entity_id,
23120         p_org_id                    =>p_invoice_rec.org_id,
23121         p_payee_party_id            =>nvl(l_remit_party_id,p_invoice_rec.party_id),	--Bug 8345877
23122         p_payee_party_site_id       =>nvl(l_remit_party_site_id,p_invoice_rec.party_site_id), --Bug 8345877
23123         p_supplier_site_id          =>nvl(p_invoice_rec.remit_to_supplier_site_id,p_invoice_rec.vendor_site_id), --Bug 8345877
23124         p_payment_currency          =>p_invoice_rec.payment_currency_code,
23125         p_payment_amount            =>p_invoice_rec.invoice_amount,
23126         p_payment_function          =>p_invoice_rec.payment_function,
23127         p_pay_proc_trxn_type_code   =>p_invoice_rec.pay_proc_trxn_type_code,
23128 
23129         p_PAYMENT_METHOD_CODE       => l_payment_method_code,
23130         p_PAYMENT_REASON_CODE       => l_payment_reason_code,
23131         p_BANK_CHARGE_BEARER        => l_bank_charge_bearer,
23132         p_DELIVERY_CHANNEL_CODE     => l_delivery_channel_code,
23133         p_SETTLEMENT_PRIORITY       => l_settlement_priority,
23134         p_PAY_ALONE                 => l_exclusive_payment_flag,
23135         p_external_bank_account_id  => l_external_bank_account_id,
23136 
23137         p_IBY_PAYMENT_METHOD        => l_IBY_PAYMENT_METHOD,
23138         p_PAYMENT_REASON            => l_PAYMENT_REASON,
23139         p_BANK_CHARGE_BEARER_DSP    => l_BANK_CHARGE_BEARER_DSP,
23140         p_DELIVERY_CHANNEL          => l_DELIVERY_CHANNEL,
23141         p_SETTLEMENT_PRIORITY_DSP   => l_SETTLEMENT_PRIORITY_DSP,
23142         p_bank_account_num          => l_bank_account_num,
23143         p_bank_account_name         => l_bank_account_name,
23144         p_bank_branch_name          => l_bank_branch_name,
23145         p_bank_branch_num           => l_bank_branch_num,
23146         p_bank_name                 => l_bank_name,
23147         p_bank_number               => l_bank_number,
23148         p_payment_reason_comments   => l_payment_reason_comments, -- 4874927
23149         p_application_id            => p_invoice_rec.application_id);  --5115632
23150 
23151 
23152 
23153 
23154 
23155       debug_info := 'assign iby defaults to null fields';
23156 
23157       if p_invoice_rec.payment_method_code is null then
23158         p_invoice_rec.payment_method_code := l_payment_method_code;
23159       end if;
23160 
23161       if p_invoice_rec.payment_reason_code is null then
23162         p_invoice_rec.payment_reason_code := l_payment_reason_code;
23163       end if;
23164 
23165       if p_invoice_rec.bank_charge_bearer is null then
23166         p_invoice_rec.bank_charge_bearer := l_bank_charge_bearer;
23167       end if;
23168 
23169       if p_invoice_rec.delivery_channel_code is null then
23170         p_invoice_rec.delivery_channel_code := l_delivery_channel_code;
23171       end if;
23172 
23173       if p_invoice_rec.settlement_priority is null then
23174         p_invoice_rec.settlement_priority := l_settlement_priority;
23175       end if;
23176 
23177       if p_invoice_rec.exclusive_payment_flag is null then
23178         p_invoice_rec.exclusive_payment_flag := l_exclusive_payment_flag;
23179       end if;
23180 
23181       if p_invoice_rec.external_bank_account_id is null then
23182         p_invoice_rec.external_bank_account_id := l_external_bank_account_id;
23183       end if;
23184 
23185       --4874927
23186       if p_invoice_rec.payment_reason_comments is null then
23187         p_invoice_rec.payment_reason_comments := l_payment_reason_comments;
23188       end if;
23189 
23190 
23191     end if;
23192 
23193     --the payment method code is a required field so we should reject if it's
23194     --not present at this point (no default was found)
23195     if p_invoice_rec.payment_method_code is null then
23196       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
23197                (AP_IMPORT_INVOICES_PKG.g_invoices_table,
23198                 p_invoice_rec.invoice_id,
23199                 'INVALID PAY METHOD',
23200                 p_default_last_updated_by,
23201                 p_default_last_update_login,
23202                 current_calling_sequence) <> TRUE) THEN
23203             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
23204               AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
23205                                             'insert_rejections<-'
23206                                             ||current_calling_sequence);
23207             END IF;
23208             RAISE pmt_attr_validation_failure;
23209       END IF;
23210       l_current_invoice_status := 'N';
23211     end if;
23212 
23213 
23214 
23215     p_current_invoice_status := l_current_invoice_status;
23216 
23217   return(true);
23218 
23219   EXCEPTION
23220 	WHEN OTHERS THEN
23221 		IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
23222 			AP_IMPORT_UTILITIES_PKG.Print(
23223 				AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
23224 		END IF;
23225 
23226 		IF (SQLCODE < 0) THEN
23227 			IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
23228 				AP_IMPORT_UTILITIES_PKG.Print(
23229 					AP_IMPORT_INVOICES_PKG.g_debug_switch, SQLERRM);
23230 			END IF;
23231 		END IF;
23232 		RETURN(FALSE);
23233   end v_check_payment_defaults;
23234 
23235 
23236 
23237 FUNCTION v_check_party_vendor(
23238     p_invoice_rec               IN OUT NOCOPY AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
23239     p_current_invoice_status	IN OUT NOCOPY VARCHAR2,
23240     p_calling_sequence          IN            VARCHAR2,
23241     p_default_last_updated_by   IN            NUMBER,
23242     p_default_last_update_login IN            NUMBER
23243     ) return boolean is
23244 
23245 l_dummy varchar2(1);
23246 l_current_invoice_status varchar2(1):='Y';
23247 debug_info                  VARCHAR2(500);
23248 current_calling_sequence    VARCHAR2(2000);
23249 vendor_party_failure        exception;
23250 
23251 -- Bug 7871425.
23252 l_vendor_type_lookup_code   ap_suppliers.vendor_type_lookup_code%type ;
23253 
23254 begin
23255 
23256   current_calling_sequence := 'AP_IMPORT_VALIDATION_PKG.v_check_party_vendor<-'
23257 					||P_calling_sequence;
23258   debug_info := 'Check vendor and party info are consistent';
23259 
23260 
23261 
23262 
23263   --if the vendor and party are populated, I think we should make sure they are
23264   --consistent, the same goes for vedor site and party site
23265   -- Release won't be able to seed a rejection for the 2 cases below before the
23266   -- freeze.  So for now I am using existin ones.
23267 
23268   if p_invoice_rec.party_id is not null and p_invoice_rec.vendor_id is not null then
23269     begin
23270       select 'x'
23271       into l_dummy
23272       from po_vendors
23273       where vendor_id = p_invoice_rec.vendor_id
23274       and party_id = p_invoice_rec.party_id;
23275     exception
23276       when no_data_found then
23277         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
23278              (AP_IMPORT_INVOICES_PKG.g_invoices_table,
23279               p_invoice_rec.invoice_id,
23280               'INCONSISTENT SUPPLIER',
23281               p_default_last_updated_by,
23282               p_default_last_update_login,
23283               current_calling_sequence) <> TRUE) THEN
23284           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
23285             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
23286                                           'insert_rejections<-'
23287                                           ||current_calling_sequence);
23288           END IF;
23289           RAISE vendor_party_failure;
23290         END IF;
23291       l_current_invoice_status := 'N';
23292     end;
23293   end if;
23294 
23295 
23296 
23297   if p_invoice_rec.party_site_id is not null and
23298      p_invoice_rec.vendor_site_id is not null then
23299     begin
23300       select 'x'
23301       into l_dummy
23302       from po_vendor_sites
23303       where vendor_site_id = p_invoice_rec.vendor_site_id
23304       and party_site_id = p_invoice_rec.party_site_id;
23305     exception
23306       when no_data_found then
23307         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
23308              (AP_IMPORT_INVOICES_PKG.g_invoices_table,
23309               p_invoice_rec.invoice_id,
23310               'INCONSISTENT SUPPL SITE',
23311               p_default_last_updated_by,
23312               p_default_last_update_login,
23313               current_calling_sequence) <> TRUE) THEN
23314           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
23315             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
23316                                           'insert_rejections<-'
23317                                           ||current_calling_sequence);
23318           END IF;
23319           RAISE vendor_party_failure;
23320         END IF;
23321       l_current_invoice_status := 'N';
23322     end;
23323   end if;
23324 
23325 
23326 
23327 
23328 
23329   --according to Shelley, we want to populate a negative application
23330   --id when we have party info but no vendor info
23331 
23332   if p_invoice_rec.party_id is not null and p_invoice_rec.vendor_id is null then
23333     p_invoice_rec.vendor_id := -1 * p_invoice_rec.application_id;
23334   end if;
23335 
23336   if p_invoice_rec.party_site_id is not null and p_invoice_rec.vendor_site_id is null then
23337     p_invoice_rec.vendor_site_id := -1 * p_invoice_rec.application_id;
23338   end if;
23339 
23340   -- Bug 7871425.
23341 
23342   IF (nvl(p_invoice_rec.invoice_type_lookup_code, 'STANDARD') = 'EXPENSE REPORT'
23343       AND p_invoice_rec.party_site_id is null) THEN
23344 
23345     select vendor_type_lookup_code into l_vendor_type_lookup_code
23346     from ap_suppliers where vendor_id = p_invoice_rec.vendor_id ;
23347 
23348   END IF ;
23349 
23350   -- Bug 7871425.
23351   -- Populate the party_site_id for expense reports created for non-employee
23352   -- type suppliers. Now party site id will be populated if invoice type is
23353   -- EXPENSE REPORT and vendor type is not EMPLOYEE.
23354 
23355   --if we just have vendor info then also populate the party info
23356   if p_invoice_rec.vendor_site_id is not null and p_invoice_rec.party_site_id is null
23357      and (nvl(p_invoice_rec.invoice_type_lookup_code, 'STANDARD') <> 'EXPENSE REPORT'
23358      or(nvl(p_invoice_rec.invoice_type_lookup_code, 'STANDARD') = 'EXPENSE REPORT'
23359         and nvl(l_vendor_type_lookup_code, 'VENDOR') <> 'EMPLOYEE')) then
23360     Begin
23361       select party_site_id
23362       into p_invoice_rec.party_site_id
23363       from po_vendor_sites
23364       where vendor_site_id = p_invoice_rec.vendor_site_id;
23365     Exception
23366       when no_data_found then
23367       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
23368              (AP_IMPORT_INVOICES_PKG.g_invoices_table,
23369               p_invoice_rec.invoice_id,
23370               'INCONSISTENT SUPPL SITE',
23371               p_default_last_updated_by,
23372               p_default_last_update_login,
23373               current_calling_sequence) <> TRUE) THEN
23374         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
23375             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
23376                                           'insert_rejections<-'
23377                                           ||current_calling_sequence);
23378         END IF;
23379         RAISE vendor_party_failure;  --bug6367302
23380       END IF;
23381       --RAISE vendor_party_failure;
23382     End;
23383   end if;
23384 
23385   if p_invoice_rec.vendor_id is not null and p_invoice_rec.party_id is null then
23386     Begin
23387       select party_id
23388       into p_invoice_rec.party_id
23389       from po_vendors
23390       where vendor_id = p_invoice_rec.vendor_id;
23391     Exception
23392       when no_data_found then
23393       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
23394              (AP_IMPORT_INVOICES_PKG.g_invoices_table,
23395               p_invoice_rec.invoice_id,
23396               'INCONSISTENT SUPPLIER',
23397               p_default_last_updated_by,
23398               p_default_last_update_login,
23399               current_calling_sequence) <> TRUE) THEN
23400         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
23401             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
23402                                           'insert_rejections<-'
23403                                           ||current_calling_sequence);
23404         END IF;
23405         RAISE vendor_party_failure;  --bug6367302
23406       END IF;
23407       --RAISE vendor_party_failure;
23408     End;
23409   end if;
23410 
23411 
23412 
23413   p_current_invoice_status := l_current_invoice_status;
23414   return(true);
23415 
23416 EXCEPTION
23417   WHEN OTHERS THEN
23418 		IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
23419 			AP_IMPORT_UTILITIES_PKG.Print(
23420 				AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
23421 		END IF;
23422 
23423 		IF (SQLCODE < 0) THEN
23424 			IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
23425 				AP_IMPORT_UTILITIES_PKG.Print(
23426 					AP_IMPORT_INVOICES_PKG.g_debug_switch, SQLERRM);
23427 			END IF;
23428 		END IF;
23429 		RETURN(FALSE);
23430 end v_check_party_vendor;
23431 
23432 
23433 --bugfix:5565310
23434 FUNCTION v_check_line_get_po_tax_attr(
23435 		-- bug 8495005 : Changed IN as IN OUT NOCOPY for p_invoice_rec parameter
23436 		p_invoice_rec IN OUT NOCOPY AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
23437                 p_invoice_lines_rec IN OUT NOCOPY AP_IMPORT_INVOICES_PKG.r_line_info_rec,
23438 	        p_calling_sequence IN VARCHAR2) return boolean  IS
23439 
23440  l_ref_doc_application_id      zx_transaction_lines_gt.ref_doc_application_id%TYPE;
23441  l_ref_doc_entity_code         zx_transaction_lines_gt.ref_doc_entity_code%TYPE;
23442  l_ref_doc_event_class_code    zx_transaction_lines_gt.ref_doc_event_class_code%TYPE;
23443  l_ref_doc_line_quantity       zx_transaction_lines_gt.ref_doc_line_quantity%TYPE;
23444  l_po_header_curr_conv_rat     po_headers_all.rate%TYPE;
23445  l_ref_doc_trx_level_type      zx_transaction_lines_gt.ref_doc_trx_level_type%TYPE;
23446  l_po_header_curr_conv_rate    po_headers_all.rate%TYPE;
23447  l_uom_code                    mtl_units_of_measure.uom_code%TYPE;
23448  l_ref_doc_trx_id              po_headers_all.po_header_id%TYPE;
23449  l_error_code                  varchar2(2000);
23450  current_calling_sequence VARCHAR2(2000);
23451  l_success		       boolean;
23452  l_intended_use                  zx_lines_det_factors.line_intended_use%type;
23453  l_product_type                  zx_lines_det_factors.product_type%type;
23454  l_product_category              zx_lines_det_factors.product_category%type;
23455  l_product_fisc_class            zx_lines_det_factors.product_fisc_classification%type;
23456  l_user_defined_fisc_class       zx_lines_det_factors.user_defined_fisc_class%type;
23457  l_assessable_value              zx_lines_det_factors.assessable_value%type;
23458  l_dflt_tax_class_code           zx_transaction_lines_gt.input_tax_classification_code%type;
23459  l_dummy			 number;
23460  debug_info			 varchar2(1000);
23461    -- bug 8495005 fix starts
23462  l_taxation_country	zx_lines_det_factors.default_taxation_country%type;
23463  l_trx_biz_category	zx_lines_det_factors.trx_business_category%type;
23464  -- bug 8495005 fix ends
23465 
23466  -- bug 8483345: start
23467  l_product_org_id              ap_invoices.org_id%TYPE;
23468  l_allow_tax_code_override     varchar2(10);
23469  l_dflt_tax_class_code2         zx_transaction_lines_gt.input_tax_classification_code%type;
23470  -- bug 8483345: end
23471 
23472 l_code_combination_id         NUMBER ; -- Bug 10050094
23473 l_full_mtch_amt NUMBER;       --Bug#13505998
23474 BEGIN
23475     current_calling_sequence := 'AP_IMPORT_VALIDATION_PKG.v_check_line_get_po_tax_attr<-' || p_calling_sequence ;  -- Bug 10050094
23476 
23477     IF (p_invoice_lines_rec.primary_intended_use IS NULL OR
23478         p_invoice_lines_rec.product_fisc_classification IS NULL OR
23479 	p_invoice_lines_rec.product_type IS NULL OR
23480 	p_invoice_lines_rec.product_category IS NULL OR
23481 	p_invoice_lines_rec.user_defined_fisc_class IS NULL OR
23482 	p_invoice_lines_rec.assessable_value IS NULL OR
23483 	p_invoice_lines_rec.tax_classification_code IS NULL OR
23484 	-- bug 8495005 fix starts
23485 	p_invoice_rec.taxation_country IS NULL OR
23486 	p_invoice_lines_rec.trx_business_category IS NULL
23487 	-- bug 8495005 fix ends
23488 	) THEN
23489 
23490 	debug_info := 'Call Ap_Etx_Utility_Pkg.Get_PO_Info';
23491 	IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
23492 	    AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
23493 	                                      debug_info);
23494         END IF;
23495 
23496         l_success := AP_ETAX_UTILITY_PKG.Get_PO_Info(
23497 	                  P_Po_Line_Location_Id         => p_invoice_lines_rec.po_line_location_id,
23498 			  P_PO_Distribution_Id          => null,
23499 			  P_Application_Id              => l_ref_doc_application_id,
23500 			  P_Entity_code                 => l_ref_doc_entity_code,
23501 			  P_Event_Class_Code            => l_ref_doc_event_class_code,
23502 			  P_PO_Quantity                 => l_ref_doc_line_quantity,
23503 			  P_Product_Org_Id              => l_product_org_id, -- 8483345
23504 			  P_Po_Header_Id                => l_ref_doc_trx_id,
23505 			  P_Po_Header_curr_conv_rate    => l_po_header_curr_conv_rate,
23506 			  P_Uom_Code                    => l_uom_code,
23507 			  P_Dist_Qty                    => l_dummy,
23508 			  P_Ship_Price                  => l_dummy,
23509 			  P_Error_Code                  => l_error_code,
23510 			  P_Calling_Sequence            => current_calling_sequence);
23511 
23512     -- Bug 10050094
23513     AP_ETAX_UTILITY_PKG.Get_Default_CCID( p_default_dist_ccid     => p_invoice_lines_rec.default_dist_ccid,
23514                                           p_match_type 	          => p_invoice_lines_rec.match_type,
23515 			                  p_po_line_location_id   => p_invoice_lines_rec.po_line_location_id,
23516 			                  p_po_distribution_id    => p_invoice_lines_rec.po_distribution_id,
23517 			                  p_rcv_transaction_id    => p_invoice_lines_rec.rcv_transaction_id,
23518 			                  p_line_type_lookup_code => p_invoice_lines_rec.line_type_lookup_code,
23519 			                  p_reference_key1        => p_invoice_lines_rec.reference_key1,
23520 			                  p_reference_key2        => p_invoice_lines_rec.reference_key2,
23521 					  p_invoice_line_number   => p_invoice_lines_rec.line_number,
23522 					  p_distribution_set_id   => p_invoice_lines_rec.distribution_set_id,
23523                                           p_calling_sequence      => current_calling_sequence,
23524                                           x_derived_ccid          => l_code_combination_id ) ;
23525 
23526 	          -- bug 8483345: start
23527  	     debug_info := 'Get Default Tax Classification';
23528  	     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
23529  	             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
23530  	     END IF;
23531 
23532  	     ZX_AP_TAX_CLASSIFICATN_DEF_PKG.get_default_tax_classification
23533  	                     (p_ref_doc_application_id           => l_ref_doc_application_id,
23534  	                      p_ref_doc_entity_code              => l_ref_doc_entity_code,
23535  	                      p_ref_doc_event_class_code         => l_ref_doc_event_class_code,
23536  	                      p_ref_doc_trx_id                   => l_ref_doc_trx_id,
23537  	                      p_ref_doc_line_id                  => p_invoice_lines_rec.po_line_location_id,
23538  	                      p_ref_doc_trx_level_type           => 'SHIPMENT',
23539  	                      p_vendor_id                        => p_invoice_rec.vendor_id,
23540  	                      p_vendor_site_id                   => p_invoice_rec.vendor_site_id,
23541  	                      p_code_combination_id              => l_code_combination_id, -- Bug 10050094  p_invoice_lines_rec.dist_code_combination_id,
23542  	                      p_concatenated_segments            => null,
23543  	                      p_templ_tax_classification_cd      => null,
23544  	                      p_ship_to_location_id              => null,
23545  	                      p_ship_to_loc_org_id               => null,
23546  	                      p_inventory_item_id                => null,
23547  	                      p_item_org_id                      => l_product_org_id,
23548  	                      p_tax_classification_code          => l_dflt_tax_class_code,
23549  	                      p_allow_tax_code_override_flag     => l_allow_tax_code_override,
23550  	                      APPL_SHORT_NAME                    => 'SQLAP',
23551  	                      FUNC_SHORT_NAME                    => 'NONE',
23552  	                      p_calling_sequence                 => current_calling_sequence, -- Bug 10050094  'AP_ETAX_SERVICES_PKG',
23553  	                      p_event_class_code                 => l_ref_doc_event_class_code,
23554  	                      p_entity_code                      => 'AP_INVOICES',
23555  	                      p_application_id                   => 200,
23556  	                      p_internal_organization_id         => p_invoice_lines_rec.org_id);
23557  	          -- bug 8483345: end
23558 
23559 	 debug_info := 'Call ap_etx_servies_pkg.get_po_tax_attributes';
23560 	 IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
23561 	     AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
23562 	                                       debug_info);
23563          END IF;
23564 
23565 	-- bug 8495005 fix starts
23566 	 IF (p_invoice_rec.source = 'ERS') THEN
23567 		 AP_Etax_Services_Pkg.Get_Po_Tax_Attributes(
23568 				  p_application_id              => l_ref_doc_application_id,
23569 				  p_org_id                      => p_invoice_lines_rec.org_id,
23570 				  p_entity_code                 => l_ref_doc_entity_code,
23571 				  p_event_class_code            => l_ref_doc_event_class_code,
23572 				  p_trx_level_type              => 'SHIPMENT',
23573 				  p_trx_id                      => l_ref_doc_trx_id,
23574 				  p_trx_line_id                 => p_invoice_lines_rec.po_line_location_id,
23575 				  x_line_intended_use           => l_intended_use,
23576 				  x_product_type                => l_product_type,
23577 				  x_product_category            => l_product_category,
23578 				  x_product_fisc_classification => l_product_fisc_class,
23579 				  x_user_defined_fisc_class     => l_user_defined_fisc_class,
23580 				  x_assessable_value            => l_assessable_value,
23581 				  x_tax_classification_code     => l_dflt_tax_class_code2, -- bug 8483345
23582 				  x_taxation_country		=> l_taxation_country,
23583 				  x_trx_biz_category		=> l_trx_biz_category
23584 				  );
23585 	 ELSE
23586 		 AP_Etax_Services_Pkg.Get_Po_Tax_Attributes(
23587 				  p_application_id              => l_ref_doc_application_id,
23588 				  p_org_id                      => p_invoice_lines_rec.org_id,
23589 				  p_entity_code                 => l_ref_doc_entity_code,
23590 				  p_event_class_code            => l_ref_doc_event_class_code,
23591 				  p_trx_level_type              => 'SHIPMENT',
23592 				  p_trx_id                      => l_ref_doc_trx_id,
23593 				  p_trx_line_id                 => p_invoice_lines_rec.po_line_location_id,
23594 				  x_line_intended_use           => l_intended_use,
23595 				  x_product_type                => l_product_type,
23596 				  x_product_category            => l_product_category,
23597 				  x_product_fisc_classification => l_product_fisc_class,
23598 				  x_user_defined_fisc_class     => l_user_defined_fisc_class,
23599 				  x_assessable_value            => l_assessable_value,
23600 				  x_tax_classification_code     => l_dflt_tax_class_code2 -- bug 8483345
23601 				  );
23602   	 END IF;
23603 	 -- bug 8495005 fix ends
23604 
23605       -- bug 8483345: start
23606          -- if tax classification code not retrieved from hierarchy
23607          -- retrieve it from PO
23608          IF (l_dflt_tax_class_code is null) THEN
23609              l_dflt_tax_class_code := l_dflt_tax_class_code2;
23610          END IF;
23611       -- bug 8483345: end
23612 
23613 	  debug_info := 'populate the lines record with tax attr info';
23614 	  IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
23615 	        AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
23616 	                                         debug_info);
23617 	  END IF;
23618 
23619           IF (p_invoice_lines_rec.primary_intended_use IS NULL) THEN
23620               p_invoice_lines_rec.primary_intended_use := l_intended_use;
23621 	  END IF;
23622 
23623 	  IF (p_invoice_lines_rec.product_type IS NULL) THEN
23624 	      p_invoice_lines_rec.product_type := l_product_type;
23625 	  END IF;
23626 
23627 	  IF (p_invoice_lines_rec.product_category IS NULL) THEN
23628 	      p_invoice_lines_rec.product_category := l_product_category;
23629 	  END IF;
23630 
23631 	  IF (p_invoice_lines_rec.product_fisc_classification IS NULL) THEN
23632 	      p_invoice_lines_rec.product_fisc_classification:= l_product_fisc_class;
23633 	  END IF;
23634 
23635 	  IF (p_invoice_lines_rec.USER_DEFINED_FISC_CLASS IS NULL) THEN
23636 	    p_invoice_lines_rec.USER_DEFINED_FISC_CLASS := l_user_defined_fisc_class;
23637 	  END IF;
23638 
23639 	  IF (p_invoice_lines_rec.assessable_value IS NULL) THEN
23640               --Bug13505998 starts
23641             l_full_mtch_amt := ap_matching_utils_pkg.get_full_mtch_amt
23642                           (p_invoice_lines_rec.po_line_location_id,
23643 			    p_invoice_rec.invoice_currency_code);
23644 
23645 
23646             debug_info := 'l_full_mtch_amt '||l_full_mtch_amt;
23647            IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
23648               AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
23649                                               debug_info);
23650            END IF;
23651             IF(l_full_mtch_amt = p_invoice_lines_rec.amount)THEN
23652               p_invoice_lines_rec.assessable_value := l_assessable_value;
23653             END IF;
23654 	  --End 13505998
23655 	  END IF;
23656 
23657 	  IF (p_invoice_lines_rec.tax_classification_code IS NULL) THEN
23658 	      p_invoice_lines_rec.tax_classification_code := l_dflt_tax_class_code;
23659 	  END IF;
23660 
23661 	  -- bug 8495005 fix starts
23662 	  IF (p_invoice_rec.source = 'ERS') THEN
23663 		IF (p_invoice_rec.taxation_country IS NULL) THEN
23664 		   p_invoice_rec.taxation_country := l_taxation_country;
23665 		END IF;
23666 
23667 		IF (p_invoice_lines_rec.trx_business_category IS NULL) THEN
23668 		   p_invoice_lines_rec.trx_business_category := l_trx_biz_category;
23669 		END IF;
23670 	  END IF;
23671 	  -- bug 8495005 fix ends
23672 
23673     END IF;
23674 
23675    return(true);
23676 
23677 EXCEPTION
23678   WHEN OTHERS THEN
23679       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
23680            AP_IMPORT_UTILITIES_PKG.Print(
23681                AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
23682        END IF;
23683 
23684   IF (SQLCODE < 0) THEN
23685     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
23686         AP_IMPORT_UTILITIES_PKG.Print(
23687             AP_IMPORT_INVOICES_PKG.g_debug_switch, SQLERRM);
23688      END IF;
23689   END IF;
23690   RETURN(FALSE);
23691 
23692 
23693 END v_check_line_get_po_tax_attr;
23694 
23695 --bug# 6989166 starts
23696 FUNCTION v_check_ship_to_location_code(
23697 		 p_invoice_rec	IN  AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
23698 		 p_invoice_line_rec  IN OUT NOCOPY AP_IMPORT_INVOICES_PKG.r_line_info_rec,
23699          p_default_last_updated_by      IN            NUMBER,
23700  		 p_default_last_update_login    IN            NUMBER,
23701 		 p_current_invoice_status	IN OUT NOCOPY VARCHAR2,
23702 	     p_calling_sequence IN VARCHAR2) return boolean  IS
23703 
23704   Cursor c_ship_to_location (p_ship_to_loc_code HR_LOCATIONS.LOCATION_CODE%TYPE) Is
23705   Select ship_to_location_id
23706     From hr_locations
23707    Where location_code = p_ship_to_loc_code
23708      and nvl(ship_to_site_flag, 'N') = 'Y';
23709 
23710   l_ship_to_location_id  ap_supplier_sites_all.ship_to_location_id%type;
23711   current_calling_sequence VARCHAR2(2000);
23712   debug_info			 varchar2(1000);
23713   ship_to_location_code_failure EXCEPTION;
23714   l_current_invoice_status    VARCHAR2(1) := 'Y';
23715 
23716 BEGIN
23717 
23718 	current_calling_sequence := 'AP_IMPORT_VALIDATION_PKG.v_check_ship_to_location_code<-'
23719 				||P_calling_sequence;
23720 	debug_info := 'Check valid ship to location code';
23721 
23722     IF lg_ship_to_loc_id_code.EXISTS(p_invoice_line_rec.ship_to_location_code) THEN
23723        p_invoice_line_rec.ship_to_location_id := lg_ship_to_loc_id_code(p_invoice_line_rec.ship_to_location_code);
23724     ELSE
23725 
23726     	Open c_ship_to_location (p_invoice_line_rec.ship_to_location_code);
23727 	    Fetch c_ship_to_location
23728 	    Into lg_ship_to_loc_id_code(p_invoice_line_rec.ship_to_location_code);
23729 
23730        p_invoice_line_rec.ship_to_location_id := lg_ship_to_loc_id_code(p_invoice_line_rec.ship_to_location_code);
23731 
23732 
23733 
23734 
23735 	IF (c_ship_to_location%NOTFOUND) THEN
23736 		IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
23737 			(AP_IMPORT_INVOICES_PKG.g_invoices_table,
23738 						p_invoice_rec.invoice_id,
23739 						'INVALID LOCATION CODE',
23740 					    p_default_last_updated_by,
23741 						p_default_last_update_login,
23742 						current_calling_sequence) <> TRUE) THEN
23743 
23744 			IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
23745 			    AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
23746 							  'insert_rejections<-'
23747 							  ||current_calling_sequence);
23748 
23749 		        END IF;
23750 
23751 			Close c_ship_to_location;
23752 			RAISE ship_to_location_code_failure;
23753 
23754                END IF;
23755 		l_current_invoice_status := 'N';
23756 	END IF;
23757 
23758 	 IF c_ship_to_location%isopen then
23759            Close c_ship_to_location;
23760          END IF;
23761 
23762 
23763     END IF; --bug 16078816
23764 
23765    p_current_invoice_status := l_current_invoice_status;
23766 
23767    return(true);
23768 
23769 EXCEPTION
23770   WHEN OTHERS THEN
23771       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
23772            AP_IMPORT_UTILITIES_PKG.Print(
23773                AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
23774        END IF;
23775 
23776   IF (SQLCODE < 0) THEN
23777     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
23778         AP_IMPORT_UTILITIES_PKG.Print(
23779             AP_IMPORT_INVOICES_PKG.g_debug_switch, SQLERRM);
23780      END IF;
23781   END IF;
23782   RETURN(FALSE);
23783 
23784 
23785 END v_check_ship_to_location_code;
23786 --bug# 6989166 ends
23787 
23788 FUNCTION v_check_invalid_remit_supplier(
23789              p_invoice_rec      IN OUT NOCOPY AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
23790              p_default_last_updated_by     IN            NUMBER,
23791              p_default_last_update_login   IN            NUMBER,
23792              p_current_invoice_status      IN OUT NOCOPY VARCHAR2,
23793              p_calling_sequence           IN            VARCHAR2)
23794     RETURN BOOLEAN IS
23795 
23796   current_calling_sequence VARCHAR2(2000);
23797   debug_info			varchar2(1000);
23798 
23799   l_remit_supplier_name       VARCHAR2(240) := NULL;
23800   l_remit_supplier_id            NUMBER := NULL;
23801   l_remit_supplier_num            VARCHAR2(30) := NULL;
23802   l_remit_supplier_site         VARCHAR2(240) := NULL;
23803   l_remit_supplier_site_id     NUMBER := NULL;
23804   l_remit_party_id            NUMBER := NULL;
23805   l_remit_party_site_id            NUMBER := NULL;
23806   l_relationship_id           NUMBER;
23807   l_result                    VARCHAR2(25);
23808 
23809   --bug 8345877
23810   l_dummy_flag VARCHAR2(1);
23811   invalid_remit_supplier_failure  EXCEPTION;
23812 
23813   /* Added for bug#9852174 Start */
23814   TYPE refcurtyp IS REF CURSOR;
23815   refcur         REFCURTYP;
23816   l_sql_stmt     LONG;
23817   /* Added for bug#9852174 End */
23818 
23819 BEGIN
23820 	current_calling_sequence := 'AP_IMPORT_VALIDATION_PKG.v_check_invalid_remit_supplier<-'
23821 					      ||P_calling_sequence;
23822 
23823 	IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
23824 		debug_info := 'Check valid remit to supplier details';
23825 		AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
23826 					  debug_info);
23827 
23828 		debug_info := 'Remit to supplier Name '||p_invoice_rec.remit_to_supplier_name;
23829 		AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
23830 					  debug_info);
23831 
23832 		debug_info := 'Remit to supplier Id '||p_invoice_rec.remit_to_supplier_id;
23833 		AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
23834 					  debug_info);
23835 
23836 		debug_info := 'Remit to supplier Site Id '||p_invoice_rec.remit_to_supplier_site_id;
23837 		AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
23838 					  debug_info);
23839 
23840 		debug_info := 'Remit to supplier Site Name '||p_invoice_rec.remit_to_supplier_site;
23841 		AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
23842 					  debug_info);
23843 	END IF;
23844 
23845 	If(p_invoice_rec.remit_to_supplier_name IS NOT NULL) then
23846 		BEGIN
23847 			select vendor_name
23848 			into l_remit_supplier_name
23849 			from ap_suppliers
23850 			where vendor_name = p_invoice_rec.remit_to_supplier_name
23851 			-- bug 8504185
23852 			AND nvl(trunc(START_DATE_ACTIVE),
23853 				AP_IMPORT_INVOICES_PKG.g_inv_sysdate)
23854 				<= AP_IMPORT_INVOICES_PKG.g_inv_sysdate
23855 			AND nvl(trunc(END_DATE_ACTIVE),
23856 				AP_IMPORT_INVOICES_PKG.g_inv_sysdate+1)
23857 				> AP_IMPORT_INVOICES_PKG.g_inv_sysdate;
23858 
23859 		EXCEPTION
23860 			WHEN NO_DATA_FOUND THEN
23861 				BEGIN
23862 					SELECT party_name
23863 					INTO l_remit_supplier_name
23864 					FROM hz_parties
23865 					WHERE party_name = p_invoice_rec.remit_to_supplier_name;
23866 				EXCEPTION
23867 					WHEN NO_DATA_FOUND THEN
23868 						IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
23869 										AP_IMPORT_INVOICES_PKG.g_invoices_table,
23870 										p_invoice_rec.invoice_id,
23871 										'INVALID REMIT TO SUPPLIER NAME',
23872 										p_default_last_updated_by,
23873 										p_default_last_update_login,
23874 										current_calling_sequence) <> TRUE) THEN
23875 						   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
23876 							AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
23877 							'insert_rejections<-'||current_calling_sequence);
23878 						   END IF;
23879 
23880 						END IF;
23881 
23882 						RAISE invalid_remit_supplier_failure;
23883 				END;
23884 		END;
23885 	END IF;
23886 
23887 	IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
23888 		debug_info := 'If Remit to supplier Name '||l_remit_supplier_name;
23889 		AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
23890 					  debug_info);
23891 	END IF;
23892 
23893 	if(p_invoice_rec.remit_to_supplier_id IS NOT NULL) then
23894 		BEGIN
23895 			select vendor_id
23896 			into l_remit_supplier_id
23897 			from ap_suppliers
23898 			where vendor_id = p_invoice_rec.remit_to_supplier_id
23899 			-- bug 8504185
23900 			AND nvl(trunc(START_DATE_ACTIVE),
23901 				AP_IMPORT_INVOICES_PKG.g_inv_sysdate)
23902 				<= AP_IMPORT_INVOICES_PKG.g_inv_sysdate
23903 			AND nvl(trunc(END_DATE_ACTIVE),
23904 				AP_IMPORT_INVOICES_PKG.g_inv_sysdate+1)
23905 				> AP_IMPORT_INVOICES_PKG.g_inv_sysdate;
23906 
23907 		EXCEPTION
23908 			WHEN NO_DATA_FOUND THEN
23909 				IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
23910 								AP_IMPORT_INVOICES_PKG.g_invoices_table,
23911 								p_invoice_rec.invoice_id,
23912 								 'INVALID REMIT TO SUPPLIER ID',
23913 								p_default_last_updated_by,
23914 								p_default_last_update_login,
23915 								current_calling_sequence) <> TRUE) THEN
23916 				   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
23917 					AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
23918 					'insert_rejections<-'||current_calling_sequence);
23919 				   END IF;
23920 
23921 				END IF;
23922 
23923 				RAISE invalid_remit_supplier_failure;
23924 		END;
23925 	END IF;
23926 
23927 	IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
23928 		debug_info := 'If Remit to supplier Id '||l_remit_supplier_id;
23929 		AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
23930 					  debug_info);
23931 	END IF;
23932 
23933 	if(p_invoice_rec.remit_to_supplier_num IS NOT NULL) then
23934 		BEGIN
23935 			select segment1
23936 			into l_remit_supplier_num
23937 			from ap_suppliers
23938 			where segment1= p_invoice_rec.remit_to_supplier_num	-- bug 7836976
23939 			-- bug 8504185
23940 			AND nvl(trunc(START_DATE_ACTIVE),
23941 				AP_IMPORT_INVOICES_PKG.g_inv_sysdate)
23942 				<= AP_IMPORT_INVOICES_PKG.g_inv_sysdate
23943 			AND nvl(trunc(END_DATE_ACTIVE),
23944 				AP_IMPORT_INVOICES_PKG.g_inv_sysdate+1)
23945 				> AP_IMPORT_INVOICES_PKG.g_inv_sysdate;
23946 
23947 		EXCEPTION
23948 			WHEN NO_DATA_FOUND THEN
23949 				IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
23950 								AP_IMPORT_INVOICES_PKG.g_invoices_table,
23951 								p_invoice_rec.invoice_id,
23952 								 'INVALID REMIT TO SUPPLIER NUM',
23953 								p_default_last_updated_by,
23954 								p_default_last_update_login,
23955 								current_calling_sequence) <> TRUE) THEN
23956 				   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
23957 					AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
23958 					'insert_rejections<-'||current_calling_sequence);
23959 				   END IF;
23960 
23961 				END IF;
23962 
23963 				RAISE invalid_remit_supplier_failure;
23964 		END;
23965 	END IF;
23966 
23967 	IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
23968 		debug_info := 'Remit to supplier Num '||l_remit_supplier_num;
23969 		AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
23970 					  debug_info);
23971 	END IF;
23972 
23973 	--BEGIN
23974 		--bug 8474864
23975 		If NOT (p_invoice_rec.remit_to_supplier_id is NULL and
23976 			p_invoice_rec.remit_to_supplier_name is NULL and
23977 			p_invoice_rec.remit_to_supplier_num is NULL) THEN
23978 
23979               /* Added for bug#9852174 Start */
23980               l_sql_stmt := ' SELECT party_id FROM ap_suppliers ' ||
23981                             '  WHERE nvl(trunc(START_DATE_ACTIVE), :p_inv_sysdate ) <= :p_inv_sysdate'||
23982 		            '    AND nvl(trunc(END_DATE_ACTIVE),:p_inv_sysdate +1) > :p_inv_sysdate';
23983 
23984               IF p_invoice_rec.remit_to_supplier_id IS NOT NULL
23985               THEN
23986                  l_sql_stmt := l_sql_stmt || ' AND vendor_id = :p_remit_to_supplier_id';
23987               ELSE
23988                  l_sql_stmt := l_sql_stmt || ' AND nvl(:p_remit_to_supplier_id, -9999) = -9999 ';
23989               END IF;
23990 
23991               IF p_invoice_rec.remit_to_supplier_name IS NOT NULL
23992               THEN
23993                  l_sql_stmt := l_sql_stmt || ' AND vendor_name = :p_remit_to_supplier_name';
23994               ELSE
23995                  l_sql_stmt := l_sql_stmt || ' AND nvl(:p_remit_to_supplier_name, -9999) = -9999 ';
23996               END IF;
23997 
23998               IF p_invoice_rec.remit_to_supplier_num IS NOT NULL
23999               THEN
24000                  l_sql_stmt := l_sql_stmt || ' AND SEGMENT1 = :p_remit_to_supplier_num';
24001               ELSE
24002                  l_sql_stmt := l_sql_stmt || ' AND nvl(:p_remit_to_supplier_num, -9999) = -9999 ';
24003               END IF;
24004 
24005               OPEN refcur FOR l_sql_stmt
24006                 USING AP_IMPORT_INVOICES_PKG.g_inv_sysdate
24007                     , AP_IMPORT_INVOICES_PKG.g_inv_sysdate
24008                     , AP_IMPORT_INVOICES_PKG.g_inv_sysdate
24009                     , AP_IMPORT_INVOICES_PKG.g_inv_sysdate
24010                     , p_invoice_rec.remit_to_supplier_id
24011                     , p_invoice_rec.remit_to_supplier_name
24012                     , p_invoice_rec.remit_to_supplier_num;
24013 
24014               FETCH refcur
24015                INTO l_remit_party_id;
24016 
24017               IF refcur%rowcount = 0
24018               THEN
24019 		IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
24020 		       ( AP_IMPORT_INVOICES_PKG.g_invoices_table,
24021 			 p_invoice_rec.invoice_id,
24022 			 'INCONSISTENT REMIT SUPPLIER',
24023 			 p_default_last_updated_by,
24024 			 p_default_last_update_login,
24025 			 current_calling_sequence) <> TRUE)
24026 		THEN
24027 		   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
24028 			AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
24029 			'insert_rejections<-'||current_calling_sequence);
24030 		   END IF;
24031 		END IF;
24032 		RAISE invalid_remit_supplier_failure;
24033               END IF;
24034               /* Added for bug#9852174 End */
24035 
24036               /* Commented for bug#9852174 Start
24037 				-- bug 8504185
24038 				SELECT party_id
24039 				INTO l_remit_party_id
24040 				FROM ap_suppliers
24041 				WHERE vendor_id = nvl(p_invoice_rec.remit_to_supplier_id,vendor_id)
24042 				AND vendor_name = nvl(p_invoice_rec.remit_to_supplier_name,vendor_name)
24043 				AND SEGMENT1 = nvl(p_invoice_rec.remit_to_supplier_num,SEGMENT1)
24044 				-- bug 8504185
24045 				AND nvl(trunc(START_DATE_ACTIVE),
24046 					AP_IMPORT_INVOICES_PKG.g_inv_sysdate)
24047 					<= AP_IMPORT_INVOICES_PKG.g_inv_sysdate
24048 				AND nvl(trunc(END_DATE_ACTIVE),
24049 					AP_IMPORT_INVOICES_PKG.g_inv_sysdate+1)
24050 					> AP_IMPORT_INVOICES_PKG.g_inv_sysdate;
24051               Commented for bug#9852174 End */
24052 		 END IF;
24053         /* Commented for bug#9852174 Start
24054 	EXCEPTION
24055 		WHEN NO_DATA_FOUND THEN
24056 			IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
24057 							AP_IMPORT_INVOICES_PKG.g_invoices_table,
24058 							p_invoice_rec.invoice_id,
24059 							 'INCONSISTENT REMIT SUPPLIER',
24060 							p_default_last_updated_by,
24061 							p_default_last_update_login,
24062 							current_calling_sequence) <> TRUE) THEN
24063 			   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
24064 				AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
24065 				'insert_rejections<-'||current_calling_sequence);
24066 			   END IF;
24067 
24068 			END IF;
24069 
24070 			RAISE invalid_remit_supplier_failure;
24071 	END;
24072 	Commented for bug#9852174 End */
24073 
24074 	if(p_invoice_rec.remit_to_supplier_site_id IS NOT NULL) then
24075 		BEGIN
24076 			select vendor_site_id
24077 			into l_remit_supplier_site_id
24078 			from ap_supplier_sites_all
24079 			where vendor_site_id = p_invoice_rec.remit_to_supplier_site_id
24080 			and org_id = p_invoice_rec.org_id;
24081 
24082 		EXCEPTION
24083 			WHEN NO_DATA_FOUND THEN
24084 				IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
24085 								AP_IMPORT_INVOICES_PKG.g_invoices_table,
24086 								p_invoice_rec.invoice_id,
24087 								'INVALID REMIT TO SUPP SITE ID',
24088 								p_default_last_updated_by,
24089 								p_default_last_update_login,
24090 								current_calling_sequence) <> TRUE) THEN
24091 				   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
24092 					AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
24093 					'insert_rejections<-'||current_calling_sequence);
24094 				   END IF;
24095 
24096 				END IF;
24097 
24098 				RAISE invalid_remit_supplier_failure;
24099 		END;
24100 	END IF;
24101 
24102 	IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
24103 		debug_info := 'Remit to supplier Site Id '||l_remit_supplier_site_id;
24104 		AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
24105 					  debug_info);
24106 	END IF;
24107 
24108 	if(p_invoice_rec.remit_to_supplier_site IS NOT NULL) then
24109 		BEGIN
24110 			If (l_remit_supplier_site_id IS NOT NULL) then
24111 				select vendor_site_code
24112 				 into l_remit_supplier_site
24113 				from ap_supplier_sites_all
24114 				where vendor_site_code = p_invoice_rec.remit_to_supplier_site
24115 				and org_id = p_invoice_rec.org_id
24116 				and vendor_site_id = p_invoice_rec.remit_to_supplier_site_id;
24117 			elsif(l_remit_supplier_id IS NOT NULL) then
24118 				select vendor_site_code
24119 				 into l_remit_supplier_site
24120 				from ap_supplier_sites_all
24121 				where vendor_site_code = p_invoice_rec.remit_to_supplier_site
24122 				and org_id = p_invoice_rec.org_id
24123 				and vendor_id = p_invoice_rec.remit_to_supplier_id;
24124 			elsif(l_remit_supplier_num IS NOT NULL) then
24125 				select a.vendor_site_code
24126 				 into l_remit_supplier_site
24127 				from ap_supplier_sites_all a,
24128 					ap_suppliers b
24129 				where a.vendor_site_code = p_invoice_rec.remit_to_supplier_site
24130 				and a.org_id = p_invoice_rec.org_id
24131 				and a.vendor_id = b.vendor_id
24132 				and b.segment1 = p_invoice_rec.remit_to_supplier_num;
24133 			elsif(l_remit_supplier_name IS NOT NULL) then
24134 				select a.vendor_site_code
24135 				 into l_remit_supplier_site
24136 				from ap_supplier_sites_all a,
24137 					ap_suppliers b
24138 				where a.vendor_site_code = p_invoice_rec.remit_to_supplier_site
24139 				and a.org_id = p_invoice_rec.org_id
24140 				and a.vendor_id = b.vendor_id
24141 				and b.vendor_name = p_invoice_rec.remit_to_supplier_name;
24142 			end if;
24143 
24144 		EXCEPTION
24145 			WHEN NO_DATA_FOUND THEN
24146 				IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
24147 								AP_IMPORT_INVOICES_PKG.g_invoices_table,
24148 								p_invoice_rec.invoice_id,
24149 								'INVALID REMIT TO SUPPLIER SITE',
24150 								p_default_last_updated_by,
24151 								p_default_last_update_login,
24152 								current_calling_sequence) <> TRUE) THEN
24153 				   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
24154 					AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
24155 					'insert_rejections<-'||current_calling_sequence);
24156 				   END IF;
24157 
24158 				END IF;
24159 
24160 				RAISE invalid_remit_supplier_failure;
24161 		END;
24162 	END IF;
24163 
24164 	IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
24165 		debug_info := 'Remit to supplier Site '||l_remit_supplier_site;
24166 		AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
24167 					  debug_info);
24168 
24169 		debug_info := 'Data To IBY ';
24170 		AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
24171 					  debug_info);
24172 
24173 		debug_info := 'Party Id '||p_invoice_rec.party_id;
24174 		AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
24175 					  debug_info);
24176 
24177 		debug_info := 'Vendor Site id '||p_invoice_rec.vendor_site_id;
24178 		AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
24179 					  debug_info);
24180 
24181 		debug_info := 'Invoice Date '||p_invoice_rec.invoice_date;
24182 		AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
24183 					  debug_info);
24184 	END IF;
24185 
24186 	/* commented below code as part of bug 8504185
24187 	IF (p_invoice_rec.remit_to_supplier_id is not null and p_invoice_rec.remit_to_supplier_id > 0) THEN
24188 		SELECT party_id
24189 		INTO l_remit_party_id
24190 		FROM ap_suppliers
24191 		WHERE vendor_id = p_invoice_rec.remit_to_supplier_id
24192 		-- bug 8504185
24193 		AND nvl(trunc(START_DATE_ACTIVE),
24194 			AP_IMPORT_INVOICES_PKG.g_inv_sysdate)
24195 			<= AP_IMPORT_INVOICES_PKG.g_inv_sysdate
24196 		AND nvl(trunc(END_DATE_ACTIVE),
24197 			AP_IMPORT_INVOICES_PKG.g_inv_sysdate+1)
24198 			> AP_IMPORT_INVOICES_PKG.g_inv_sysdate;
24199 	ELS*/IF (p_invoice_rec.remit_to_supplier_name is not null) THEN
24200 		BEGIN
24201 			SELECT party_id
24202 			INTO l_remit_party_id
24203 			FROM ap_suppliers
24204 			WHERE vendor_name = p_invoice_rec.remit_to_supplier_name
24205 			-- bug 8504185
24206 			AND nvl(trunc(START_DATE_ACTIVE),
24207 				AP_IMPORT_INVOICES_PKG.g_inv_sysdate)
24208 				<= AP_IMPORT_INVOICES_PKG.g_inv_sysdate
24209 			AND nvl(trunc(END_DATE_ACTIVE),
24210 				AP_IMPORT_INVOICES_PKG.g_inv_sysdate+1)
24211 				> AP_IMPORT_INVOICES_PKG.g_inv_sysdate;
24212 		EXCEPTION
24213 			WHEN NO_DATA_FOUND THEN
24214 				SELECT party_id
24215 				INTO l_remit_party_id
24216 				FROM hz_parties
24217 				WHERE party_name = p_invoice_rec.remit_to_supplier_name;
24218 		END;
24219 	END IF;
24220 
24221 	IF (p_invoice_rec.remit_to_supplier_site_id is null and p_invoice_rec.remit_to_supplier_site is not null) THEN
24222 		SELECT vendor_site_id
24223 		INTO l_remit_supplier_site_id
24224 		FROM ap_supplier_sites_all
24225 		WHERE org_id = p_invoice_rec.org_id
24226 		AND vendor_site_code = p_invoice_rec.remit_to_supplier_site;
24227 	END IF;
24228 
24229 	IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
24230 		debug_info := 'Remit Party Id '||l_remit_party_id;
24231 		AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
24232 					  debug_info);
24233 
24234 		debug_info := 'Remit Supplier Site Id '||l_remit_supplier_site_id;
24235 		AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
24236 					  debug_info);
24237 	END IF;
24238 
24239 	l_relationship_id := p_invoice_rec.relationship_id;	-- bug 8224788
24240 
24241 	IBY_EXT_PAYEE_RELSHIPS_PKG.import_Ext_Payee_Relationship(
24242 		p_party_id => p_invoice_rec.party_id,
24243 		p_supplier_site_id => p_invoice_rec.vendor_site_id,
24244 		p_date => p_invoice_rec.invoice_date,
24245 		x_result => l_result,
24246 		x_remit_party_id => l_remit_party_id,
24247 		x_remit_supplier_site_id => l_remit_supplier_site_id,
24248 		x_relationship_id => l_relationship_id
24249 		);
24250 
24251 	IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
24252 		debug_info := 'Data From IBY ';
24253 		AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
24254 					  debug_info);
24255 
24256 		debug_info := 'x_result : ' || l_result;
24257 		AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
24258 					  debug_info);
24259 	END IF;
24260 
24261 	IF (l_result = FND_API.G_TRUE) THEN
24262 		IF (l_relationship_id <> -1) THEN	-- bug 8345877
24263 		-- Bug 7675510
24264 		-- Added AND condition so as to Select data from ap_supplier_sites_all when
24265 		-- l_remit_supplier_site_id is having a Positive value
24266 		-- Negative value of l_remit_supplier_site_id does not have any data in ap_supplier_sites_all
24267 		-- This negative value is assigned to p_invoice_rec.vendor_site_id in
24268 		-- FUNCTION v_check_party_vendor earlier in this package
24269 
24270 		   IF (l_remit_supplier_site_id is not null AND
24271 			l_remit_supplier_site_id > 0) THEN
24272 		-- Bug 7675510 ends
24273 			SELECT vendor_site_id, vendor_site_code
24274 			INTO l_remit_supplier_site_id, l_remit_supplier_site
24275 			FROM ap_supplier_sites_all
24276 			WHERE vendor_site_id = l_remit_supplier_site_id
24277 			and org_id = p_invoice_rec.org_id;
24278 		   END IF;
24279 
24280 		   p_invoice_rec.remit_to_supplier_site_id := l_remit_supplier_site_id;
24281 		   p_invoice_rec.remit_to_supplier_site := l_remit_supplier_site;
24282 
24283 		   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
24284 			   debug_info := 'Invoice Type Lookup Code '||p_invoice_rec.invoice_type_lookup_code;
24285 			    AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
24286 						     debug_info);
24287 		   END IF;
24288 
24289 		-- Bug 7675510
24290 		-- Added the invoice_type_lookup_code condition to populate the l_remit_supplier_id,
24291 		-- l_remit_supplier_name, l_remit_supplier_num from HZ_PARTIES table in case of PAYMENT REQUEST
24292 		-- since the data is not available in AP_SUPPLIERS table for PAYMENT REQUEST type
24293 
24294 
24295 		  -- commented below IF part as part of bug 8345877.
24296 		  -- After TPP re-modelling, remit to supplier fields need not be populated.
24297 		  -- Since, payment request type of invoices will not have any relationships
24298 		  -- and expected to have the same trading partner values in remit to supplier fields,
24299 		  -- we need not derive the other values based on values returned from IBY API.
24300 
24301 		   /*IF (p_invoice_rec.invoice_type_lookup_code = 'PAYMENT REQUEST') THEN
24302 
24303 			IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
24304 				AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
24305 			END IF;
24306 
24307 			IF (l_remit_party_id is not null) THEN
24308 			    --Bug 7860631 Removed the party_id field into the supplier_id field.
24309 				SELECT party_name, party_number
24310 				INTO   l_remit_supplier_name, l_remit_supplier_num
24311 				FROM hz_parties
24312 				WHERE party_id = l_remit_party_id;
24313 			   --Bug 7860631 Defaulting the remit_supplier_id from the invoice
24314 			   l_remit_supplier_id :=p_invoice_rec.vendor_id;
24315 			END IF;
24316 
24317 		   ELSE*/
24318 
24319 		   -- bug 7629217 starts- dcshanmu - changed l_party_id to l_remit_party_id
24320 			   IF (l_remit_party_id is not null) THEN
24321 				SELECT vendor_id, vendor_name, segment1
24322 				INTO l_remit_supplier_id, l_remit_supplier_name, l_remit_supplier_num
24323 				FROM ap_suppliers
24324 				WHERE party_id = l_remit_party_id;
24325 			END IF;
24326 		   -- bug 7629217 starts- dcshanmu ends
24327 
24328 		   --END IF ;
24329 		   -- commented above END IF as part of bug 8345877
24330 		-- Bug 7675510 ends
24331 
24332 		   p_invoice_rec.remit_to_supplier_id := l_remit_supplier_id;
24333 		   p_invoice_rec.remit_to_supplier_name := l_remit_supplier_name;
24334 		   p_invoice_rec.remit_to_supplier_num := l_remit_supplier_num;
24335 		   p_invoice_rec.relationship_id := l_relationship_id;
24336 
24337 		   p_current_invoice_status := 'Y';
24338 
24339 		   -- bug 8497933
24340 		   IF (l_is_inv_date_null = 'Y') THEN
24341 			p_invoice_rec.payment_method_code := null;
24342 			p_invoice_rec.payment_reason_code := null;
24343 			p_invoice_rec.bank_charge_bearer := null;
24344 			p_invoice_rec.delivery_channel_code := null;
24345 			p_invoice_rec.settlement_priority := null;
24346 			p_invoice_rec.exclusive_payment_flag := null;
24347 			p_invoice_rec.external_bank_account_id := null;
24348 			p_invoice_rec.payment_reason_comments := null;
24349 		   END IF;
24350 		   -- bug 8497933
24351 
24352 		   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
24353 			   debug_info := 'Remit To Party Id  '||l_remit_party_id;
24354 			   AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
24355 						     debug_info);
24356 
24357 			   debug_info := 'Remit To Supplier Id '||l_remit_supplier_id;
24358 			   AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
24359 						     debug_info);
24360 
24361 			   debug_info := 'Remit To Supplier '||l_remit_supplier_name;
24362 			   AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
24363 						     debug_info);
24364 
24365 			   debug_info := 'Remit To Supplier Num '||l_remit_supplier_num;
24366 			   AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
24367 						    debug_info);
24368 
24369 			   debug_info := 'Relationship Id '||l_relationship_id;
24370 			   AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
24371 						     debug_info);
24372 		   END IF;
24373 
24374 		ELSE		-- if relationship_id <> -1 -- bug 8345877
24375 			p_invoice_rec.remit_to_supplier_id := null;
24376 			p_invoice_rec.remit_to_supplier_name := null;
24377 			p_invoice_rec.remit_to_supplier_num := null;
24378 			p_invoice_rec.remit_to_supplier_site_id := null;
24379 			p_invoice_rec.remit_to_supplier_site := null;
24380 			p_invoice_rec.relationship_id := null;
24381 		END IF; -- if relationship_id <> -1 -- bug 8345877
24382 
24383 	ELSE
24384 
24385 	    IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
24386 						AP_IMPORT_INVOICES_PKG.g_invoices_table,
24387 						p_invoice_rec.invoice_id,
24388 						'INVALID THIRD PARTY RELATION',
24389 						p_default_last_updated_by,
24390 						p_default_last_update_login,
24391 						current_calling_sequence) <> TRUE) THEN
24392 		   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
24393 			AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
24394 			'insert_rejections<-'||current_calling_sequence);
24395 		   END IF;
24396 	    END IF;
24397 
24398 	    RAISE invalid_remit_supplier_failure;
24399 	END IF;
24400 
24401 	RETURN TRUE;
24402 
24403 EXCEPTION
24404 	WHEN invalid_remit_supplier_failure THEN
24405 
24406 		p_current_invoice_status := 'N';
24407 		RETURN FALSE;
24408 	WHEN OTHERS THEN
24409 		p_current_invoice_status := 'N';
24410 
24411 		IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
24412 		   AP_IMPORT_UTILITIES_PKG.Print(
24413 		       AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
24414 		END IF;
24415 
24416 		IF (SQLCODE < 0) THEN
24417 			IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
24418 			AP_IMPORT_UTILITIES_PKG.Print(
24419 			    AP_IMPORT_INVOICES_PKG.g_debug_switch, SQLERRM);
24420 			END IF;
24421 		END IF;
24422 		RETURN FALSE;
24423 
24424 END v_check_invalid_remit_supplier;
24425 
24426 --Created procedure for Bug#13464635
24427 FUNCTION V_CHECK_GDF_VALIDATION(
24428               p_invoice_line_id            IN NUMBER,
24429 	      p_valid_level                IN VARCHAR2,
24430               p_default_last_updated_by    IN NUMBER,
24431               p_default_last_update_login  IN NUMBER,
24432               p_current_invoice_status     IN OUT NOCOPY VARCHAR2,
24433               p_calling_sequence           IN VARCHAR2) RETURN BOOLEAN IS
24434 
24435 l_hold_reject_exists_flag VARCHAR2(1) := 'N';
24436 l_return_code VARCHAR2(100);
24437 invalid_gdf_check_failure EXCEPTION;
24438 l_current_invoice_status    VARCHAR2(1) := 'Y';
24439 current_calling_sequence    VARCHAR2(2000);
24440 debug_info VARCHAR2(1000);
24441 
24442 BEGIN
24443 current_calling_sequence :=
24444     'AP_IMPORT_VALIDATION_PKG.V_CHECK_GDF_VALIDATION<-'
24445     ||P_calling_sequence;
24446 
24447  debug_info := '(Check GDF VALIDATION) Call CHECK_GDF_VALID';
24448  IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
24449       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
24450                                     debug_info);
24451  END IF;
24452 
24453 IF (p_valid_level = 'INVOICE LINE')THEN
24454        AP_INVOICES_UTILITY_PKG.CHECK_GDF_VALID
24455          (p_invoice_line_id,                  --P_id
24456 	  'INV_IMP',                     --P_calling_mode
24457 	  'AP_INVOICE_LINES_INTERFACE',  --P_table_name
24458           l_hold_reject_exists_flag,     --P_hold_reject_exists_flag
24459 	  l_return_code,                 --p_return_code
24460 	  current_calling_sequence);
24461 
24462 END IF;
24463 
24464 IF(l_hold_reject_exists_flag = 'Y' and
24465    l_return_code IS NOT NULL)THEN
24466 
24467  debug_info := '(Check GDF VALIDATION) GDF is invalid';
24468  IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
24469       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
24470                                     debug_info);
24471  END IF;
24472 
24473    IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
24474           AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
24475           p_invoice_line_id,
24476           'AP_INCORRECT_GTAS_INFO',
24477           p_default_last_updated_by,
24478           p_default_last_update_login,
24479           current_calling_sequence) <> TRUE) THEN
24480        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
24481            AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
24482                   'insert_rejections<-'|| current_calling_sequence);
24483        END IF;
24484       RAISE invalid_gdf_check_failure;
24485     END IF;
24486   l_current_invoice_status := 'N';
24487   p_current_invoice_status := l_current_invoice_status;
24488 ELSE
24489  debug_info := '(Check GDF VALIDATION) GDF is valid';
24490  IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
24491       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
24492                                     debug_info);
24493  END IF;
24494  p_current_invoice_status := l_current_invoice_status;
24495 END IF;
24496   RETURN (TRUE);
24497 
24498 EXCEPTION
24499 WHEN OTHERS THEN
24500     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
24501       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
24502                                     debug_info);
24503     END IF;
24504 
24505     IF (SQLCODE < 0) then
24506       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
24507         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
24508                                       SQLERRM);
24509       END IF;
24510     END IF;
24511     RETURN(FALSE);
24512 END V_CHECK_GDF_VALIDATION;
24513 --End Bug#13464635
24514 
24515 
24516 --bug 15862708  starts
24517   FUNCTION V_POPULATE_LINES_MISC(
24518 		 p_invoice_rec                IN   AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
24519          p_lines_rec                  IN OUT NOCOPY AP_IMPORT_INVOICES_PKG.r_line_info_rec,
24520 		 p_calling_sequence            IN            VARCHAR2) RETURN BOOLEAN
24521 
24522  AS
24523   BEGIN
24524    IF ( NVL(AP_IMPORT_INVOICES_PKG.tab_get_info_rec(p_invoice_rec.org_id).p_approval_workflow_flag, 'N') = 'N' )
24525    THEN
24526     p_lines_rec.wfapproval_status := 'NOT REQUIRED';
24527    ELSE
24528     p_lines_rec.wfapproval_status := 'REQUIRED';
24529    END IF;
24530 
24531 
24532    	IF  p_invoice_rec.invoice_type_lookup_code = 'EXPENSE REPORT' THEN
24533 	  	p_lines_rec.wfapproval_status := 'NOT REQUIRED';
24534 	END IF;
24535        p_lines_rec.generate_dists := 'Y';  --defaulting to 'Y'
24536 
24537 	  IF  (p_invoice_rec.invoice_type_lookup_code IN ('EXPENSE REPORT','PAYMENT REQUEST')) THEN
24538 	  	      p_lines_rec.generate_dists := 'Y';
24539 
24540 
24541       ELSIF (p_lines_rec.line_type_lookup_code <> 'ITEM'
24542             AND NVL(p_lines_rec.prorate_across_flag, 'N') = 'Y') THEN -- bug 8851140: modify
24543               p_lines_rec.generate_dists := 'Y';
24544 
24545 	  ELSIF ( p_lines_rec.project_id IS NULL
24546 			AND p_lines_rec.distribution_set_id IS NULL
24547 			AND p_lines_rec.po_header_id IS NULL
24548 			AND p_lines_rec.dist_code_combination_id IS NULL
24549 			AND p_lines_rec.rcv_transaction_id IS NULL
24550 		) THEN
24551 			p_lines_rec.generate_dists := 'N';
24552 	  END IF;
24553 
24554   RETURN TRUE;
24555   EXCEPTION
24556   WHEN OTHERS THEN
24557   NULL;
24558   END V_POPULATE_LINES_MISC;
24559 --bug 15862708 ends
24560 
24561 END AP_IMPORT_VALIDATION_PKG;