DBA Data[Home] [Help]

PACKAGE BODY: APPS.AP_IMPORT_UTILITIES_PKG

Source


1 PACKAGE BODY AP_IMPORT_UTILITIES_PKG AS
2 /* $Header: apiimutb.pls 120.100.12020000.3 2012/12/18 12:37:00 nbshaik ship $ */
3 
4 -- Bug 3929697
5 -- Declared two global variables for getting the value of
6 -- distribution line number
7 
8 lg_invoice_id                NUMBER :=0;
9 lg_dist_line_num             NUMBER ;
10 
11 /* Added for bug#10175718
12    This function will return the "maximum line number"+1 in the input pl/sql table.
13  */
14 FUNCTION max_line_number
15 (
16   p_invoice_lines_tab    IN AP_IMPORT_INVOICES_PKG.lines_table --bug 15862708
17 )
18 RETURN NUMBER IS
19   l_max_line_number  NUMBER;
20 
21 BEGIN
22   l_max_line_number := 0;
23 
24   FOR I IN p_invoice_lines_tab.FIRST..p_invoice_lines_tab.LAST
25   LOOP
26     IF    p_invoice_lines_tab(I).line_number IS NOT NULL
27       AND l_max_line_number <= p_invoice_lines_tab(I).line_number
28     THEN
29       l_max_line_number := NVL(p_invoice_lines_tab(I).line_number, l_max_line_number);
30     END IF;
31   END LOOP;
32   RETURN l_max_line_number+1;
33 
34 EXCEPTION
35   WHEN OTHERS THEN
36   l_max_line_number := 0;
37 END;
38 
39 /* Added for bug#10175718
40    This function will cascade all the receipts for a shipment and append the newly
41    created lines to the p_invoice_lines_tab pl/sql table.
42    Receipts will be consumed based on the transaction date (first created receipt will be consumed first).
43    If the inovice causes the overbilling of the PO, last consumed receipt will be overbilled.
44    In case of CREDIT MEMO, overbilling means billed amount/ quantity on PO goes to -ve, that is not allowed.
45  */
46 FUNCTION create_receipt_match_lines
47 (
48   p_po_line_location_id  IN    NUMBER,
49   p_cascade_flag         IN    VARCHAR2,
50   p_amount               IN    NUMBER,
51   p_quantity             IN    NUMBER,
52   p_price                IN    NUMBER,
53   p_invoice_currency     IN    VARCHAR2,
54   p_index                IN    NUMBER,
55   p_invoice_lines_tab    IN OUT NOCOPY AP_IMPORT_INVOICES_PKG.lines_table --bug 15862708
56 )
57 RETURN BOOLEAN IS
58 
59   CURSOR rcv_txn_cur IS
60   SELECT rt.transaction_id
61        , rt.unit_of_measure
62        , lt.matching_basis
63     FROM rcv_transactions rt
64        , rcv_shipment_headers sh
65        , po_lines pl
66        , po_line_types lt
67    WHERE sh.receipt_source_code = 'VENDOR'
68      AND rt.shipment_header_id  = sh.shipment_header_id
69      AND rt.transaction_type IN ('RECEIVE','MATCH')
70      AND rt.po_line_id          = pl.po_line_id
71      AND pl.line_type_id        = lt.line_type_id(+)
72      AND rt.po_line_location_id = p_po_line_location_id
73     ORDER by transaction_date;
74 
75   l_rcv_txn_id              NUMBER;
76   l_rcv_uom                 VARCHAR2(30);
77   l_remain_qty              NUMBER;
78   l_unbilled_qty            NUMBER;
79   l_billed_qty              NUMBER;
80   l_match_qty               NUMBER;
81   l_match_amt               NUMBER;
82 
83   l_ordered_po_qty          NUMBER;
84   l_cancelled_po_qty        NUMBER;
85   l_received_po_qty         NUMBER;
86   l_corrected_po_qty        NUMBER;
87   l_delivered_po_qty        NUMBER;
88   l_rtv_po_qty              NUMBER;
89   l_billed_po_qty           NUMBER;
90   l_accepted_po_qty         NUMBER;
91   l_rejected_po_qty         NUMBER;
92   l_ordered_txn_qty         NUMBER;
93   l_cancelled_txn_qty       NUMBER;
94   l_received_txn_qty        NUMBER;
95   l_corrected_txn_qty       NUMBER;
96   l_delivered_txn_qty       NUMBER;
97   l_rtv_txn_qty             NUMBER;
98   l_billed_txn_qty          NUMBER;
99   l_accepted_txn_qty        NUMBER;
100   l_rejected_txn_qty        NUMBER;
101   l_matching_error          VARCHAR2(2000);
102   debug_info                VARCHAR2(2000);
103 
104   l_match_basis             PO_LINE_TYPES.MATCHING_BASIS%TYPE;
105   l_ordered_amt             NUMBER;
106   l_received_amt            NUMBER;
107   l_delivered_amt           NUMBER;
108   l_cancelled_amt           NUMBER;
109   l_corrected_amt           NUMBER;
110   l_billed_amt              NUMBER;
111   l_unbilled_amt            NUMBER;
112   l_remain_amt              NUMBER;
113   l_ret_status              VARCHAR2(100);
114   l_msg_count               NUMBER;
115   l_msg_data                VARCHAR2(250);
116   l_uom_conv_rate           NUMBER;
117   l_remain_qty_rcv_uom      NUMBER;
118   l_po_uom                  VARCHAR2(30);
119   l_item_id                 NUMBER;
120   l_price                   NUMBER;
121 
122   l_index                   NUMBER;
123   l_line_number             NUMBER;
124 
125 BEGIN
126 
127   l_index := p_index;
128   ---------------------------------------------------------------------------------
129   -- If cascade flag = 'Y' then get the rcv_transaction ids from the cursor,
130   -- For each line fetched , get the unbilled quantity and amount to be matched
131   -- and call the receipt matching pkg to do the match at the shipment level.
132   -- WE match here in a cascading manner, we pick up all rcv_transactions in order
133   -- of the date (earliest - first , most recent -last) and match the p_quantity
134   -- to the unbilled quantity on each rcv transaction
135   -- Bill positive quantities
136   ---------------------------------------------------------------------------------
137   IF (p_cascade_flag = 'Y' AND (p_quantity > 0 OR p_amount > 0)) THEN
138 
139     debug_info := '(Receipt Matching 3a) Matching to receipts by Cascading';
140     IF AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' THEN
141        AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
142     END IF;
143 
144     OPEN rcv_txn_cur;
145 
146     -- initialize remaining qty to the total quantity to be matched
147     l_remain_qty := p_quantity;
148     l_remain_amt := p_amount;
149 
150     -- bug 3903136 select the po uom and item id
151     SELECT pol.unit_meas_lookup_code, pol.item_id
152       INTO l_po_uom, l_item_id
153       FROM po_lines pol,
154            po_line_locations pll
155      WHERE pol.po_line_id       = pll.po_line_id
156        AND pll.line_location_id = p_po_line_location_id;
157 
158     LOOP
159        debug_info := '(Receipt Matching 3a) Fetch into cursor rcv_txn_cur';
160        If AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' then
161           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
162        End if;
163 
164        FETCH rcv_txn_cur INTO
165          l_rcv_txn_id,
166          l_rcv_uom,
167          l_match_basis;
168 
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                     '------------------> l_rcv_txn_id = '||to_char(l_rcv_txn_id)
172                   ||' l_rcv_uom = '   ||l_rcv_uom
173                   ||' l_remain_qty = '||to_char(l_remain_qty));
174        end if;
175 
176        -- Exit if either the remaining quantity is zero or the cursor can not find any more rows.
177        Exit when rcv_txn_cur%NOTFOUND;
178 
179        If (l_match_basis = 'QUANTITY') Then
180           If (l_remain_qty <= 0) then
181              exit;
182           End if;
183        elsif (l_match_basis = 'AMOUNT') Then
184           if (l_remain_amt <=0) then
185             exit;
186           end if;
187        end if;
188 
189        debug_info := '(Receipt Matching 3a) Get quantities on the rcv_transaction ';
190        If AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' then
191           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
192        End if;
193 
194        IF (l_match_basis ='QUANTITY') THEN
195 
196           IF NVL(l_po_uom, 'X') <> NVL(l_rcv_uom, 'X') then
197              debug_info := '(Get Item Line Info 13.7-1) Get uom conv rate';
198              If AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' then
199                 AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
200              End if;
201 
202              l_uom_conv_rate :=
203                  po_uom_s.po_uom_convert
204                  (
205                    l_rcv_uom,
206                    l_po_uom,
207                    l_item_id
208                  );
209 
210              l_remain_qty_rcv_uom := l_remain_qty / l_uom_conv_rate;
211           ELSE
212              l_uom_conv_rate := 1;
213              l_remain_qty_rcv_uom := l_remain_qty;
214           END IF;
215 
216           debug_info := '(Get Item Line Info 13.7-1) call get_quantities';
217           If AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' then
218              AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
219           End if;
220 
221           RCV_INVOICE_MATCHING_SV.get_quantities
222           (
223             top_transaction_id => l_rcv_txn_id,
224             ordered_po_qty     => l_ordered_po_qty,
225             cancelled_po_qty   => l_cancelled_po_qty,
226             received_po_qty    => l_received_po_qty,
227             corrected_po_qty   => l_corrected_po_qty,
228             delivered_po_qty   => l_delivered_po_qty,
229             rtv_po_qty         => l_rtv_po_qty,
230             billed_po_qty      => l_billed_po_qty,
231             accepted_po_qty    => l_accepted_po_qty,
232             rejected_po_qty    => l_rejected_po_qty,
233             ordered_txn_qty    => l_ordered_txn_qty,
234             cancelled_txn_qty  => l_cancelled_txn_qty,
235             received_txn_qty   => l_received_txn_qty,
236             corrected_txn_qty  => l_corrected_txn_qty,
237             delivered_txn_qty  => l_delivered_txn_qty,
238             rtv_txn_qty        => l_rtv_txn_qty,
239             billed_txn_qty     => l_billed_txn_qty,
240             accepted_txn_qty   => l_accepted_txn_qty,
241             rejected_txn_qty   => l_rejected_txn_qty
242           );
243 
244           -- Calculate the unbilled quantity on the rcv transaction
245           l_unbilled_qty :=
246                  nvl(l_received_txn_qty,0)
247                - nvl(l_corrected_txn_qty,0)
248                - nvl(l_cancelled_txn_qty ,0)
249                - nvl(l_rtv_txn_qty,0)
250                - nvl(l_billed_txn_qty,0);
251 
252           If AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' then
253              AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
254                         '------------------> ordered_txn_qty = '||to_char(l_ordered_txn_qty)
255                       ||' cancelled_txn_qty = '||to_char(l_cancelled_txn_qty)
256                       ||' received_txn_qty = '||to_char(l_received_txn_qty)
257                       ||' corrected_txn_qty = '||to_char(l_corrected_txn_qty)
258                       ||' delivered_txn_qty = '||to_char(l_delivered_txn_qty)
259                       ||' rtv_txn_qty = '||to_char(l_rtv_txn_qty)
260                       ||' billed_txn_qty = '||to_char(l_billed_txn_qty)
261                       ||' accepted_txn_qty = '||to_char(l_accepted_txn_qty)
262                       ||' rejected_txn_qty = '||to_char(l_rejected_txn_qty)
263                       ||' unbilled qty = '||to_char(l_unbilled_qty));
264           end if;
265 
266           -- Match only if there is unbilled quantity on the rcv transaction
267           If (l_unbilled_qty > 0) Then
268 
269              -- Match only the remaining qty if it is less than the unbilled quantity
270              If (l_unbilled_qty < l_remain_qty) Then
271                 l_match_qty := l_unbilled_qty;
272 
273                 l_match_amt :=
274                     ap_utilities_pkg.ap_round_currency ((l_match_qty * (p_price * l_uom_conv_rate)), p_invoice_currency);
275 
276                 debug_info := '(Receipt Match 3a) Call the receipt match package ';
277                 If AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' then
278                    AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
279                 End if;
280 
281                 p_invoice_lines_tab(p_invoice_lines_tab.LAST+1):= p_invoice_lines_tab(l_index);
282 
283                 p_invoice_lines_tab(p_invoice_lines_tab.LAST).amount            := p_invoice_lines_tab(l_index).amount - l_match_amt;
284                 p_invoice_lines_tab(p_invoice_lines_tab.LAST).quantity_invoiced := p_invoice_lines_tab(l_index).quantity_invoiced - l_match_qty;
285 
286                 l_line_number := max_line_number(p_invoice_lines_tab);
287                 IF   NVL(l_line_number,1) <= p_invoice_lines_tab.LAST
288                 THEN
289                   p_invoice_lines_tab(p_invoice_lines_tab.LAST).line_number       := p_invoice_lines_tab.LAST;
290                 ELSE
291                   p_invoice_lines_tab(p_invoice_lines_tab.LAST).line_number       := l_line_number;
292                 END IF;
293 
294                 p_invoice_lines_tab(l_index).amount            := l_match_amt;
295                 p_invoice_lines_tab(l_index).quantity_invoiced := l_match_qty;
296                 p_invoice_lines_tab(l_index).rcv_transaction_id:= l_rcv_txn_id;
297 
298                 l_index := p_invoice_lines_tab.LAST;
299 
300              Else
301                 l_match_qty := l_remain_qty_rcv_uom;
302 
303                 l_match_amt :=
304                     ap_utilities_pkg.ap_round_currency ((l_match_qty * (p_price * l_uom_conv_rate)), p_invoice_currency);
305 
306                 p_invoice_lines_tab(l_index).rcv_transaction_id:= l_rcv_txn_id;
307 
308              End if;
309 
310              l_remain_qty := l_remain_qty - l_match_qty * l_uom_conv_rate;
311 
312           End if; -- unbilled_qty <> 0
313 
314        ELSIF (l_match_basis ='AMOUNT') THEN
315 
316           RCV_INVOICE_MATCHING_SV.Get_ReceiveAmount
317           (
318            P_Api_Version    => 1.0,
319            P_Init_Msg_List  => FND_API.G_TRUE,
320            X_Return_Status  => l_ret_status,
321            X_Msg_Count      => l_msg_count,
322            X_Msg_Data       => l_msg_data,
323            P_Receive_Transaction_id => l_rcv_txn_id,
324            X_Billed_amt     => l_billed_amt,
325            X_Received_amt   => l_received_amt ,
326            X_Delivered_amt  => l_delivered_amt,
327            X_Corrected_amt  => l_corrected_amt
328           );
329 
330           PO_AP_INVOICE_MATCH_GRP.get_po_ship_amounts
331           (
332            p_api_version            => 1.0,
333            p_receive_transaction_id => l_rcv_txn_id,
334            x_ship_amt_ordered       => l_ordered_amt,
335            x_ship_amt_cancelled     => l_cancelled_amt,
336            x_ret_status             => l_ret_status,
337            x_msg_count              => l_msg_count,
338            x_msg_data               => l_msg_data
339           );
340 
341           -- Calculate the unbilled amount on the rcv transaction
342           l_unbilled_amt :=
343                 nvl(l_received_amt,0)
344               - nvl(l_corrected_amt,0)
345               - nvl(l_cancelled_amt,0)
346               - nvl(l_billed_amt,0);
347 
348           If AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' then
349               AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
350                    '------------------> ordered_amount = '||to_char(l_ordered_amt)
351                  ||' cancelled_amount = '||to_char(l_cancelled_amt)
352                  ||' received_amount = ' ||to_char(l_received_amt)
353                  ||' corrected_amount = '||to_char(l_corrected_amt)
354                  ||' delivered_amount = '||to_char(l_delivered_amt)
355                  ||' billed_amount = '   ||to_char(l_billed_amt));
356           end if;
357 
358           -- Match only if there is unbilled amount on the rcv transaction
359           If (l_unbilled_amt > 0) Then
360 
361              -- Match only the remaining qty if it is less than the unbilled quantity
362              If (l_unbilled_amt < l_remain_amt) Then
363                 l_match_amt := l_unbilled_amt;
364 
365                 p_invoice_lines_tab(p_invoice_lines_tab.LAST+1):= p_invoice_lines_tab(l_index);
366 
367                 p_invoice_lines_tab(p_invoice_lines_tab.LAST).amount            := p_invoice_lines_tab(l_index).amount - l_match_amt;
368 
369                 l_line_number := max_line_number(p_invoice_lines_tab);
370                 IF   NVL(l_line_number,1) <= p_invoice_lines_tab.LAST
371                 THEN
372                   p_invoice_lines_tab(p_invoice_lines_tab.LAST).line_number       := p_invoice_lines_tab.LAST;
373                 ELSE
374                   p_invoice_lines_tab(p_invoice_lines_tab.LAST).line_number       := l_line_number;
375                 END IF;
376 
377                 p_invoice_lines_tab(l_index).amount            := l_match_amt;
378                 p_invoice_lines_tab(l_index).rcv_transaction_id:= l_rcv_txn_id;
379 
380                 l_index := p_invoice_lines_tab.LAST;
381 
382              Else
383                 l_match_amt:= l_remain_amt;
384 
385                 p_invoice_lines_tab(l_index).rcv_transaction_id:= l_rcv_txn_id;
386 
387              End if;
388              l_remain_amt := l_remain_amt - l_match_amt;
389           End if; -- unbilled_amt <> 0
390       END IF;  --if l_match_basis ='QUANTITY'
391 
392     End Loop;
393 
394     Close rcv_txn_cur;
395 
396     If (l_remain_qty  > 0 and l_match_basis ='QUANTITY') Then
397 
398        debug_info := '(Receipt Match 3a) Assign the receipt number for the overbill - Quantity Match';
399        If AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' then
400           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
401        End if;
402 
403        l_match_qty := l_remain_qty;
404        l_match_amt :=
405           ap_utilities_pkg.ap_round_currency
406                       (
407                         (l_match_qty * p_price),
408                         p_invoice_currency
409                       );
410 
411        IF l_uom_conv_rate is not null then
412         l_match_qty := l_match_qty / l_uom_conv_rate;
413         l_price := p_price * l_uom_conv_rate;
414        ELSE
415         l_price := p_price;
416        END IF;
417 
418        p_invoice_lines_tab(l_index-1).quantity_invoiced := p_invoice_lines_tab(l_index-1).quantity_invoiced + l_match_qty;
419        p_invoice_lines_tab(l_index-1).amount            := p_invoice_lines_tab(l_index-1).amount + l_match_amt;
420        p_invoice_lines_tab.delete(l_index);
421 
422     Elsif (l_remain_amt > 0 and l_match_basis ='AMOUNT') Then
423 
424        debug_info := '(Receipt Match 3a) Assign the receipt number for the overbill - Amount Match';
425        If AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' then
426           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
427        End if;
428 
429        l_match_amt := l_remain_amt;
430        p_invoice_lines_tab(l_index-1).amount := p_invoice_lines_tab(l_index-1).amount + l_match_amt;
431        p_invoice_lines_tab.delete(l_index);
432 
433     End if;  -- remain_qty  > 0
434 
435   Elsif  (nvl(p_cascade_flag,'N') = 'Y' and (p_quantity < 0 or p_amount < 0)) Then
436     ------------------------------------------------------------------------------
437     -- Step 3b : If cascade flag = 'Y' and quantity is negative, we should
438     --           Match negative quantities to the billed qty on that receipt,
439     --           as we should not decrease the quantity billed to < 0.  Note,
440     --           in this case we will not have any thing as an overbill, as
441     --           we reject earlier on itself if the total quantity we are trying
442     --           to bill would reduce the total quantity billed , 0
443     ------------------------------------------------------------------------------
444     debug_info := '(Receipt match 3b) Matching to receipts by Cascading';
445     If AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' then
446        AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
447     End if;
448 
449     Open rcv_txn_cur;
450 
451     -- initialize remaining qty to the total quantity to be matched
452     l_remain_qty := p_quantity;
453     l_remain_amt := p_amount;
454 
455     Loop
456        debug_info := 'Fetch into cursor rcv_txn_cur';
457        If AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' then
458           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
459        End if;
460 
461        Fetch rcv_txn_cur INTO
462              l_rcv_txn_id,
463              l_rcv_uom,
464              l_match_basis;
465 
466        If AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' then
467           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
468               '------------------> l_rcv_txn_id = '||to_char(l_rcv_txn_id)
469             ||' l_rcv_uom = '||l_rcv_uom
470             ||' l_remain_qty '||to_char(l_remain_qty)
471             ||' l_match_basis = '||l_match_basis);
472        end if;
473 
474        -- Exit if either the remaining quantity is zero for quantity_based matching or
475        -- remaining amount is zero for amount_based matching
476        -- or the cursor can not find any more rows.
477 
478        Exit when rcv_txn_cur%NOTFOUND;
479 
480        If (l_match_basis = 'QUANTITY') Then
481           If (l_remain_qty = 0) then
482              exit;
483           End if;
484        Elsif (l_match_basis ='AMOUNT') Then
485           If(l_remain_amt = 0) then
486              exit;
487           End if;
488        End if;
489 
490        IF (l_match_basis ='QUANTITY') THEN
491 
492           debug_info := '(Receipt Match 3b) Get quantities on the rcv_transaction ';
493           If AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' then
494              AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
495           End if;
496 
497           RCV_INVOICE_MATCHING_SV.get_quantities
498           (
499            top_transaction_id =>l_rcv_txn_id,
500            ordered_po_qty     =>l_ordered_po_qty,
501            cancelled_po_qty   =>l_cancelled_po_qty,
502            received_po_qty    =>l_received_po_qty,
503            corrected_po_qty   =>l_corrected_po_qty,
504            delivered_po_qty   =>l_delivered_po_qty,
505            rtv_po_qty         =>l_rtv_po_qty,
506            billed_po_qty      =>l_billed_po_qty,
507            accepted_po_qty    =>l_accepted_po_qty,
508            rejected_po_qty    =>l_rejected_po_qty,
509            ordered_txn_qty    =>l_ordered_txn_qty,
510            cancelled_txn_qty  =>l_cancelled_txn_qty,
511            received_txn_qty   =>l_received_txn_qty,
512            corrected_txn_qty  =>l_corrected_txn_qty,
513            delivered_txn_qty  =>l_delivered_txn_qty,
514            rtv_txn_qty        =>l_rtv_txn_qty,
515            billed_txn_qty     =>l_billed_txn_qty,
516            accepted_txn_qty   =>l_accepted_txn_qty,
517            rejected_txn_qty   =>l_rejected_txn_qty
518           );
519 
520           -- Calculate the billed quantity on the rcv transaction
521           l_billed_qty :=  nvl(l_billed_txn_qty,0);
522 
523           If AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' then
524              AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
525                   '------------------> ordered_txn_qty = '||to_char(l_ordered_txn_qty)
526                 ||' cancelled_txn_qty = '||to_char(l_cancelled_txn_qty)
527                 ||' received_txn_qty = '||to_char(l_received_txn_qty)
528                 ||' corrected_txn_qty = '||to_char(l_corrected_txn_qty)
529                 ||' delivered_txn_qty = '||to_char(l_delivered_txn_qty)
530                 ||' rtv_txn_qty = '||to_char(l_rtv_txn_qty)
531                 ||' billed_txn_qty = '||to_char(l_billed_txn_qty)
532                 ||' accepted_txn_qty = '||to_char(l_accepted_txn_qty)
533                 ||' rejected_txn_qty = '||to_char(l_rejected_txn_qty));
534           end if;
535 
536           -- Match only if there is billed quantity on the rcv transaction
537           If (l_billed_qty > 0) Then
538              -- Match only the remaining qty if it is less than the unbilled quantity
539              If (abs(l_remain_qty) > l_billed_qty) Then
540                 l_match_qty :=  -1 * l_billed_qty;
541 
542                 l_match_amt :=
543                        ap_utilities_pkg.ap_round_currency ( (l_match_qty * p_price), p_invoice_currency);
544 
545                 p_invoice_lines_tab(p_invoice_lines_tab.LAST+1):= p_invoice_lines_tab(l_index);
546 
547                 p_invoice_lines_tab(p_invoice_lines_tab.LAST).amount            := p_invoice_lines_tab(l_index).amount - l_match_amt;
548                 p_invoice_lines_tab(p_invoice_lines_tab.LAST).quantity_invoiced := p_invoice_lines_tab(l_index).quantity_invoiced - l_match_qty;
549 
550                 l_line_number := max_line_number(p_invoice_lines_tab);
551                 IF   NVL(l_line_number,1) <= p_invoice_lines_tab.LAST
552                 THEN
553                   p_invoice_lines_tab(p_invoice_lines_tab.LAST).line_number       := p_invoice_lines_tab.LAST;
554                 ELSE
555                   p_invoice_lines_tab(p_invoice_lines_tab.LAST).line_number       := l_line_number;
556                 END IF;
557 
558 
559                 p_invoice_lines_tab(l_index).amount            := l_match_amt;
560                 p_invoice_lines_tab(l_index).quantity_invoiced := l_match_qty;
561                 p_invoice_lines_tab(l_index).rcv_transaction_id:= l_rcv_txn_id;
562 
563                 l_index := p_invoice_lines_tab.LAST;
564 
565              Else
566                 l_match_qty := l_remain_qty;
567 
568                 l_match_amt :=
569                        ap_utilities_pkg.ap_round_currency ( (l_match_qty * p_price), p_invoice_currency);
570 
571                 p_invoice_lines_tab(l_index).rcv_transaction_id:= l_rcv_txn_id;
572 
573              End if;
574 
575               l_remain_qty := l_remain_qty - l_match_qty;
576 
577           End if; -- billed_qty > 0
578 
579        ELSIF (l_match_basis ='AMOUNT') THEN
580 
581           debug_info := '(Receipt Match 3b) Get amounts on the rcv_transaction ';
582           If AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' then
583              AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
584           End if;
585 
586           RCV_INVOICE_MATCHING_SV.Get_ReceiveAmount
587           (
588             p_api_version            => 1.0,
589             p_init_msg_list          => FND_API.G_TRUE,
590             x_return_status          =>l_ret_status,
591             x_msg_count              =>l_msg_count,
592             x_msg_data               =>l_msg_data,
593             P_Receive_Transaction_id => l_rcv_txn_id,
594             X_Billed_amt             => l_billed_amt,
595             X_Received_amt           => l_received_amt ,
596             X_Delivered_amt          => l_delivered_amt,
597             X_Corrected_amt          => l_corrected_amt
598           );
599 
600           PO_AP_INVOICE_MATCH_GRP.get_po_ship_amounts
601           (
602             p_api_version            => 1.0,
603             p_receive_transaction_id =>l_rcv_txn_id,
604             x_ship_amt_ordered       =>l_ordered_amt,
605             x_ship_amt_cancelled     =>l_cancelled_amt,
606             x_ret_status             =>l_ret_status,
607             x_msg_count              =>l_msg_count,
608             x_msg_data               =>l_msg_data
609           );
610 
611           -- Calculate the billed amount on the rcv transaction
612           l_billed_amt :=  nvl(l_billed_amt,0);
613 
614           If AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' then
615              AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
616                        '------------------> ordered_amount = '||to_char(l_ordered_amt)
617                      ||' cancelled_amount = '||to_char(l_cancelled_amt)
618                      ||' received_amount = '||to_char(l_received_amt)
619                      ||' corrected_amount = '||to_char(l_corrected_amt)
620                      ||' delivered_amount = '||to_char(l_delivered_amt)
621                      ||' billed_amount = '||to_char(l_billed_amt));
622           end if;
623 
624           -- Match only if there is billed amount on the rcv transaction
625           If (l_billed_amt > 0) Then
626 
627              -- Match only the remaining amt if it is less than the unbilled amount
628              If (abs(l_remain_amt) >= l_billed_amt) Then
629                 l_match_amt := -1 * l_billed_amt;
630 
631                 p_invoice_lines_tab(p_invoice_lines_tab.LAST+1):= p_invoice_lines_tab(l_index);
632 
633                 p_invoice_lines_tab(p_invoice_lines_tab.LAST).amount            := p_invoice_lines_tab(l_index).amount - l_match_amt;
634 
635                 l_line_number := max_line_number(p_invoice_lines_tab);
636                 IF   NVL(l_line_number,1) <= p_invoice_lines_tab.LAST
637                 THEN
638                   p_invoice_lines_tab(p_invoice_lines_tab.LAST).line_number       := p_invoice_lines_tab.LAST;
639                 ELSE
640                   p_invoice_lines_tab(p_invoice_lines_tab.LAST).line_number       := l_line_number;
641                 END IF;
642 
643                 p_invoice_lines_tab(l_index).amount            := l_match_amt;
644                 p_invoice_lines_tab(l_index).rcv_transaction_id:= l_rcv_txn_id;
645 
646                 l_index := p_invoice_lines_tab.LAST;
647 
648              Else
649                 l_match_amt := l_remain_amt;
650 
651                 p_invoice_lines_tab(l_index).rcv_transaction_id:= l_rcv_txn_id;
652 
653              End if;
654 
655              l_remain_amt := l_remain_amt - l_match_amt;
656 
657           End if; -- billed_amt > 0
658 
659        END IF; --if l_match_basis ='QUANTITY'
660 
661     End Loop;
662 
663     Close rcv_txn_cur;
664 
665   End if; -- cascade_flag = 'Y' and quantity < 0
666   RETURN(TRUE);
667 EXCEPTION
668  WHEN OTHERS THEN
669      If AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' then
670         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
671      End if;
672      -- Get Error from Matching Package
673 
674      AP_UTILITIES_PKG.AP_GET_MESSAGE(l_matching_error);
675      If AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' then
676         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,l_matching_error);
677      end if;
678 
679      IF (SQLCODE < 0) then
680         If AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' then
681            AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,SQLERRM);
682         End if;
683      END IF;
684 
685      RETURN(FALSE);
686 END create_receipt_match_lines;
687 
688 --==============================================================
689 -- copy attachment association
690 --
691 --==============================================================
692 FUNCTION copy_attachments(p_from_invoice_id    IN NUMBER,
693                           p_to_invoice_id      IN NUMBER)
694         RETURN NUMBER IS
695   l_attachments_count   NUMBER := 0;
696   debug_info            VARCHAR2(500);
697 BEGIN
698   select count(1)
699   into   l_attachments_count
700   from   fnd_attached_documents
701   where  entity_name = 'AP_INVOICES_INTERFACE'
702   and    pk1_value = p_from_invoice_id;
703 
704   -- we only need to copy attachments if there is one
705   if ( l_attachments_count > 0 )
706   then
707     fnd_attached_documents2_pkg.copy_attachments(
708       x_from_entity_name => 'AP_INVOICES_INTERFACE',
709       x_from_pk1_value   => p_from_invoice_id,
710       x_to_entity_name   => 'AP_INVOICES',
711       x_to_pk1_value     => p_to_invoice_id);
712   end if;
713 
714   return l_attachments_count;
715 EXCEPTION
716 
717  WHEN OTHERS then
718 
719     IF (SQLCODE < 0) then
720       IF AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' THEN
721         AP_IMPORT_UTILITIES_PKG.Print(
722           AP_IMPORT_INVOICES_PKG.g_debug_switch, SQLERRM);
723       END IF;
724     END IF;
725     RETURN 0;
726 END copy_attachments;
727 
728 
729 /*======================================================================
730  Function: Check_Control_Table
731    This function is called at the beginning of the Import Program to handle
732    concurrency control.  It prevents the program from running if another
733    process is running for the same set of parameters.
734 ========================================================================*/
735 FUNCTION Check_control_table(
736           p_source              IN     VARCHAR2,
737           p_group_id            IN     VARCHAR2,
738           p_calling_sequence    IN     VARCHAR2) RETURN BOOLEAN IS
739 
740 -- Bug 4145391. Modified the select for the cursor to improve performance.
741 -- Removed the p_group_id where clause and added it to the cursor
742 -- import_requests_group
743 CURSOR import_requests IS
744     SELECT request_id,
745            group_id
746       FROM ap_interface_controls
747      WHERE source = p_source
748      ORDER BY request_id DESC;
749 
750 CURSOR import_requests_group IS
751     SELECT request_id,
752            group_id
753       FROM ap_interface_controls
754      WHERE source = p_source
755        AND group_id = p_group_id
756      ORDER BY request_id DESC;
757 
758   check_control_failure    EXCEPTION;
759   current_calling_sequence VARCHAR2(2000);
760   debug_info               VARCHAR2(500);
761   l_phase                  VARCHAR2(30);
762   l_status                 VARCHAR2(30);
763   l_dev_phase              VARCHAR2(30);
764   l_dev_status             VARCHAR2(30);
765   l_message                VARCHAR2(240);
766   l_new_record             VARCHAR2(1)  := 'Y';
767   l_previous_request_id    NUMBER;
768   l_group_id               VARCHAR2(80);
769 
770 BEGIN
771 
772   -- Update the calling sequence
773 
774   current_calling_sequence :=
775    'AP_Import_Utilities_Pkg.Check_control_table<-'||P_calling_sequence;
776 
777   -----------------------------------------------------------------------
778   -- Step 1,
779   -- Lock the control table, in case some other concurrent process try to
780   -- insert a idential record
781   -----------------------------------------------------------------------
782 
783   debug_info := '(Check_control_table 1) Lock the control table ';
784   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
785     Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
786   END IF;
787 
788   LOCK TABLE AP_INTERFACE_CONTROLS IN EXCLUSIVE MODE;
789 
790   debug_info := '(Check_control_table) Open import_requests cursor';
791 
792   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
793     Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
794   END IF;
795 
796   -- Bug 4145391. To improve the performance of the import program coding two
797   -- different cursors based on the parameter p_group_id
798   IF (p_group_id IS NULL) THEN
799       OPEN import_requests;
800   ELSE
801       OPEN import_requests_group;
802   END IF;
803 
804   LOOP
805     -------------------------------------------------------------------------
806     -- Step 2, Fetch l_previous_request_id from ap_interface_controls with
807     -- the same source and group_id (optional). If group_id is null,
808     -- all requests from the source will be fetched
809     -------------------------------------------------------------------------
810 
811     debug_info := '(Check_control_table 2) Fetch import_requests';
812     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
813       Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
814     END IF;
815 
816     -- Bug 4145391
817     IF (p_group_id IS NULL) THEN
818         FETCH import_requests INTO l_previous_request_id,
819                                    l_group_id;
820         EXIT WHEN import_requests%NOTFOUND OR
821                   import_requests%NOTFOUND IS NULL;
822     ELSE
823         FETCH import_requests_group INTO l_previous_request_id,
824                                          l_group_id;
825         EXIT WHEN import_requests_group%NOTFOUND OR
826                   import_requests_group%NOTFOUND IS NULL;
827     END IF;
828 
829 
830     -- It won't be new record if program is up to this point
831     l_new_record := 'N';
832 
833     -----------------------------------------------------------------------
834     -- Step 3,
835     -- Check status for the concurrent program from the request_id
836     -----------------------------------------------------------------------
837 
838     debug_info := '(Check_control_table 3) Check concurrent program status';
839     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
840       Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
841             debug_info||' previous req id ='||l_previous_request_id);
842     END IF;
843 
844     IF (FND_CONCURRENT.GET_REQUEST_STATUS(
845     request_id  =>l_previous_request_id,
846     appl_shortname  =>'',
847     program    =>'',
848     phase    =>l_phase,
849     status    =>l_status,
850     dev_phase  =>l_dev_phase,
851     dev_status  =>l_dev_status,
852     message    =>l_message) <> TRUE) THEN
853       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
854         Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
855              'FUNCTION GET_REQUEST_STATUS ERROR, Reason: '||l_message);
856         Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
857              'FND_CONCURRENT.GET_REQUEST_STATUS<-'||current_calling_sequence);
858       END IF;
859       RAISE Check_control_failure;
860 
861     END IF;
862 
863     -- show output values (only if debug_switch = 'Y')
864 
865     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
866       Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
867         '------------------> l_dev_phase = '||l_dev_phase
868         ||' l_dev_status = '||l_dev_status
869         ||' l_previous_request_id = '||to_char(l_previous_request_id));
870     END IF;
871 
872     -------------------------------------------------------------------------
873     -- Step 4.1
874     -- Reject if any process for the source and group_id (optional) is
875     -- currentlt running
876     -------------------------------------------------------------------------
877     IF (l_dev_phase in ('PENDING','RUNNING','INACTIVE')) then
878 
879       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
880         Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
881          'ERROR: There are existing import processes currently in the status '
882          ||l_dev_phase||' for this source ('||p_source||') and group_id ('
883          ||p_group_id
884          ||') , please check your concurrent process requests');
885       END IF;
886       RAISE Check_control_failure;
887 
888     ELSIF (l_dev_phase = 'COMPLETE') THEN
889 
890        ---------------------------------------------------------------------
891        -- Step 4.2
892        -- Delete the previous record in ap_interface_controls if the status
893        -- is 'COMPLETE'
894        ---------------------------------------------------------------------
895        debug_info := '(Check_control_table 4.2) Delete the previous record '||
896                      'in ap_interface_controls';
897        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
898          Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
899        END IF;
900 
901        -- Bug 4145391
902        IF (p_group_id IS NULL) THEN
903            DELETE FROM AP_INTERFACE_CONTROLS
904             WHERE source = p_source
905               AND request_id = l_previous_request_id;
906        ELSE
907            DELETE FROM AP_INTERFACE_CONTROLS
908             WHERE source = p_source
909               AND group_id = p_group_id
910               AND request_id = l_previous_request_id;
911        END IF;
912 
913     END IF;   -- for step 4
914 
915   END LOOP;
916 
917   debug_info := '(Check_control_table) CLOSE import_requests cursor';
918   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
919     Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
920   END IF;
921 
922   -- Bug 4145391
923   IF (p_group_id IS NULL) THEN
924       CLOSE import_requests;
925   ELSE
926       CLOSE import_requests_group;
927   END IF;
928 
929   -----------------------------------------
930   -- Step 5
931   -- Insert record into control table
932   -----------------------------------------
933 
934   debug_info := '(Check_control_table 5) Insert record into control table';
935   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
936     Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
937   END IF;
938 
939   INSERT INTO AP_INTERFACE_CONTROLS(
940           source,
941           group_id,
942           request_id)
943   VALUES (p_source,
944           p_group_id,
945           AP_IMPORT_INVOICES_PKG.g_conc_request_id);
946 
947   ----------------------------------------------------------------------------
948   -- Step 6
949   -- Commit the change to database, it will also release the lock for the table
950   ----------------------------------------------------------------------------
951 
952   debug_info := '(Check_control_table 6) Commit';
953   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
954     Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
955   END IF;
956 
957   COMMIT;
958 
959   RETURN(TRUE);
960 
961 EXCEPTION
962 
963  WHEN OTHERS then
964     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
965       Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
966     END IF;
967 
968     IF (SQLCODE < 0) then
969       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
970         Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,SQLERRM);
971       END IF;
972     END IF;
973 
974     -- Bug 4145391
975     IF (p_group_id IS NULL) THEN
976         CLOSE import_requests;
977     ELSE
978         CLOSE import_requests_group;
979     END IF;
980 
981     RETURN (FALSE);
982 
983 END Check_control_table;
984 
985 
986 /*======================================================================
987  Procedure: Print
988    Procedure to output debug messages in strings no longer than 80 chars.
989 ========================================================================*/
990 PROCEDURE Print (
991           P_debug               IN     VARCHAR2,
992           P_string              IN     VARCHAR2)
993 IS
994   stemp    VARCHAR2(80);
995   nlength  NUMBER := 1;
996 BEGIN
997 
998   IF (P_Debug = 'Y') THEN
999      WHILE(length(P_string) >= nlength)
1000      LOOP
1001 
1002         stemp := substrb(P_string, nlength, 80);
1003         fnd_file.put_line(FND_FILE.LOG, stemp);
1004         nlength := (nlength + 80);
1005 
1006      END LOOP;
1007   END IF;
1008 
1009 EXCEPTION
1010   WHEN OTHERS THEN
1011     IF (SQLCODE <> -20001) THEN
1012       FND_MESSAGE.SET_NAME('SQLAP','AP_DEBUG');
1013       FND_MESSAGE.SET_TOKEN('ERROR',SQLERRM);
1014     END IF;
1015     APP_EXCEPTION.RAISE_EXCEPTION;
1016 
1017 END Print;
1018 
1019 /*======================================================================
1020  Function: Insert_Rejections
1021    This function is called whenever the process needs to insert a
1022    rejection.  If the process is called in the context of the 'XML
1023    Gateway' as source, the supplier must be notifies and the rejection
1024    code is one of a fixed list of rejection codes, then it inserts all
1025    tokens into the interface rejections table, else it ignores token
1026    parameters.
1027 ========================================================================*/
1028 FUNCTION insert_rejections (
1029           p_parent_table        IN     VARCHAR2,
1030           p_parent_id           IN     NUMBER,
1031           p_reject_code         IN     VARCHAR2,
1032           p_last_updated_by     IN     NUMBER,
1033           p_last_update_login   IN     NUMBER,
1034           p_calling_sequence    IN     VARCHAR2,
1035           p_notify_vendor_flag  IN     VARCHAR2 DEFAULT NULL,
1036           p_token_name1         IN     VARCHAR2 DEFAULT NULL,
1037           p_token_value1        IN     VARCHAR2 DEFAULT NULL,
1038           p_token_name2         IN     VARCHAR2 DEFAULT NULL,
1039           p_token_value2        IN     VARCHAR2 DEFAULT NULL,
1040           p_token_name3         IN     VARCHAR2 DEFAULT NULL,
1041           p_token_value3        IN     VARCHAR2 DEFAULT NULL,
1042           p_token_name4         IN     VARCHAR2 DEFAULT NULL,
1043           p_token_value4        IN     VARCHAR2 DEFAULT NULL,
1044           p_token_name5         IN     VARCHAR2 DEFAULT NULL,
1045           p_token_value5        IN     VARCHAR2 DEFAULT NULL,
1046           p_token_name6         IN     VARCHAR2 DEFAULT NULL,
1047           p_token_value6        IN     VARCHAR2 DEFAULT NULL,
1048           p_token_name7         IN     VARCHAR2 DEFAULT NULL,
1049           p_token_value7        IN     VARCHAR2 DEFAULT NULL,
1050           p_token_name8         IN     VARCHAR2 DEFAULT NULL,
1051           p_token_value8        IN     VARCHAR2 DEFAULT NULL,
1052           p_token_name9         IN     VARCHAR2 DEFAULT NULL,
1053           p_token_value9        IN     VARCHAR2 DEFAULT NULL,
1054           p_token_name10        IN     VARCHAR2 DEFAULT NULL,
1055           p_token_value10       IN     VARCHAR2 DEFAULT NULL)
1056 RETURN BOOLEAN IS
1057 
1058   current_calling_sequence    VARCHAR2(2000);
1059   debug_info               VARCHAR2(500);
1060 
1061 BEGIN
1062   -- Update the calling sequence
1063 
1064   current_calling_sequence := 'AP_Import_Utilities_Pkg.Insert_rejections<-'
1065                               ||P_calling_sequence;
1066 
1067   --------------------------------------------------------------------------
1068   -- Step1
1069   -- Insert into AP_INTERFACE_REJECTIONS
1070   --------------------------------------------------------------------------
1071 
1072   debug_info := '(Insert Rejections 1) Insert into AP_INTERFACE_REJECTIONS, '||
1073                 'REJECT CODE:'||p_reject_code;
1074 
1075   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
1076     Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
1077   END IF;
1078 
1079   IF(AP_IMPORT_INVOICES_PKG.g_source = 'XML GATEWAY'
1080      AND NVL(p_notify_vendor_flag,'Y') = 'Y'
1081      AND p_reject_code in ('CAN MATCH TO ONLY 1 LINE',
1082                            'DUPLICATE INVOICE NUMBER',
1083                            'DUPLICATE LINE NUMBER',
1084                            'INCONSISTENT CURR',
1085                            'INCONSISTENT PO LINE INFO',
1086                            'INCONSISTENT PO SUPPLIER',
1087                            'INVALID INVOICE AMOUNT',
1088                            'INVALID ITEM',
1089                            'INVALID PO INFO',
1090                            'INVALID PO NUM',
1091                            'INVALID PO RELEASE INFO',
1092                            'INVALID PO RELEASE NUM',
1093                            'INVALID PO SHIPMENT NUM',
1094                            'NEGATIVE QUANTITY BILLED',  --Bug 5134622
1095                            'INVALID PRICE/QUANTITY',
1096                            'INVALID QUANTITY',
1097                            'INVALID UNIT PRICE',
1098                            'NO PO LINE NUM',
1099                            'RELEASE MISSING',
1100                            'MISSING PO NUM') ) THEN
1101     -------------------------------------------------
1102     -- Step 2
1103     -- Set notify_vendor_flag for XML GATEWAY source
1104     -------------------------------------------------
1105 
1106     debug_info := '(Insert Rejections 2) '||
1107                   'Set notify_vendor_flag for XML GATEWAY';
1108     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
1109       Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
1110     END IF;
1111 
1112     INSERT INTO AP_INTERFACE_REJECTIONS(
1113           parent_table,
1114           parent_id,
1115           reject_lookup_code,
1116           last_updated_by,
1117           last_update_date,
1118           last_update_login,
1119           created_by,
1120           creation_date,
1121           notify_vendor_flag,
1122           token_name1,
1123           token_value1,
1124           token_name2,
1125           token_value2,
1126           token_name3,
1127           token_value3,
1128           token_name4,
1129           token_value4,
1130           token_name5,
1131           token_value5,
1132           token_name6,
1133           token_value6,
1134           token_name7,
1135           token_value7,
1136           token_name8,
1137           token_value8,
1138           token_name9,
1139           token_value9,
1140           token_name10,
1141           token_value10)
1142    VALUES (
1143           p_parent_table,
1144           p_parent_id,
1145           p_reject_code,
1146           p_last_updated_by,
1147           SYSDATE,
1148           p_last_update_login,
1149           p_last_updated_by,
1150           SYSDATE,
1151           'Y', -- p_notify_vendor_flag,
1152           p_token_name1,
1153           p_token_value1,
1154           p_token_name2,
1155           p_token_value2,
1156           p_token_name3,
1157           p_token_value3,
1158           p_token_name4,
1159           p_token_value4,
1160           p_token_name5,
1161           p_token_value5,
1162           p_token_name6,
1163           p_token_value6,
1164           p_token_name7,
1165           p_token_value7,
1166           p_token_name8,
1167           p_token_value8,
1168           p_token_name9,
1169           p_token_value9,
1170           p_token_name10,
1171           p_token_value10);
1172   ELSE
1173     INSERT INTO AP_INTERFACE_REJECTIONS(
1174           parent_table,
1175           parent_id,
1176           reject_lookup_code,
1177           last_updated_by,
1178           last_update_date,
1179           last_update_login,
1180           created_by,
1181           creation_date)
1182     VALUES (
1183           p_parent_table,
1184           p_parent_id,
1185           p_reject_code,
1186           p_last_updated_by,
1187           SYSDATE,
1188           p_last_update_login,
1189           p_last_updated_by,
1190           SYSDATE);
1191 
1192   END IF; -- if XML GATEWAY supplier rejection
1193 
1194   RETURN(TRUE);
1195 
1196 EXCEPTION
1197   WHEN OTHERS then
1198     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1199       Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
1200     END IF;
1201 
1202     IF (SQLCODE < 0) then
1203       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1204         Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,SQLERRM);
1205       END IF;
1206     END IF;
1207 
1208     RETURN (FALSE);
1209 
1210 END insert_rejections;
1211 
1212 
1213 FUNCTION get_overbill_for_shipment (
1214           p_po_shipment_id      IN             NUMBER,
1215           p_quantity_invoiced   IN             NUMBER,
1216 	  p_amount_invoiced	   IN	       NUMBER,
1217           p_overbilled             OUT NOCOPY  VARCHAR2,
1218           p_quantity_outstanding   OUT NOCOPY  NUMBER,
1219           p_quantity_ordered       OUT NOCOPY  NUMBER,
1220           p_qty_already_billed     OUT NOCOPY  NUMBER,
1221 	  p_amount_outstanding     OUT NOCOPY  NUMBER,
1222 	  p_amount_ordered	   OUT NOCOPY  NUMBER,
1223 	  p_amt_already_billed	   OUT NOCOPY  NUMBER,
1224           P_calling_sequence    IN             VARCHAR2) RETURN BOOLEAN IS
1225 
1226 current_calling_sequence    VARCHAR2(2000);
1227 debug_info           VARCHAR2(500);
1228 l_matching_basis	    PO_LINE_LOCATIONS_ALL.MATCHING_BASIS%TYPE;
1229 
1230 BEGIN
1231   -- Update the calling sequence
1232 
1233   current_calling_sequence :=
1234          'AP_Import_Utilities_Pkg.get_overbill_for_shipment<-'
1235          ||P_calling_sequence;
1236 
1237   --------------------------------------------------------------------------
1238   -- Step 1
1239   -- Get quantity_outstanding
1240   --------------------------------------------------------------------------
1241 
1242   debug_info := '(Get Overbill for Shipment 1) Get quantity_outstanding';
1243   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1244     Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
1245   END IF;
1246 
1247   --Contract Payments: modified the SELECT clause
1248   SELECT   decode(pod.distribution_type,'PREPAYMENT',
1249                   sum(NVL(pod.quantity_ordered,0) - NVL(pod.quantity_financed,0)
1250                        - NVL(pod.quantity_cancelled,0)),
1251                   sum(NVL(pod.quantity_ordered,0) - NVL(pod.quantity_billed,0)
1252                        - NVL(pod.quantity_cancelled,0))
1253 	         ),
1254            sum(NVL(pod.quantity_ordered,0) - NVL(pod.quantity_cancelled,0)),
1255            decode(pod.distribution_type,'PREPAYMENT',
1256                  sum(NVL(pod.quantity_financed,0)),
1257                  sum(NVL(pod.quantity_billed,0))
1258                  ),
1259 	   decode(pod.distribution_type,'PREPAYMENT',
1260                   sum(NVL(pod.amount_ordered,0) - NVL(pod.amount_financed,0)
1261                        - NVL(pod.amount_cancelled,0)),
1262                   sum(NVL(pod.amount_ordered,0) - NVL(pod.amount_billed,0)
1263                        - NVL(pod.amount_cancelled,0))
1264                  ),
1265            sum(NVL(pod.amount_ordered,0) - NVL(pod.amount_cancelled,0)),
1266            decode(pod.distribution_type,'PREPAYMENT',
1267                  sum(NVL(pod.amount_financed,0)),
1268                  sum(NVL(pod.amount_billed,0))
1269                  ),
1270 	   pll.matching_basis
1271     INTO   p_quantity_outstanding,
1272            p_quantity_ordered,
1273            p_qty_already_billed,
1274 	   p_amount_outstanding,
1275 	   p_amount_ordered,
1276 	   p_amt_already_billed,
1277 	   l_matching_basis
1278     FROM   po_distributions_ap_v pod,
1279 	   po_line_locations pll
1280    WHERE   pod.line_location_id = p_po_shipment_id
1281    AND     pll.line_location_id = pod.line_location_id
1282    GROUP BY  pod.distribution_type,pll.matching_basis ;
1283 
1284 
1285   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1286     Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,'------------------>
1287             p_quantity_outstanding = '||to_char(p_quantity_outstanding)
1288             ||' p_quantity_ordered = '||to_char(p_quantity_ordered)
1289             ||' p_qty_already_billed = '||to_char(p_qty_already_billed)
1290 	    ||' p_amount_outstanding = '||to_char(p_amount_outstanding)
1291             ||' p_amount_ordered = '||to_char(p_amount_ordered)
1292             ||' p_amt_already_billed = '||to_char(p_amt_already_billed)
1293          );
1294   END IF;
1295 
1296   ---------------------------------------------------------------------------
1297   -- Decide if overbilled
1298   -- Bug 562898
1299   -- Overbill flag should be Y is l_quantity_outstanding =0
1300   ---------------------------------------------------------------------------
1301 
1302   IF (l_matching_basis = 'QUANTITY') THEN
1303   IF ((p_quantity_outstanding - p_quantity_invoiced) <= 0) THEN
1304     P_overbilled := 'Y';
1305   ELSE
1306     P_overbilled := 'N';
1307   END IF;
1308   ELSIF (l_matching_basis = 'AMOUNT') THEN
1309      IF ((p_amount_outstanding - p_amount_invoiced) <= 0) THEN
1310         P_overbilled := 'Y';
1311      ELSE
1312         P_overbilled := 'N';
1313      END IF;
1314   END IF;
1315 
1316   RETURN(TRUE);
1317 
1318 EXCEPTION
1319 
1320   WHEN OTHERS THEN
1321     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
1322       Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
1323     END IF;
1324     IF (SQLCODE < 0) THEN
1325       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
1326         Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,SQLERRM);
1327       END IF;
1328     END IF;
1329 
1330     RETURN (FALSE);
1331 
1332 END get_overbill_for_shipment;
1333 
1334 
1335 /*======================================================================
1336  Function: Get_Batch_ID
1337    This function returns a batch_id and batch_type given a batch_name.
1338    If the batch already exists the batch_type returned is 'OLD BATCH',
1339    else the batch_type returned is 'NEW BATCH'.  If this is a NEW
1340    BATCH the batch_id is obtained from the appropriate sequence, else
1341    it is read off the AP_BATCHES table.
1342 ========================================================================*/
1343 FUNCTION get_batch_id (
1344           p_batch_name          IN             VARCHAR2,
1345           P_batch_id               OUT NOCOPY  NUMBER,
1346           p_batch_type             OUT NOCOPY  VARCHAR2,
1347           P_calling_sequence    IN             VARCHAR2)
1348 RETURN BOOLEAN
1349 IS
1350   l_batch_id      NUMBER;
1351   current_calling_sequence    VARCHAR2(2000);
1352   debug_info               VARCHAR2(500);
1353 
1354 BEGIN
1355   -- Update the calling sequence
1356 
1357   current_calling_sequence :=
1358     'AP_Import_Utilities_Pkg.get_batch_id<-'||P_calling_sequence;
1359 
1360   ------------------------------------------------------------------
1361   -- Find the old batch_id if it's existing batch, or use sequence
1362   -- find the next available batch_id
1363   ------------------------------------------------------------------
1364   debug_info := 'Check batch_name existance';
1365 
1366   BEGIN
1367    debug_info := '(Get_batch_id 1) Get old batch id';
1368    IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
1369      Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
1370    END IF;
1371 
1372    SELECT  'OLD BATCH',
1373             batch_id
1374      INTO   p_batch_type,
1375             l_batch_id
1376      FROM   ap_batches_all
1377     WHERE   batch_name = P_batch_name;
1378 
1379   EXCEPTION
1380     WHEN NO_DATA_FOUND THEN
1381       p_batch_type := 'NEW BATCH';
1382   END;
1383 
1384   IF (p_batch_type = 'NEW BATCH') THEN
1385 
1386     ---------------------------------------------
1387     -- Get New batch_id and Batch_date
1388     ---------------------------------------------
1389 
1390     debug_info := '(Get_batch_id 2) Get New batch_id';
1391     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
1392       Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
1393     END IF;
1394 
1395     SELECT  ap_batches_s.nextval
1396     INTO    l_batch_id
1397     FROM    sys.dual;
1398 
1399   END IF;
1400 
1401   p_batch_id := l_batch_id;
1402 
1403   RETURN(TRUE);
1404 
1405 EXCEPTION
1406  WHEN OTHERS then
1407    IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
1408      Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
1409    END IF;
1410 
1411    IF (SQLCODE < 0) THEN
1412      IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
1413        Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,SQLERRM);
1414      END IF;
1415    END IF;
1416 
1417    RETURN (FALSE);
1418 
1419 END get_batch_id;
1420 
1421 FUNCTION get_auto_batch_name(
1422           p_source                      IN            VARCHAR2,
1423           p_batch_name                     OUT NOCOPY VARCHAR2,
1424           p_calling_sequence            IN            VARCHAR2)
1425 RETURN BOOLEAN
1426 IS
1427   l_batch_num                     NUMBER;
1428   current_calling_sequence        VARCHAR2(2000);
1429   debug_info                      VARCHAR2(500);
1430 
1431 BEGIN
1432   -- Update the calling sequence
1433   --
1434   current_calling_sequence :=
1435     'AP_Import_Utilities_Pkg.get_auto_batch_name<-' ||p_calling_sequence;
1436 
1437   debug_info := '(Get_auto_batch_name 1) automatically create batch name';
1438 
1439   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
1440     Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
1441   END IF;
1442 
1443   SELECT  ap_batches_s2.nextval
1444   INTO    l_batch_num
1445   FROM    sys.dual;
1446 
1447   p_batch_name := p_source || ':' || to_char(l_batch_num);
1448   RETURN(TRUE);
1449 
1450 EXCEPTION
1451 
1452   WHEN OTHERS THEN
1453     RETURN(FALSE);
1454 
1455 END get_auto_batch_name;
1456 
1457 
1458 /*======================================================================
1459  Function: Get_Info
1460    This function returns values of system options, profile options and
1461    financials options once an OU has been detected.
1462 ========================================================================*/
1463 FUNCTION get_info (
1464           p_org_id                         IN         NUMBER,
1465           p_set_of_books_id                OUT NOCOPY NUMBER,
1466           p_multi_currency_flag            OUT NOCOPY VARCHAR2,
1467           p_make_rate_mandatory_flag       OUT NOCOPY VARCHAR2,
1468           p_default_exchange_rate_type     OUT NOCOPY VARCHAR2,
1469           p_base_currency_code             OUT NOCOPY VARCHAR2,
1470           p_batch_control_flag             OUT NOCOPY VARCHAR2,
1471           p_invoice_currency_code          OUT NOCOPY VARCHAR2,
1472           p_base_min_acct_unit             OUT NOCOPY NUMBER,
1473           p_base_precision                 OUT NOCOPY NUMBER,
1474           p_sequence_numbering             OUT NOCOPY VARCHAR2,
1475           p_awt_include_tax_amt            OUT NOCOPY VARCHAR2,
1476           p_gl_date                        IN OUT NOCOPY DATE,
1477        -- p_ussgl_transcation_code         OUT NOCOPY VARCHAR2, - Bug 4277744
1478           p_trnasfer_desc_flex_flag        OUT NOCOPY VARCHAR2,
1479           p_gl_date_from_receipt_flag      OUT NOCOPY VARCHAR2,
1480           p_purch_encumbrance_flag         OUT NOCOPY VARCHAR2,
1481 	      p_retainage_ccid		           OUT NOCOPY NUMBER,
1482           P_pa_installed                   OUT NOCOPY VARCHAR2,
1483           p_chart_of_accounts_id           OUT NOCOPY NUMBER,
1484           p_inv_doc_cat_override           OUT NOCOPY VARCHAR2,
1485           p_calc_user_xrate                OUT NOCOPY VARCHAR2,
1486           p_calling_sequence               IN         VARCHAR2,
1487           p_approval_workflow_flag         OUT NOCOPY VARCHAR2,
1488           p_freight_code_combination_id    OUT NOCOPY NUMBER,
1489 	      p_allow_interest_invoices	   OUT NOCOPY VARCHAR2, --bug 4113223
1490 	      p_add_days_settlement_date       OUT NOCOPY NUMBER,   --bug 4930111
1491           p_disc_is_inv_less_tax_flag      OUT NOCOPY VARCHAR2, --bug 4931755
1492           p_source                         IN         VARCHAR2, --bug 5382889. LE TimeZone
1493           p_invoice_date                   IN         DATE,     -- bug 5382889. LE TimeZone
1494           p_goods_received_date            IN         DATE,     -- bug 5382889. LE TimeZone
1495           p_asset_book_type                OUT NOCOPY VARCHAR2  -- Bug 5448579
1496         )
1497 RETURN BOOLEAN
1498 IS
1499 
1500   l_status                   VARCHAR2(10);
1501   l_industry                 VARCHAR2(10);
1502   get_info_failure           EXCEPTION;
1503   current_calling_sequence   VARCHAR2(2000);
1504   debug_info                 VARCHAR2(500);
1505   l_ext_precision            NUMBER(2);
1506 
1507 
1508 
1509   l_inv_gl_date                DATE;   --Bug 5382889. LE Timezone
1510   l_rts_txn_le_date            DATE;   --Bug 5382889. LE Timezone
1511   l_inv_le_date                DATE;   --Bug 5382889. LE Timezone
1512   l_sys_le_date                DATE;   --Bug 5382889. LE Timezone
1513 
1514   l_asset_book_count           NUMBER;
1515 
1516 BEGIN
1517   -- Update the calling sequence
1518 
1519   current_calling_sequence :=
1520     'AP_Import_Utilities_Pkg.Get_info<-'||P_calling_sequence;
1521 
1522   debug_info := '(Get_info 1) Read from ap_system_parameters';
1523   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
1524      Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
1525   END IF;
1526 
1527   SELECT
1528           set_of_books_id,
1529           multi_currency_flag,
1530           make_rate_mandatory_flag,
1531           default_exchange_rate_type,
1532           base_currency_code,
1533           aps.invoice_currency_code,
1534           awt_include_tax_amt,
1535        -- ussgl_transaction_code, - Bug 4277744
1536           transfer_desc_flex_flag,
1537           gl_date_from_receipt_flag,
1538           inv_doc_category_override,
1539           NVL(calc_user_xrate, 'N'),
1540           NVL(approval_workflow_flag,'N'),
1541           freight_code_combination_id ,
1542 	  /*we need to get the value of allow_interest_invoices
1543 	  from system_parameters versus product setup, since the value
1544 	  in the product setup is only for defaulting into suppliers,
1545 	  whereas the value in asp decides whether we create INT invoices
1546 	  or not*/
1547 	  asp.auto_calculate_interest_flag,
1548 	  --bugfix:4930111
1549 	  asp.add_days_settlement_date,
1550           NVL(asp.disc_is_inv_less_tax_flag, 'N') /* bug 4931755 */
1551      INTO p_set_of_books_id,
1552           p_multi_currency_flag,
1553           p_make_rate_mandatory_flag,
1554           p_default_exchange_rate_type,
1555           p_base_currency_code,
1556           p_invoice_currency_code,
1557           p_awt_include_tax_amt,
1558        -- p_ussgl_transcation_code, - Bug 4277744
1559           p_trnasfer_desc_flex_flag,
1560           p_gl_date_from_receipt_flag,
1561           p_inv_doc_cat_override,
1562           p_calc_user_xrate,
1563           p_approval_workflow_flag,
1564           p_freight_code_combination_id,
1565 	      p_allow_interest_invoices,
1566 	      p_add_days_settlement_date,
1567           p_disc_is_inv_less_tax_flag
1568     FROM  ap_system_parameters_all asp,
1569           ap_product_setup aps
1570    WHERE  asp.org_id = p_org_id;
1571 
1572   debug_info := '(Get_info 2) Get Batch Control Profile Option';
1573   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
1574      Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
1575   END IF;
1576 
1577   BEGIN
1578     FND_PROFILE.GET('AP_USE_INV_BATCH_CONTROLS',p_batch_control_flag);
1579 
1580   EXCEPTION
1581     WHEN OTHERS THEN
1582     p_batch_control_flag := 'N';
1583   END ;
1584 
1585   debug_info := '(Get_info 3) Get encumbrance option';
1586   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
1587      Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
1588   END IF;
1589 
1590   SELECT  purch_encumbrance_flag, retainage_code_combination_id
1591     INTO  p_purch_encumbrance_flag, p_retainage_ccid
1592     FROM  financials_system_params_all
1593    WHERE  org_id = p_org_id;
1594 
1595   debug_info := '(Get_info 4) Get minimum_accountable_unit';
1596   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1597     Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
1598   END IF;
1599 
1600   FND_CURRENCY.GET_INFO(
1601           p_base_currency_code  ,
1602           p_base_precision ,
1603           l_ext_precision ,
1604           p_base_min_acct_unit);
1605 
1606   debug_info := '(Get_info 5) Get p_sequence_numbering';
1607   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
1608     Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
1609   END IF;
1610 
1611   p_sequence_numbering := FND_PROFILE.VALUE('UNIQUE:SEQ_NUMBERS');
1612 
1613 
1614   debug_info := '(Get_info 6) Get gl_date based on report parameters';
1615   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
1616     Print(AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
1617   END IF;
1618 
1619   -- Bug 5645581. Gl_date will calculated at the Import_Invoices
1620   -- Procedure in the Main Package
1621   /*IF p_source = 'ERS' THEN     -- bug 5382889, LE TimeZone
1622 
1623     debug_info := 'Determine gl_date from ERS invoice';
1624 
1625     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
1626       Print(AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
1627     END IF;
1628 
1629     l_rts_txn_le_date :=  INV_LE_TIMEZONE_PUB.Get_Le_Day_For_Ou(
1630                           p_trxn_date    => nvl(p_goods_received_date, p_invoice_date)
1631                          ,p_ou_id        => p_org_id);
1632 
1633     l_inv_le_date :=  INV_LE_TIMEZONE_PUB.Get_Le_Day_For_Ou(
1634                           p_trxn_date    => p_invoice_date
1635                          ,p_ou_id        => p_org_id);
1636 
1637     l_sys_le_date :=  INV_LE_TIMEZONE_PUB.Get_Le_Day_For_Ou(
1638                           p_trxn_date    => sysdate
1639                          ,p_ou_id        => p_org_id);
1640 
1641 
1642       -- The gl_date id determined from the flag gl_date_from_receipt_flag
1643       -- If the flag = 'I' -- take Invoice_date
1644       --             = 'S' -- take System date
1645       --             = 'N' -- take nvl(receipt_date, invoice_date)
1646       --             = 'Y' -- take nvl(receipt_date, sysdate)
1647       -- Note here that the Invoice date is no longer the same as the receipt_date,
1648       -- i.e. the RETURN tranasaction_date , so case I and N are no longer the same
1649 
1650     debug_info := 'Determine invoice gl_date from LE Timezone API ';
1651     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
1652       Print(AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
1653     END IF;
1654 
1655     If (p_gl_date_from_receipt_flag = 'I') Then
1656         l_inv_gl_date := l_inv_le_date;
1657     Elsif (p_gl_date_from_receipt_flag = 'N') Then
1658         l_inv_gl_date := nvl(l_rts_txn_le_date, l_inv_le_date);
1659     Elsif (p_gl_date_from_receipt_flag = 'S') Then
1660         l_inv_gl_date := l_sys_le_date;
1661     Elsif (p_gl_date_from_receipt_flag = 'Y') then
1662         l_inv_gl_date := nvl(l_rts_txn_le_date, l_sys_le_date);
1663     End if;
1664 
1665     p_gl_date  := l_inv_gl_date;
1666 
1667   ELSE
1668     IF (p_gl_date IS NULL) THEN
1669       IF (p_gl_date_from_receipt_flag IN ('S','Y')) THEN
1670         debug_info := '(Get_info 6a) GL Date is Sysdate';
1671         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
1672           Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
1673         END IF;
1674 
1675         p_gl_date := sysdate;
1676 
1677       ELSE
1678         debug_info := '(Get_info 6b) GL Date should be Invoice Date';
1679         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
1680           Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
1681         END IF;
1682       END IF;
1683     END IF;
1684   END IF;
1685 
1686   p_gl_date := trunc(p_gl_date); */
1687   debug_info := '(Get_info 7) Check if PA is installed';
1688   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
1689     Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
1690   END IF;
1691 
1692   IF (FND_INSTALLATION.GET(275, 275, l_status, l_industry)) THEN
1693     IF (l_status <> 'I') THEN
1694       P_PA_INSTALLED := 'N';
1695     ELSE
1696       P_PA_INSTALLED := 'Y';
1697       AP_IMPORT_INVOICES_PKG.g_pa_allows_overrides :=
1698          NVL(FND_PROFILE.VALUE('PA_ALLOW_FLEXBUILDER_OVERRIDES'), 'N');
1699     END IF;
1700   ELSE
1701     RAISE get_info_failure;
1702   END IF;
1703 
1704   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
1705     Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1706         '------------------> l_status = '|| l_status
1707         ||' l_industry  = '   ||l_industry
1708         ||' p_pa_installed = '||p_pa_installed);
1709   END IF;
1710 
1711   debug_info := '(Get_info 8) Get chart_of_accounts_id from p_set_of_books_id';
1712   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
1713     Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
1714   END IF;
1715 
1716   SELECT chart_of_accounts_id
1717     INTO p_chart_of_accounts_id
1718     FROM gl_sets_of_books
1719    WHERE set_of_books_id = p_set_of_books_id;
1720 
1721   -- Bug 5448579
1722 
1723   /* debug_info := '(Get_info 9) Get Asset Book Type Code';
1724   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
1725     Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
1726   END IF;
1727   BEGIN
1728     SELECT count(*)
1729     INTO l_asset_book_count
1730     FROM fa_book_controls bc
1731     WHERE bc.book_class = 'CORPORATE'
1732     AND bc.set_of_books_id = p_set_of_books_id
1733     AND bc.date_ineffective IS NULL;
1734 
1735     IF (l_asset_book_count = 1) THEN
1736       SELECT bc.book_type_code
1737       INTO p_asset_book_type
1738       FROM fa_book_controls bc
1739       WHERE  bc.book_class = 'CORPORATE'   --bug7040148
1740       AND bc.set_of_books_id = p_set_of_books_id
1741       AND bc.date_ineffective IS NULL;
1742 
1743     ELSE
1744       p_asset_book_type := NULL;
1745     END IF;
1746 
1747   EXCEPTION
1748       -- No need to error handle if FA information not available.
1749       WHEN no_data_found THEN
1750         NULL;
1751       WHEN OTHERS THEN
1752         NULL;
1753   END; */ --bug 7584682
1754 
1755   p_asset_book_type := NULL; --bug 7584682
1756 
1757   debug_info := '(Get_info 9) Get system tolerances';
1758   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
1759     Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
1760   END IF;
1761 
1762   -- For EDI transactions, if the price and qty tolerance is set to null
1763   -- we assume this to be zero. This is implemented as per discussion with
1764   -- Subir.
1765 
1766   --Bug 4051803 commented out the below code and moved it to
1767   --function get_tolerance_info, which will be called to for
1768   --get tolerance info specific to site as oppose to org.
1769  /*
1770  SELECT
1771   DECODE(price_tolerance, NULL,1,(1 + (price_tolerance/100))),
1772   DECODE(price_tolerance, NULL,1,(1 - (price_tolerance/100))),
1773   DECODE(quantity_tolerance, NULL,1, (1 + (quantity_tolerance/100))),
1774   DECODE(qty_received_tolerance, NULL,NULL, (1 +(qty_received_tolerance/100))),
1775   max_qty_ord_tolerance,
1776   max_qty_rec_tolerance,
1777   ship_amt_tolerance,
1778   rate_amt_tolerance,
1779   total_amt_tolerance
1780  INTO
1781   p_positive_price_tolerance,
1782   p_negative_price_tolerance,
1783   p_qty_tolerance,
1784   p_qty_rec_tolerance,
1785   p_max_qty_ord_tolerance,
1786   p_max_qty_rec_tolerance,
1787   p_ship_amt_tolerance,
1788   p_rate_amt_tolerance,
1789   p_total_amt_tolerance
1790  FROM  ap_tolerances_all
1791 where  org_id = p_org_id; */
1792 
1793   RETURN (TRUE);
1794 
1795 
1796 EXCEPTION
1797  WHEN OTHERS then
1798    IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
1799      Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
1800    END IF;
1801 
1802    IF (SQLCODE < 0) then
1803      IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
1804        Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,SQLERRM);
1805      END IF;
1806    END IF;
1807 
1808    RETURN (FALSE);
1809 
1810 END get_info;
1811 
1812 
1813 -- Bug 4051803
1814 --===================================================================
1815 -- Function: get_tolerance_info
1816 -- Get tolerance info. from po_vendor_sites_all
1817 -- based on vendor_site_id
1818 --===================================================================
1819 FUNCTION get_tolerance_info(
1820 	    p_vendor_site_id		        IN 		NUMBER,
1821         p_positive_price_tolerance      OUT NOCOPY      NUMBER,
1822         p_negative_price_tolerance      OUT NOCOPY      NUMBER,
1823         p_qty_tolerance                 OUT NOCOPY      NUMBER,
1824         p_qty_rec_tolerance             OUT NOCOPY      NUMBER,
1825         p_max_qty_ord_tolerance         OUT NOCOPY      NUMBER,
1826         p_max_qty_rec_tolerance         OUT NOCOPY      NUMBER,
1827 	    p_amt_tolerance		            OUT NOCOPY      NUMBER,
1828 	    p_amt_rec_tolerance		        OUT NOCOPY	    NUMBER,
1829 	    p_max_amt_ord_tolerance         OUT NOCOPY      NUMBER,
1830 	    p_max_amt_rec_tolerance         OUT NOCOPY      NUMBER,
1831         p_goods_ship_amt_tolerance      OUT NOCOPY      NUMBER,
1832         p_goods_rate_amt_tolerance      OUT NOCOPY      NUMBER,
1833         p_goods_total_amt_tolerance     OUT NOCOPY      NUMBER,
1834 	    p_services_ship_amt_tolerance   OUT NOCOPY      NUMBER,
1835         p_services_rate_amt_tolerance   OUT NOCOPY      NUMBER,
1836         p_services_total_amt_tolerance  OUT NOCOPY      NUMBER,
1837         p_calling_sequence		        IN		VARCHAR2)
1838 RETURN BOOLEAN IS
1839   debug_info                      VARCHAR2(500);
1840   l_price_tolerance		  ap_tolerance_templates.price_tolerance%TYPE;
1841 BEGIN
1842 
1843   debug_info := '(Get_tolerance_info 1) Get tolerance info...';
1844   If AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' then
1845    Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
1846   End if;
1847 
1848   -- For EDI transactions, if the price and qty tolerance is set to null
1849   -- we assume this to be zero. This is implemented as per discussion with
1850   -- Subir.
1851 
1852   BEGIN
1853 
1854       select price_tolerance,
1855              decode(price_tolerance, NULL,1,(1 + (price_tolerance/100))),
1856              decode(price_tolerance, NULL,1,(1 - (price_tolerance/100))),
1857             -- decode(quantity_tolerance, NULL,1, (1 + (quantity_tolerance/100))), Commented and added for bug 9381715
1858              decode(quantity_tolerance, NULL,NULL, (1 + (quantity_tolerance/100))),
1859 	     decode(qty_received_tolerance, NULL,NULL, (1 +(qty_received_tolerance/100))),
1860              max_qty_ord_tolerance,
1861              max_qty_rec_tolerance,
1862              ship_amt_tolerance,
1863              rate_amt_tolerance,
1864              total_amt_tolerance
1865       into
1866              l_price_tolerance,
1867              p_positive_price_tolerance,
1868              p_negative_price_tolerance,
1869              p_qty_tolerance,
1870              p_qty_rec_tolerance,
1871              p_max_qty_ord_tolerance,
1872              p_max_qty_rec_tolerance,
1873              p_goods_ship_amt_tolerance,
1874              p_goods_rate_amt_tolerance,
1875              p_goods_total_amt_tolerance
1876       from   ap_tolerance_templates att,
1877              po_vendor_sites_all pvs
1878       where  pvs.vendor_site_id = p_vendor_site_id
1879       and    pvs.tolerance_id = att.tolerance_id;
1880 
1881   EXCEPTION
1882      when no_data_found then
1883        debug_info := '(get_tolerance_info 1) NO_DATA_FOUND exception';
1884        If AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' then
1885          Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
1886        End if;
1887   END;
1888 
1889 
1890   BEGIN
1891       select decode(quantity_tolerance, NULL,1, (1 + (quantity_tolerance/100))),
1892              decode(qty_received_tolerance, NULL,NULL, (1 +(qty_received_tolerance/100))),
1893 	     max_qty_ord_tolerance,
1894 	     max_qty_rec_tolerance,
1895              ship_amt_tolerance,
1896              rate_amt_tolerance,
1897              total_amt_tolerance
1898       into
1899              p_amt_tolerance,
1900              p_amt_rec_tolerance,
1901 	     p_max_amt_ord_tolerance,
1902 	     p_max_amt_rec_tolerance,
1903              p_services_ship_amt_tolerance,
1904              p_services_rate_amt_tolerance,
1905              p_services_total_amt_tolerance
1906       from   ap_tolerance_templates att,
1907              po_vendor_sites_all pvs
1908       where  pvs.vendor_site_id = p_vendor_site_id
1909       and    pvs.services_tolerance_id = att.tolerance_id;
1910 
1911 
1912   EXCEPTION WHEN NO_DATA_FOUND THEN
1913 
1914        debug_info := '(get_tolerance_info 2) NO_DATA_FOUND exception';
1915        If AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' then
1916          Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
1917        End if;
1918 
1919   END;
1920 
1921   If AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y'  then
1922     Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,'------------------> p_vendor_site_id = '||
1923                 to_char(p_vendor_site_id)
1924                 ||' l_price_tolerance  = '||to_char(l_price_tolerance)
1925                 ||' l_positive_price_tolerance  = '||to_char(p_positive_price_tolerance)
1926                 ||' l_negative_price_tolerance  = '||to_char(p_negative_price_tolerance)
1927                 ||' l_qty_tolerance  = '||to_char(p_qty_tolerance)
1928                 ||' l_qty_received_tolerance  = '||to_char(p_qty_rec_tolerance)
1929                 ||' l_max_qty_ord_tolerance  = '||to_char(p_max_qty_ord_tolerance)
1930                 ||' l_max_qty_rec_tolerance  = '||to_char(p_max_qty_rec_tolerance)
1931 		        ||' l_amt_tolerance  = '||to_char(p_amt_tolerance)
1932                 ||' l_amt_received_tolerance  = '||to_char(p_amt_rec_tolerance)
1933 		        ||' l_max_amt_ord_tolerance  = '||to_char(p_max_amt_ord_tolerance)
1934 	            ||' l_max_amt_rec_tolerance  = '||to_char(p_max_amt_rec_tolerance)
1935                 ||' l_goods_ship_amt_tolerance  = '||to_char(p_goods_ship_amt_tolerance)
1936                 ||' l_goods_rate_amttolerance  = '||to_char(p_goods_rate_amt_tolerance)
1937                 ||' l_goods_total_amt_tolerance  = '||to_char(p_goods_total_amt_tolerance)
1938 		        ||' l_services_ship_amt_tolerance  = '||to_char(p_services_ship_amt_tolerance)
1939                 ||' l_services_rate_amttolerance  = '||to_char(p_services_rate_amt_tolerance)
1940                 ||' l_services_total_amt_tolerance  = '||to_char(p_services_total_amt_tolerance));
1941   end if;
1942 
1943   RETURN (TRUE);
1944 
1945 EXCEPTION
1946 
1947  WHEN OTHERS then
1948     If AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' then
1949       Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info); End if;
1950 
1951     IF (SQLCODE < 0) then
1952       If AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y'
1953       then Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,SQLERRM); End if;
1954     END IF;
1955 
1956     RETURN (FALSE);
1957 
1958 END get_tolerance_info;
1959 
1960 
1961 /*======================================================================
1962  Function: find_vendor_primary_paysite
1963   This function is called when import program is  trying to default a
1964   vendor site in case user did not give input of vendor site information.
1965    1. Return primary site id if there is one
1966    2. Return the only paysite if there is no primary paysite
1967    3. Return null if there are multiple paysite but no primary paysite
1968    4. Return null if there is no paysite
1969 ========================================================================*/
1970 FUNCTION find_vendor_primary_paysite(
1971           p_vendor_id                   IN            NUMBER,
1972           p_vendor_primary_paysite_id      OUT NOCOPY NUMBER,
1973           p_calling_sequence            IN            VARCHAR2)
1974 RETURN BOOLEAN
1975 IS
1976 
1977   CURSOR primary_pay_site_cur IS
1978   SELECT vendor_site_id
1979     FROM po_vendor_sites PVS
1980    WHERE vendor_id = p_vendor_id
1981      AND pay_site_flag = 'Y'
1982      AND primary_pay_site_flag = 'Y'
1983      AND NVL(trunc(PVS.INACTIVE_DATE),AP_IMPORT_INVOICES_PKG.g_inv_sysdate+1)
1984          > AP_IMPORT_INVOICES_PKG.g_inv_sysdate ;
1985 
1986   CURSOR pay_site_cur IS
1987   SELECT vendor_site_id
1988     FROM po_vendor_sites PVS
1989    WHERE vendor_id = p_vendor_id
1990     AND pay_site_flag = 'Y'
1991     AND NVL(trunc(PVS.INACTIVE_DATE),AP_IMPORT_INVOICES_PKG.g_inv_sysdate+1)
1992          > AP_IMPORT_INVOICES_PKG.g_inv_sysdate ;
1993 
1994   l_vendor_site_id           PO_VENDOR_SITES.VENDOR_SITE_ID%TYPE;
1995   l_paysite_count            NUMBER;
1996   current_calling_sequence   VARCHAR2(2000);
1997   debug_info                 VARCHAR2(500);
1998 
1999 BEGIN
2000   -- Update the calling sequence
2001 
2002   current_calling_sequence :=
2003          'AP_IMPORT_UTILITIES_PKG.find_vendor_primary_paysite<-'
2004          ||P_calling_sequence;
2005 
2006   debug_info := '(Find vendor primary paysite 1) Get the primary paysite';
2007   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2008     Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
2009   END IF;
2010 
2011   OPEN primary_pay_site_cur;
2012   FETCH primary_pay_site_cur INTO l_vendor_site_id;
2013   CLOSE primary_pay_site_cur;
2014 
2015   IF ( l_vendor_site_id is null ) THEN
2016 
2017     SELECT count(*)
2018       INTO l_paysite_count
2019       FROM po_vendor_sites PVS
2020      WHERE vendor_id = p_vendor_id
2021       AND pay_site_flag = 'Y'
2022       AND NVL(trunc(PVS.INACTIVE_DATE),AP_IMPORT_INVOICES_PKG.g_inv_sysdate+1)
2023           > AP_IMPORT_INVOICES_PKG.g_inv_sysdate ;
2024 
2025     IF ( l_paysite_count = 1 ) THEN
2026       OPEN pay_site_cur;
2027       FETCH pay_site_cur INTO l_vendor_site_id;
2028       CLOSE pay_site_cur;
2029       p_vendor_primary_paysite_id := l_vendor_site_id;
2030     ELSE
2031       p_vendor_primary_paysite_id := null;
2032     END IF;
2033   ELSE
2034     p_vendor_primary_paysite_id := l_vendor_site_id;
2035   END IF;
2036 
2037   RETURN(TRUE);
2038 
2039 EXCEPTION
2040 
2041   WHEN OTHERS THEN
2042     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
2043       Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
2044     END IF;
2045     IF (SQLCODE < 0) then
2046       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
2047         Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,SQLERRM);
2048       END IF;
2049     END IF;
2050 
2051     RETURN (FALSE);
2052 
2053 END find_vendor_primary_paysite;
2054 
2055 
2056 FUNCTION get_employee_id(
2057           p_invoice_id                  IN            NUMBER,
2058           p_vendor_id                   IN            NUMBER,
2059           p_employee_id                    OUT NOCOPY NUMBER,
2060           p_default_last_updated_by     IN            NUMBER,
2061           p_default_last_update_login   IN            NUMBER,
2062           p_current_invoice_status         OUT NOCOPY VARCHAR2,
2063           p_calling_sequence            IN            VARCHAR2)
2064 RETURN BOOLEAN
2065 IS
2066   get_employee_failure    EXCEPTION;
2067   l_current_invoice_status  VARCHAR2(1) := 'Y';
2068   l_employee_id      NUMBER;
2069   current_calling_sequence    VARCHAR2(2000);
2070   debug_info               VARCHAR2(500);
2071 
2072 BEGIN
2073   -- Update the calling sequence
2074 
2075   current_calling_sequence := 'get_employee_id<-'||P_calling_sequence;
2076 
2077   BEGIN
2078     debug_info := '(Get_employee_id 1) Get employee id from po_vendors';
2079     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
2080       Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
2081     END IF;
2082 
2083     SELECT  employee_id
2084       INTO  l_employee_id
2085       FROM  po_vendors
2086      WHERE  vendor_id = p_vendor_id;
2087 
2088   EXCEPTION
2089     WHEN NO_DATA_FOUND THEN
2090 
2091     -- Potentially this should never happen
2092     -- as vendor is already validated at the invoice level
2093 
2094     debug_info := '(Get_employee_id 2) Vendor Id is invalid';
2095     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2096       Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
2097     END IF;
2098 
2099     -- Reject Here for Invalid Vendor
2100 
2101     debug_info := '(Get emloyee_id 3) Check for invalid Supplier.';
2102     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
2103       Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
2104     END IF;
2105 
2106     IF (insert_rejections(AP_IMPORT_INVOICES_PKG.g_invoices_table,
2107           p_invoice_id,
2108           'INVALID SUPPLIER',
2109           p_default_last_updated_by,
2110           p_default_last_update_login,
2111           current_calling_sequence) <> TRUE) THEN
2112       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2113         Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2114            'insert_rejections<-'||current_calling_sequence);
2115       END IF;
2116       RAISE get_employee_failure;
2117     END IF;
2118     l_current_invoice_status := 'N';
2119   END;
2120 
2121   IF (l_employee_id IS NULL) THEN
2122 
2123     -- We shall not reject if employee id is Null
2124 
2125     debug_info := '(Get_employee_id 3) Employee_id id Null';
2126     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
2127       Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
2128     END IF;
2129 
2130   END IF;
2131   --
2132   p_employee_id            :=l_employee_id;
2133   p_current_invoice_status := l_current_invoice_status;
2134 
2135   RETURN(TRUE);
2136 
2137 EXCEPTION
2138   WHEN OTHERS THEN
2139     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
2140       Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
2141     END IF;
2142 
2143     IF (SQLCODE < 0) THEN
2144       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
2145         Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,SQLERRM);
2146       END IF;
2147     END IF;
2148 
2149     RETURN (FALSE);
2150 
2151 END get_employee_id;
2152 
2153 
2154 FUNCTION get_next_dist_line_num(
2155           p_invoice_id         IN            NUMBER,
2156           p_line_num           IN            NUMBER,
2157           p_next_dist_num         OUT NOCOPY NUMBER,
2158           P_calling_sequence   IN            VARCHAR2)
2159 RETURN BOOLEAN
2160 IS
2161   current_calling_sequence    VARCHAR2(2000);
2162   debug_info               VARCHAR2(500);
2163 
2164 BEGIN
2165 
2166   -- Update the calling sequence
2167 
2168   current_calling_sequence := 'get_next_dist_line_num<-'||P_calling_sequence;
2169 
2170   --------------------------------------------------------------------------
2171   -- Step 1
2172   -- Get the next available distribution line number given the invoice
2173   -- and line number
2174   --------------------------------------------------------------------------
2175 
2176   debug_info := '(Get Next Dist Line Num 1) Get the next available '||
2177                 'distribution line number';
2178   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
2179      Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
2180   END IF;
2181 
2182 /* For bug 3929697
2183    * Before executing the select for getting the value
2184    * of distribution line number check whether it is already
2185    * fetched. If so, increment distribution line number
2186    * else execute the select to get the corresponding value
2187    * */
2188 
2189   If (lg_invoice_id = p_invoice_id and lg_dist_line_num is not null) Then
2190     p_next_dist_num := lg_dist_line_num + 1;
2191   Else
2192      SELECT max(distribution_line_number)
2193        INTO p_next_dist_num
2194        FROM ap_invoice_distributions
2195       WHERE invoice_id = p_invoice_id
2196      AND invoice_line_number = p_line_num;
2197     p_next_dist_num := nvl(p_next_dist_num,0) + 1;
2198   End if;
2199   lg_invoice_id := p_invoice_id;
2200   lg_dist_line_num := p_next_dist_num;
2201 
2202   RETURN(TRUE);
2203 
2204 RETURN NULL; EXCEPTION
2205 
2206   WHEN NO_DATA_FOUND THEN
2207     p_next_dist_num := 1;
2208     /* For bug 3929697
2209        Initialized the global variables */
2210     lg_invoice_id := p_invoice_id;
2211     lg_dist_line_num := p_next_dist_num;
2212     RETURN(TRUE);
2213 
2214   WHEN OTHERS THEN
2215     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
2216       Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
2217     END IF;
2218 
2219     IF (SQLCODE < 0) THEN
2220       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
2221         Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,SQLERRM);
2222       END IF;
2223     END IF;
2224 
2225     RETURN (FALSE);
2226 
2227 END get_next_dist_line_num;
2228 
2229 
2230 FUNCTION get_overbill_for_po_line(
2231           p_po_line_id                  IN            NUMBER,
2232           p_quantity_invoiced           IN            NUMBER,
2233 	      p_amount_invoiced		        IN	          NUMBER,
2234           p_overbilled                  OUT NOCOPY    VARCHAR2,
2235           p_outstanding                 OUT NOCOPY    NUMBER,
2236           p_ordered                     OUT NOCOPY    NUMBER,
2237           p_already_billed              OUT NOCOPY    NUMBER,
2238 	      p_po_line_matching_basis	    OUT NOCOPY    VARCHAR2,
2239           P_calling_sequence            IN            VARCHAR2)
2240 RETURN BOOLEAN
2241 
2242 IS
2243   current_calling_sequence   VARCHAR2(2000);
2244   debug_info                 VARCHAR2(500);
2245 
2246 BEGIN
2247   -- Update the calling sequence
2248 
2249   current_calling_sequence := 'get_overbill_for_po_line<-'||P_calling_sequence;
2250 
2251   ----------------------------------------------------------------------------
2252   -- Step 1
2253   -- Get quantity_outstanding
2254   ----------------------------------------------------------------------------
2255   debug_info := '(Get Overbill for PO Line 1) Get quantity_outstanding';
2256   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
2257     Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
2258   END IF;
2259 
2260   --Contract Payments: Modified the SELECT clause
2261   /*-----------------------------------------------------------------------------------------+
2262    --For the case of complex works, following scenarios are possible:
2263   1.Matching Basis at PO Line = 'AMOUNT' and
2264      shipments could have matching_basis of 'QUANTITY'/'AMOUNT'. And within that
2265      shipment_type could be 'PREPAYMENT' or 'STANDARD'. For 'PREPAYMENT'
2266      we need to go off of financed columns and
2267      for 'STANDARD' we need to go off of Billed columns.
2268   2.Matching Basis at PO Line = 'QUANTITY'
2269     and then shipments can have the matching basis of only 'QUANTITY'. And within that
2270      shipment_type could be 'PREPAYMENT' or 'STANDARD'. For 'PREPAYMENT'
2271      we need to go off of financed columns and
2272      for 'STANDARD' we need to go off of Billed columns.
2273   +------------------------------------------------------------------------------------------*/
2274 
2275   SELECT
2276   	 DECODE(pl.matching_basis, 'QUANTITY',
2277      	          DECODE(pll.shipment_type,'PREPAYMENT',
2278                          sum(NVL(pll.quantity,0) - NVL(pll.quantity_financed,0) -
2279                              NVL(pll.quantity_cancelled,0)),
2280                          sum(NVL(pll.quantity,0) - NVL(pll.quantity_billed,0) -
2281                              NVL(pll.quantity_cancelled,0))
2282 		 ),
2283 	          'AMOUNT',
2284 		   SUM(DECODE(pll.matching_basis,'QUANTITY',
2285 			      (DECODE(pll.shipment_type,'PREPAYMENT',
2286                                       NVL(pll.quantity,0) - NVL(pll.quantity_financed,0) -
2287                                           NVL(pll.quantity_cancelled,0),
2288                                       NVL(pll.quantity,0) - NVL(pll.quantity_billed,0) -
2289                                           NVL(pll.quantity_cancelled,0)
2290                                      )
2291                               )*pll.price_override,
2292 			      'AMOUNT',
2293 			      DECODE(pll.shipment_type,'PREPAYMENT',
2294                          	     NVL(pll.amount,0) - NVL(pll.amount_financed,0) -
2295                              		 NVL(pll.amount_cancelled,0),
2296                          	     NVL(pll.amount,0) - NVL(pll.amount_billed,0) -
2297                                          NVL(pll.amount_cancelled,0)
2298 	                            )
2299                              )
2300                       )
2301                  ),
2302            DECODE(pl.matching_basis,
2303 		  'QUANTITY',
2304 	    	  SUM(NVL(pll.quantity,0) - NVL(pll.quantity_cancelled,0)),
2305 		  'AMOUNT',
2306 		  SUM(DECODE(pll.matching_basis,
2307 			     'QUANTITY',
2308 			     (NVL(pll.quantity,0) - NVL(pll.quantity_cancelled,0))*pll.price_override,
2309 			     'AMOUNT',
2310 			      NVL(pll.amount,0) - NVL(pll.amount_cancelled,0)
2311 			    )
2312 		     )
2313                  ),
2314           DECODE(pl.matching_basis,
2315 		 'QUANTITY',
2316   	         DECODE(shipment_type,'PREPAYMENT',
2317                         sum(NVL(quantity_financed,0)),sum(NVL(quantity_billed,0))
2318                        ),
2319 		 'AMOUNT',
2320 		 SUM(DECODE(pll.matching_basis,
2321 			    'QUANTITY',
2322            		    DECODE(shipment_type,'PREPAYMENT',
2323                         	   NVL(quantity_financed,0),NVL(quantity_billed,0)
2324                                    )*pll.price_override,
2325 			    'AMOUNT',
2326 			    DECODE(pll.shipment_type,'PREPAYMENT',
2327                           	  NVL(pll.amount_financed,0),NVL(pll.amount_billed,0)
2328   		                  )
2329 			   )
2330 		    )
2331 		 ),
2332 	   pl.matching_basis
2333     INTO   p_outstanding,
2334            p_ordered,
2335            p_already_billed,
2336 	   p_po_line_matching_basis
2337     FROM   po_line_locations pll,
2338 	   po_lines pl
2339    WHERE   pll.po_line_id = p_po_line_id
2340    AND     pl.po_line_id = pll.po_line_id
2341    -- bug fix 6959362 starts
2342    group by pl.matching_basis, pll.shipment_type;
2343    -- bug fix 6959362 ends
2344 
2345   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
2346     Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2347      '------------------> p_outstanding = '
2348         ||to_char(p_outstanding)
2349         ||' p_ordered = '||to_char(p_ordered)
2350   ||' p_already_billed = '||to_char(p_already_billed));
2351   END IF;
2352 
2353   ----------------------------------------------------
2354   -- Decide if overbilled
2355   ----------------------------------------------------
2356   -- Bug 562898
2357   -- Overbill flag should be Y is l_quantity_outstanding =0
2358   IF (p_po_line_matching_basis = 'QUANTITY') THEN
2359      IF ((p_outstanding - p_quantity_invoiced) <= 0) THEN
2360     P_overbilled := 'Y';
2361   ELSE
2362     P_overbilled := 'N';
2363   END IF;
2364   ELSIF (p_po_line_matching_basis = 'AMOUNT') THEN
2365      IF ((p_outstanding - p_amount_invoiced) <= 0) THEN
2366         P_overbilled := 'Y';
2367      ELSE
2368         P_overbilled := 'N';
2369      END IF;
2370   END IF;
2371 
2372   RETURN(TRUE);
2373 
2374   EXCEPTION
2375     WHEN OTHERS THEN
2376     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
2377       Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
2378     END IF;
2379 
2380     IF (SQLCODE < 0) THEN
2381       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
2382         Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,SQLERRM);
2383       END IF;
2384     END IF;
2385 
2386     RETURN (FALSE);
2387 
2388 END get_overbill_for_po_line;
2389 
2390 
2391 FUNCTION pa_flexbuild (
2392           p_invoice_rec                 IN
2393              AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
2394           p_invoice_lines_rec           IN OUT NOCOPY
2395              AP_IMPORT_INVOICES_PKG.r_line_info_rec,
2396           p_accounting_date             IN            DATE,
2397           p_pa_installed                IN            VARCHAR2,
2398           p_employee_id                 IN            NUMBER,
2399           p_base_currency_code          IN            VARCHAR2,
2400           p_chart_of_accounts_id        IN            NUMBER,
2401           p_default_last_updated_by     IN            NUMBER,
2402           p_default_last_update_login   IN            NUMBER,
2403           p_pa_default_dist_ccid        OUT NOCOPY    NUMBER,
2404           p_pa_concatenated_segments    OUT NOCOPY    VARCHAR2,
2405           p_current_invoice_status      OUT NOCOPY    VARCHAR2,
2406           p_calling_sequence            IN            VARCHAR2)
2407 RETURN BOOLEAN
2408 IS
2409   pa_flexbuild_failure         EXCEPTION;
2410   l_current_invoice_status     VARCHAR2(1) := 'Y';
2411   user_id                      NUMBER;
2412   procedure_billable_flag      VARCHAR2(60) := '';
2413   l_msg_application            VARCHAR2(25);
2414   l_msg_type                   VARCHAR2(25);
2415   l_msg_token1                 VARCHAR2(30);
2416   l_msg_token2                 VARCHAR2(30);
2417   l_msg_token3                 VARCHAR2(30);
2418   l_msg_count                  NUMBER;
2419   l_msg_data                   VARCHAR2(500);
2420   l_concat_ids                 VARCHAR2(200);
2421   -- CHANGES FOR BUG - 3657665 ** STARTS **
2422   --l_errmsg                     VARCHAR2(200);
2423   l_errmsg                     VARCHAR2(2000);
2424   -- CHANGES FOR BUG - 3657665 ** ENDS   **
2425   l_concat_descrs              VARCHAR2(500);
2426   l_concat_segs                VARCHAR2(2000);
2427   current_calling_sequence     VARCHAR2(2000);
2428   debug_info                   VARCHAR2(500);
2429   l_sys_link_function          VARCHAR2(2); --Bugfix:5725904
2430 
2431 BEGIN
2432 
2433   -- Update the calling sequence
2434 
2435   current_calling_sequence :=
2436     'AP_IMPORT_UTILITIES_PKG.pa_flexbuild<-'||P_calling_sequence;
2437 
2438   ----------------------------------------------------------------------------
2439   -- Step 1
2440   ----------------------------------------------------------------------------
2441 
2442   debug_info := '(PA Flexbuild 1) Check for PA installation and Project Info';
2443   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
2444     Print(AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
2445   END IF;
2446 
2447   IF (p_pa_installed = 'Y' AND
2448       p_invoice_lines_rec.project_id is not null) THEN
2449 
2450     -- We only care to VAlidate Transactions and flexbuild if PA is
2451     -- installed and there is a project_id; that is, the invoice is
2452     -- project-related.
2453 
2454     debug_info := '(PA Flexbuild 1) Get User Id';
2455     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
2456       Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
2457     END IF;
2458 
2459     user_id := to_number(FND_GLOBAL.USER_ID);
2460 
2461     debug_info := '(PA Flexbuild 1) PA_TRANSACTIONS_PUB.VALIDATE_TRANSACTION';
2462     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2463       Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
2464     END IF;
2465 
2466     --bugfix:5725904
2467     If (p_invoice_rec.invoice_type_lookup_code ='EXPENSE REPORT') Then
2468         l_sys_link_function :='ER' ;
2469     Else
2470         l_sys_link_function :='VI' ;
2471     End if;
2472 
2473     PA_TRANSACTIONS_PUB.VALIDATE_TRANSACTION(
2474     X_PROJECT_ID         => p_invoice_lines_rec.project_id,
2475     X_TASK_ID            => p_invoice_lines_rec.task_id,
2476     X_EI_DATE            => p_invoice_lines_rec.expenditure_item_date,
2477     X_EXPENDITURE_TYPE   => p_invoice_lines_rec.expenditure_type,
2478     X_NON_LABOR_RESOURCE => NULL,
2479     X_PERSON_ID          => p_employee_id,
2480     X_QUANTITY           => '1',
2481     X_DENOM_CURRENCY_CODE=> p_invoice_rec.invoice_currency_code,
2482     X_ACCT_CURRENCY_CODE => p_base_currency_code,
2483     X_DENOM_RAW_COST     => p_invoice_lines_rec.amount,
2484     X_ACCT_RAW_COST      => p_invoice_lines_rec.base_amount,
2485     X_ACCT_RATE_TYPE     => p_invoice_rec.exchange_rate_type,
2486     X_ACCT_RATE_DATE     => p_invoice_rec.exchange_date,
2487     X_ACCT_EXCHANGE_RATE => p_invoice_rec.exchange_rate,
2488     X_TRANSFER_EI        => null,
2489     X_INCURRED_BY_ORG_ID => p_invoice_lines_rec.expenditure_organization_id,
2490     X_NL_RESOURCE_ORG_ID => null,
2491     X_TRANSACTION_SOURCE => l_sys_link_function,--bug2853287 --bug:5725904
2492     X_CALLING_MODULE     => 'APXIIMPT',
2493     X_VENDOR_ID          => p_invoice_rec.vendor_id,
2494     X_ENTERED_BY_USER_ID => user_id,
2495     X_ATTRIBUTE_CATEGORY => p_invoice_lines_rec.attribute_category,
2496     X_ATTRIBUTE1         => p_invoice_lines_rec.attribute1,
2497     X_ATTRIBUTE2         => p_invoice_lines_rec.attribute2,
2498     X_ATTRIBUTE3         => p_invoice_lines_rec.attribute3,
2499     X_ATTRIBUTE4         => p_invoice_lines_rec.attribute4,
2500     X_ATTRIBUTE5         => p_invoice_lines_rec.attribute5,
2501     X_ATTRIBUTE6         => p_invoice_lines_rec.attribute6,
2502     X_ATTRIBUTE7         => p_invoice_lines_rec.attribute7,
2503     X_ATTRIBUTE8         => p_invoice_lines_rec.attribute8,
2504     X_ATTRIBUTE9         => p_invoice_lines_rec.attribute9,
2505     X_ATTRIBUTE10        => p_invoice_lines_rec.attribute10,
2506     X_ATTRIBUTE11        => p_invoice_lines_rec.attribute11,
2507     X_ATTRIBUTE12        => p_invoice_lines_rec.attribute12,
2508     X_ATTRIBUTE13        => p_invoice_lines_rec.attribute13,
2509     X_ATTRIBUTE14        => p_invoice_lines_rec.attribute14,
2510     X_ATTRIBUTE15        => p_invoice_lines_rec.attribute15,
2511     X_MSG_APPLICATION    => l_msg_application,  -- IN OUT
2512     X_MSG_TYPE           => l_msg_type,    -- OUT NOCOPY
2513     X_MSG_TOKEN1         => l_msg_token1,  -- OUT NOCOPY
2514     X_MSG_TOKEN2         => l_msg_token2,  -- OUT NOCOPY
2515     X_MSG_TOKEN3         => l_msg_token3,  -- OUT NOCOPY
2516     X_MSG_COUNT          => l_msg_count,  -- OUT NOCOPY
2517     X_MSG_DATA           => l_msg_data,    -- OUT NOCOPY
2518     X_BILLABLE_FLAG      => procedure_billable_flag ,       -- OUT NOCOPY
2519     P_Document_Type      => p_invoice_rec.invoice_type_lookup_code,
2520     P_Document_Line_Type => p_invoice_lines_rec.line_type_lookup_code,
2521     P_SYS_LINK_FUNCTION  => 'VI'); -- Added for bug2714409
2522 
2523     IF (l_msg_data IS NOT NULL) THEN
2524       debug_info :=
2525           '(PA Flexbuild 1) PA_TRANSACTIONS_PUB.VALIDATE_TRANSACTION '||
2526           'Failed :Insert Rejection';
2527       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
2528         Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
2529       END IF;
2530 
2531       -- Bug 5214592 . Added the debug message.
2532       debug_info := SUBSTR(l_msg_data,1,80);
2533       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
2534         Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
2535       END IF;
2536 
2537 
2538       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
2539           AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
2540           p_invoice_lines_rec.invoice_line_id,
2541           'PA FLEXBUILD FAILED',
2542           p_default_last_updated_by,
2543           p_default_last_update_login,
2544           current_calling_sequence) <> TRUE) THEN
2545             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
2546               Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2547                'insert_rejections<- '||current_calling_sequence);
2548             END IF;
2549             RAISE pa_flexbuild_failure;
2550       END IF;
2551 
2552       l_current_invoice_status := 'N';
2553       p_current_invoice_status := l_current_invoice_status;
2554       RETURN (TRUE);
2555 
2556     END IF; -- l_msg_data is not null
2557 
2558     --------------------------------------------------------------------------
2559     -- Step 2 - Flexbuild
2560     --------------------------------------------------------------------------
2561 
2562     debug_info := '(PA Flexbuild 2) Call for flexbuilding';
2563     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
2564       Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
2565       Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2566         '------------> '
2567         ||' P_CHART_OF_ACCOUNTS_ID = '||to_char(P_CHART_OF_ACCOUNTS_ID)
2568         ||' PROJECT_ID = '||to_char(P_invoice_lines_rec.PROJECT_ID)
2569         ||' TASK_ID = '||to_char(P_invoice_lines_rec.TASK_ID)
2570         ||' award_ID = '||to_char(P_invoice_lines_rec.AWARD_ID)
2571         ||' EXPENDITURE_TYPE = '||P_invoice_lines_rec.EXPENDITURE_TYPE
2572         ||' EXPENDITURE_ORGANIZATION_ID = '
2573         ||to_char(P_invoice_lines_rec.EXPENDITURE_ORGANIZATION_ID)
2574         ||' VENDOR_ID = '||to_char(P_invoice_rec.VENDOR_ID)
2575         ||' procedure_billable_flag= '||procedure_billable_flag);
2576     END IF;
2577 
2578     -- Flexbuild using Workflow.
2579 
2580     debug_info :=
2581        '(PA Flexbuild 2) Call pa_acc_gen_wf_pkg.ap_inv_generate_account '||
2582        'for flexbuilding';
2583     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2584       Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
2585     END IF;
2586 
2587     IF ( NOT pa_acc_gen_wf_pkg.ap_inv_generate_account (
2588         p_project_id              => p_invoice_lines_rec.project_id,
2589         p_task_id                 => p_invoice_lines_rec.task_id,
2590         p_award_id                => p_invoice_lines_rec.award_id,
2591         --replacing p_award_id in place of X_AWARD_PSET_ID for bug#8474307
2592         p_expenditure_type        => p_invoice_lines_rec.expenditure_type,
2593         p_vendor_id               => P_invoice_rec.VENDOR_ID,
2594         p_expenditure_organization_id =>
2595                        P_invoice_lines_rec.EXPENDITURE_ORGANIZATION_ID,
2596         p_expenditure_item_date       =>
2597                        P_invoice_lines_rec.EXPENDITURE_ITEM_DATE,
2598         p_billable_flag           => procedure_billable_flag,
2599         p_chart_of_accounts_id    => P_CHART_OF_ACCOUNTS_ID,
2600         p_accounting_date         => P_ACCOUNTING_DATE,
2601         P_ATTRIBUTE_CATEGORY      => P_invoice_rec.ATTRIBUTE_CATEGORY,
2602         P_ATTRIBUTE1              => P_invoice_rec.ATTRIBUTE1,
2603         P_ATTRIBUTE2              => P_invoice_rec.ATTRIBUTE2,
2604         P_ATTRIBUTE3              => P_invoice_rec.ATTRIBUTE3,
2605         P_ATTRIBUTE4              => P_invoice_rec.ATTRIBUTE4,
2606         P_ATTRIBUTE5              => P_invoice_rec.ATTRIBUTE5,
2607         P_ATTRIBUTE6              => P_invoice_rec.ATTRIBUTE6,
2608         P_ATTRIBUTE7              => P_invoice_rec.ATTRIBUTE7,
2609         P_ATTRIBUTE8              => P_invoice_rec.ATTRIBUTE8,
2610         P_ATTRIBUTE9              => P_invoice_rec.ATTRIBUTE9,
2611         P_ATTRIBUTE10             => P_invoice_rec.ATTRIBUTE10,
2612         P_ATTRIBUTE11             => P_invoice_rec.ATTRIBUTE11,
2613         P_ATTRIBUTE12             => P_invoice_rec.ATTRIBUTE12,
2614         P_ATTRIBUTE13             => P_invoice_rec.ATTRIBUTE13,
2615         P_ATTRIBUTE14             => P_invoice_rec.ATTRIBUTE14,
2616         P_ATTRIBUTE15             => P_invoice_rec.ATTRIBUTE15,
2617         P_DIST_ATTRIBUTE_CATEGORY => p_invoice_lines_rec.attribute_category,
2618         P_DIST_ATTRIBUTE1         => p_invoice_lines_rec.attribute1,
2619         P_DIST_ATTRIBUTE2         => p_invoice_lines_rec.attribute2,
2620         P_DIST_ATTRIBUTE3         => p_invoice_lines_rec.attribute3,
2621         P_DIST_ATTRIBUTE4         => p_invoice_lines_rec.attribute4,
2622         P_DIST_ATTRIBUTE5         => p_invoice_lines_rec.attribute5,
2623         P_DIST_ATTRIBUTE6         => p_invoice_lines_rec.attribute6,
2624         P_DIST_ATTRIBUTE7         => p_invoice_lines_rec.attribute7,
2625         P_DIST_ATTRIBUTE8         => p_invoice_lines_rec.attribute8,
2626         P_DIST_ATTRIBUTE9         => p_invoice_lines_rec.attribute9,
2627         P_DIST_ATTRIBUTE10        => p_invoice_lines_rec.attribute10,
2628         P_DIST_ATTRIBUTE11        => p_invoice_lines_rec.attribute11,
2629         P_DIST_ATTRIBUTE12        => p_invoice_lines_rec.attribute12,
2630         P_DIST_ATTRIBUTE13        => p_invoice_lines_rec.attribute13,
2631         P_DIST_ATTRIBUTE14        => p_invoice_lines_rec.attribute14,
2632         P_DIST_ATTRIBUTE15        => p_invoice_lines_rec.attribute15,
2633         x_return_ccid             => P_PA_DEFAULT_DIST_CCID, --OUT
2634         x_concat_segs             => l_concat_segs,   -- OUT NOCOPY
2635         x_concat_ids              => l_concat_ids,    -- OUT NOCOPY
2636         x_concat_descrs           => l_concat_descrs, -- OUT NOCOPY
2637         x_error_message           => l_errmsg,        -- OUT NOCOPY
2638         p_input_ccid		      => p_invoice_lines_rec.dist_code_combination_id)) THEN  /* IN for bug#9010924 */
2639 
2640       -- Show error message
2641 
2642       -- CHANGES FOR BUG - 3657665 ** STARTS **
2643       -- Need to encode the message and then print the value for the same returned by PA.
2644          fnd_message.set_encoded(l_errmsg);
2645          l_errmsg := fnd_message.get;
2646       -- CHANGES FOR BUG - 3657665 ** ENDS   **
2647 
2648       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
2649         Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2650           '------------>  l_errmsg '|| l_errmsg);
2651       END IF;
2652 
2653       -- REJECT here
2654 
2655       debug_info :=
2656         '(PA Flexbuild 2) pa_acc_gen_wf_pkg.ap_inv_generate_account '||
2657         'Failed :Insert Rejection';
2658       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
2659         Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
2660       END IF;
2661 
2662       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
2663            AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
2664            p_invoice_lines_rec.invoice_line_id,
2665            'PA FLEXBUILD FAILED',
2666            p_default_last_updated_by,
2667            p_default_last_update_login,
2668            current_calling_sequence) <> TRUE) THEN
2669 
2670         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
2671           Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2672             'insert_rejections<- '||current_calling_sequence);
2673         END IF;
2674         RAISE pa_flexbuild_failure;
2675       END IF;
2676 
2677       l_current_invoice_status   := 'N';
2678       P_PA_CONCATENATED_SEGMENTS := l_concat_segs;
2679       p_current_invoice_status   := l_current_invoice_status;
2680 
2681       RETURN (TRUE);
2682 
2683     END IF; -- If not pa generate account
2684 
2685     debug_info := '(PA Flexbuild 2) Return Concatenated Segments';
2686     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
2687       Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
2688     END IF;
2689 
2690     P_PA_CONCATENATED_SEGMENTS := l_concat_segs;
2691     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
2692       Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2693          '------------>  p_pa_default_dist_ccid = '
2694          || to_char(p_pa_default_dist_ccid)
2695          ||' p_pa_concatenated_segments = '||p_pa_concatenated_segments
2696          ||' l_concat_segs = '||l_concat_segs
2697          ||' l_concat_ids = '||l_concat_ids
2698          ||' procedure_billable_flag = '||procedure_billable_flag
2699          ||' l_concat_descrs = '||l_concat_descrs
2700          ||' l_errmsg = '||l_errmsg);
2701     END IF;
2702   END IF; -- pa installed and project id is not null
2703 
2704   debug_info := '(PA Flexbuild 3) Return Invoice Status';
2705   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
2706     Print(AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
2707   END IF;
2708 
2709   p_current_invoice_status := l_current_invoice_status;
2710   RETURN(TRUE);
2711 
2712 EXCEPTION
2713   WHEN OTHERS THEN
2714     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
2715       Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
2716     END IF;
2717     IF (SQLCODE < 0) THEN
2718       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
2719         Print(AP_IMPORT_INVOICES_PKG.g_debug_switch, SQLERRM);
2720       END IF;
2721     END IF;
2722 
2723     RETURN (FALSE);
2724 END pa_flexbuild;
2725 
2726 /*==========================================================================
2727  Private Function: Get Document Sequence
2728  Note: Method has to be automatic!
2729        Mode 1: Simple Manual Entry without Audit
2730                (Use Voucher Num, Seq Num "Not Used")
2731        Mode 3: Auto voucher numbering with Audit
2732                (Use doc_sequence_value, Seq Num 'P','A'))
2733        Mode 3 will override Mode 1
2734        Mode 2 Audited Manual Entry is not supported
2735 
2736  The following is a brief description of the implementation of Document
2737  Sequential Numbering in Invoice Open Interface (R11 only)
2738 
2739  The two modes for numbering can be:
2740    - Simple Manual Entry without Audit: Any value entered in the column
2741      AP_INVOICES_INTERFACE.VOUCHER_NUM will be inserted in AP_INVOICES.
2742      VOUCHER_NUM without validation.
2743 
2744    - Auto Voucher Numbering with Audit: A value will be obtained
2745      automatically for the record being imported and will be populated in
2746      AP_INVOICES. DOC_SEQUENCE_VALUE. Also audit information would be inserted
2747      into the audit table.
2748 
2749  The latter mode will always override the first one.
2750 
2751  The logic for the five new rejections is as follows:
2752    - 'Category not needed' - 'Document sequential numbering is not used'.
2753    - 'Invalid Category' - 'Document category specified is not valid'.
2754    - 'Override Disabled' - 'Document Category Override Payables option
2755                             is disabled'
2756    - 'Invalid Assignment' - 'Invalid sequence assigned to specified document
2757                              category'
2758    - 'Invalid Sequence' - 'Could not retrieve document sequence value from
2759                            the given sequence'
2760 
2761    If the profile value for the "Sequential Numbering" option is "Not Used"
2762    and the user specifies a document category then the invoice would be
2763    rejected for 'Category not needed'.
2764 
2765    If the profile value is "Partial" or "Always" and
2766    the payables option of Invoice Document Category override is
2767    "Yes" then the user can specify  the document category, else the
2768    invoice will be rejected for 'Override Disabled', if the user populates
2769    AP_INVOICES_INTERFACE.DOC_CATEGORY_CODE (and override is "No").
2770 
2771    If the profile value is "Always" and no document category is specified
2772    by the user, then "Standard Invoices" category will be used for
2773    standard invoices and "Credit Memo Invoices" category will be used
2774    for credits.
2775    We assume that a valid automatic sequence exists for such categories.
2776 
2777    If the payables option of Invoice Document Category override is
2778    "Yes" and the user specifies any of the following categories then
2779    the invoice is rejected for 'Invalid Category'.
2780 
2781                                        ('INT INV',
2782                                         'MIX INV',
2783                                         'DBM INV',
2784                                         'CHECK PAY',
2785                                         'CLEAR PAY',
2786                                         'EFT PAY',
2787                                         'FUTURE PAY',
2788                                         'MAN FUTURE PAY',
2789  ... 8995762 -- this now accepted ...   --'PREPAY INV',
2790                                         'REC INV',
2791                                         'WIRE PAY',
2792                                         'EXP REP INV')
2793 
2794    If the document category is "Standard Invoices" and the invoice amount
2795    is less than zero, or, the document category is "Credit Memo Invoices"
2796    and the invoice amount is greated than zero then the invoice will be
2797    rejected for 'Invalid Category'.
2798 
2799    The document category specified should be valid in
2800    FND_DOC_SEQUENCE_CATEGORIES for AP_INVOICES or AP_INVOICES_ALL
2801    table. If not then the invoice will be rejected for 'Invalid Category'.
2802 
2803    If the document category is valid then Check the status of the
2804    sequence assigned to this category.The sequence should be automatic
2805    and active. If not then reject for 'Invalid Assignment'.
2806 
2807    If the sequence is valid then get the next value for the assigned
2808    sequence. If there is an error in retrieving the nextval then reject
2809    for 'Invalid Sequence'. This should not happen in the ideal scenario.
2810 ============================================================================*/
2811 
2812 FUNCTION get_doc_sequence(
2813           p_invoice_rec                 IN OUT
2814                  AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
2815           p_inv_doc_cat_override        IN            VARCHAR2,
2816           p_set_of_books_id             IN            NUMBER,
2817           p_sequence_numbering          IN            VARCHAR2,
2818           p_default_last_updated_by     IN            NUMBER,
2819           p_default_last_update_login   IN            NUMBER,
2820           p_db_sequence_value              OUT NOCOPY NUMBER,
2821           p_db_seq_name                    OUT NOCOPY VARCHAR2,
2822           p_db_sequence_id                 OUT NOCOPY NUMBER,
2823           p_current_invoice_status         OUT NOCOPY VARCHAR2,
2824           p_calling_sequence            IN            VARCHAR2)
2825 RETURN BOOLEAN
2826 IS
2827   get_doc_seq_failure       EXCEPTION;
2828   l_name                    VARCHAR2(80);
2829   l_doc_category_code
2830       ap_invoices.doc_category_code%TYPE := p_invoice_rec.doc_category_code;
2831   l_application_id          NUMBER;
2832   l_doc_seq_ass_id          NUMBER;
2833   l_current_invoice_status  VARCHAR2(1) := 'Y';
2834   current_calling_sequence  VARCHAR2(2000);
2835   debug_info                VARCHAR2(500);
2836   l_return_code             NUMBER;
2837 
2838 BEGIN
2839   -- Update the calling sequence
2840 
2841   current_calling_sequence := 'get_doc_sequence<-'||P_calling_sequence;
2842 
2843   IF ((p_sequence_numbering = 'N') AND
2844       (p_invoice_rec.doc_category_code IS NOT NULL)) THEN
2845     --------------------------------------------------------------------------
2846     -- Step 1
2847     -- p_sequence_numbering should be in ('A','P')
2848     -- Do not use seq num if N (Not Used)
2849     -- Reject if Doc category provided is provided by user in this case.
2850     --------------------------------------------------------------------------
2851 
2852     debug_info := '(Get Doc Sequence 1) Reject Seq Num is not enabled ';
2853     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
2854       Print( AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
2855     END IF;
2856 
2857     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
2858             'AP_INVOICE_INTERFACE',
2859             p_invoice_rec.invoice_id,
2860             'DOC CAT NOT REQD',
2861             p_default_last_updated_by,
2862             p_default_last_update_login,
2863             current_calling_sequence) <> TRUE) THEN
2864       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
2865         Print( AP_IMPORT_INVOICES_PKG.g_debug_switch,
2866           'insert_rejections<- '||current_calling_sequence);
2867       END IF;
2868       RAISE get_doc_seq_failure;
2869       l_current_invoice_status := 'N';
2870       p_current_invoice_status := l_current_invoice_status;
2871     END IF;
2872     RETURN (TRUE);
2873 
2874   ELSIF (p_sequence_numbering IN ('A','P')) THEN
2875 
2876     -------------------------------------------------------------------------
2877     -- Step 2
2878     -- Seq Numbering is enabled process doc category
2879     -------------------------------------------------------------------------
2880     IF (p_invoice_rec.doc_category_code IS NOT NULL) THEN
2881       debug_info := '(Get Doc Sequence 2) Seq Numbering is enabled AND doc_cat'
2882                     || ' is not null  process doc category  ';
2883       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
2884         Print(AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
2885       END IF;
2886 
2887       IF (p_inv_doc_cat_override = 'Y') THEN
2888         ---------------------------------------------------------------------
2889         -- Step 2.1
2890         --  Doc Category Override is allowed
2891         ---------------------------------------------------------------------
2892         debug_info := '(Get Doc Sequence 2.1) Doc Category Override allowed';
2893         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
2894           Print(AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
2895         END IF;
2896 
2897         -- Reject if category is a seeded one and not allowed in this case
2898 
2899 	--Bug: 4410499, Added the support for EXP REP INV doc category type
2900 
2901 	-- Contract Payments: Modified the below IF condition to add logic for
2902 	-- 'Prepayment' type invoices.
2903 
2904         IF (  ( p_invoice_rec.doc_category_code = 'STD INV' and
2905 	        p_invoice_rec.invoice_type_lookup_code <> 'STANDARD')
2906             OR
2907               ( p_invoice_rec.doc_category_code = 'PAY REQ INV' and
2908                 p_invoice_rec.invoice_type_lookup_code <> 'PAYMENT REQUEST')
2909             OR
2910               ( p_invoice_rec.doc_category_code = 'CRM INV' and
2911                 p_invoice_rec.invoice_type_lookup_code <> 'CREDIT')
2912             -- Bug 7299826: Added support for Debit Memos
2913             OR
2914               ( p_invoice_rec.doc_category_code = 'DBM INV' and
2915                 p_invoice_rec.invoice_type_lookup_code <> 'DEBIT')
2916             OR
2917 	      ( p_invoice_rec.doc_category_code = 'PREPAY INV' and
2918 	        p_invoice_rec.invoice_type_lookup_code <> 'PREPAYMENT')
2919             OR
2920 	      ( p_invoice_rec.doc_category_code = 'EXP REP INV' and
2921 	        p_invoice_rec.invoice_type_lookup_code <> 'EXPENSE REPORT')
2922 
2923             OR
2924               ( p_invoice_rec.doc_category_code IN (
2925                                   'INT INV',
2926                                   'MIX INV',
2927                                   --'DBM INV', -- bug 7299826
2928                                   'CHECK PAY',
2929                                   'CLEAR PAY',
2930                                   'EFT PAY',
2931                                   'FUTURE PAY',
2932                                   'MAN FUTURE PAY',
2933                                   --'PREPAY INV',  .. B 8995762
2934                                   'REC INV',
2935                                   'WIRE PAY'))) THEN
2936 
2937           debug_info := '(Get Doc Sequence 2.1)  Reject->category seeded one';
2938           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
2939             Print(AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
2940           END IF;
2941 
2942           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
2943                   AP_IMPORT_INVOICES_PKG.g_invoices_table,
2944                    p_invoice_rec.invoice_id,
2945                    'INVALID DOC CATEGORY',
2946                    p_default_last_updated_by,
2947                    p_default_last_update_login,
2948                    current_calling_sequence) <> TRUE) THEN
2949 
2950             debug_info := 'insert_rejections<- '||current_calling_sequence;
2951             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
2952                Print(AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
2953             END IF;
2954             RAISE get_doc_seq_failure;
2955           END IF;
2956           l_current_invoice_status := 'N';
2957         END IF;  -- end of seeded category check
2958 
2959         -----------------------------------------------------------------------
2960         -- Step 2.2
2961         -- Validate Doc Category
2962         -----------------------------------------------------------------------
2963         debug_info := '(Get Doc Sequence 2.2)  Check Doc Category ' ||
2964                       'exists and valid';
2965         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
2966           Print(AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
2967         END IF;
2968 
2969         BEGIN
2970           SELECT name, application_id
2971             INTO l_name, l_application_id
2972             FROM fnd_doc_sequence_categories
2973            WHERE code = p_invoice_rec.doc_category_code
2974              AND table_name IN ('AP_INVOICES','AP_INVOICES_ALL');
2975         EXCEPTION
2976           WHEN NO_DATA_FOUND THEN
2977             debug_info := debug_info || 'Reject->Doc cat does not exist';
2978             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
2979               Print(AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
2980             END IF;
2981             IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
2982                     AP_IMPORT_INVOICES_PKG.g_invoices_table,
2983                     p_invoice_rec.invoice_id,
2984                     'INVALID DOC CATEGORY',
2985                     p_default_last_updated_by,
2986                     p_default_last_update_login,
2987                     current_calling_sequence) <> TRUE) THEN
2988 
2989               debug_info := 'insert_rejections<- '||current_calling_sequence;
2990               IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
2991                 Print(AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
2992               END IF;
2993               RAISE get_doc_seq_failure;
2994             END IF;
2995             l_current_invoice_status := 'N';
2996           END;
2997       ELSE  -- override is no
2998         -----------------------------------------------------------------------
2999         -- Step 3
3000         -- override <> 'Y'
3001         -- Reject Override not allowed
3002         -----------------------------------------------------------------------
3003 
3004         debug_info := '(Get Doc Sequence 3) Reject->cat override not allowed';
3005         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
3006           Print(AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
3007         END IF;
3008 
3009         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
3010                 AP_IMPORT_INVOICES_PKG.g_invoices_table,
3011                 p_invoice_rec.invoice_id,
3012                 'OVERRIDE DISALLOWED',
3013                 p_default_last_updated_by,
3014                 p_default_last_update_login,
3015                 current_calling_sequence) <> TRUE) THEN
3016           debug_info := 'insert_rejections<- '||current_calling_sequence;
3017           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
3018             Print(AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
3019           END IF;
3020           RAISE get_doc_seq_failure;
3021         END IF;
3022         l_current_invoice_status := 'N';
3023       END IF; -- end of check l_doc_cat_override = 'Y'
3024     ELSIF ( (p_invoice_rec.doc_category_code IS NULL) AND
3025             (p_sequence_numbering in ('A','P'))) THEN  --Introduced 'P' for bug#9088303
3026       ---------------------------------------------------------------------
3027       -- Step 4
3028       -- Use Default Doc Category
3029       ---------------------------------------------------------------------
3030       debug_info := '(Get Doc Sequence 4) Use Default Category, Seq:Always';
3031       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
3032         Print(AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
3033       END IF;
3034 
3035       --Contract Payments: Modified the IF condition to look at the invoice_type
3036       --rather than the sign of the invoice_amount in deciding which category to
3037       --apply, and also added the logic for 'PREPAYMENT' invoices.
3038 
3039       IF (p_invoice_rec.invoice_type_lookup_code = 'STANDARD') THEN
3040         l_doc_category_code := 'STD INV';
3041       ELSIF (p_invoice_rec.invoice_type_lookup_code = 'PAYMENT REQUEST') THEN
3042         l_doc_category_code := 'PAY REQ INV';
3043       ELSIF (p_invoice_rec.invoice_type_lookup_code = 'CREDIT') THEN
3044         l_doc_category_code := 'CRM INV';
3045       -- Bug 7299826
3046       ELSIF (p_invoice_rec.invoice_type_lookup_code = 'DEBIT') THEN
3047         l_doc_category_code := 'DBM INV';
3048       -- Bug 7299826 End
3049       ELSIF (p_invoice_rec.invoice_type_lookup_code = 'PREPAYMENT') THEN
3050         l_doc_category_code := 'PREPAY INV';
3051       --Bug8408197
3052       ELSIF (p_invoice_rec.invoice_type_lookup_code = 'EXPENSE REPORT') THEN
3053         l_doc_category_code := 'EXP REP INV';
3054       --End of Bug8408197
3055       END IF;
3056 
3057       debug_info := '-----> l_doc_category_code = ' || l_doc_category_code ;
3058       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
3059         Print(AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
3060       END IF;
3061     END IF; -- end of check Doc_category_code is not null
3062 
3063     ---------------------------------------------------------------------------
3064     -- Step 5
3065     -- Get Doc Sequence Number
3066     ---------------------------------------------------------------------------
3067 
3068     IF ((l_doc_category_code IS NOT NULL) AND
3069         (l_current_invoice_status = 'Y')) THEN
3070 
3071        debug_info := '(Get Doc Sequence 5) Valid Category ->Check if valid ' ||
3072                      ' Sequence assigned';
3073        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
3074         Print(AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
3075        END IF;
3076 
3077        BEGIN
3078            SELECT SEQ.DB_SEQUENCE_NAME,
3079                 SEQ.DOC_SEQUENCE_ID,
3080                 SA.doc_sequence_assignment_id
3081            INTO p_db_seq_name,
3082                 p_db_sequence_id ,
3083                 l_doc_seq_ass_id
3084            FROM FND_DOCUMENT_SEQUENCES SEQ,
3085                 FND_DOC_SEQUENCE_ASSIGNMENTS SA
3086           WHERE SEQ.DOC_SEQUENCE_ID        = SA.DOC_SEQUENCE_ID
3087             AND SA.APPLICATION_ID          = 200
3088             AND SA.CATEGORY_CODE           = l_doc_category_code
3089             AND NVL(SA.METHOD_CODE,'A')    = 'A'
3090             AND NVL(SA.SET_OF_BOOKS_ID,
3091                     p_set_of_books_id)     = p_set_of_books_id   -- 3817492
3092             AND NVL(p_invoice_rec.gl_date,
3093                     AP_IMPORT_INVOICES_PKG.g_inv_sysdate) between
3094                   SA.START_DATE and
3095                   NVL(SA.END_DATE, TO_DATE('31/12/4712','DD/MM/YYYY'));
3096 
3097         -- Bug 5064959 starts. Check for inconsistent Voucher info. When a valid sequence exists ,
3098         -- user should not manually enter the voucher number.
3099 
3100        If (p_invoice_rec.voucher_num IS NOT NULL) Then
3101 
3102           debug_info := '(Get Doc Sequence 5) Reject: Inconsistent Voucher Info';
3103           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
3104              Print(AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
3105           END IF;
3106 
3107            IF (AP_IMPORT_UTILITIES_PKG.insert_rejections( AP_IMPORT_INVOICES_PKG.g_invoices_table,
3108                 p_invoice_rec.invoice_id,
3109                 'INCONSISTENT VOUCHER INFO',
3110                 p_default_last_updated_by,
3111                 p_default_last_update_login,
3112                 current_calling_sequence) <> TRUE) THEN
3113              debug_info := 'insert_rejections<- '||current_calling_sequence;
3114              IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
3115                Print(AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
3116              END IF;
3117              RAISE get_doc_seq_failure;
3118 
3119           END IF;
3120 
3121           l_current_invoice_status := 'N';
3122 
3123       End If;
3124 
3125         -- Bug 5064959 ends.
3126 
3127        EXCEPTION
3128          WHEN NO_DATA_FOUND Then
3129 
3130            --bug5854731 starts.Added the below If clause
3131            --Only if the Sequenctial numbering option is 'Always Used',we raise the error.
3132          IF(p_sequence_numbering='A') THEN  --bug5854731.Only if the Sequenctial numbering op
3133               debug_info := '(Get Doc Sequence 5) Reject:Invalid Sequence' ||
3134                             'assignment';
3135              IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
3136                  Print(AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
3137              END IF;
3138 
3139              IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
3140                    AP_IMPORT_INVOICES_PKG.g_invoices_table,
3141                    p_invoice_rec.invoice_id,
3142                    'INVALID ASSIGNMENT',
3143                    p_default_last_updated_by,
3144                    p_default_last_update_login,
3145                    current_calling_sequence) <> TRUE) THEN
3146                    debug_info := 'insert_rejections<- '||current_calling_sequence;
3147                    IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
3148                    Print(AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
3149                    END IF;
3150                RAISE get_doc_seq_failure;
3151              END IF;
3152              l_current_invoice_status := 'N';
3153          END IF;  --end of p_sequence_numbering='A' bug5854731 ends
3154        END; -- end of the above BEGION
3155 
3156 
3157        IF (l_current_invoice_status = 'Y'
3158            and  p_db_sequence_id is NOT NULL) THEN --bug5854731.Added the AND clause.
3159            --Only if the sequence_id fetched from the step5 is not null,
3160            --we proceed forward to get the sequence value.
3161 
3162         ----------------------------------------------------------------------
3163         -- Step 6
3164         -- Get Doc Sequence Val
3165         ----------------------------------------------------------------------
3166         debug_info := '(Get Doc Sequence 6) Get Next Val';
3167         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
3168           Print(AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
3169         END IF;
3170 
3171         l_return_code := FND_SEQNUM.GET_SEQ_VAL(
3172                              200,
3173                              l_doc_category_code,
3174                              p_set_of_books_id,
3175                              'A',
3176                              NVL(p_invoice_rec.gl_date,
3177                                  AP_IMPORT_INVOICES_PKG.g_inv_sysdate),
3178                              p_db_sequence_value,
3179                              p_db_sequence_id ,
3180                              'N',
3181                              'N');
3182         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
3183           Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
3184               '-----------> l_doc_category_code = '|| l_doc_category_code
3185               || ' p_set_of_books_id = '||to_char(p_set_of_books_id)
3186               || ' p_db_sequence_id  = '||to_char(p_db_sequence_id )
3187               ||' p_db_seq_name = '||p_db_seq_name
3188               ||' p_db_sequence_value = '||to_char(p_db_sequence_value));
3189         END IF;
3190 
3191         IF ((p_db_sequence_value IS NULL) or (l_return_code <> 0)) THEN
3192           debug_info := '(Get Doc Sequence 7) Reject:Invalid Sequence';
3193           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
3194             Print(AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
3195           END IF;
3196 
3197           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
3198                   AP_IMPORT_INVOICES_PKG.g_invoices_table,
3199                   p_invoice_rec.invoice_id,
3200                   'INVALID SEQUENCE',
3201                   p_default_last_updated_by,
3202                   p_default_last_update_login,
3203                   current_calling_sequence) <> TRUE) THEN
3204             debug_info := 'insert_rejections<- '||current_calling_sequence;
3205             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
3206               Print(AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
3207             END IF;
3208             RAISE get_doc_seq_failure;
3209           END IF;
3210           l_current_invoice_status := 'N';
3211         END IF;  -- end of check l_return_code and seqval
3212       END IF; -- end of check l_current_invoice_status = 'Y' for step 6
3213     END IF; -- end of check l_current_invoice_status/doc_category_code
3214 
3215     -- Bug 5064959 starts. The validation for seq value should be done if the profile value is 'A' or 'P'.
3216 
3217      --Bug 7214515/7261280 Uncommented the code changes done in 6492341 and only commented
3218     -- length check condition
3219     -- Bug 6492431 The code is commented to remove the 9 digit restriction on doc_sequnce_number.
3220     --  if ( ( LENGTH( nvl(p_db_sequence_value,0)) > 9 ) or --Condition value changed from 8 to 9 for BUG 5950643
3221          If  ( TRANSLATE( p_db_sequence_value ,'x1234567890','x') IS NOT NULL) then
3222 
3223           debug_info := '(Get Doc Sequence 8) Reject: Invalid Voucher Number';
3224           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
3225              Print(AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
3226           END IF;
3227 
3228           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections( AP_IMPORT_INVOICES_PKG.g_invoices_table,
3229                 p_invoice_rec.invoice_id,
3230                 'INCONSISTENT VOUCHER INFO',
3231                 p_default_last_updated_by,
3232                 p_default_last_update_login,
3233                 current_calling_sequence) <> TRUE) THEN
3234              debug_info := 'insert_rejections<- '||current_calling_sequence;
3235              IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
3236                Print(AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
3237              END IF;
3238              RAISE get_doc_seq_failure;
3239 
3240           END IF;
3241          l_current_invoice_status := 'N';
3242        END IF;
3243 
3244    -- Bug 5064959 ends.
3245 
3246   END IF; -- p_sequence_numbering = 'N'
3247 
3248   p_invoice_rec.doc_category_code := l_doc_category_code;
3249   p_current_invoice_status := l_current_invoice_status;
3250 
3251   RETURN(TRUE);
3252 
3253 EXCEPTION
3254   WHEN OTHERS THEN
3255 
3256     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
3257       Print(
3258           AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
3259     END IF;
3260 
3261     IF (SQLCODE < 0) THEN
3262       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
3263         Print(
3264             AP_IMPORT_INVOICES_PKG.g_debug_switch, SQLERRM);
3265       END IF;
3266     END IF;
3267 
3268     RETURN (FALSE);
3269 END get_doc_sequence;
3270 
3271 /*===================================================================
3272   Private function: get_invoice_info
3273   Get some values for creating invoices from po_vendors,
3274   po_headers
3275   =================================================================== */
3276 
3277 FUNCTION get_invoice_info(
3278           p_invoice_rec                 IN OUT NOCOPY
3279               AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
3280           p_default_last_updated_by     IN            NUMBER,
3281           p_default_last_update_login   IN            NUMBER,
3282           p_pay_curr_invoice_amount        OUT NOCOPY NUMBER,
3283           p_payment_priority               OUT NOCOPY NUMBER,
3284           p_invoice_amount_limit           OUT NOCOPY NUMBER,
3285           p_hold_future_payments_flag      OUT NOCOPY VARCHAR2,
3286           p_supplier_hold_reason           OUT NOCOPY VARCHAR2,
3287           p_exclude_freight_from_disc      OUT NOCOPY VARCHAR2, /* bug 4931755 */
3288           p_calling_sequence            IN            VARCHAR2)
3289 RETURN BOOLEAN
3290 IS
3291   get_invoice_info_failure     EXCEPTION;
3292   debug_info                   VARCHAR2(500);
3293   current_calling_sequence     VARCHAR2(2000);
3294 BEGIN
3295   -- Update the calling sequence
3296 
3297   current_calling_sequence := 'get_invoice_info->'||P_calling_sequence;
3298 
3299   ----------------------------------------------------------------------------
3300   -- Step 1
3301   -- Calculate the invoice amount in payment currency
3302   ----------------------------------------------------------------------------
3303 
3304   debug_info := '(Get Invoice Info step 1) Calculate invoice amount in ' ||
3305                 'payment currency ';
3306   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
3307     Print(AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
3308   END IF;
3309 
3310   IF ( p_invoice_rec.payment_cross_rate is NOT NULL) THEN
3311           p_pay_curr_invoice_amount := gl_currency_api.convert_amount(
3312           p_invoice_rec.invoice_currency_code,
3313           p_invoice_rec.payment_currency_code,
3314           p_invoice_rec.payment_cross_rate_date,
3315           p_invoice_rec.payment_cross_rate_type,
3316           p_invoice_rec.invoice_amount);
3317 
3318   END IF;
3319 
3320   -----------------------------------------------------------------------------
3321   -- Step 2
3322   -- Get amount_applicable_to_discount
3323   -----------------------------------------------------------------------------
3324 
3325   debug_info := '(Get Invoice Info step 2) Get amt_applicable_to_discount ' ||
3326                 ' value if not given';
3327   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
3328     Print(AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
3329   END IF;
3330 
3331   p_invoice_rec.amount_applicable_to_discount :=
3332       NVL(p_invoice_rec.amount_applicable_to_discount,
3333           p_invoice_rec.invoice_amount);
3334 
3335   -----------------------------------------------------------------------------
3336   -- Step 3
3337   -- Get information from supplier site if null in invoice record or never
3338   -- read:
3339   --       payment_method_lookup_code     into invoice rec
3340   --       pay_group_lookup_code          into invoice rec
3341   --       accts_pay_code_combination_id  into invoice rec
3342   --       payment_priority               into OUT parameter
3343   --       invoice_amount_limit           into OUT parameter
3344   --       hold_future_payments_flag      into OUT parameter
3345   --       hold_reason                    into OUT parameter
3346   -----------------------------------------------------------------------------
3347 
3348   -- Payment Requests: Added the if condition for payment requests type invoices
3349   IF (p_invoice_rec.invoice_type_lookup_code = 'PAYMENT REQUEST') THEN
3350 
3351      debug_info := '(Get Invoice Info step 3) Get payment default info ';
3352      IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
3353        Print(AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
3354      END IF;
3355      BEGIN
3356 
3357        SELECT DECODE(p_invoice_rec.pay_group_lookup_code,
3358                      NULL,asp.vendor_pay_group_lookup_code,
3359                      p_invoice_rec.pay_group_lookup_code),
3360               DECODE(p_invoice_rec.accts_pay_code_combination_id, Null,
3361                      fsp.accts_pay_code_combination_id,
3362                      p_invoice_rec.accts_pay_code_combination_id),
3363               p_invoice_rec.payment_priority,
3364               NULL, --invoice_amount_limit,
3365               'N', --hold_future_payments_flag,
3366               NULL, --hold_reason
3367               'N'  -- exclude_freight_from_discount.bug 4931755
3368         INTO  p_invoice_rec.pay_group_lookup_code,
3369               p_invoice_rec.accts_pay_code_combination_id,
3370               p_payment_priority,
3371               p_invoice_amount_limit,
3372               p_hold_future_payments_flag,
3373               p_supplier_hold_reason,
3374               p_exclude_freight_from_disc
3375         FROM  ap_system_parameters asp,
3376               financials_system_parameters fsp
3377         WHERE asp.org_id = p_invoice_rec.org_id
3378           AND asp.org_id = fsp.org_id;
3379      EXCEPTION
3380          WHEN no_data_found THEN
3381            debug_info := debug_info || '->no data found in query';
3382            IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
3383              Print(
3384                  AP_IMPORT_INVOICES_PKG.g_debug_switch,
3385                  debug_info);
3386            END IF;
3387            RAISE get_invoice_info_failure;
3388      END;
3389 
3390   ELSE
3391 
3392      debug_info := '(Get Invoice Info step 3) Get supplier site default info ';
3393      IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
3394        Print(AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
3395      END IF;
3396      BEGIN
3397 
3398        SELECT DECODE(p_invoice_rec.pay_group_lookup_code,
3399                      NULL,pay_group_lookup_code,
3400                      p_invoice_rec.pay_group_lookup_code),
3401               DECODE(p_invoice_rec.accts_pay_code_combination_id, Null,
3402                      accts_pay_code_combination_id,
3403                      p_invoice_rec.accts_pay_code_combination_id),
3404               payment_priority,
3405               invoice_amount_limit,
3406               hold_future_payments_flag,
3407               hold_reason,
3408               NVL(exclude_freight_from_discount, 'N')  /*bug 4931755 */
3409          INTO p_invoice_rec.pay_group_lookup_code,
3410               p_invoice_rec.accts_pay_code_combination_id,
3411               p_payment_priority,
3412               p_invoice_amount_limit,
3413               p_hold_future_payments_flag,
3414               p_supplier_hold_reason,
3415               p_exclude_freight_from_disc
3416          FROM ap_supplier_sites_all
3417         WHERE vendor_id = p_invoice_rec.vendor_id
3418           AND vendor_site_id = p_invoice_rec.vendor_site_id;
3419      EXCEPTION
3420          WHEN no_data_found THEN
3421            debug_info := debug_info || '->no data found in query';
3422            IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
3423              Print(
3424                  AP_IMPORT_INVOICES_PKG.g_debug_switch,
3425                  debug_info);
3426            END IF;
3427            RAISE get_invoice_info_failure;
3428      END;
3429   END IF;
3430 
3431   -----------------------------------------------------------------------------
3432   -- Step 4
3433   -- Populate who columns if null
3434   -----------------------------------------------------------------------------
3435   debug_info := '(Get Invoice Info step 4) Get WHO columns ';
3436   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
3437     Print(AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
3438   END IF;
3439   p_invoice_rec.last_updated_by  :=
3440     NVL(p_invoice_rec.last_updated_by,p_default_last_updated_by);
3441   p_invoice_rec.last_update_login :=
3442     NVL(p_invoice_rec.last_update_login,NVL(p_default_last_update_login,
3443                                             p_default_last_updated_by));
3444   p_invoice_rec.created_by        :=
3445     NVL(p_invoice_rec.created_by,p_default_last_updated_by);
3446   p_invoice_rec.creation_date     :=
3447     NVL(p_invoice_rec.creation_date, AP_IMPORT_INVOICES_PKG.g_inv_sysdate);
3448   p_invoice_rec.last_update_date  :=
3449     NVL(p_invoice_rec.last_update_date, AP_IMPORT_INVOICES_PKG.g_inv_sysdate);
3450 
3451   RETURN(TRUE);
3452 EXCEPTION
3453   WHEN OTHERS then
3454     debug_info := debug_info || '->exception';
3455     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
3456       Print(AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
3457     END IF;
3458 
3459     IF (SQLCODE < 0) then
3460       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
3461         Print(AP_IMPORT_INVOICES_PKG.g_debug_switch, SQLERRM);
3462       END IF;
3463     END IF;
3464 
3465     RETURN (FALSE);
3466 
3467 END get_invoice_info;
3468 
3469 /*=========================================================================
3470 
3471   Function  Insert_Ap_Invoices
3472   Program Flow:
3473 
3474   =========================================================================*/
3475 -- Payment Request: Added p_needs_invoice_approval for payment request invoices
3476 FUNCTION insert_ap_invoices(
3477           p_invoice_rec                 IN OUT
3478                 AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
3479           p_base_invoice_id                OUT NOCOPY NUMBER,
3480           p_set_of_books_id             IN NUMBER,
3481           p_doc_sequence_id             IN
3482                 AP_INVOICES.doc_sequence_id%TYPE,
3483           p_doc_sequence_value          IN
3484                 AP_INVOICES.doc_sequence_value%TYPE,
3485           p_batch_id                    IN            AP_INVOICES.batch_id%TYPE,
3486           p_pay_curr_invoice_amount     IN            NUMBER,
3487           p_approval_workflow_flag      IN            VARCHAR2,
3488           p_needs_invoice_approval      IN            VARCHAR2,
3489 	      p_add_days_settlement_date    IN            NUMBER,  --bug 493011
3490           p_disc_is_inv_less_tax_flag   IN            VARCHAR2, --bug 4931755
3491           p_exclude_freight_from_disc   IN            VARCHAR2, --bug 4931755
3492           p_calling_sequence            IN            VARCHAR2)
3493 RETURN BOOLEAN
3494 IS
3495   l_invoice_id              NUMBER;
3496   debug_info                VARCHAR2(500);
3497   current_calling_sequence  VARCHAR2(2000);
3498   l_approval_ready_flag     VARCHAR2(1) := 'Y';
3499   l_wfapproval_status       VARCHAR2(30);
3500   --bugfix:4930111
3501   l_earliest_settlement_date DATE;
3502   l_attachments_count       NUMBER;
3503 
3504 BEGIN
3505   -- Update the calling sequence
3506 
3507   current_calling_sequence := 'insert_ap_invoices<-'||P_calling_sequence;
3508 
3509   -----------------------------------------------------------------------------
3510   -- Step 1
3511   -- get new invoice_id for base table ap_invoices
3512   -----------------------------------------------------------------------------
3513 
3514   debug_info := '(Insert ap invoices step 1) Get new invoice_id for base ' ||
3515                 'table ap_invoices';
3516   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
3517     Print(AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
3518   END IF;
3519  -- Bug 5448579
3520 /*
3521   SELECT  ap_invoices_s.nextval
3522     INTO  l_invoice_id
3523     FROM  sys.dual;
3524 */
3525   -----------------------------------------------------------------------------
3526   -- Step 2
3527   -- get wfapproval_status from profile value - ASP.approval_workflow_flag
3528   -----------------------------------------------------------------------------
3529 
3530   debug_info := '(Insert ap invoices step 2)-Get wfapproval_status ' ||
3531                 'depends on profile value';
3532   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
3533     Print(AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
3534   END IF;
3535 
3536   IF p_approval_workflow_flag = 'N' THEN
3537     l_wfapproval_status := 'NOT REQUIRED';
3538   ELSE
3539 
3540     -- Payment Request: Added IF condition
3541     -- We need to set the approval status to approved if the
3542     -- invoice does not need approval
3543     IF p_needs_invoice_approval = 'N' AND
3544             p_invoice_rec.invoice_type_lookup_code = 'PAYMENT REQUEST' THEN
3545        l_wfapproval_status := 'WFAPPROVED';
3546     ELSE
3547        l_wfapproval_status := 'REQUIRED';
3548     END IF;
3549 
3550   END IF;
3551  -- BUG 6785691. Aded to make approval not required in case of expense reports.
3552 
3553   IF  p_invoice_rec.INVOICE_TYPE_LOOKUP_CODE = 'EXPENSE REPORT' THEN
3554      	l_wfapproval_status := 'NOT REQUIRED';
3555   END IF;
3556  -- BUG 6785691. END
3557 
3558 /* Bug 4014019: Commenting the call to jg_globe_flex_val due to build issues.
3559 
3560   -----------------------------------------------------------------------------
3561   -- Step 3
3562   -- Insert jg_zz_invoice_info
3563   -----------------------------------------------------------------------------
3564   debug_info := '(Insert ap invoices step 3) - Call ' ||
3565                 'jg_globe_flex_val.insert_jg_zz_invoice_info';
3566   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
3567     Print(AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
3568   END IF;
3569 
3570   jg_globe_flex_val.insert_jg_zz_invoice_info(
3571           l_invoice_id,
3572           p_invoice_rec.global_attribute_category,
3573           p_invoice_rec.global_attribute1,
3574           p_invoice_rec.global_attribute2,
3575           p_invoice_rec.global_attribute3,
3576           p_invoice_rec.global_attribute4,
3577           p_invoice_rec.global_attribute5,
3578           p_invoice_rec.global_attribute6,
3579           p_invoice_rec.global_attribute7,
3580           p_invoice_rec.global_attribute8,
3581           p_invoice_rec.global_attribute9,
3582           p_invoice_rec.global_attribute10,
3583           p_invoice_rec.global_attribute11,
3584           p_invoice_rec.global_attribute12,
3585           p_invoice_rec.global_attribute13,
3586           p_invoice_rec.global_attribute14,
3587           p_invoice_rec.global_attribute15,
3588           p_invoice_rec.global_attribute16,
3589           p_invoice_rec.global_attribute17,
3590           p_invoice_rec.global_attribute18,
3591           p_invoice_rec.global_attribute19,
3592           p_invoice_rec.global_attribute20,
3593           p_invoice_rec.last_updated_by,
3594           p_invoice_rec.last_update_date,
3595           p_invoice_rec.last_update_login,
3596           p_invoice_rec.created_by,
3597           p_invoice_rec.creation_date,
3598           current_calling_sequence);
3599 
3600 */
3601 
3602 
3603   debug_info := '(Insert ap invoices step 3) Calculate earliest settlement date for Prepayment type invoices';
3604   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
3605         Print(AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
3606   END IF;
3607 
3608   IF (p_invoice_rec.invoice_type_lookup_code = 'PREPAYMENT') THEN
3609      l_earliest_settlement_date := sysdate + nvl(p_add_days_settlement_date,0);
3610   END IF;
3611 
3612 
3613   -----------------------------------------------------------------------------
3614   -- Step 4
3615   -- Insert into ap_invoices table
3616   -----------------------------------------------------------------------------
3617 
3618   debug_info := '(Insert ap invoices step 4) - Insert into ap_invoices';
3619   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
3620     Print(AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
3621   END IF;
3622 
3623   -- Payment Requests: Added party_id, party_site_id,
3624   -- pay_proc_trxn_type_code, payment_function to the insert stmt
3625   INSERT INTO ap_invoices_all(
3626           invoice_id,
3627           org_id,
3628           last_update_date,
3629           last_updated_by,
3630           last_update_login,
3631           vendor_id,
3632           invoice_num,
3633           invoice_amount,
3634           vendor_site_id,
3635           amount_paid,
3636           discount_amount_taken,
3637           invoice_date,
3638           invoice_type_lookup_code,
3639           description,
3640           batch_id,
3641           amount_applicable_to_discount,
3642           terms_id,
3643           approved_amount,
3644           approval_status,
3645           approval_description,
3646           pay_group_lookup_code,
3647           set_of_books_id,
3648           accts_pay_code_combination_id,
3649           invoice_currency_code,
3650           payment_currency_code,
3651           payment_cross_rate,
3652           exchange_date,
3653           exchange_rate_type,
3654           exchange_rate,
3655           base_amount,
3656           payment_status_flag,
3657           posting_status,
3658           attribute_category,
3659           attribute1,
3660           attribute2,
3661           attribute3,
3662           attribute4,
3663           attribute5,
3664           attribute6,
3665           attribute7,
3666           attribute8,
3667           attribute9,
3668           attribute10,
3669           attribute11,
3670           attribute12,
3671           attribute13,
3672           attribute14,
3673           attribute15,
3674           global_attribute_category,
3675           global_attribute1,
3676           global_attribute2,
3677           global_attribute3,
3678           global_attribute4,
3679           global_attribute5,
3680           global_attribute6,
3681           global_attribute7,
3682           global_attribute8,
3683           global_attribute9,
3684           global_attribute10,
3685           global_attribute11,
3686           global_attribute12,
3687           global_attribute13,
3688           global_attribute14,
3689           global_attribute15,
3690           global_attribute16,
3691           global_attribute17,
3692           global_attribute18,
3693           global_attribute19,
3694           global_attribute20,
3695           creation_date,
3696           created_by,
3697           vendor_prepay_amount,
3698           prepay_flag,
3699           recurring_payment_id,
3700           terms_date,
3701           source,
3702           payment_method_code,
3703           doc_sequence_id,
3704           doc_sequence_value,
3705           doc_category_code,
3706           voucher_num,
3707           exclusive_payment_flag,
3708 	  quick_po_header_id,   --Bug 8556975
3709           awt_group_id,
3710           pay_awt_group_id,--bug6639866
3711           payment_cross_rate_type,
3712           payment_cross_rate_date,
3713           pay_curr_invoice_amount,
3714           goods_received_date,
3715           invoice_received_date,
3716        -- ussgl_transaction_code, - Bug 4277744
3717           gl_date,
3718           approval_ready_flag,
3719           wfapproval_status,
3720           requester_id,
3721           control_amount,
3722           tax_related_invoice_id,
3723           taxation_country,
3724           document_sub_type,
3725           supplier_tax_invoice_number,
3726           supplier_tax_invoice_date,
3727           supplier_tax_exchange_rate,
3728           tax_invoice_recording_date,
3729           tax_invoice_internal_seq,
3730           legal_entity_id,
3731 	      application_id,
3732 	      product_table,
3733 	      reference_key1,
3734 	      reference_key2,
3735 	      reference_key3,
3736 	      reference_key4,
3737 	      reference_key5,
3738 	      reference_1,
3739 	      reference_2,
3740 	      net_of_retainage_flag,
3741           cust_registration_code,
3742           cust_registration_number,
3743 	      paid_on_behalf_employee_id,
3744           party_id,
3745           party_site_id,
3746           pay_proc_trxn_type_code,
3747           payment_function,
3748           BANK_CHARGE_BEARER,
3749           REMITTANCE_MESSAGE1,
3750           REMITTANCE_MESSAGE2,
3751           REMITTANCE_MESSAGE3,
3752           UNIQUE_REMITTANCE_IDENTIFIER,
3753           URI_CHECK_DIGIT,
3754           SETTLEMENT_PRIORITY,
3755           PAYMENT_REASON_CODE,
3756           PAYMENT_REASON_COMMENTS,
3757           DELIVERY_CHANNEL_CODE,
3758           EXTERNAL_BANK_ACCOUNT_ID,
3759 	      --bugfix:4930111
3760 	      EARLIEST_SETTLEMENT_DATE,
3761           --bug 4931755
3762           DISC_IS_INV_LESS_TAX_FLAG,
3763           EXCLUDE_FREIGHT_FROM_DISCOUNT,
3764          --Bug 7357218 Quick Pay and Dispute Resolution Project
3765           ORIGINAL_INVOICE_AMOUNT,
3766           DISPUTE_REASON,
3767 	  --Third Party Payments
3768 	     REMIT_TO_SUPPLIER_NAME,
3769 	     REMIT_TO_SUPPLIER_ID,
3770 	     REMIT_TO_SUPPLIER_SITE,
3771 	     REMIT_TO_SUPPLIER_SITE_ID,
3772 	     RELATIONSHIP_ID
3773           )
3774   VALUES (ap_invoices_s.nextval,  -- l_invoice_id, Bug 5448579
3775           p_invoice_rec.org_id,
3776           p_invoice_rec.last_update_date,
3777           --bug 6951863 fix -start
3778           --p_invoice_rec.last_update_login,
3779           p_invoice_rec.last_updated_by,
3780           --p_invoice_rec.last_updated_by,
3781           p_invoice_rec.last_update_login,
3782 	      --bug 6951863 fix -end
3783           p_invoice_rec.vendor_id,
3784           p_invoice_rec.invoice_num,
3785           p_invoice_rec.invoice_amount,
3786           p_invoice_rec.vendor_site_id,
3787           0,                               -- amount_paid
3788           0,                               -- discount_amount_taken,
3789           p_invoice_rec.invoice_date,
3790           p_invoice_rec.invoice_type_lookup_code,
3791           p_invoice_rec.description,       -- description
3792           p_batch_id,                      -- batch_id
3793           p_invoice_rec.amount_applicable_to_discount,
3794           p_invoice_rec.terms_id,          -- terms_id
3795           NULL,                            -- approved_amount
3796           NULL,                            -- approval_status
3797           NULL,                            -- approval_description
3798           p_invoice_rec.pay_group_lookup_code,
3799           p_set_of_books_id,
3800           p_invoice_rec.accts_pay_code_combination_id,
3801           p_invoice_rec.invoice_currency_code,
3802           p_invoice_rec.payment_currency_code,
3803           p_invoice_rec.payment_cross_rate,
3804           p_invoice_rec.exchange_date,
3805           p_invoice_rec.exchange_rate_type,
3806           p_invoice_rec.exchange_rate,
3807           p_invoice_rec.no_xrate_base_amount,  -- base_amount
3808           'N',  -- payment_status_flag
3809           NULL, -- posting_status
3810           p_invoice_rec.attribute_category,
3811           p_invoice_rec.attribute1,
3812           p_invoice_rec.attribute2,
3813           p_invoice_rec.attribute3,
3814           p_invoice_rec.attribute4,
3815           p_invoice_rec.attribute5,
3816           p_invoice_rec.attribute6,
3817           p_invoice_rec.attribute7,
3818           p_invoice_rec.attribute8,
3819           p_invoice_rec.attribute9,
3820           p_invoice_rec.attribute10,
3821           p_invoice_rec.attribute11,
3822           p_invoice_rec.attribute12,
3823           p_invoice_rec.attribute13,
3824           p_invoice_rec.attribute14,
3825           p_invoice_rec.attribute15,
3826           p_invoice_rec.global_attribute_category,
3827           p_invoice_rec.global_attribute1,
3828           p_invoice_rec.global_attribute2,
3829           p_invoice_rec.global_attribute3,
3830           p_invoice_rec.global_attribute4,
3831           p_invoice_rec.global_attribute5,
3832           p_invoice_rec.global_attribute6,
3833           p_invoice_rec.global_attribute7,
3834           p_invoice_rec.global_attribute8,
3835           p_invoice_rec.global_attribute9,
3836           p_invoice_rec.global_attribute10,
3837           p_invoice_rec.global_attribute11,
3838           p_invoice_rec.global_attribute12,
3839           p_invoice_rec.global_attribute13,
3840           p_invoice_rec.global_attribute14,
3841           p_invoice_rec.global_attribute15,
3842           p_invoice_rec.global_attribute16,
3843           p_invoice_rec.global_attribute17,
3844           p_invoice_rec.global_attribute18,
3845           p_invoice_rec.global_attribute19,
3846           p_invoice_rec.global_attribute20,
3847           p_invoice_rec.creation_date,
3848           p_invoice_rec.created_by,
3849           0,                            --  vendor_prepay_amount,
3850           'N',                          --  prepay_flag,
3851           NULL,                         --  recurring_payment_id,
3852           p_invoice_rec.terms_date,
3853           p_invoice_rec.source,
3854           p_invoice_rec.payment_method_code,
3855           p_doc_sequence_id,
3856           p_doc_sequence_value,                   -- doc_sequence_value
3857           p_invoice_rec.doc_category_code,        -- doc_category_code
3858           DECODE(p_invoice_rec.doc_category_code, NULL,
3859                  p_invoice_rec.voucher_num, ''),  -- voucher_num
3860           --p_invoice_rec.exclusive_payment_flag,   -- **exclusive_payment_flag
3861 	  DECODE(p_invoice_rec.invoice_type_lookup_code, 'CREDIT', 'N', p_invoice_rec.exclusive_payment_flag), -- BUG 7195865
3862 	  (select po_header_id from po_headers where segment1 =p_invoice_rec.po_number
3863 	     /* Added for bug#11702161 Start */
3864 	         AND type_lookup_code in ('BLANKET', 'PLANNED', 'STANDARD')
3865              AND nvl(authorization_status,'INCOMPLETE') in ('APPROVED','REQUIRES REAPPROVAL','IN PROCESS')
3866              /* Added for bug#11702161 End */
3867 	  ),  /* Bug 8556975 Changed po_headers_all to po_headers for * bug#9577089 */
3868           p_invoice_rec.awt_group_id,             -- awt_group_id
3869           p_invoice_rec.pay_awt_group_id,         -- pay_awt_group_id--bug6639866
3870           p_invoice_rec.payment_cross_rate_type,  -- payment_cross_rate_type
3871           p_invoice_rec.payment_cross_rate_date,  -- payment_crosss_rate_date
3872           p_pay_curr_invoice_amount,              -- pay_curr_invoice_amount
3873           p_invoice_rec.goods_received_date,      -- goods_received_date
3874           p_invoice_rec.invoice_received_date,    -- invoice_received_date
3875        -- Removed for bug 4277744
3876        -- p_invoice_rec.ussgl_transaction_code,   -- ussgl_transaction_code
3877           TRUNC(p_invoice_rec.gl_date),           -- gl_date
3878           l_approval_ready_flag,                  -- approval_ready_flag
3879           l_wfapproval_status,                    -- wfapproval_status
3880           p_invoice_rec.requester_id,             -- request_id
3881           p_invoice_rec.control_amount,           -- control_amount
3882           p_invoice_rec.tax_related_invoice_id,   -- tax_related_invoice_id
3883           p_invoice_rec.taxation_country,         -- taxation_country
3884           p_invoice_rec.document_sub_type,        -- document_sub_type
3885           p_invoice_rec.supplier_tax_invoice_number,
3886             -- supplier_tax_invoice_number
3887           p_invoice_rec.supplier_tax_invoice_date,
3888             -- supplier_tax_invoice_date
3889           p_invoice_rec.supplier_tax_exchange_rate,
3890              -- supplier_tax_exchange_rate
3891           p_invoice_rec.tax_invoice_recording_date,
3892              -- tax_invoice_recording_date
3893           p_invoice_rec.tax_invoice_internal_seq,  -- tax_invoice_internal_seq
3894           p_invoice_rec.legal_entity_id,           -- legal_entity_id
3895 	      p_invoice_rec.application_id,		   --application identifier
3896 	      p_invoice_rec.product_table,		   --product_table
3897 	      p_invoice_rec.reference_key1,		   --reference_key1
3898 	      p_invoice_rec.reference_key2,		   --reference_key2
3899 	      p_invoice_rec.reference_key3,		   --reference_key3
3900 	      p_invoice_rec.reference_key4,		   --reference_key4
3901 	      p_invoice_rec.reference_key5,		   --reference_key5
3902 	      p_invoice_rec.reference_1,		   --reference_1
3903 	      p_invoice_rec.reference_2,		   --reference_2
3904 	      p_invoice_rec.net_of_retainage_flag, --net_of_retainage_flag
3905           P_invoice_rec.cust_registration_code,
3906           P_invoice_rec.cust_registration_number,
3907 	      P_invoice_rec.paid_on_behalf_employee_id,
3908           p_invoice_rec.party_id,
3909           p_invoice_rec.party_site_id,
3910           p_invoice_rec.pay_proc_trxn_type_code,
3911           p_invoice_rec.payment_function,
3912           p_invoice_rec.BANK_CHARGE_BEARER,
3913           p_invoice_rec.REMITTANCE_MESSAGE1,
3914           p_invoice_rec.REMITTANCE_MESSAGE2,
3915           p_invoice_rec.REMITTANCE_MESSAGE3,
3916           p_invoice_rec.UNIQUE_REMITTANCE_IDENTIFIER,
3917           p_invoice_rec.URI_CHECK_DIGIT,
3918           p_invoice_rec.SETTLEMENT_PRIORITY,
3919           p_invoice_rec.PAYMENT_REASON_CODE,
3920           p_invoice_rec.PAYMENT_REASON_COMMENTS,
3921           p_invoice_rec.DELIVERY_CHANNEL_CODE,
3922           p_invoice_rec.EXTERNAL_BANK_ACCOUNT_ID,
3923 	      --bugfix:4930111
3924 	      l_earliest_settlement_date,
3925           --bug4931755
3926           p_disc_is_inv_less_tax_flag,
3927           p_exclude_freight_from_disc,
3928           --Bug 7357218 Quick Pay and Dispute Resolution Project
3929           p_invoice_rec.ORIGINAL_INVOICE_AMOUNT,
3930           p_invoice_rec.DISPUTE_REASON,
3931 	      --Third Party Payments
3932 	      p_invoice_rec.REMIT_TO_SUPPLIER_NAME,
3933 	      p_invoice_rec.REMIT_TO_SUPPLIER_ID,
3934 	      p_invoice_rec.REMIT_TO_SUPPLIER_SITE,
3935 	      p_invoice_rec.REMIT_TO_SUPPLIER_SITE_ID,
3936 	      p_invoice_rec.RELATIONSHIP_ID
3937         ) RETURNING invoice_id INTO l_invoice_id;
3938 
3939   -----------------------------------------------------------------------------
3940   -- Step 5
3941   -- copy attachment for the invoice
3942   -----------------------------------------------------------------------------
3943   debug_info := '(Insert ap invoices step 5) before copy attachments: '||
3944         'source = ' || p_invoice_rec.source || ', from_invoice_id = ' ||
3945         p_invoice_rec.invoice_id || ', to_invoice_id = ' || l_invoice_id;
3946   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
3947     Print(AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
3948   END IF;
3949 
3950   l_attachments_count :=
3951                 copy_attachments(p_invoice_rec.invoice_id, l_invoice_id);
3952   debug_info := '(Insert ap invoices step 5) copy attachments done: ' ||
3953                 l_attachments_count;
3954   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
3955     Print(AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
3956   END IF;
3957 
3958   -----------------------------------------------------------------------------
3959   -- Step 6
3960   -- Assign the out parameter for new invoice_id
3961   -----------------------------------------------------------------------------
3962   debug_info := '(Insert ap invoices step 6) - Return the new invoice_id-> ' ||
3963                 to_char(l_invoice_id);
3964   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
3965     Print(AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
3966   END IF;
3967 
3968 
3969   p_base_invoice_id := l_invoice_id;
3970 
3971   RETURN( TRUE );
3972 EXCEPTION
3973   WHEN OTHERS THEN
3974     debug_info := debug_info || '->exception';
3975     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
3976       Print(
3977           AP_IMPORT_INVOICES_PKG.g_debug_switch,
3978           debug_info);
3979     END IF;
3980     IF (SQLCODE < 0) THEN
3981       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
3982         Print(
3983             AP_IMPORT_INVOICES_PKG.g_debug_switch,
3984             SQLERRM);
3985       END IF;
3986     END IF;
3987     RETURN (FALSE);
3988 
3989 END insert_ap_invoices;
3990 
3991 /*======================================================================
3992  Function: Change_invoice_status
3993 
3994  The available statuses are:
3995  'PROCESSING' - Temporary status to prevent the invoice cursor pick it up
3996                 again. It means invoice is ok during this run and will be
3997                 changed to 'PROCESSED' after the batch finished.
3998  'REJECTING' - Temporary status to prevent the invoice cursor pick it up
3999                 again. It means invoice is rejected during this run and
4000                 will be changed to 'REJECTED' after the batch finished.
4001  'PROCESSED' - It means invoice has been successfully imported
4002  'REJECTED' - It means there are some rejections or error for this invoice.
4003   Interface invoice cannot be purged if the flag is other than 'PRECESSED'
4004   ========================================================================*/
4005 
4006 FUNCTION change_invoice_status(
4007           p_status                      IN            VARCHAR2,
4008           p_import_invoice_id           IN            NUMBER,
4009           P_calling_sequence            IN            VARCHAR2)
4010 RETURN BOOLEAN
4011 IS
4012   current_calling_sequence        VARCHAR2(2000);
4013   debug_info                      VARCHAR2(500);
4014 
4015 BEGIN
4016   -- Update the calling sequence
4017 
4018   current_calling_sequence := 'Change_invoice_status<-'||P_calling_sequence;
4019 
4020   ---------------------------------------------
4021   -- Step 1
4022   -- Update status to p_invoices_interface
4023   ---------------------------------------------
4024 
4025   debug_info := '(Change_invoice_status 1) Change invoice status to '||
4026                 p_status;
4027   IF AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' THEN
4028     Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
4029   END IF;
4030 
4031   UPDATE AP_INVOICES_INTERFACE
4032      SET status = p_status
4033    WHERE invoice_id = p_import_invoice_id;
4034 
4035   RETURN(TRUE);
4036 
4037 EXCEPTION
4038   WHEN OTHERS THEN
4039     IF AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' THEN
4040       Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
4041     END IF;
4042 
4043     IF (SQLCODE < 0) THEN
4044       IF AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' THEN
4045         Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,SQLERRM);
4046       END IF;
4047     END IF;
4048 
4049     RETURN (FALSE);
4050 
4051 END change_invoice_status;
4052 
4053 /*======================================================================
4054  Private Funtion: Update_temp_invoice_status
4055 
4056   Change temporary invoice status from
4057                   'PROCESSING' to 'PROCESSED'
4058                   'REJECTING' to 'REJECTED'
4059   ======================================================================*/
4060 
4061 FUNCTION Update_temp_invoice_status(
4062           p_source                      IN            VARCHAR2,
4063           p_group_id                    IN            VARCHAR2,
4064           p_calling_sequence            IN            VARCHAR2)
4065 RETURN BOOLEAN
4066 IS
4067   current_calling_sequence        VARCHAR2(2000);
4068   debug_info                      VARCHAR2(500);
4069 --4019310, use binds for literals
4070 l_processed  varchar2(10);
4071 l_rejected   varchar2(10);
4072 l_processing varchar2(10);
4073 l_rejecting  varchar2(10);
4074 BEGIN
4075 
4076 l_processed := 'PROCESSED';
4077 l_rejected  := 'REJECTED';
4078 l_rejecting := 'REJECTING';
4079 l_processing:= 'PROCESSING';
4080  -- Update the calling sequence
4081   --
4082   current_calling_sequence := 'Update_temp_invoice_status<-'||
4083                               P_calling_sequence;
4084 
4085   ---------------------------------------------
4086   -- 1.  Change PROCESSING to PROCESSED
4087   ---------------------------------------------
4088   debug_info := '(Update_temp_invoice_status 1) Change '||
4089                 'PROCESSING to PROCESSED ';
4090 
4091   IF AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' THEN
4092     Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
4093   END IF;
4094 
4095   ---------------------------------------------
4096   -- 2.  Change REJECTING to REJECTED
4097   ---------------------------------------------
4098   debug_info := '(Update_temp_invoice_status 2) Change REJECTING to REJECTED';
4099 
4100   IF AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' THEN
4101     Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
4102   END IF;
4103 --  Bug fix: 1952122
4104 --  Rewrite with two statements avoiding AND ((p_group_id is NULL) OR (group_id = --p_group_id))
4105 --3910020, used binds in the sql below
4106 
4107   --Bug 6801046
4108   --Update statement should only update the status of Invoices
4109   --pertaining to the current request. Modified the below 4 update stmts.
4110   	 -- bug 7608232 added an additional or in request_id = AP_IMPORT_INVOICES_PKG.g_conc_request_id
4111  	  -- as  (request_id = AP_IMPORT_INVOICES_PKG.g_conc_request_id or request_id is null)
4112 
4113   IF p_group_id IS NULL THEN
4114 
4115    UPDATE AP_INVOICES_INTERFACE
4116       SET status = l_processed
4117     WHERE source = p_source
4118       AND p_group_id is NULL
4119       AND status = l_processing
4120       AND (request_id = AP_IMPORT_INVOICES_PKG.g_conc_request_id or request_id is null);
4121       -- bug 7608232
4122 
4123    UPDATE AP_INVOICES_INTERFACE
4124       SET status = l_rejected
4125     WHERE source = p_source
4126       AND p_group_id is NULL
4127       AND status = l_rejecting
4128       AND (request_id = AP_IMPORT_INVOICES_PKG.g_conc_request_id or request_id is null);
4129 -- bug 7608232
4130   ELSE
4131 
4132    UPDATE AP_INVOICES_INTERFACE
4133       SET status = l_processed
4134     WHERE source = p_source
4135       AND group_id = p_group_id
4136       AND status = l_processing
4137       AND (request_id = AP_IMPORT_INVOICES_PKG.g_conc_request_id or request_id is null);
4138 -- bug 7608232
4139    UPDATE AP_INVOICES_INTERFACE
4140       SET status = l_rejected
4141     WHERE source = p_source
4142       AND group_id = p_group_id
4143       AND status = l_rejecting
4144       AND (request_id =AP_IMPORT_INVOICES_PKG.g_conc_request_id or request_id is null);
4145 -- bug 7608232
4146   END IF;
4147 
4148   RETURN(TRUE);
4149 
4150 EXCEPTION
4151   WHEN OTHERS THEN
4152     IF AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' THEN
4153       Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
4154     END IF;
4155 
4156     IF (SQLCODE < 0) THEN
4157       IF AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' THEN
4158         Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,SQLERRM);
4159       END IF;
4160     END IF;
4161 
4162     RETURN (FALSE);
4163 
4164 END Update_temp_invoice_status;
4165 
4166 /*======================================================================
4167   Private Procedure: Insert new AP_BATCHES lines
4168 
4169   Insert New Batch line if the batch name is new
4170   ======================================================================*/
4171 
4172 FUNCTION Insert_ap_batches(
4173           p_batch_id                    IN            NUMBER,
4174           p_batch_name                  IN            VARCHAR2,
4175           p_invoice_currency_code       IN            VARCHAR2,
4176           p_payment_currency_code       IN            VARCHAR2,
4177           p_actual_invoice_count        IN            NUMBER,
4178           p_actual_invoice_total        IN            NUMBER,
4179           p_last_updated_by             IN            NUMBER,
4180           p_calling_sequence            IN            VARCHAR2)
4181 RETURN BOOLEAN
4182 IS
4183   current_calling_sequence        VARCHAR2(2000);
4184   debug_info                      VARCHAR2(500);
4185 BEGIN
4186   -- Update the calling sequence
4187 
4188   current_calling_sequence := 'Insert_ap_batches<-'||p_calling_sequence;
4189 
4190   ---------------------------------------------
4191   -- Insert ap_batches
4192   ---------------------------------------------
4193   debug_info := 'Insert ap_batches';
4194   -- bug 5441261. Insert should be into AP_BATCHES_ALL
4195   INSERT INTO ap_batches_all(
4196           batch_id,
4197           batch_name,
4198           batch_date,
4199           last_update_date,
4200           last_updated_by,
4201           control_invoice_count,
4202           control_invoice_total,
4203           actual_invoice_count,
4204           actual_invoice_total,
4205           invoice_currency_code,
4206           payment_currency_code,
4207           creation_date,
4208           created_by)
4209   VALUES(
4210           p_batch_id,
4211           p_batch_name,
4212           TRUNC(SYSDATE),
4213           SYSDATE,
4214           p_last_updated_by,
4215           p_actual_invoice_count ,
4216           p_actual_invoice_total ,
4217           p_actual_invoice_count ,
4218           p_actual_invoice_total ,
4219           p_invoice_currency_code,
4220           p_payment_currency_code,
4221           SYSDATE,
4222           p_last_updated_by);
4223 
4224    RETURN(TRUE);
4225 
4226 EXCEPTION
4227 
4228  WHEN OTHERS then
4229     IF AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' THEN
4230       Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
4231     END IF;
4232 
4233     IF (SQLCODE < 0) THEN
4234       IF AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' THEN
4235         Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,SQLERRM);
4236       END IF;
4237     END IF;
4238 
4239     RETURN (FALSE);
4240 
4241 END Insert_ap_batches;
4242 
4243 /*======================================================================
4244   Function: Update_Ap_Batches
4245   This function updates the value of control invoice count and
4246   control invoice total in ap_batches
4247   ======================================================================*/
4248 
4249 FUNCTION Update_Ap_Batches(
4250           p_batch_id                    IN            NUMBER,
4251           p_batch_name                  IN            VARCHAR2,
4252           p_actual_invoice_count        IN            NUMBER,
4253           p_actual_invoice_total        IN            NUMBER,
4254           p_last_updated_by             IN            NUMBER,
4255           p_calling_sequence            IN            VARCHAR2)
4256 RETURN BOOLEAN
4257 IS
4258   current_calling_sequence  varchar2(2000);
4259   debug_info     varchar2(500);
4260 
4261 BEGIN
4262 
4263   -- Update the calling sequence
4264 
4265   current_calling_sequence :='Update_Ap_Batches<-'||p_calling_sequence;
4266 
4267   -- Update ap_batches
4268 
4269   debug_info :='Update ap_batches';
4270 
4271   UPDATE ap_batches_all --Bug 8419706 Changed the table ap_batches to ap_batches_all
4272                         --    as the update is not taking place, since org_id is updated
4273                         --    as null in ap_batches_all during insertion of data.
4274      SET control_invoice_count =
4275               NVL(control_invoice_count,0)+
4276               p_actual_invoice_count,
4277          control_invoice_total =
4278               NVL(control_invoice_total,0)+
4279               p_actual_invoice_total,
4280          actual_invoice_count =
4281               actual_invoice_count+
4282               p_actual_invoice_count,
4283          actual_invoice_total =
4284               actual_invoice_total+
4285               p_actual_invoice_total
4286    WHERE batch_id = p_batch_id; -- Added for bug2003024
4287 
4288 RETURN(TRUE);
4289 
4290 EXCEPTION
4291   WHEN OTHERS THEN
4292     IF AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' THEN
4293       Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
4294     END IF;
4295 
4296     IF (SQLCODE<0) THEN
4297       IF AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' THEN
4298         Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,SQLERRM);
4299       END IF;
4300     END IF;
4301 
4302 RETURN(FALSE);
4303 
4304 END Update_ap_Batches;
4305 
4306 /*=========================================================================*/
4307 /*                                                                         */
4308 /* Function  Insert_Ap_Invoices_lines                                      */
4309 /* Program Flow:                                                           */
4310 /* 1. Insert into ap_invoice_lines with the validated interface lines      */
4311 /*    data                                                                 */
4312 /* 2. Bulk  select primary key of lines                                    */
4313 /* Parameters                                                              */
4314 /*    p_base_invoice_id                                                    */
4315 /*    p_invoice_lines_tab - validated interface lines data                 */
4316 /*    p_set_of_books_id - set_of_books_id populated in get_info()          */
4317 /*    p_default_last_updated_by                                            */
4318 /*    p_default_last_update_login                                          */
4319 /*    p_calling_sequence  - for debug purpose                              */
4320 /*                                                                         */
4321 /*=========================================================================*/
4322 
4323 FUNCTION insert_ap_invoice_lines(
4324           p_base_invoice_id             IN            NUMBER,
4325           p_invoice_lines_tab           IN OUT NOCOPY            AP_IMPORT_INVOICES_PKG.LINES_TABLE, --bug 15862708
4326           p_set_of_books_id             IN            NUMBER,
4327           p_approval_workflow_flag      IN            VARCHAR2,
4328           p_tax_only_flag               IN            VARCHAR2,
4329           p_tax_only_rcv_matched_flag   IN            VARCHAR2,
4330           p_default_last_updated_by     IN            NUMBER,
4331           p_default_last_update_login   IN            NUMBER,
4332           p_calling_sequence            IN            VARCHAR2)
4333 RETURN BOOLEAN
4334 IS
4335   debug_info                VARCHAR2(500);
4336   current_calling_sequence  VARCHAR2(2000);
4337   i                         BINARY_INTEGER := 0;
4338   l_generate_dists          AP_INVOICE_LINES.generate_dists%TYPE := 'Y';
4339   l_wfapproval_status       AP_INVOICE_LINES.wfapproval_status%TYPE := NULL;
4340   l_key_value_list          gl_ca_utility_pkg.r_key_value_arr;
4341 
4342   l_inv_code				VARCHAR2(50); -- BUG 6785691
4343 
4344   --bug 15862708
4345   /*
4346    -- bug# 6989166 starts
4347   Cursor c_ship_to_location (p_ship_to_loc_code HR_LOCATIONS.LOCATION_CODE%TYPE) Is
4348   Select ship_to_location_id
4349   From   hr_locations
4350   Where  location_code = p_ship_to_loc_code
4351   and	nvl(ship_to_site_flag, 'N') = 'Y';
4352   -- bug# 6989166 ends
4353 
4354   Cursor c_ship_to (c_invoice_id NUMBER) Is
4355   Select aps.ship_to_location_id
4356   From   ap_invoices_all       ai,
4357          ap_supplier_sites_all aps
4358   Where  ai.invoice_id     = c_invoice_id
4359   And    ai.vendor_site_id = aps.vendor_site_id;
4360 
4361   l_ship_to_location_id  ap_supplier_sites_all.ship_to_location_id%type;
4362   -- bug# 6989166 starts
4363   p_ship_to_location_id  ap_supplier_sites_all.ship_to_location_id%type;
4364   -- bug# 6989166 ends
4365   */
4366   --bug 15862708
4367 BEGIN
4368   -- Update the calling sequence
4369 
4370   current_calling_sequence := 'insert_ap_invoice_lines<-'||P_calling_sequence;
4371 
4372 
4373   -----------------------------------------------------------------------------
4374   -- Step 2
4375   -- Insert into the ap_invoice_lines table
4376   -----------------------------------------------------------------------------
4377 
4378   debug_info := '(Insert ap invoice lines step 2) - Loop the Pl/sql table';
4379 
4380   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
4381     Print( AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
4382   END IF;
4383 
4384   --bug 15862708
4385   /*
4386   Open  c_ship_to (p_base_invoice_id);
4387   Fetch c_ship_to
4388   Into  p_ship_to_location_id; --l_ship_to_location_id; -- bug 6989166
4389   Close c_ship_to;
4390   */
4391   --bug 15862708
4392 
4393   BEGIN
4394     FOR i IN p_invoice_lines_tab.FIRST..p_invoice_lines_tab.LAST LOOP
4395              p_invoice_lines_tab(i).invoice_id 	:= p_base_invoice_id;
4396     END LOOP;
4397 
4398 	FORALL i IN p_invoice_lines_tab.FIRST..p_invoice_lines_tab.LAST
4399 	    INSERT INTO ap_invoice_lines_all
4400 	    VALUES p_invoice_lines_tab(i);
4401     END; -- end of insert
4402 
4403   RETURN( TRUE );
4404 EXCEPTION
4405   WHEN OTHERS THEN
4406     debug_info := debug_info || '->exception';
4407     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
4408       Print( AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
4409     END IF;
4410 
4411     IF (SQLCODE < 0) THEN
4412       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
4413         Print( AP_IMPORT_INVOICES_PKG.g_debug_switch, SQLERRM);
4414       END IF;
4415     END IF;
4416 
4417     RETURN (FALSE);
4418 
4419 END insert_ap_invoice_lines;
4420 
4421 /*=========================================================================*/
4422 /*                                                                         */
4423 /* Private Function  Create_Lines                                          */
4424 /* Program Flow:                                                           */
4425 /*   1. Insert interface lines data into transaction lines table           */
4426 /*   2. Allocate base amount rounding for lines inserted into transaction  */
4427 /*      table                                                              */
4428 /*   3. Loop through lines and either match to PO/RCV, produce price       */
4429 /*      correction or create allocation rules.                             */
4430 /* Parameters:                                                             */
4431 /*                                                                         */
4432 /*   p_batch_id                                                            */
4433 /*   p_base_invoice_id                                                     */
4434 /*   p_invoice_lines_tab                                                   */
4435 /*   p_base_currency_code                                                  */
4436 /*   p_set_of_books_id                                                     */
4437 /*   p_chart_of_accounts_id                                                */
4438 /*   p_default_last_updated_by                                             */
4439 /*   p_default_last_update_login                                           */
4440 /*   p_calling_sequence                                                    */
4441 /*                                                                         */
4442 /*=========================================================================*/
4443 
4444 FUNCTION Create_Lines(
4445           p_batch_id                    IN            NUMBER,
4446           p_base_invoice_id             IN            NUMBER,
4447           p_invoice_lines_tab           IN OUT NOCOPY AP_IMPORT_INVOICES_PKG.lines_table,  --bug 15862708
4448           p_base_currency_code          IN            VARCHAR2,
4449           p_set_of_books_id             IN            NUMBER,
4450           p_approval_workflow_flag      IN            VARCHAR2,
4451           p_tax_only_flag               IN            VARCHAR2,
4452           p_tax_only_rcv_matched_flag   IN            VARCHAR2,
4453           p_default_last_updated_by     IN            NUMBER,
4454           p_default_last_update_login   IN            NUMBER,
4455           p_calling_sequence            IN            VARCHAR2)
4456 RETURN BOOLEAN
4457 IS
4458   create_lines_failure        EXCEPTION;
4459   current_calling_sequence    VARCHAR2(2000);
4460   debug_info                  VARCHAR2(500);
4461   l_debug_context             VARCHAR2(1000);
4462   l_round_amt_exist           BOOLEAN := FALSE;
4463   l_rounded_line_num          NUMBER;
4464   l_rounded_amt               NUMBER := 0;
4465   l_error_code                VARCHAR2(30);
4466   i                           BINARY_INTEGER := 0;
4467   l_overbill_flag	      VARCHAR2(1) := 'N';
4468   l_quantity_outstanding      NUMBER;
4469   l_quantity_ordered          NUMBER;
4470   l_qty_already_billed	      NUMBER;
4471   l_amount_outstanding        NUMBER;
4472   l_amount_ordered            NUMBER;
4473   l_amt_already_billed        NUMBER;
4474 
4475   l_modified_line_rounding_amt   NUMBER; --6892789
4476   l_base_amt                     NUMBER; --6892789
4477   l_round_inv_line_numbers       AP_INVOICES_UTILITY_PKG.inv_line_num_tab_type; --6892789
4478 
4479   l_start_index               NUMBER;
4480   l_end_index                 NUMBER;
4481 
4482 BEGIN
4483   -- Update the calling sequence
4484 
4485   current_calling_sequence := 'Create_lines<-'||P_calling_sequence;
4486 
4487   /* Added for bug#10175718 Start
4488      Split the lines into multiple lines in case of cascade flag
4489    */
4490   l_start_index := p_invoice_lines_tab.FIRST;
4491   l_end_index   := p_invoice_lines_tab.LAST;
4492 
4493   FOR i IN l_start_index..l_end_index LOOP
4494      IF (AP_IMPORT_VALIDATION_PKG.lg_cascade_rept_flag.EXISTS(p_invoice_lines_tab(i).invoice_id||'-'||p_invoice_lines_tab(i).line_number) AND
4495 	 NVL(AP_IMPORT_VALIDATION_PKG.lg_cascade_rept_flag(p_invoice_lines_tab(i).invoice_id||'-'||p_invoice_lines_tab(i).line_number),'N')= 'Y')
4496 	 THEN
4497 
4498        IF (
4499   	    create_receipt_match_lines (
4500           p_po_line_location_id  => p_invoice_lines_tab(i).po_line_location_id,
4501           p_cascade_flag         => 'Y',
4502           p_amount               => p_invoice_lines_tab(i).amount,
4503           p_quantity             => p_invoice_lines_tab(i).quantity_invoiced,
4504           p_price                => p_invoice_lines_tab(i).unit_price,
4505           p_invoice_currency     => p_base_currency_code,
4506           p_index                => i,
4507           p_invoice_lines_tab    => p_invoice_lines_tab
4508            )<> TRUE
4509           ) then
4510             RAISE create_lines_failure;
4511        END IF;
4512 
4513      END IF;
4514   END LOOP;
4515   /* Added for bug#10175718 End */
4516   --------------------------------------------------------------------------
4517   -- Step 1
4518   -- Call API that Bulk insert invoice lines regardless of line type.
4519   --------------------------------------------------------------------------
4520 
4521   debug_info := '(Create lines 1) Call API to Insert all the lines ';
4522   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
4523     Print( AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
4524   END IF;
4525 
4526   IF ( insert_ap_invoice_lines(
4527           p_base_invoice_id           => p_base_invoice_id,
4528           p_invoice_lines_tab         => p_invoice_lines_tab,
4529           p_set_of_books_id           => p_set_of_books_id,
4530           p_approval_workflow_flag    => p_approval_workflow_flag,
4531           p_tax_only_flag             => p_tax_only_flag,
4532           p_tax_only_rcv_matched_flag => p_tax_only_rcv_matched_flag,
4533           p_default_last_updated_by   => p_default_last_updated_by,
4534           p_default_last_update_login => p_default_last_update_login,
4535           p_calling_sequence          => current_calling_sequence )<>TRUE) THEN
4536 
4537     debug_info := debug_info || 'exceptions';
4538     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
4539       Print( AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
4540       RAISE create_lines_failure;
4541     END IF;
4542   END IF;
4543 
4544   --------------------------------------------------------------------------
4545   -- Step 2
4546   -- Call API to do base amount rounding for x_base_invoice_id in
4547   -- ap_invoice_lines core transaction table
4548   --------------------------------------------------------------------------
4549 
4550   debug_info := '(Create lines 2) Call Utility function to round the line '||
4551                 ' before create distributions';
4552   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
4553     Print( AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
4554   END IF;
4555 
4556     /* modifying following code as per the bug 6892789 as there is a chance
4557      that line base amt goes to -ve value (line amount being +ve) so in such
4558      case, adjust line base amount upto zero and adjust the remaing amount in
4559      another line having next max amount */
4560 
4561   -- get the lines which can be adjusted
4562     l_round_amt_exist := AP_INVOICES_UTILITY_PKG.round_base_amts(
4563                            X_Invoice_Id           => p_base_invoice_id,
4564                            X_Reporting_Ledger_Id  => NULL,
4565                            X_Rounded_Line_Numbers => l_round_inv_line_numbers,
4566                            X_Rounded_Amt          => l_rounded_amt,
4567                            X_Debug_Info           => debug_info,
4568                            X_Debug_Context        => l_debug_context,
4569                            X_Calling_sequence     => current_calling_sequence);
4570 
4571     -- adjustment required and there exist line numbers that can be adjusted
4572     IF ( l_round_amt_exist  AND l_round_inv_line_numbers.count > 0 ) THEN
4573     -- iterate throgh lines until there is no need to adjust
4574       for i in 1 .. l_round_inv_line_numbers.count
4575       loop
4576         IF l_rounded_amt <> 0 THEN
4577         -- get the existing base amount for the selected line
4578           select base_amount
4579           INTO   l_base_amt
4580           FROM   AP_INVOICE_LINES
4581           WHERE  invoice_id = p_base_invoice_id
4582           AND    line_number = l_round_inv_line_numbers(i);
4583 
4584          -- get the calculated adjusted base amount and rounding amount
4585          -- get rounding amount for the next line if required
4586          l_base_amt := AP_APPROVAL_PKG.get_adjusted_base_amount(
4587                                 p_base_amount => l_base_amt,
4588                                 p_rounding_amt => l_modified_line_rounding_amt,
4589                                 p_next_line_rounding_amt => l_rounded_amt);
4590 
4591          -- update the calculatd base amount, rounding amount
4592           UPDATE AP_INVOICE_LINES
4593           SET    base_amount = l_base_amt,
4594                  rounding_amt = ABS( NVL(l_modified_line_rounding_amt, 0) ),
4595                  last_update_date = SYSDATE,
4596                  last_updated_by = FND_GLOBAL.user_id,
4597                  last_update_login = FND_GLOBAL.login_id
4598           WHERE  invoice_id = p_base_invoice_id
4599           AND    line_number = l_round_inv_line_numbers(i);
4600         ELSE
4601         -- adjustment not required or there are no lines that can be adjusted
4602          EXIT;
4603         END IF;
4604       end loop;
4605 
4606   END IF;
4607 
4608   --------------------------------------------------------------------------
4609   -- Step 3
4610   -- Loop through lines and call matching package if line is to be matched
4611   -- or call allocations package if allocation rule/lines need to be created
4612   --------------------------------------------------------------------------
4613   debug_info := '(Create lines 3) Call Matching or Allocations';
4614 
4615   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
4616     Print( AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
4617   END IF;
4618 
4619   BEGIN
4620 
4621     FOR i IN p_invoice_lines_tab.FIRST..p_invoice_lines_tab.LAST LOOP
4622 
4623      IF (p_invoice_lines_tab(i).line_type_lookup_code = 'ITEM') THEN
4624 
4625        IF (p_invoice_lines_tab(i).po_line_location_id IS NOT NULL) THEN
4626 	  debug_info := '(Create Lines 3.1) Check for quantity overbill '
4627                         ||'for PO Shipment';
4628 
4629           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4630               AP_IMPORT_UTILITIES_PKG.Print(
4631                 AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
4632           END IF;
4633 
4634           IF (AP_IMPORT_UTILITIES_PKG.get_overbill_for_shipment(
4635                 p_invoice_lines_tab(i).po_line_location_id,    -- IN
4636                 p_invoice_lines_tab(i).quantity_invoiced,      -- IN
4637 		p_invoice_lines_tab(i).amount,		       -- IN
4638                 l_overbill_flag,                    -- OUT NOCOPY
4639                 l_quantity_outstanding,             -- OUT NOCOPY
4640                 l_quantity_ordered,                 -- OUT NOCOPY
4641                 l_qty_already_billed,               -- OUT NOCOPY
4642 		l_amount_outstanding,               -- OUT NOCOPY
4643 		l_amount_ordered,                   -- OUT NOCOPY
4644 		l_amt_already_billed,               -- OUT NOCOPY
4645                 current_calling_sequence) <> TRUE) THEN
4646 
4647             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
4648                 AP_IMPORT_UTILITIES_PKG.Print(
4649                   AP_IMPORT_INVOICES_PKG.g_debug_switch,
4650                     'get_overbill_for_shipment<-'||current_calling_sequence);
4651             END IF;
4652             RAISE create_lines_failure;
4653           END IF;
4654 
4655         END IF;
4656 
4657 	debug_info := '(Create lines 4) Calling Matching API';
4658 
4659 	ap_matching_utils_pkg.match_invoice_line(
4660 				P_Invoice_Id => p_base_invoice_id,
4661 				P_Invoice_Line_Number => p_invoice_lines_tab(i).line_number,
4662 				P_Overbill_Flag => l_overbill_flag,
4663 				P_Calling_Sequence => current_calling_sequence);
4664 --bug 15862708 prorate_across_flag changed to PRORATE_ACROSS_ALL_ITEMS
4665      ELSIF (p_invoice_lines_tab(i).line_type_lookup_code <> 'ITEM' AND
4666             NVL(p_invoice_lines_tab(i).PRORATE_ACROSS_ALL_ITEMS, 'N') = 'Y' AND
4667             p_invoice_lines_tab(i).line_group_number IS NULL) THEN
4668 
4669           IF (NOT (ap_allocation_rules_pkg.insert_fully_prorated_rule(
4670 		                     p_base_invoice_id,
4671                                      p_invoice_lines_tab(i).line_number,
4672 		                     l_error_code))) THEN
4673 
4674              debug_info := '(Create lines 5) Error encountered: '||l_error_code;
4675              IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
4676                 Print( AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
4677              END IF;
4678              RETURN(FALSE);
4679 
4680           END IF;
4681 
4682        ELSIF (p_invoice_lines_tab(i).line_type_lookup_code <> 'ITEM' AND
4683               NVL(p_invoice_lines_tab(i).PRORATE_ACROSS_ALL_ITEMS, 'N') = 'Y' AND --bug 15862708
4684               p_invoice_lines_tab(i).line_group_number IS NOT NULL) THEN
4685 
4686           IF (NOT (ap_allocation_rules_pkg.insert_from_line_group_number(
4687       				             p_base_invoice_id,
4688                                 	     p_invoice_lines_tab(i).line_number,
4689 			                     l_error_code))) THEN
4690 
4691 	      debug_info := '(Create lines 6) Error encountered: '||l_error_code;
4692 
4693 	      IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
4694 	            Print( AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
4695 	      END IF;
4696 
4697 	      RETURN(FALSE);
4698 	  END IF;
4699 
4700       END IF;
4701 
4702     END LOOP;
4703 
4704   END;
4705 
4706   RETURN( TRUE );
4707 EXCEPTION
4708   WHEN OTHERS THEN
4709 
4710     debug_info := debug_info || '->exception';
4711     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
4712       Print( AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
4713     END IF;
4714 
4715     IF (SQLCODE < 0) THEN
4716       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
4717         Print( AP_IMPORT_INVOICES_PKG.g_debug_switch, SQLERRM);
4718       END IF;
4719     END IF;
4720     RETURN (FALSE);
4721 END Create_lines;
4722 
4723 FUNCTION insert_holds(
4724           p_base_invoice_id             IN            NUMBER,
4725           p_hold_code                   IN            VARCHAR2,
4726           p_hold_reason                 IN            VARCHAR2,
4727           p_hold_future_payments_flag   IN            VARCHAR2,
4728           p_supplier_hold_reason        IN            VARCHAR2,
4729           p_invoice_amount_limit        IN            NUMBER,
4730           p_invoice_base_amount         IN            NUMBER,
4731           p_last_updated_by             IN            NUMBER,
4732           P_calling_sequence            IN            VARCHAR2)
4733 RETURN BOOLEAN
4734 IS
4735   current_calling_sequence        VARCHAR2(2000);
4736   debug_info                      VARCHAR2(500);
4737 
4738 BEGIN
4739   -- Update the calling sequence
4740 
4741   current_calling_sequence := 'insert_holds<-'||P_calling_sequence;
4742 
4743   --------------------------------------------------------------------------
4744   -- Step 1
4745   -- Insert invoice holds FROM the import batch
4746   --------------------------------------------------------------------------
4747 
4748   debug_info := '(Insert Holds 1)  Insert invoice holds FROM the import batch';
4749   IF AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' THEN
4750     AP_IMPORT_UTILITIES_PKG.Print(
4751       AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
4752   END IF;
4753 
4754   IF (p_hold_code is NOT NULL) THEN
4755     ap_holds_pkg.insert_single_hold(
4756           X_invoice_id          =>p_base_invoice_id,
4757           X_hold_lookup_code    =>p_hold_code,
4758           X_hold_type           =>'INVOICE HOLD REASON',
4759           X_hold_reason         =>p_hold_reason,
4760           X_held_by             =>p_last_updated_by,
4761           X_calling_sequence    =>current_calling_sequence);
4762   END IF;
4763 
4764   ---------------------------------------------------------------------------
4765   -- Step 2
4766   -- Insert Suppler's holds
4767   ---------------------------------------------------------------------------
4768 
4769   debug_info := '(Insert Holds 2) Insert Suppler holds';
4770   IF AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' THEN
4771     AP_IMPORT_UTILITIES_PKG.Print(
4772       AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
4773   END IF;
4774 
4775   iF (NVL(p_hold_future_payments_flag,'N') = 'Y') THEN
4776      ap_holds_pkg.insert_single_hold(
4777           X_invoice_id          =>p_base_invoice_id,
4778           --Bug 7448784 Changed 'Vendor' to 'VENDOR'
4779           X_hold_lookup_code    =>'VENDOR',
4780           X_hold_type           =>'INVOICE HOLD REASON',
4781           X_hold_reason         =>p_supplier_hold_reason,
4782           X_held_by             =>5,
4783           X_calling_sequence    =>current_calling_sequence);
4784   END IF;
4785 
4786   IF (p_invoice_base_amount > p_invoice_amount_limit) THEN
4787 
4788     --------------------------------------------------------------------------
4789     -- Step 3
4790     -- Insert Hold IF invoice_base_amount > invoice_amount_limit
4791     --------------------------------------------------------------------------
4792     debug_info := '(Insert Holds 3) Insert Hold IF invoice_base_amount > '||
4793                   'invoice_amount_limit';
4794     IF AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' THEN
4795       AP_IMPORT_UTILITIES_PKG.Print(
4796         AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
4797     END IF;
4798 
4799     ap_holds_pkg.insert_single_hold(
4800           X_invoice_id                      =>p_base_invoice_id,
4801           X_hold_lookup_code                =>'AMOUNT',
4802           X_hold_type                       =>'INVOICE HOLD REASON',
4803           X_hold_reason                     =>p_supplier_hold_reason,
4804           X_held_by                         =>5,
4805           X_calling_sequence                =>current_calling_sequence);
4806    END IF;
4807 
4808    RETURN(TRUE);
4809 
4810 EXCEPTION
4811  WHEN OTHERS THEN
4812     IF AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' THEN
4813       AP_IMPORT_UTILITIES_PKG.Print(
4814         AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
4815     END IF;
4816 
4817     IF (SQLCODE < 0) 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,SQLERRM);
4821       END IF;
4822     END IF;
4823 
4824     RETURN (FALSE);
4825 
4826 END insert_holds;
4827 
4828 /*=========================================================================*/
4829 /*                                                                         */
4830 /* Function  Get_tax_only_rcv_matched_flag                                 */
4831 /*  This function is used to determine if the invoice is a tax only and if */
4832 /*  the existing tax lines are rcv matched and no tax information is       */
4833 /*  populated for the lines.                                               */
4834 /*                                                                         */
4835 /* Parameters                                                              */
4836 /*    p_invoice_id                                                         */
4837 /*                                                                         */
4838 /*=========================================================================*/
4839 
4840 FUNCTION get_tax_only_rcv_matched_flag(
4841   P_invoice_id             IN NUMBER) RETURN VARCHAR2
4842 
4843 IS
4844 
4845   l_tax_only_rcv_matched_flag   VARCHAR2(1);
4846 
4847 BEGIN
4848 
4849   --------------------------------------------------------------------------
4850   -- Select Y if invoice is tax only and tax lines are RCV matched and no
4851   -- tax line has tax info populated
4852   --------------------------------------------------------------------------
4853 
4854   IF (p_invoice_id IS NOT NULL) THEN
4855 
4856     BEGIN
4857       SELECT 'N'
4858         INTO l_tax_only_rcv_matched_flag
4859         FROM ap_invoice_lines_interface
4860        WHERE invoice_id = p_invoice_id
4861          AND (line_type_lookup_code <> 'TAX' OR
4862              (line_type_lookup_code = 'TAX' AND
4863               rcv_transaction_id IS NULL AND
4864               (tax_regime_code IS NOT NULL OR
4865                tax IS NOT NULL OR
4866                tax_jurisdiction_code IS NOT NULL OR
4867                tax_status_code IS NOT NULL OR
4868                tax_rate_id IS NOT NULL OR
4869                tax_rate_code IS NOT NULL OR
4870                tax_rate IS NOT NULL OR
4871                incl_in_taxable_line_flag IS NOT NULL OR
4872                tax_classification_code is not null)))  --bug6255826
4873          AND ROWNUM = 1;
4874 
4875     EXCEPTION
4876       WHEN NO_DATA_FOUND THEN
4877         l_tax_only_rcv_matched_flag := 'Y';
4878     END;
4879 
4880   END IF;
4881 
4882   RETURN l_tax_only_rcv_matched_flag;
4883 
4884 END get_tax_only_rcv_matched_flag;
4885 
4886 /*=========================================================================*/
4887 /*                                                                         */
4888 /* Function  Get_tax_only_flag                                             */
4889 /*  This function is used to determine if the invoice is a tax only one    */
4890 /*  This flag will be used by the eTax validate_default_import API to      */
4891 /*  determine how the global temporary tables for the tax lines should be  */
4892 /*  populated.                                                             */
4893 /*                                                                         */
4894 /* Parameters                                                              */
4895 /*    p_invoice_id                                                         */
4896 /*                                                                         */
4897 /*=========================================================================*/
4898 
4899 FUNCTION get_tax_only_flag(
4900   P_invoice_id             IN NUMBER) RETURN VARCHAR2
4901 
4902 IS
4903 
4904   l_tax_only_flag   VARCHAR2(1);
4905 
4906 BEGIN
4907 
4908   --------------------------------------------------------------------------
4909   -- Select Y if invoice is tax only
4910   --------------------------------------------------------------------------
4911   IF (p_invoice_id IS NOT NULL) THEN
4912 
4913     BEGIN
4914       SELECT 'N'
4915         INTO l_tax_only_flag
4916         FROM ap_invoice_lines_interface
4917        WHERE invoice_id = p_invoice_id
4918          AND line_type_lookup_code <> 'TAX'
4919          AND ROWNUM = 1;
4920 
4921     EXCEPTION
4922       WHEN NO_DATA_FOUND THEN
4923         l_tax_only_flag := 'Y';
4924     END;
4925   END IF;
4926 
4927   RETURN l_tax_only_flag;
4928 
4929 END get_tax_only_flag;
4930 
4931 /*  5039042. Function for Checking if Distribution Generation Event is rgeistered for the
4932    source application */
4933 FUNCTION Is_Product_Registered(P_Application_Id      IN         NUMBER,
4934                                X_Registration_Api    OUT NOCOPY VARCHAR2,
4935                                X_Registration_View   OUT NOCOPY VARCHAR2,
4936                                P_Calling_Sequence    IN         VARCHAR2)
4937   RETURN BOOLEAN IS
4938 
4939   l_debug_info VARCHAR2(1000);
4940   l_curr_calling_sequence VARCHAR2(2000);
4941 
4942 BEGIN
4943 
4944   l_curr_calling_sequence := 'Is_Product_Registered <-'||p_calling_sequence;
4945   IF AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' THEN
4946     AP_IMPORT_UTILITIES_PKG.Print(
4947       AP_IMPORT_INVOICES_PKG.g_debug_switch,l_curr_calling_sequence);
4948   END IF;
4949 
4950   l_debug_info := 'Check if the other application is registered for Distribution Generation';
4951   IF AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' THEN
4952     AP_IMPORT_UTILITIES_PKG.Print(
4953       AP_IMPORT_INVOICES_PKG.g_debug_switch,l_debug_info);
4954   END IF;
4955 
4956 
4957   BEGIN
4958 
4959      SELECT registration_api,
4960             registration_view
4961      INTO x_registration_api,
4962           x_registration_view
4963      FROM ap_product_registrations
4964      WHERE application_id = 200
4965      AND reg_application_id = p_application_id
4966      AND registration_event_type = 'DISTRIBUTION_GENERATION';
4967 
4968   EXCEPTION WHEN NO_DATA_FOUND THEN
4969      x_registration_view := NULL;
4970      x_registration_api := NULL;
4971      RETURN(FALSE);
4972   END;
4973 
4974   RETURN(TRUE);
4975 
4976 EXCEPTION
4977   WHEN OTHERS then
4978      IF (SQLCODE <> -20001) THEN
4979        FND_MESSAGE.SET_NAME('SQLAP','AP_DEBUG');
4980        FND_MESSAGE.SET_TOKEN('ERROR',SQLERRM);
4981        FND_MESSAGE.SET_TOKEN('CALLING_SEQUENCE',l_curr_calling_sequence);
4982        FND_MESSAGE.SET_TOKEN('PARAMETERS',
4983                          '  Application Id  = '    || to_char(P_Application_Id) );
4984      END IF;
4985      APP_EXCEPTION.RAISE_EXCEPTION;
4986 
4987 END Is_Product_Registered;
4988 
4989 -- Bug 5448579. This function will be used for caching org_id, name
4990 FUNCTION Cache_Org_Id_Name (
4991           P_Moac_Org_Table     OUT NOCOPY   AP_IMPORT_INVOICES_PKG.moac_ou_tab_type,
4992           P_Fsp_Org_Table      OUT NOCOPY   AP_IMPORT_INVOICES_PKG.fsp_org_tab_type,
4993           P_Calling_Sequence    IN   VARCHAR2 )
4994 
4995   RETURN BOOLEAN IS
4996 
4997   CURSOR moac_org  IS
4998   SELECT organization_id,
4999          mo_global.get_ou_name(organization_id)
5000   FROM Mo_Glob_Org_Access_Tmp;
5001 
5002   CURSOR fsp_org IS
5003   SELECT org_id
5004   FROM Financials_System_Parameters;
5005 
5006   l_debug_info    VARCHAR2(1000);
5007   l_curr_calling_sequence  VARCHAR2(2000);
5008 
5009 
5010 BEGIN
5011 
5012   l_curr_calling_sequence := 'Cache_Org_Id_Name <- '||P_calling_sequence;
5013   IF AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' THEN
5014     AP_IMPORT_UTILITIES_PKG.Print(
5015       AP_IMPORT_INVOICES_PKG.g_debug_switch,l_curr_calling_sequence);
5016   END IF;
5017 
5018   l_debug_info := 'Caching Org_id , Name from MO: Security Profile';
5019   IF AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' THEN
5020     AP_IMPORT_UTILITIES_PKG.Print(
5021       AP_IMPORT_INVOICES_PKG.g_debug_switch,l_debug_info);
5022   END IF;
5023 
5024   OPEN moac_org;
5025     FETCH  moac_org
5026     BULK COLLECT INTO  P_Moac_Org_Table;
5027   CLOSE moac_org;
5028 
5029   l_debug_info := 'Caching Org_id  from Financials Systems';
5030   IF AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' THEN
5031     AP_IMPORT_UTILITIES_PKG.Print(
5032       AP_IMPORT_INVOICES_PKG.g_debug_switch,l_debug_info);
5033   END IF;
5034 
5035   OPEN fsp_org;
5036     FETCH  fsp_org
5037     BULK COLLECT INTO  P_Fsp_Org_Table;
5038   CLOSE fsp_org;
5039 
5040 
5041   RETURN(TRUE);
5042 
5043 EXCEPTION
5044   WHEN OTHERS then
5045      IF (SQLCODE <> -20001) THEN
5046        FND_MESSAGE.SET_NAME('SQLAP','AP_DEBUG');
5047        FND_MESSAGE.SET_TOKEN('ERROR',SQLERRM);
5048        FND_MESSAGE.SET_TOKEN('CALLING_SEQUENCE',l_curr_calling_sequence);
5049        FND_MESSAGE.SET_TOKEN('DEBUG_INFO', l_debug_info);
5050      END IF;
5051      APP_EXCEPTION.RAISE_EXCEPTION;
5052 
5053 END Cache_Org_Id_Name;
5054 
5055 -- Bug 5448579. This function will be used for checking term claendar based on terms_id
5056 PROCEDURE Check_For_Calendar_Term
5057              (p_terms_id          IN       number,
5058               p_terms_date        IN       date,
5059               p_no_cal            IN OUT NOCOPY  varchar2,
5060               p_calling_sequence  IN       varchar2) IS
5061 
5062 CURSOR c IS
5063   SELECT calendar
5064   FROM   ap_terms,
5065          ap_terms_lines
5066   WHERE  ap_terms.term_id = ap_terms_lines.term_id
5067   AND    ap_terms.term_id = p_terms_id
5068   AND    ap_terms_lines.calendar is not null;
5069 
5070 l_calendar               VARCHAR2(30);
5071 l_cal_exists             VARCHAR2(1);
5072 l_debug_info             VARCHAR2(100);
5073 l_curr_calling_sequence  VARCHAR2(2000);
5074 
5075 BEGIN
5076   -- Update the calling sequence
5077   --
5078   l_curr_calling_sequence :=
5079   'AP_IMPORT_UTILITIES_PKG.Check_For_Calendar_Term<-'||p_calling_sequence;
5080   IF AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' THEN
5081     AP_IMPORT_UTILITIES_PKG.Print(
5082       AP_IMPORT_INVOICES_PKG.g_debug_switch,l_curr_calling_sequence);
5083   END IF;
5084 
5085   --------------------------------------------------------
5086   l_debug_info := 'OPEN  cursor c';
5087   --------------------------------------------------------
5088   IF AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' THEN
5089     AP_IMPORT_UTILITIES_PKG.Print(
5090       AP_IMPORT_INVOICES_PKG.g_debug_switch,l_debug_info);
5091   END IF;
5092 
5093   l_cal_exists := '';
5094   OPEN c;
5095 
5096   LOOP
5097      --------------------------------------------------------
5098      l_debug_info := 'Fetch cursor C';
5099      --------------------------------------------------------
5100      IF AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' THEN
5101      AP_IMPORT_UTILITIES_PKG.Print(
5102        AP_IMPORT_INVOICES_PKG.g_debug_switch,l_debug_info);
5103      END IF;
5104 
5105      FETCH c INTO l_calendar;
5106      EXIT WHEN c%NOTFOUND;
5107 
5108      --------------------------------------------------------
5109      l_debug_info := 'Check for calendar';
5110      --------------------------------------------------------
5111      IF AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' THEN
5112      AP_IMPORT_UTILITIES_PKG.Print(
5113        AP_IMPORT_INVOICES_PKG.g_debug_switch,l_debug_info);
5114      END IF;
5115 
5116      BEGIN
5117 
5118        -- Bug1769230 Added truncate function to eliminate time part
5119        -- from p_terms_date variable.
5120        SELECT 'Y'
5121        INTO   l_cal_exists
5122        FROM   ap_other_periods aop,
5123               ap_other_period_types aopt
5124        WHERE  aopt.period_type = l_calendar
5125        AND    aopt.module = 'PAYMENT TERMS'
5126        AND    aopt.module = aop.module -- bug 2902681
5127        AND    aopt.period_type = aop.period_type
5128        AND    aop.start_date <= trunc(p_terms_date)
5129        AND    aop.end_date >= trunc(p_terms_date);
5130      EXCEPTION
5131        WHEN NO_DATA_FOUND then
5132          null;
5133      END;
5134 
5135      if (l_cal_exists <> 'Y') or (l_cal_exists is null) then
5136          p_no_cal := 'Y';
5137          return;
5138      end if;
5139 
5140   END LOOP;
5141   --------------------------------------------------------
5142   l_debug_info := 'CLOSE  cursor c';
5143   --------------------------------------------------------
5144   IF AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' THEN
5145     AP_IMPORT_UTILITIES_PKG.Print(
5146       AP_IMPORT_INVOICES_PKG.g_debug_switch,l_debug_info);
5147   END IF;
5148 
5149   CLOSE c;
5150 
5151 EXCEPTION
5152   WHEN OTHERS THEN
5153     IF (SQLCODE <> -20001) THEN
5154       FND_MESSAGE.SET_NAME('SQLAP','AP_DEBUG');
5155       FND_MESSAGE.SET_TOKEN('ERROR',SQLERRM);
5156       FND_MESSAGE.SET_TOKEN('CALLING_SEQUENCE', l_curr_calling_sequence);
5157       FND_MESSAGE.SET_TOKEN('PARAMETERS',
5158                     'Payment Terms = '|| p_terms_id
5159                  ||' Terms date = '||to_char(p_terms_date));
5160       FND_MESSAGE.SET_TOKEN('DEBUG_INFO',l_debug_info);
5161     END IF;
5162     APP_EXCEPTION.RAISE_EXCEPTION;
5163 End Check_For_Calendar_Term;
5164 
5165 -- Bug 5448579. This function will be used for caching Pay Group
5166 FUNCTION Cache_Pay_Group (
5167          P_Pay_Group_Table    OUT NOCOPY  AP_IMPORT_INVOICES_PKG.pay_group_tab_type,
5168          P_Calling_Sequence   IN    VARCHAR2)
5169 RETURN BOOLEAN IS
5170 
5171   CURSOR pay_group  IS
5172   SELECT lookup_code
5173   FROM po_lookup_codes
5174   WHERE lookup_type = 'PAY GROUP'
5175   AND DECODE(SIGN(NVL(inactive_date,
5176                AP_IMPORT_INVOICES_PKG.g_inv_sysdate) -
5177                AP_IMPORT_INVOICES_PKG.g_inv_sysdate),
5178                -1,'','*') = '*';
5179 
5180   l_debug_info    VARCHAR2(1000);
5181   l_curr_calling_sequence  VARCHAR2(2000);
5182 
5183 
5184 BEGIN
5185 
5186   l_curr_calling_sequence := 'Cache_Pay_group <- '||P_calling_sequence;
5187   IF AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' THEN
5188     AP_IMPORT_UTILITIES_PKG.Print(
5189       AP_IMPORT_INVOICES_PKG.g_debug_switch,l_curr_calling_sequence);
5190   END IF;
5191 
5192   l_debug_info := 'Caching Pay Group from PO Lookup Codes';
5193   IF AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' THEN
5194     AP_IMPORT_UTILITIES_PKG.Print(
5195       AP_IMPORT_INVOICES_PKG.g_debug_switch,l_debug_info);
5196   END IF;
5197 
5198   OPEN pay_group;
5199     FETCH pay_group
5200     BULK COLLECT INTO  P_Pay_Group_Table;
5201   CLOSE pay_group;
5202 
5203   RETURN(TRUE);
5204 
5205 EXCEPTION
5206   WHEN OTHERS then
5207      IF (SQLCODE <> -20001) THEN
5208        FND_MESSAGE.SET_NAME('SQLAP','AP_DEBUG');
5209        FND_MESSAGE.SET_TOKEN('ERROR',SQLERRM);
5210        FND_MESSAGE.SET_TOKEN('CALLING_SEQUENCE',l_curr_calling_sequence);
5211        FND_MESSAGE.SET_TOKEN('DEBUG_INFO', l_debug_info);
5212      END IF;
5213      APP_EXCEPTION.RAISE_EXCEPTION;
5214 
5215 END Cache_Pay_Group;
5216 
5217 -- Bug 5448579. This function will be used for caching Payment Method from IBY
5218 FUNCTION Cache_Payment_Method (
5219          P_Payment_Method_Table    OUT NOCOPY AP_IMPORT_INVOICES_PKG.payment_method_tab_type,
5220          P_Calling_Sequence        IN    VARCHAR2)
5221 RETURN BOOLEAN IS
5222 
5223   CURSOR payment_method  IS
5224   SELECT payment_method_code
5225   FROM IBY_PAYMENT_METHODS_VL;
5226 
5227   l_debug_info    VARCHAR2(1000);
5228   l_curr_calling_sequence  VARCHAR2(2000);
5229 
5230 
5231 BEGIN
5232 
5233   l_curr_calling_sequence := 'Cache_Payment_Method <- '||P_calling_sequence;
5234   IF AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' THEN
5235     AP_IMPORT_UTILITIES_PKG.Print(
5236       AP_IMPORT_INVOICES_PKG.g_debug_switch,l_curr_calling_sequence);
5237   END IF;
5238 
5239   l_debug_info := 'Caching Payment Method from IBY';
5240   IF AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' THEN
5241     AP_IMPORT_UTILITIES_PKG.Print(
5242       AP_IMPORT_INVOICES_PKG.g_debug_switch,l_debug_info);
5243   END IF;
5244 
5245   OPEN payment_method;
5246     FETCH payment_method
5247     BULK COLLECT INTO  P_Payment_Method_Table;
5248   CLOSE payment_method;
5249 
5250   RETURN(TRUE);
5251 
5252 EXCEPTION
5253   WHEN OTHERS then
5254      IF (SQLCODE <> -20001) THEN
5255        FND_MESSAGE.SET_NAME('SQLAP','AP_DEBUG');
5256        FND_MESSAGE.SET_TOKEN('ERROR',SQLERRM);
5257        FND_MESSAGE.SET_TOKEN('CALLING_SEQUENCE',l_curr_calling_sequence);
5258        FND_MESSAGE.SET_TOKEN('DEBUG_INFO', l_debug_info);
5259      END IF;
5260      APP_EXCEPTION.RAISE_EXCEPTION;
5261 
5262 END Cache_Payment_Method;
5263 
5264 FUNCTION Cache_Fnd_Currency (
5265          P_Fnd_Currency_Table    OUT NOCOPY  AP_IMPORT_INVOICES_PKG.fnd_currency_tab_type,
5266          P_Calling_Sequence      IN   VARCHAR2)
5267 RETURN BOOLEAN IS
5268 
5269   CURSOR currency_code_cur  IS
5270   SELECT currency_code,
5271          start_date_active,
5272          end_date_active,
5273          minimum_accountable_unit,
5274          precision,
5275          enabled_flag
5276   FROM fnd_currencies;
5277 
5278   l_debug_info    VARCHAR2(1000);
5279   l_curr_calling_sequence  VARCHAR2(2000);
5280 
5281 
5282 BEGIN
5283 
5284   l_curr_calling_sequence := 'Cache_Fnd_Currency <- '||P_calling_sequence;
5285   IF AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' THEN
5286     AP_IMPORT_UTILITIES_PKG.Print(
5287       AP_IMPORT_INVOICES_PKG.g_debug_switch,l_curr_calling_sequence);
5288   END IF;
5289 
5290   l_debug_info := 'Caching Currency from Fnd Currency';
5291   IF AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' THEN
5292     AP_IMPORT_UTILITIES_PKG.Print(
5293       AP_IMPORT_INVOICES_PKG.g_debug_switch,l_debug_info);
5294   END IF;
5295 
5296   OPEN currency_code_cur;
5297     FETCH currency_code_cur
5298     BULK COLLECT INTO  P_Fnd_Currency_Table;
5299   CLOSE currency_code_cur;
5300 
5301   RETURN(TRUE);
5302 
5303 EXCEPTION
5304   WHEN OTHERS then
5305      IF (SQLCODE <> -20001) THEN
5306        FND_MESSAGE.SET_NAME('SQLAP','AP_DEBUG');
5307        FND_MESSAGE.SET_TOKEN('ERROR',SQLERRM);
5308        FND_MESSAGE.SET_TOKEN('CALLING_SEQUENCE',l_curr_calling_sequence);
5309        FND_MESSAGE.SET_TOKEN('DEBUG_INFO', l_debug_info);
5310      END IF;
5311      APP_EXCEPTION.RAISE_EXCEPTION;
5312 
5313 END Cache_Fnd_Currency;
5314 
5315 END AP_IMPORT_UTILITIES_PKG;