DBA Data[Home] [Help]

PACKAGE BODY: APPS.AP_APPROVAL_MATCHED_PKG

Source


1 PACKAGE BODY AP_APPROVAL_MATCHED_PKG AS
2 /* $Header: aprmtchb.pls 120.84.12020000.11 2013/03/07 14:55:02 cmaredup ship $ */
3   --bug 9242891
4      G_PKG_NAME          CONSTANT VARCHAR2(30) := 'AP_APPROVAL_MATCHED_PKG';
5      G_MSG_UERROR        CONSTANT NUMBER       := FND_MSG_PUB.G_MSG_LVL_UNEXP_ERROR;
6      G_MSG_ERROR         CONSTANT NUMBER       := FND_MSG_PUB.G_MSG_LVL_ERROR;
7      G_MSG_SUCCESS       CONSTANT NUMBER       := FND_MSG_PUB.G_MSG_LVL_SUCCESS;
8      G_MSG_HIGH          CONSTANT NUMBER       := FND_MSG_PUB.G_MSG_LVL_DEBUG_HIGH;
9      G_MSG_MEDIUM        CONSTANT NUMBER       := FND_MSG_PUB.G_MSG_LVL_DEBUG_MEDIUM;
10      G_MSG_LOW           CONSTANT NUMBER       := FND_MSG_PUB.G_MSG_LVL_DEBUG_LOW;
11      G_LINES_PER_FETCH   CONSTANT NUMBER       := 1000;
12 
13      G_CURRENT_RUNTIME_LEVEL CONSTANT NUMBER       := FND_LOG.G_CURRENT_RUNTIME_LEVEL;
14      G_LEVEL_UNEXPECTED      CONSTANT NUMBER       := FND_LOG.LEVEL_UNEXPECTED;
15      G_LEVEL_ERROR           CONSTANT NUMBER       := FND_LOG.LEVEL_ERROR;
16      G_LEVEL_EXCEPTION       CONSTANT NUMBER       := FND_LOG.LEVEL_EXCEPTION;
17      G_LEVEL_EVENT           CONSTANT NUMBER       := FND_LOG.LEVEL_EVENT;
18      G_LEVEL_PROCEDURE       CONSTANT NUMBER       := FND_LOG.LEVEL_PROCEDURE;
19      G_LEVEL_STATEMENT       CONSTANT NUMBER       := FND_LOG.LEVEL_STATEMENT;
20      G_MODULE_NAME           CONSTANT VARCHAR2(100) := 'AP.PLSQL.AP_APPROVAL_MATCHED_PKG.';
21 --bug 9242891
22 
23 /*===========================================================================
24  | Private (Non Public) Procedure Specifications
25  *==========================================================================*/
26 -- 7922826 Enc Project
27 Procedure Print_Debug(
28 		p_api_name		IN VARCHAR2,
29 		p_debug_info		IN VARCHAR2);
30 
31 PROCEDURE Check_Receipt_Exception(
32               p_invoice_id          IN            NUMBER,
33               p_line_location_id    IN            NUMBER,
34               p_match_option        IN            VARCHAR2,
35               p_rcv_transaction_id  IN            NUMBER,
36               p_system_user         IN            NUMBER,
37               p_holds               IN OUT NOCOPY AP_APPROVAL_PKG.HOLDSARRAY,
38               p_holds_count         IN OUT NOCOPY AP_APPROVAL_PKG.COUNTARRAY,
39               p_release_count       IN OUT NOCOPY AP_APPROVAL_PKG.COUNTARRAY,
40               p_calling_sequence    IN            VARCHAR2);
41 
42 PROCEDURE Calc_Shipment_Qty_Billed(
43               p_invoice_id         IN            NUMBER,
44               p_line_location_id   IN            NUMBER,
45               p_match_option       IN            VARCHAR2,
46               p_rcv_transaction_id IN            NUMBER,
47               p_qty_billed         IN OUT NOCOPY NUMBER,
48         p_calling_sequence   IN            VARCHAR2);
49 
50 PROCEDURE Calc_Total_Shipment_Qty_Billed(
51               p_invoice_id         IN            NUMBER,
52               p_line_location_id   IN            NUMBER,
53               p_match_option       IN            VARCHAR2,
54               p_rcv_transaction_id IN            NUMBER,
55               p_qty_billed         IN OUT NOCOPY NUMBER,
56         p_invoice_type_lookup_code IN   VARCHAR2,
57               p_calling_sequence   IN            VARCHAR2);
58 
59 --Contract Payments: Tolerances Redesign
60 PROCEDURE Calc_Shipment_Amt_Billed(
61               p_invoice_id         IN            NUMBER,
62               p_line_location_id   IN            NUMBER,
63               p_match_option       IN            VARCHAR2,
64               p_rcv_transaction_id IN            NUMBER,
65               p_amt_billed         IN OUT NOCOPY NUMBER,
66               p_calling_sequence   IN            VARCHAR2);
67 
68 PROCEDURE Calc_Total_Shipment_Amt_Billed(
69               p_invoice_id         IN            NUMBER,
70               p_line_location_id   IN            NUMBER,
71               p_match_option       IN            VARCHAR2,
72               p_rcv_transaction_id IN            NUMBER,
73               p_amt_billed         IN OUT NOCOPY NUMBER,
74               p_invoice_type_lookup_code IN   VARCHAR2,
75               p_calling_sequence   IN            VARCHAR2);
76 
77 PROCEDURE Check_Price(
78               p_invoice_id            IN            NUMBER,
79               p_line_location_id      IN            NUMBER,
80               p_rcv_transaction_id    IN            NUMBER,
81               p_match_option          IN            VARCHAR2,
82               p_txn_uom               IN            VARCHAR2,
83               p_po_uom                IN            VARCHAR2,
84               p_item_id               IN            NUMBER,
85               p_invoice_currency_code IN            VARCHAR2,
86               p_po_unit_price         IN            NUMBER,
87               p_price_tolerance       IN            NUMBER,
88               p_system_user           IN            NUMBER,
89               p_holds                 IN OUT NOCOPY AP_APPROVAL_PKG.HOLDSARRAY,
90               p_holds_count           IN OUT NOCOPY AP_APPROVAL_PKG.COUNTARRAY,
91               p_release_count         IN OUT NOCOPY AP_APPROVAL_PKG.COUNTARRAY,
92               p_calling_sequence      IN VARCHAR2);
93 
94 PROCEDURE CHECK_AVERAGE_PRICE(
95               p_invoice_id            IN            NUMBER,
96               p_line_location_id      IN            NUMBER,
97               p_match_option          IN            VARCHAR2,
98               p_txn_uom               IN            VARCHAR2,
99               p_po_uom                IN            VARCHAR2,
100               p_item_id               IN            NUMBER,
101               p_price_tolerance       IN            NUMBER ,
102               p_po_unit_price         IN            NUMBER ,
103               p_invoice_currency_code IN            VARCHAR2,
104               p_price_error_exists    IN OUT NOCOPY VARCHAR2,
105               p_calling_sequence      IN            VARCHAR2);
106 
107 PROCEDURE Calc_Ship_Trx_Amt(
108               p_invoice_id         IN            NUMBER,
109               p_line_location_id   IN            NUMBER,
110               p_match_option       IN            VARCHAR2,
111               p_ship_trx_amt       IN OUT NOCOPY NUMBER,
112               p_calling_sequence   IN            VARCHAR2);
113 
114 PROCEDURE Calc_Ship_Total_Trx_Amt_Var(
115               p_invoice_id            IN            NUMBER,
116               p_line_location_id      IN            NUMBER,
117               p_match_option          IN            VARCHAR2,
118               p_po_price              IN            NUMBER,
119               p_ship_amount           OUT NOCOPY    NUMBER, -- 3488259 (3110072)
120               p_match_basis           IN            VARCHAR2,
121               p_ship_trx_amt_var      IN OUT NOCOPY NUMBER,
122               p_calling_sequence      IN            VARCHAR2,
123               p_org_id                IN            NUMBER); -- 5500101
124 
125 PROCEDURE Calc_Max_Rate_Var(
126               p_invoice_id           IN            NUMBER,
127               p_line_location_id     IN            NUMBER,
128               p_rcv_transaction_id   IN            NUMBER,
129               p_match_option         IN            VARCHAR2,
130               p_rate_amt_var         IN OUT NOCOPY NUMBER,
131               p_calling_sequence     IN            VARCHAR2);
132 
133 PROCEDURE Calc_Ship_Trx_Base_Amt(
134               p_invoice_id         IN            NUMBER,
135               p_line_location_id   IN            NUMBER,
136               p_rcv_transaction_id   IN            NUMBER,  /*Added for Bug 14726598 as additional fix*/
137               p_match_option       IN            VARCHAR2,
138               p_inv_curr_code      IN            VARCHAR2,
139               p_base_curr_code     IN            VARCHAR2,
140               p_ship_base_amt      IN OUT NOCOPY NUMBER,
141               p_calling_sequence   IN            VARCHAR2);
142 
143 PROCEDURE Calc_Ship_Total_Base_Amt_Var(
144               p_invoice_id           IN            NUMBER,
145               p_line_location_id     IN            NUMBER,
146               p_rcv_transaction_id   IN            NUMBER, /*Added for Bug 14726598 */
147               p_match_option         IN            VARCHAR2,
148               p_po_price             IN            NUMBER,
149               p_match_basis          IN            VARCHAR2,
150               p_inv_curr_code        IN            VARCHAR2,
151               p_base_curr_code       IN            VARCHAR2,
152               p_ship_base_amt_var    IN OUT NOCOPY NUMBER,
153               p_calling_sequence     IN            VARCHAR2);
154 
155 --
156 -- Bug 5077550
157 -- Added a new procedure to check to see if the pay item is milestone pay
158 -- item and the unit price on the invoice line should be same as that
159 -- of the PO shipment. Also the quantity should be an integer and should not
160 -- have decimals tied to it.
161 --
162 
163 FUNCTION Check_Milestone_Price_Qty(
164               p_invoice_id         IN            NUMBER,
165               p_line_location_id   IN            NUMBER,
166               p_po_unit_price      IN            NUMBER,
167               p_calling_sequence   IN            VARCHAR2) RETURN VARCHAR2;
168 
169 
170 /*===========================================================================
171  |Procedure Definitions
172  *==========================================================================*/
173 
174 
175 /*============================================================================
176  |  PUBLIC PROCEDURE  EXEC_MATCHED_VARIANCE_CHECKS
177  |
178  |  DESCRIPTION:
179  |                Procedure to calculate IPV, ERV and QV and compare the
180  |                values to the system tolerances and place or release holds
181  |                depending on the condition.
182  |
183  |  PARAMETERS
184  |      p_invoice_id - Invoice Id
185  |      p_inv_line_number - Invoice Line number
186  |      p_base_currency_code - Base Currency Code
187  |      p_sys_xrate_gain_ccid - System Exchange Rate Gain Ccid
188  |      p_sys_xrate_loss_ccid - System Exchange Rate Loss Ccid
189  |      p_ship_amt_tolerance - System Shipment Amount Tolerance
190  |      p_rate_amt_tolerance - System Rate Amount Tolerance
191  |      p_total_amt_tolerance - System Total Amount Tolerance
192  |      p_system_user - Approval Program User Id
193  |      p_holds - Holds Array
194  |      p_hold_count - Hold Count Array
195  |      p_release_count - Release Count Array
196  |      p_calling_sequence - Debugging string to indicate path of module calls
197  |                           to beprinted out upon error.
198 
199    NOTE : EXTRA_PO_ERV Calculation details:
200  | --  |-----------------------------------------------------------------+
201  | --  | EXAMPLE                                                         |
202  | --  |   DOC           QTY   UOM    EXCH.RATE   UNIT_PRICE BASE_AMT    |
203  | --  |   po             2    dozen  0.5         10         $10         |
204  | --  |   rect           2    dozen  0.55        10         $11         |
205  | --  |  inv(to rect)   2    dozen  0.7         10         $14          |
206  | --  |  when Accrue on Receipt = 'N' and match to receipt              |
207  | --  |  po creation - encumber $10                                     |
208  | --  |  rect creation - encumber 0                                     |
209  | --  |  inv creation - unencumber PO type - $14- $4 = $10              |
210  | --  |                encumber INV type - qty * rxtn_rate * pirce = $11|
211  | --  |  po_erv = (inv_rate - po_rate) * qty_invoiced * po_price = $4   |
212  | --  |  erv = (inv_rate -rxtn_rate ) * qty_invoiced * rxtn_price = $3  |
213  | --  |  unencumbered po amt = po_qty * po_price * po_rate              |
214  | --  |                      = inv_rate * qty * unit_price - po_erv     |
215  | --  |  when Accrue on Receipt = 'N' and PO encumb.type=INV encumb.type|
216  | --  |  actual_encumbrance_amt = po_erv - erv (match for receipt )     |
217  | --  |-----------------------------------------------------------------+
218  |
219  |   PROGRAM FLOW
220  |
221  |  KNOWN ISSUES:
222  |
223  |  NOTES:
224  |  --------------------------------------------------------------------------
225  |  --                                                                      --
226  |  -- Meaning of dist_enc_flag:                                            --
227  |  --   Y: Regular line, has already been successfully encumbered by AP.   --
228  |  --   W: Regular line, has been encumbered in advisory mode even though  --
229  |  --      insufficient funds existed.                                     --
230  |  --   H: Line has not been encumbered yet, since it was put on hold.     --
231  |  --   N or Null : Line not yet seen by this code.                        --
232  |  --   D: Same as Y for reversal distribution line.                       --
233  |  --   X: Same as W for reversal distribution line.                       --
234  |  --   P: Same as H for reversal distribution line.                       --
235  |  --   R: Same as N for reversal distribution line.                       --
236  |  -- 'R' is currently IGNORED by all approval code because it is part     --
237  |  -- of a reversal pair.  Since they cancel each other out, it doesn't    --
238  |  -- need to be seen by this code.                                        --
239  |  --------------------------------------------------------------------------
240  |
241  |  MODIFICATION HISTORY
242  |  Date         Author             Description of Change
243  |
244  *==========================================================================*/
245 
246 PROCEDURE Exec_Matched_Variance_Checks(
247               p_invoice_id                IN NUMBER,
248               p_inv_line_number           IN NUMBER,
249               p_base_currency_code        IN VARCHAR2,
250               p_inv_currency_code         IN VARCHAR2,
251               p_sys_xrate_gain_ccid       IN NUMBER,
252               p_sys_xrate_loss_ccid       IN NUMBER,
253               p_system_user               IN NUMBER,
254               p_holds               IN OUT NOCOPY AP_APPROVAL_PKG.HOLDSARRAY,
255               p_hold_count          IN OUT NOCOPY AP_APPROVAL_PKG.COUNTARRAY,
256               p_release_count       IN OUT NOCOPY AP_APPROVAL_PKG.COUNTARRAY,
257               p_calling_sequence    IN VARCHAR2) IS
258 
259   -- Project LCM 7588322
260   l_lcm_enabled                   VARCHAR2(1) := 'N';
261   l_rcv_transaction_id            NUMBER;
262   l_lcm_account_id                NUMBER;
263   l_tax_variance_account_id       NUMBER;
264   l_def_charges_account_id        NUMBER;
265   l_exchange_variance_account_id  NUMBER;
266   l_inv_variance_account_id       NUMBER;
267   l_ipv_exsts_flg VARCHAR2(1) := 'N';  --Introduced for bug#9252266
268 
269 
270 
271   CURSOR Distribution_Cur IS
272     SELECT   D.Invoice_Distribution_Id
273             ,D.line_type_lookup_code
274             ,D.dist_code_combination_id
275             ,D.distribution_line_number
276             ,D.related_id
277             ,D.reversal_flag
278             ,DECODE(l_lcm_enabled,'Y',l_inv_variance_account_id,DECODE(PD.destination_type_code,
279                    'EXPENSE', DECODE(PD.accrue_on_receipt_flag,
280                                      'Y', PD.code_combination_id,
281                                      D.dist_code_combination_id),
282                   PD.variance_account_id))      -- l_po_variance_ccid
283            ,PD.destination_type_code            -- l_po_destination_type
284            ,NVL(PD.accrue_on_receipt_flag,'N')  -- l_accrue_on_receipt_flag
285      ,D.matched_uom_lookup_code           -- rtxn_uom
286      ,PL.unit_meas_lookup_code    -- po_uom
287      ,nvl(PLL.match_option, 'P')    -- match_option
288          ,RSL.item_id                         -- rtxn_item_id
289      ,nvl(D.quantity_invoiced, 0)          -- qty_invoiced
290      ,D.corrected_invoice_dist_id          -- corrected_invoice_dist_id
291      ,decode(I.invoice_currency_code,
292              p_base_currency_code,1,
293              nvl(PD.rate,1))              -- po_rate
294            ,nvl(I.exchange_rate, 1)    -- inv_rate
295      ,nvl(PLL.price_override,0)          -- po_price
296            ,PLL.matching_basis                  -- matching basis./*Amount Based Matching*/
297     FROM    ap_invoice_distributions D,
298             ap_invoices I,
299             po_distributions PD,
300       po_line_locations PLL,
301       po_lines PL,
302       rcv_transactions RTXN,
303       rcv_shipment_lines RSL,
304       ap_invoice_lines_all ail
305     WHERE  I.invoice_id = p_invoice_id
306     AND    I.invoice_id = D.invoice_id
307     AND    D.invoice_line_number = p_inv_line_number
308     AND    D.invoice_id= ail.invoice_id
309     AND    D.invoice_line_number=ail.line_number
310     AND    D.po_distribution_id = PD.po_distribution_id
311     AND    PL.po_line_id = PD.po_line_id
312     AND    PLL.line_location_id = PD.line_location_id
313     AND    NVL(D.match_status_flag,'N') IN ('N', 'S', 'A')
314     AND    NVL(D.posted_flag, 'N') IN ('N', 'P')
315     AND    NVL(D.encumbered_flag, 'N') not in ('Y','R') --bug6921447
316     --Retropricing: The ERV/IPV calculation is only done for
317     --RetroItem with match_type 'PO_PRICE_ADJUSTMENT'
318     --Exec_Matched_Variance_Checks is not called for lines with
319     --match_type 'ADJUSTMENT_CORRECTION'
320     --Modified below condition for bug#14360581
321     AND    (D.line_type_lookup_code IN ('ITEM', 'ACCRUAL',
322                                        'RETROEXPENSE', 'RETROACCRUAL')
323             OR (D.line_type_lookup_code ='IPV'
324                 AND D.corrected_invoice_dist_id IS NOT NULL))
325      --Bug#10416960
326     AND NVL(D.dist_match_type,'NOT_MATCHED') <> 'ADJUSTMENT_CORRECTION'
327     AND (  (NVL(D.dist_match_type,'NOT_MATCHED') = 'PO_PRICE_ADJUSTMENT'
328 	    AND ail.line_source = 'PO PRICE ADJUSTMENT')
329 	 OR NVL(D.dist_match_type,'NOT_MATCHED') <> 'PO_PRICE_ADJUSTMENT' )
330     --End 10416960
331     AND    D.rcv_transaction_id = RTXN.transaction_id (+)
332     AND    RTXN.shipment_line_id = RSL.shipment_line_id (+)
333     ORDER BY D.po_distribution_id, D.distribution_line_number;
334 
335      --Bug 9242891 added new cursor for ERV creation on retainage release inv
336     --added line_type_lookup_code RETAINAGE condition and relevant column
337     --changes. Basic assumptions for this fix: NO IPV,ITEM,ACCRUAL line type can
338     --be added in retainage release invoice. Retropricing/corrections are not allowed
339     --once a retainage release has been issued.
340     CURSOR Retainage_Distribution_Cur IS
341     SELECT   D.Invoice_Distribution_Id
342             ,D.line_type_lookup_code
343             ,D.dist_code_combination_id
344             ,D.distribution_line_number
345             ,D.related_id
346             ,D.reversal_flag
347             ,DECODE(l_lcm_enabled,'Y',l_inv_variance_account_id,DECODE(PD.destination_type_code,
348                    'EXPENSE', DECODE(PD.accrue_on_receipt_flag,
349                                      'Y', PD.code_combination_id,
350                                      D.dist_code_combination_id),
351                   PD.variance_account_id))      -- l_po_variance_ccid
352            ,PD.destination_type_code            -- l_po_destination_type
353            ,NVL(PD.accrue_on_receipt_flag,'N')  -- l_accrue_on_receipt_flag
354      ,D.matched_uom_lookup_code           -- rtxn_uom
355      ,PL.unit_meas_lookup_code    -- po_uom
356      ,nvl(PLL.match_option, 'P')    -- match_option
357          ,RSL.item_id                         -- rtxn_item_id
358      ,nvl(D.quantity_invoiced, 0)          -- qty_invoiced
359      ,D.corrected_invoice_dist_id          -- corrected_invoice_dist_id
360      ,decode(I.invoice_currency_code,
361              p_base_currency_code,1,
362              nvl(retain_I.exchange_rate,1))              --bug 9242891 retained_inv_rate
363            ,nvl(I.exchange_rate, 1)    -- inv_rate
364      ,nvl(PLL.price_override,0)          -- po_price
365            ,PLL.matching_basis                  -- matching basis./*Amount Based Matching*/
366     FROM    ap_invoice_distributions D, --retainage release inv dists
367             ap_invoice_distributions retain_D, --bug 9242891 retainage invoice dist
368             ap_invoices I, --retainage release invoice
369             ap_invoices retain_I, --bug 9242891 retainage invoice
370             po_distributions PD,
371       po_line_locations PLL,
372       po_lines PL,
373       rcv_transactions RTXN,
374       rcv_shipment_lines RSL
375     WHERE  I.invoice_id = p_invoice_id
376     AND    I.invoice_type_lookup_code = 'RETAINAGE RELEASE' --bug 9242891
377     AND    I.invoice_id = D.invoice_id
378     AND    D.retained_invoice_dist_id = retain_D.Invoice_Distribution_Id --bug 9242891
379     AND    retain_I.invoice_id = retain_D.invoice_id --bug 9242891
380     AND    D.invoice_line_number = p_inv_line_number
381     AND    D.po_distribution_id = PD.po_distribution_id
382     AND    PL.po_line_id = PD.po_line_id
383     AND    PLL.line_location_id = PD.line_location_id
384     AND    NVL(D.match_status_flag,'N') IN ('N', 'S', 'A')
385     AND    NVL(D.posted_flag, 'N') IN ('N', 'P')
386     AND    NVL(D.encumbered_flag, 'N') not in ('Y','R') --bug6921447
387     --Retropricing: The ERV/IPV calculation is only done for
388     --RetroItem with match_type 'PO_PRICE_ADJUSTMENT'
389     --Exec_Matched_Variance_Checks is not called for lines with
390     --match_type 'ADJUSTMENT_CORRECTION'
391     AND    D.line_type_lookup_code = 'RETAINAGE'  --bug 9242891
392     AND    D.retained_invoice_dist_id is not NULL --bug 9242891
393     AND    D.rcv_transaction_id = RTXN.transaction_id (+)
394     AND    RTXN.shipment_line_id = RSL.shipment_line_id (+)
395     ORDER BY D.po_distribution_id, D.distribution_line_number;
396 
397     CURSOR Check_Variance_Cur(
398                x_invoice_distribution_id IN NUMBER,
399                x_variance_type           IN VARCHAR2) IS
400     SELECT D.Invoice_Distribution_Id,
401            NVL(D.amount, 0),
402            NVL(D.base_amount, D.amount)
403       FROM ap_invoice_distributions D
404      WHERE D.related_id = x_invoice_distribution_id
405        AND D.line_type_lookup_code = x_variance_type;
406 
407 
408   l_invoice_distribution_id
409       ap_invoice_distributions.invoice_distribution_id%TYPE;
410   l_reversal_flag
411       ap_invoice_distributions.reversal_flag%TYPE;
412   l_distribution_line_number
413       ap_invoice_distributions.distribution_line_number%TYPE;
414   l_dist_code_combination_id
415       ap_invoice_distributions.dist_code_combination_id%TYPE;
416   l_related_id
417       ap_invoice_distributions.related_id%TYPE;
418   l_amount
419       ap_invoice_distributions.amount%TYPE;
420   l_base_amount
421       ap_invoice_distributions.base_amount%TYPE;
422   l_ipv_distribution_id
423       ap_invoice_distributions.invoice_distribution_id%TYPE := -1;
424   l_erv_distribution_id
425       ap_invoice_distributions.invoice_distribution_id%TYPE := -1;
426   l_line_type_lookup_code
427       ap_invoice_distributions.line_type_lookup_code%TYPE;
428 
429   l_po_variance_ccid        NUMBER;
430   l_accrue_on_receipt_flag  VARCHAR2(1);
431   l_destination_type        VARCHAR2(25);
432 
433   l_ipv                     NUMBER;
434   l_bipv                    NUMBER;
435   l_erv                     NUMBER;
436   l_amount_holder           NUMBER;
437   l_erv_ccid                NUMBER(15);
438   l_erv_acct_invalid_exists VARCHAR2(1) := 'N';
439   l_variance_success        BOOLEAN := FALSE;
440   l_po_uom        PO_LINES.UNIT_MEAS_LOOKUP_CODE%TYPE;
441   l_rtxn_uom        PO_LINES.UNIT_MEAS_LOOKUP_CODE%TYPE;
442   l_match_option      PO_LINE_LOCATIONS.MATCH_OPTION%TYPE;
443   l_qty_invoiced      AP_INVOICE_DISTRIBUTIONS.QUANTITY_INVOICED%TYPE;
444   l_rtxn_item_id      RCV_SHIPMENT_LINES.ITEM_ID%TYPE;
445   l_corrected_invoice_dist_id AP_INVOICE_DISTRIBUTIONS.INVOICE_DISTRIBUTION_ID%TYPE;
446   l_uom_conv_rate      NUMBER := NULL;
447   l_inv_qty        AP_INVOICE_DISTRIBUTIONS.QUANTITY_INVOICED%TYPE :=0;
448   l_inv_rate        AP_INVOICES.EXCHANGE_RATE%TYPE := 0;
449   l_po_rate        AP_INVOICES.EXCHANGE_RATE%TYPE := 0;
450   l_po_price        PO_LINE_LOCATIONS.PRICE_OVERRIDE%TYPE := 0;
451   l_po_erv        NUMBER := 0;
452   l_extra_po_erv      AP_INVOICE_DISTRIBUTIONS.EXTRA_PO_ERV%TYPE ;
453 
454   l_key_value               NUMBER;
455   l_max_dist_line_number AP_INVOICE_DISTRIBUTIONS.DISTRIBUTION_LINE_NUMBER%TYPE;
456 
457   l_debug_loc               VARCHAR2(30) := 'Exec_Matched_Variance_Checks';
458   l_curr_calling_sequence   VARCHAR2(2000);
459   l_debug_info              VARCHAR2(2000);
460   l_debug_context           VARCHAR2(2000);
461   l_match_basis             PO_LINE_LOCATIONS.matching_basis%TYPE; /*Amount Based Matching */
462   l_cnt                     PLS_INTEGER DEFAULT 0; --bug 9242891
463   l_api_name                VARCHAR2(100); --Bug 9242891
464 
465 BEGIN
466 
467   l_api_name := 'Exec_Matched_Variance_Checks'; --Bug 9242891
468 
469   l_curr_calling_sequence := 'AP_APPROVAL_MATCHED_PKG.'||l_debug_loc||'<-'||
470                               p_calling_sequence;
471   --bug 9242891
472     IF (G_LEVEL_STATEMENT >= G_CURRENT_RUNTIME_LEVEL) THEN
473        FND_LOG.STRING(G_LEVEL_STATEMENT,G_MODULE_NAME||l_api_name,'AP_APPROVAL_MATCHED_PKG.Exec_Matched_Variance_Checks(+)');
474     END IF; --bug 9242891
475 
476   IF ( AP_APPROVAL_PKG.g_debug_mode = 'Y' ) THEN
477     g_debug_mode := 'Y';
478   END IF;
479 
480   IF (g_debug_mode = 'Y') THEN
481     AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
482     AP_Debug_Pkg.Print(g_debug_mode, 'Invoice id: '|| TO_CHAR(p_invoice_id));
483     AP_Debug_Pkg.Print(g_debug_mode, 'Invoice line number: '||
484                        TO_CHAR(p_inv_line_number));
485     AP_Debug_Pkg.Print(g_debug_mode, 'base currency code: '||
486                        p_base_currency_code);
487     AP_Debug_Pkg.Print(g_debug_mode, 'invoice currency code: '||
488                        p_inv_currency_code);
489     AP_Debug_Pkg.Print(g_debug_mode, 'sys gain ccid: '||
490                        TO_CHAR(p_sys_xrate_gain_ccid));
491     AP_Debug_Pkg.Print(g_debug_mode, 'sys loss ccid: '||
492                        TO_CHAR(p_sys_xrate_loss_ccid));
493   END IF;
494 
495 
496   -- Project LCM 7588322
497 
498   BEGIN
499    SELECT ail.rcv_transaction_id
500 	 INTO   l_rcv_transaction_id
501 	 FROM   ap_invoice_lines ail
502 	 WHERE  ail.invoice_id  = p_invoice_id
503 	 AND    ail.line_number = p_inv_line_number;
504   EXCEPTION
505    WHEN NO_DATA_FOUND THEN NULL;
506   END;
507 
508   BEGIN
509 	 SELECT 'Y'
510 	 INTO   l_lcm_enabled
511 	 FROM   RCV_TRANSACTIONS
512 	 WHERE  TRANSACTION_ID = l_rcv_transaction_id
513 	 AND    LCM_SHIPMENT_LINE_ID IS NOT NULL;
514   EXCEPTION
515    WHEN NO_DATA_FOUND THEN NULL;
516   END;
517 
518 	 IF(l_lcm_enabled = 'Y') THEN
519 	   RCV_UTILITIES.Get_RtLcmInfo(
520 	              p_rcv_transaction_id           => l_rcv_transaction_id,
521 	              x_lcm_account_id               => l_lcm_account_id,
522 								x_tax_variance_account_id      => l_tax_variance_account_id,
523 								x_def_charges_account_id       => l_def_charges_account_id,
524 								x_exchange_variance_account_id => l_exchange_variance_account_id,
525 								x_inv_variance_account_id      => l_inv_variance_account_id
526 								);
527 
528      END IF;
529 	 -- End Project LCM 7588322
530 
531 
532 	/*------------------------------------------------------------------+
533     |  Open Cursor and initialize data for all distribution Line and   |
534     |  loop through for calculation                                    |
535     +-----------------------------------------------------------------*/
536 
537   --bug 9242891 select added to determine which cursor to open.
538       SELECT COUNT(*)
539        INTO l_cnt
540       FROM AP_INVOICES_all ai
541       WHERE ai.invoice_id = p_invoice_id
542       AND ai.invoice_type_lookup_code = 'RETAINAGE RELEASE';
543  --bug 9242891
544 
545   IF l_cnt = 0 then --bug 9242891
546 
547   l_debug_info := 'Open Distribution_Cur';
548   IF (g_debug_mode = 'Y') THEN
549         AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
550   END IF;
551 
552    --bug 9242891
553     IF (G_LEVEL_STATEMENT >= G_CURRENT_RUNTIME_LEVEL) THEN
554        FND_LOG.STRING(G_LEVEL_STATEMENT,G_MODULE_NAME||l_api_name,l_debug_info);
555     END IF; --bug 9242891
556 
557   OPEN Distribution_Cur;
558 
559   ELSE --bug 9242891
560 
561    l_debug_info := 'Open Retainage_Distribution_Cur';
562    IF (g_debug_mode = 'Y') THEN
563        AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
564    END IF;
565 
566     --bug 9242891
567     IF (G_LEVEL_STATEMENT >= G_CURRENT_RUNTIME_LEVEL) THEN
568        FND_LOG.STRING(G_LEVEL_STATEMENT,G_MODULE_NAME||l_api_name,l_debug_info);
569     END IF; --bug 9242891
570 
571    OPEN Retainage_Distribution_Cur;
572 
573   END IF; --bug 9242891
574 
575   LOOP
576   IF l_cnt = 0 then --bug 9242891
577 
578     FETCH Distribution_Cur
579      INTO   l_invoice_distribution_id
580            ,l_line_type_lookup_code
581            ,l_dist_code_combination_id
582            ,l_distribution_line_number
583            ,l_related_id
584            ,l_reversal_flag
585            ,l_po_variance_ccid
586            ,l_destination_type
587            ,l_accrue_on_receipt_flag
588      ,l_rtxn_uom
589      ,l_po_uom
590      ,l_match_option
591      ,l_rtxn_item_id
592      ,l_qty_invoiced
593      ,l_corrected_invoice_dist_id
594      ,l_po_rate
595      ,l_inv_rate
596      ,l_po_price
597            ,l_match_basis;
598 
599     EXIT WHEN Distribution_Cur%NOTFOUND;
600   ELSE  --bug 9242891
601     l_debug_info := 'Fetch Retainage_Distribution_Cur';
602     IF (g_debug_mode = 'Y') THEN
603      AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
604     END IF;
605 
606     --bug 9242891
607     IF (G_LEVEL_STATEMENT >= G_CURRENT_RUNTIME_LEVEL) THEN
608        FND_LOG.STRING(G_LEVEL_STATEMENT,G_MODULE_NAME||l_api_name,l_debug_info);
609     END IF; --bug 9242891
610 
611     FETCH Retainage_Distribution_Cur
612      INTO   l_invoice_distribution_id
613            ,l_line_type_lookup_code
614            ,l_dist_code_combination_id
615            ,l_distribution_line_number
616            ,l_related_id
617            ,l_reversal_flag
618            ,l_po_variance_ccid
619            ,l_destination_type
620            ,l_accrue_on_receipt_flag
621            ,l_rtxn_uom
622            ,l_po_uom
623            ,l_match_option
624            ,l_rtxn_item_id
625            ,l_qty_invoiced
626            ,l_corrected_invoice_dist_id
627            ,l_po_rate
628            ,l_inv_rate
629            ,l_po_price
630            ,l_match_basis;
631 
632 
633       EXIT WHEN Retainage_Distribution_Cur%NOTFOUND;
634 
635    END IF;  --bug 9242891
636 
637 
638     -- bug#13696938 added the NVL condition on reversal flag for distributions upgraded from 11i.
639     IF (NVL(l_reversal_flag,'N') <> 'Y') THEN       -- 13781647 added NVL condition to reversal flag in case of upgraded PO matched distributions.
640 
641    /*-----------------------------------------------------------------+
642     | if distribution is not a reversal (bipv, ipv, and erv are       |
643     | negated in reversal lines when the reversals are created )      |
644     +-----------------------------------------------------------------*/
645 
646       IF (g_debug_mode = 'Y') THEN
647         l_debug_info := 'Calculate IPV and ERV';
648         AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
649       END IF;
650 
651    /*-----------------------------------------------------------------+
652     | Step 1 - Open check variance cursor to check if ERV already     |
653     |          exists. Otherwise l_erv_distribution_id = -1            |
654     +-----------------------------------------------------------------*/
655       OPEN Check_Variance_Cur(
656                l_invoice_distribution_id,
657                'ERV');
658       FETCH Check_Variance_Cur
659       INTO l_erv_distribution_id,
660            l_amount_holder,
661            l_erv;
662       IF Check_Variance_Cur%NOTFOUND THEN
663         l_erv_distribution_id := -1;
664         l_erv := 0;
665       END IF;
666       CLOSE Check_Variance_Cur;
667 
668    /*-----------------------------------------------------------------+
669     | Step 2 - Open check variance cursor to check if IPV already     |
670     |          exists for non-IPV type line. If not exists,           |
671     |          l_ipv_distribution_id = -1                             |
672     +-----------------------------------------------------------------*/
673       IF ( l_line_type_lookup_code <> 'IPV' ) THEN
674         OPEN Check_Variance_Cur(
675                  l_invoice_distribution_id,
676                  'IPV');
677         FETCH Check_Variance_Cur
678         INTO l_ipv_distribution_id,
679              l_ipv,
680              l_bipv;
681         IF Check_Variance_Cur%NOTFOUND THEN
682           l_ipv_distribution_id := -1;
683           l_ipv := 0;
684           l_bipv := 0;
685         END IF;
686 
687        --Start of bug#9252266
688 	IF (Check_Variance_Cur%ROWCOUNT <>0)THEN
689           l_ipv_exsts_flg := 'Y';
690         ELSE
691           l_ipv_exsts_flg := 'N';
692         END IF;
693        --End bug#9252266
694 
695         CLOSE Check_Variance_Cur;
696       END IF;
697 
698    /*-----------------------------------------------------------------+
699     | Step 3 - Calculate Variance                                     |
700     +-----------------------------------------------------------------*/
701 
702       l_variance_success := AP_INVOICE_DISTRIBUTIONS_PKG.Calculate_Variance(
703                                   l_invoice_distribution_id,
704                                   NULL,
705                                   l_amount,
706                                   l_base_amount,
707                                   l_ipv,
708                                   l_bipv,
709                                   l_erv,
710                                   l_debug_info,
711                                   l_debug_context,
712                                   l_curr_calling_sequence);
713 
714       IF (g_debug_mode = 'Y') THEN
715         l_debug_info := 'After calling Calculate_variance' || l_debug_info;
716         AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
717         AP_Debug_Pkg.Print(g_debug_mode, l_debug_context );
718       END IF;
719 
720       /*--------------------------------------------------------------+
721       | Step 3.1: Calculate extra_po_erv for the ITEM distribution    |
722       |            or IPV distribution of a correction distribution.  |
723       +--------------------------------------------------------------*/
724 
725       --ETAX: Validation.
726       --Added the following logic to calculate extra_po_erv along
727       --with IPV and ERV and store it in the new column extra_po_erv
728       --bugfix:3881673
729       IF (l_line_type_lookup_code IN ('ITEM','ACCRUAL') OR
730           (l_line_type_lookup_code ='IPV'
731             AND l_corrected_invoice_dist_id IS NOT NULL)) THEN
732          IF (l_accrue_on_receipt_flag = 'N' and l_match_option = 'R') THEN
733 
734             IF (g_debug_mode = 'Y') THEN
735          l_debug_info := l_debug_loc ||
736                         'receipt match line when accrue on receipt is N' ||
737                         'calculate po_erv';
738          AP_Debug_Pkg.Print(g_debug_mode, l_debug_info);
739       END IF;
740 
741             -- Amount Based Matching
742             IF l_match_basis = 'QUANTITY' THEN
743 
744               IF (l_po_uom <> l_rtxn_uom) THEN
745           l_uom_conv_rate := po_uom_s.po_uom_convert (
746                                 l_rtxn_uom,
747               l_po_uom,
748               l_rtxn_item_id);
749 
750                 l_inv_qty :=  round(l_qty_invoiced *l_uom_conv_rate, 15);
751               ELSE
752           l_inv_qty := l_qty_invoiced;
753         END IF;
754 
755         l_po_erv := AP_UTILITIES_PKG.ap_round_currency(
756                      (( l_inv_rate - l_po_rate) * l_inv_qty
757                * l_po_price),
758             p_base_currency_code);
759 
760             ELSE  -- Amount Based Matching
761 
762               l_po_erv := AP_UTILITIES_PKG.ap_round_currency(
763                            (( l_inv_rate - l_po_rate) * l_amount),
764                               p_base_currency_code);
765 
766             END IF;  -- End l_matching_basis. /* Amount Based Matching */
767 
768          END IF; /*l_accrue_on_receipt_flag = 'N' and l_match_option = 'R'*/
769 
770       END IF; /*l_line_type_lookup_code  ='ITEM' OR ...*/
771 
772    /*-----------------------------------------------------------------+
773     | Step 4 - Process Variance Line                                  |
774     +-----------------------------------------------------------------*/
775 
776       IF ( l_variance_success ) THEN
777 
778    /*--------------------------------------------------------------+
779    |  Step 4.1a - Since variance exists, calculate the extra_po_erv|
780    ---------------------------------------------------------------*/
781 
782   --ETAX: Validation
783   IF (l_accrue_on_receipt_flag = 'N' and l_match_option = 'R') THEN
784            l_extra_po_erv := l_po_erv - nvl(l_erv,0);
785         END IF;
786 
787    /*-----------------------------------------------------------------+
788     | Step 4.1.a - Variance exists and get variance ccid information  |
789     |              call API to get ERV ccid                           |
790     |              ipv ccid is either charge acct ccid or po variance |
791     |              ccid                                               |
792     +-----------------------------------------------------------------*/
793 
794         IF (g_debug_mode = 'Y') THEN
795           l_debug_info := 'Exec_Matched_Variance_Checks - variance exists ' ||
796                           'calling get_erv_ccid ';
797           AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
798         END IF;
799 
800         IF ( NVL(l_erv,0 ) <> 0 ) THEN
801 
802      --Etax : Validation project
803      --Removed the logic to flexbuild the erv_ccid when automatic
804            --offsets is turned on
805 
806      --bugfix:5718702 added the NULL assignment stmt so that the
807      --variable doesn't carry over the previous distribution's erv_ccid
808      l_erv_ccid := NULL;
809 
810 
811 			 -- Project LCM 7588322
812 			 IF (l_lcm_enabled = 'Y') THEN
813 			   l_erv_ccid := l_exchange_variance_account_id;
814 			 ELSE
815 		           AP_FUNDS_CONTROL_PKG.GET_ERV_CCID(
816 		                p_sys_xrate_gain_ccid,
817 		                p_sys_xrate_loss_ccid,
818 		                l_dist_code_combination_id,
819 		                l_po_variance_ccid,
820 		                l_destination_type,
821 		                l_invoice_distribution_id,
822 		                l_related_id,
823 		                l_erv,
824 		                l_erv_ccid,
825 		                l_curr_calling_sequence);
826 		     END IF;
827 
828         END IF;
829 
830    /*-----------------------------------------------------------------+
831     | Step 4.1.b - Check if INVALID ERV CCID HOLD needs to be put     |
832     +-----------------------------------------------------------------*/
833 
834         IF ( (l_erv <> 0) AND (l_erv_ccid = -1)) THEN
835           l_erv_acct_invalid_exists := 'Y';
836         END IF;
837 
838    /*-----------------------------------------------------------------+
839     | Step 4.1.c - Process IPV variance line for distribution         |
840     +-----------------------------------------------------------------*/
841 
842         IF ( l_line_type_lookup_code <> 'IPV' ) THEN
843 
844 	--Introduced 'OR' condition for bug#9252266
845           IF (( l_ipv <> 0 ) OR l_ipv_exsts_flg = 'Y') THEN
846 
847 	    ------------------------------------------------------------
848             -- Case A - There is IPV Variance
849             ------------------------------------------------------------
850             IF ( l_ipv_distribution_id = -1 ) THEN
851               -----------------------------------------------------------
852               -- Case A.1 - There is no existing IPV line - insert
853               -----------------------------------------------------------
854               IF (g_debug_mode = 'Y') THEN
855                 l_debug_info := 'Non reversal dist line - Insert IPV line';
856                 AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
857               END IF;
858 
859               l_related_id := l_invoice_distribution_id;
860 
861         l_max_dist_line_number := AP_INVOICE_LINES_PKG.get_max_dist_line_num(
862                                       p_invoice_id,
863                                 p_inv_line_number) + 1;
864 
865               INSERT INTO ap_invoice_distributions (
866                     invoice_id,
867                     invoice_line_number,
868                     distribution_class,
869                     invoice_distribution_id,
870                     dist_code_combination_id,
871                     last_update_date,
872                     last_updated_by,
873                     accounting_date,
874                     period_name,
875                     set_of_books_id,
876                     amount,
877                     description,
878                     type_1099,
879                     posted_flag,
880                     batch_id,
881                     quantity_invoiced,
882                     unit_price,
883                     match_status_flag,
884                     attribute_category,
885                     attribute1,
886                     attribute2,
887                     attribute3,
888                     attribute4,
889                     attribute5,
890                     assets_addition_flag,
891                     assets_tracking_flag,
892                     distribution_line_number,
893                     line_type_lookup_code,
894                     po_distribution_id,
895                     base_amount,
896                     encumbered_flag,
897                     accrual_posted_flag,
898                     cash_posted_flag,
899                     last_update_login,
900                     creation_date,
901                     created_by,
902                     attribute11,
903                     attribute12,
904                     attribute13,
905                     attribute14,
906                     attribute6,
907                     attribute7,
908                     attribute8,
909                     attribute9,
910                     attribute10,
911                     attribute15,
912                     final_match_flag,
913                     expenditure_item_date,
914                     expenditure_organization_id,
915                     expenditure_type,
916                     project_id,
917                     task_id,
918         award_id,
919         pa_addition_flag, --4591003
920                     quantity_variance,
921                     base_quantity_variance,
922                     packet_id,
923                     reference_1,
924                     reference_2,
925                     program_application_id,
926                     program_id,
927                     program_update_date,
928                     request_id,
929                     rcv_transaction_id,
930                     dist_match_type,
931                     global_attribute_category,
932                     global_attribute1,
933                     global_attribute2,
934                     global_attribute3,
935                     global_attribute4,
936                     global_attribute5,
937                     global_attribute6,
938                     global_attribute7,
939                     global_attribute8,
940                     global_attribute9,
941                     global_attribute10,
942                     global_attribute11,
943                     global_attribute12,
944                     global_attribute13,
945                     global_attribute14,
946                     global_attribute15,
947                     global_attribute16,
948                     global_attribute17,
949                     global_attribute18,
950                     global_attribute19,
951                     global_attribute20,
952                     org_id,
953                     related_id,
954                     asset_book_type_code,
955                     asset_category_id,
956                     accounting_event_id,
957                     cancellation_flag ,
958               --Freight and Special Charges
959                     rcv_charge_addition_flag,
960                     awt_group_id,  -- bug6843734
961 	   	    pay_awt_group_id, -- bug8222382
962 		    inventory_transfer_status,  /*Bug#11067286 */
963 		    income_tax_region  --bug 12908372
964 		    )
965               (SELECT invoice_id,
966                     invoice_line_number,
967                     distribution_class,
968                     ap_invoice_distributions_s.NEXTVAL, -- distribution_id
969                     l_Po_variance_ccid, -- dist_code_combination_id
970                     SYSDATE, -- last_update_date
971                     p_system_user, -- last_updated_by
972                     accounting_date, -- accounting_date
973                     period_name,  -- period_name
974                     Set_Of_Books_Id, -- set_of_book_id
975                     l_ipv,  -- Amount
976                     Description,  -- description
977                     Type_1099, -- type_1099
978                     'N',       -- posted_flag
979                     batch_id,
980                     NULL, -- quantity_invoiced
981                     NULL, -- unit_price,
982                     'N',  -- match_status_flag
983                     attribute_category,
984                     attribute1,
985                     attribute2,
986                     attribute3,
987                     attribute4,
988                     attribute5,
989                     'U', -- assets_addition_flag
990                     assets_tracking_flag,
991                     l_max_dist_line_number,  --distribution_line_number,
992                     'IPV', --line_type_lookup_code,
993                     po_distribution_id,
994                     l_bipv, --base_amount,
995                     'N', -- encumbered_flag
996                     'N', -- accrual_posted_flag
997                     'N', -- cash_posted_flag
998                     fnd_global.login_id, -- last_update_login
999                     SYSDATE, --Creation_Date,
1000                     FND_GLOBAL.user_id, --Created_By,
1001                     attribute11,
1002                     attribute12,
1003                     attribute13,
1004                     attribute14,
1005                     attribute6,
1006                     attribute7,
1007                     attribute8,
1008                     attribute9,
1009                     attribute10,
1010                     attribute15,
1011                     final_match_flag,
1012                     expenditure_item_date,
1013                     expenditure_organization_id,
1014                     expenditure_type,
1015                     project_id,
1016                     task_id,
1017                     award_id,
1018 		    decode(project_id,NULL,'E','N'), --Modified for bug#9504423 pa_addition_flag
1019 	              -- pa_addition_flag, --4591003
1020                     NULL, -- quantity_variance,
1021                     NULL, -- base_quantity_variance,
1022                     NULL, -- packet_id
1023                     reference_1,
1024                     reference_2,
1025                     FND_GLOBAL.prog_appl_id, -- program_application_id
1026                     FND_GLOBAL.conc_program_id, -- program_id
1027                     SYSDATE, -- program_update_date
1028                     FND_GLOBAL.conc_request_id, --request_id
1029                     rcv_transaction_id,
1030                     dist_match_type,
1031                     global_attribute_category,
1032                     global_attribute1,
1033                     global_attribute2,
1034                     global_attribute3,
1035                     global_attribute4,
1036                     global_attribute5,
1037                     global_attribute6,
1038                     global_attribute7,
1039                     global_attribute8,
1040                     global_attribute9,
1041                     global_attribute10,
1042                     global_attribute11,
1043                     global_attribute12,
1044                     global_attribute13,
1045                     global_attribute14,
1046                     global_attribute15,
1047                     global_attribute16,
1048                     global_attribute17,
1049                     global_attribute18,
1050                     global_attribute19,
1051                     global_attribute20,
1052                     org_id,
1053                     l_related_id, --related_id,
1054                     asset_book_type_code,
1055                     asset_category_id,
1056                     NULL,        -- accounting_event_id
1057                     cancellation_flag ,
1058         'N',   --rcv_charge_addition_flag
1059                     awt_group_id,  -- bug6843734
1060 					pay_awt_group_id, -- bug8222382
1061                     'N',  --Bug#11067286
1062 		    income_tax_region  --bug 12908372
1063                  FROM ap_invoice_distributions
1064                 WHERE invoice_distribution_id = l_invoice_distribution_id );
1065 
1066 
1067             ELSE
1068               ------------------------------------------------------------
1069               -- Case A.2 - There is an existing IPV line - update
1070               ------------------------------------------------------------
1071               IF (g_debug_mode = 'Y') THEN
1072                 l_debug_info := 'Non reversal line - UPDATE exist ipv line';
1073                 AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
1074               END IF;
1075 
1076               -----------------------------------------------------------
1077               -- Update the existing IPV line for newly calculated IPV
1078               -- Although IPV is not going to change, bipv might be
1079               -- changed because of exchange rate changes
1080               ------------------------------------------------------------
1081 
1082               UPDATE ap_invoice_distributions
1083                  SET base_amount = l_bipv,
1084 		     amount      = l_ipv,  --Introduced for bug# 9252266
1085                      last_updated_by = p_system_user,
1086                      last_update_login = fnd_global.login_id
1087                WHERE invoice_distribution_id = l_ipv_distribution_id;
1088 
1089             END IF; -- end of check l_ipv_distribution_id = -1 for case A
1090           END IF; -- end of check l_ipv <> 0
1091         END IF; -- end of check l_line_type_lookup_code <> 'IPV'
1092 
1093    /*-----------------------------------------------------------------+
1094     | Step 4.1.d - Process ERV variance line for distribution         |
1095     +-----------------------------------------------------------------*/
1096 
1097         IF ( l_erv <> 0 ) THEN
1098           -----------------------------------------------------------
1099           -- Case A - there is ERV in this round calculation
1100           -----------------------------------------------------------
1101 
1102           IF ( l_erv_distribution_id = -1 ) THEN
1103             -----------------------------------------------------------
1104             -- No existing ERV line - insert
1105             -----------------------------------------------------------
1106 
1107             IF (g_debug_mode = 'Y') THEN
1108               l_debug_info := 'Non reversal dist line - Insert ERV line';
1109               AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
1110             END IF;
1111 
1112             l_related_id := l_invoice_distribution_id;
1113 
1114       l_max_dist_line_number := AP_INVOICE_LINES_PKG.get_max_dist_line_num(
1115                                                               p_invoice_id,
1116                     p_inv_line_number) + 1;
1117 
1118             INSERT INTO ap_invoice_distributions (
1119                     invoice_id,
1120                     invoice_line_number,
1121                     distribution_class,
1122                     invoice_distribution_id,
1123                     dist_code_combination_id,
1124                     last_update_date,
1125                     last_updated_by,
1126                     accounting_date,
1127                     period_name,
1128                     set_of_books_id,
1129                     amount,
1130                     description,
1131                     type_1099,
1132                     posted_flag,
1133                     batch_id,
1134                     quantity_invoiced,
1135                     unit_price,
1136                     match_status_flag,
1137                     attribute_category,
1138                     attribute1,
1139                     attribute2,
1140                     attribute3,
1141                     attribute4,
1142                     attribute5,
1143                     assets_addition_flag,
1144                     assets_tracking_flag,
1145                     distribution_line_number,
1146                     line_type_lookup_code,
1147                     po_distribution_id,
1148                     base_amount,
1149                     encumbered_flag,
1150                     accrual_posted_flag,
1151                     cash_posted_flag,
1152                     last_update_login,
1153                     creation_date,
1154                     created_by,
1155                     attribute11,
1156                     attribute12,
1157                     attribute13,
1158                     attribute14,
1159                     attribute6,
1160                     attribute7,
1161                     attribute8,
1162                     attribute9,
1163                     attribute10,
1164                     attribute15,
1165                     final_match_flag,
1166                     expenditure_item_date,
1167                     expenditure_organization_id,
1168                     expenditure_type,
1169                     project_id,
1170                     task_id,
1171         award_id,
1172         pa_addition_flag,
1173                     quantity_variance,
1174                     base_quantity_variance,
1175                     packet_id,
1176                     reference_1,
1177                     reference_2,
1178                     program_application_id,
1179                     program_id,
1180                     program_update_date,
1181                     request_id,
1182                     rcv_transaction_id,
1183                     dist_match_type,
1184                     global_attribute_category,
1185                     global_attribute1,
1186                     global_attribute2,
1187                     global_attribute3,
1188                     global_attribute4,
1189                     global_attribute5,
1190                     global_attribute6,
1191                     global_attribute7,
1192                     global_attribute8,
1193                     global_attribute9,
1194                     global_attribute10,
1195                     global_attribute11,
1196                     global_attribute12,
1197                     global_attribute13,
1198                     global_attribute14,
1199                     global_attribute15,
1200                     global_attribute16,
1201                     global_attribute17,
1202                     global_attribute18,
1203                     global_attribute19,
1204                     global_attribute20,
1205                     org_id,
1206                     related_id,
1207                     asset_book_type_code,
1208                     asset_category_id,
1209                     accounting_event_id,
1210                     cancellation_flag,
1211                    --Freight and Special Charges
1212                     rcv_charge_addition_flag,
1213                     awt_group_id,  -- bug6843734
1214 		    pay_awt_group_id, -- bug8222382
1215 		    inventory_transfer_status,  /*Bug#11067286 */
1216 		    income_tax_region  --bug 12908372
1217 		    )
1218             (SELECT  Invoice_Id, -- invoice_id
1219                      Invoice_Line_Number, -- invoice_line_number
1220                      distribution_class,
1221                      ap_invoice_distributions_s.NEXTVAL, -- distribution_id
1222                      l_erv_ccid, -- dist_code_combination_id
1223                      SYSDATE, -- last_update_date
1224                      p_system_user, -- last_updated_by
1225                      accounting_date, -- accounting_date
1226                      period_name,  -- period_name
1227                      Set_Of_Books_Id, -- set_of_book_id
1228                      0, --amount
1229                      description, -- description
1230                      type_1099, -- type_1099
1231                      'N',  -- posted_flag
1232                      batch_id, -- batch_id
1233                      NULL, -- quantity_invoiced,
1234                      NULL, -- unit_price,
1235                      'N',  -- match_status_flag
1236                      attribute_category,
1237                      attribute1,
1238                      attribute2,
1239                      attribute3,
1240                      attribute4,
1241                      attribute5,
1242                      'U', -- assets_addition_flag
1243                      assets_tracking_flag,
1244                      l_max_dist_line_number, --distribution_line_number,
1245                      'ERV', -- line_type_lookup_code,
1246                      po_distribution_id,
1247                      l_erv, -- base_amount,
1248                      'N', -- encumbered_flag
1249                      'N', -- accrual_posted_flag
1250                      'N', -- cash_posted_flag
1251                      fnd_global.login_id, --last_update_login,
1252                      SYSDATE,  --creation_date,
1253                      p_system_user,  --created_by,
1254                      attribute11,
1255                      attribute12,
1256                      attribute13,
1257                      attribute14,
1258                      attribute6,
1259                      attribute7,
1260                      attribute8,
1261                      attribute9,
1262                      attribute10,
1263                      attribute15,
1264                      final_match_flag,
1265                      expenditure_item_date,
1266                      expenditure_organization_id,
1267                      expenditure_type,
1268                      project_id,
1269                      task_id,
1270                      award_id,
1271 		     decode(project_id,NULL,'E','N'), --Modified for bug#9504423 pa_addition_flag
1272 	              -- pa_addition_flag,
1273                      NULL, --quantity_variance,
1274                      NULL, --base_quantity_variance,
1275                      NULL, -- packet_id
1276                      reference_1,
1277                      reference_2,
1278                      FND_GLOBAL.prog_appl_id, -- program_application_id
1279                      FND_GLOBAL.conc_program_id, -- program_id
1280                      SYSDATE, -- program_update_date
1281                      FND_GLOBAL.conc_request_id, --request_id
1282                      rcv_transaction_id,
1283                      dist_match_type,
1284                      global_attribute_category,
1285                      global_attribute1,
1286                      global_attribute2,
1287                      global_attribute3,
1288                      global_attribute4,
1289                      global_attribute5,
1290                      global_attribute6,
1291                      global_attribute7,
1292                      global_attribute8,
1293                      global_attribute9,
1294                      global_attribute10,
1295                      global_attribute11,
1296                      global_attribute12,
1297                      global_attribute13,
1298                      global_attribute14,
1299                      global_attribute15,
1300                      global_attribute16,
1301                      global_attribute17,
1302                      global_attribute18,
1303                      global_attribute19,
1304                      global_attribute20,
1305                      org_id,
1306                      l_related_id, --related_id
1307                      asset_book_type_code,
1308                      asset_category_id,
1309                      NULL,        -- accounting_event_id
1310                      cancellation_flag ,
1311                      'N',         -- rcv_charge_addition_flag
1312                      awt_group_id,  -- bug6843734
1313 	  	     pay_awt_group_id, -- bug8222382
1314 		     'N',   /*Bug#11067286 */
1315 		     income_tax_region  --bug 12908372
1316                 FROM ap_invoice_distributions
1317                WHERE invoice_distribution_id = l_invoice_distribution_id );
1318 
1319           ELSE
1320             -----------------------------------------------------------
1321             -- Existing ERV line - Update
1322             -----------------------------------------------------------
1323 
1324             IF (g_debug_mode = 'Y') THEN
1325               l_debug_info := 'Non reversal dist line-process exist ERV line';
1326               AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
1327             END IF;
1328 
1329             -------------------------------------------------------------
1330             -- UPDATE the existing ERV line for newly calculated ERV
1331             -- because of exchange rate changes
1332             -------------------------------------------------------------
1333             BEGIN
1334               UPDATE ap_invoice_distributions
1335                  SET base_amount = l_erv,
1336                      last_updated_by = p_system_user,
1337                      last_update_login = fnd_global.login_id
1338                WHERE invoice_distribution_id = l_erv_distribution_id;
1339             EXCEPTION
1340               WHEN NO_DATA_FOUND THEN
1341                 NULL;
1342             END;
1343           END IF; -- end of check l_erv_distribution_id = -1 for case A
1344 
1345         ELSE
1346 
1347           -----------------------------------------------------------
1348           -- Case B - l_erv = 0 No ERV in this round calculation
1349           -----------------------------------------------------------
1350           IF ( l_erv_distribution_id <> -1 ) THEN
1351             -----------------------------------------------------------
1352             -- Existing ERV line - Delete
1353             -----------------------------------------------------------
1354             BEGIN
1355               DELETE ap_invoice_distributions
1356               WHERE invoice_distribution_id = l_erv_distribution_id;
1357             END;
1358 
1359           END IF; -- end of check l_erv_distribution_id <> -1 for Case B
1360 
1361         END IF; -- end of check l_erv <> 0
1362 
1363    /*-----------------------------------------------------------------+
1364     | Step 4.1.e - Update the Parent line when variance exists        |
1365     |              if variance exists, related id of parent is always |
1366     |              populated otherwise clear it                       |
1367     +-----------------------------------------------------------------*/
1368 
1369   IF (l_extra_po_erv = 0) THEN
1370     l_extra_po_erv := NULL;
1371   END IF;
1372 
1373         IF ( l_erv <> 0 OR l_ipv <> 0 ) THEN
1374           ---------------------------------------------------------------
1375           -- Update the parent line with related id and reduced base amt
1376           ---------------------------------------------------------------
1377 
1378     l_debug_info := 'Updating the amounts on ap_invoice_distributions';
1379           BEGIN
1380             UPDATE ap_invoice_distributions AID
1381                SET amount = l_amount,                   -- modified entered amt
1382                    base_amount = l_base_amount,         -- modified base amt
1383                    related_id = l_invoice_distribution_id,  -- Bug 12660674 (revert 9318619)
1384                    extra_po_erv = l_extra_po_erv,
1385                    last_updated_by = p_system_user,
1386                    last_update_login = fnd_global.login_id
1387             WHERE  invoice_id = p_invoice_id
1388               AND  invoice_line_number = p_inv_line_number
1389               AND  distribution_line_number = l_distribution_line_number;
1390           END;
1391 
1392         ELSE
1393           ---------------------------------------------------------------
1394           -- Clear the parent line with related id
1395           ---------------------------------------------------------------
1396           BEGIN
1397 
1398       l_debug_info := 'Updating the amounts and related_id on ap_invoice_distributions'||l_invoice_distribution_id;
1399             UPDATE ap_invoice_distributions AID
1400                SET amount = l_amount,
1401                    base_amount = l_base_amount,
1402                    related_id = NULL,
1403        extra_po_erv = l_extra_po_erv,
1404                    last_updated_by = p_system_user,
1405                    last_update_login = fnd_global.login_id
1406              WHERE invoice_id = p_invoice_id
1407                AND invoice_line_number = p_inv_line_number
1408                AND distribution_line_number = l_distribution_line_number;
1409           END;
1410 
1411         END IF; -- end of check l_erv <> 0 or l_ipv <> 0
1412 
1413       ELSE
1414    /*-----------------------------------------------------------------+
1415     |  Error occured during Variance Calculation                      |
1416     +-----------------------------------------------------------------*/
1417         APP_EXCEPTION.RAISE_EXCEPTION;
1418 
1419       END IF; -- end of l_variance_success check
1420 
1421    /*-----------------------------------------------------------------+
1422     |  Step 6 - Re-initialize the variable value for next interation  |
1423     |           of the loop                                           |
1424     +-----------------------------------------------------------------*/
1425 
1426       l_erv_distribution_id := -1;
1427       l_ipv_distribution_id := -1;
1428 
1429     END IF;  -- end of check l_reversal_flag
1430 
1431      l_debug_info := CASE l_cnt WHEN 0 THEN --bug 9242891
1432                             'Inside the Distribution Cursor - finish one interate'
1433                       ELSE 'Inside the Retainage_Distribution Cursor - finish one interate'
1434                       END; --bug 9242891
1435 
1436     IF (g_debug_mode = 'Y') THEN
1437 
1438       AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
1439 
1440           --bug 9242891
1441     IF (G_LEVEL_STATEMENT >= G_CURRENT_RUNTIME_LEVEL) THEN
1442        FND_LOG.STRING(G_LEVEL_STATEMENT,G_MODULE_NAME||l_api_name,l_debug_info);
1443     END IF; --bug 9242891
1444     END IF;
1445 
1446   END LOOP;
1447 
1448    IF l_cnt = 0 then --bug 9242891
1449     CLOSE Distribution_Cur;
1450    ELSE --bug 9242891
1451     CLOSE Retainage_Distribution_Cur; --bug 9242891
1452    END IF; --bug 9242891
1453 
1454    /*-----------------------------------------------------------------+
1455     |  Process ERV ACCT INVALID Hold                                  |
1456     +-----------------------------------------------------------------*/
1457 
1458     IF (g_debug_mode = 'Y') THEN
1459       l_debug_info := 'Process ERV ACCT INVALID hold for the invoice';
1460       AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
1461     END IF;
1462 
1463      /* Bug 5230770. We should not process any invalid acct holds since it
1464        does not make any sense with SLA
1465     AP_APPROVAL_PKG.Process_Inv_Hold_Status(
1466             p_invoice_id,
1467             NULL,
1468             NULL,
1469             'ERV ACCT INVALID',
1470             l_erv_acct_invalid_exists,
1471             NULL,
1472             p_system_user,
1473             p_holds,
1474             p_hold_count,
1475             p_release_count,
1476             l_curr_calling_sequence);
1477      */
1478 
1479 EXCEPTION
1480   WHEN OTHERS THEN
1481     IF (SQLCODE <> -20001) THEN
1482       FND_MESSAGE.SET_NAME('SQLAP','AP_DEBUG');
1483       FND_MESSAGE.SET_TOKEN('ERROR',SQLERRM);
1484       FND_MESSAGE.SET_TOKEN('CALLING_SEQUENCE', l_curr_calling_sequence);
1485       FND_MESSAGE.SET_TOKEN('PARAMETERS',
1486                   'Invoice_id  = '|| to_char(p_invoice_id)
1487               ||', Sys Xrate Gain Ccid = '|| to_char(p_sys_xrate_gain_ccid)
1488               ||', Sys Xrate Loss Ccid = '|| to_char(p_sys_xrate_loss_ccid));
1489       FND_MESSAGE.SET_TOKEN('DEBUG_INFO',l_debug_info);
1490     END IF;
1491 
1492     IF ( Distribution_Cur%ISOPEN ) THEN
1493       CLOSE Distribution_Cur;
1494     END IF;
1495 
1496     --bug 9242891
1497     IF (Retainage_Distribution_Cur%ISOPEN ) THEN
1498       CLOSE Retainage_Distribution_Cur;
1499     END IF; --bug 9242891
1500 
1501     IF ( Check_Variance_Cur%ISOPEN ) THEN
1502       CLOSE Check_Variance_Cur;
1503     END IF;
1504 
1505     APP_EXCEPTION.RAISE_EXCEPTION;
1506 
1507 END Exec_Matched_Variance_Checks;
1508 
1509 /*============================================================================
1510  |  PUBLIC PROCEDURE  EXEC_QTY_VARIANCE_CHECK
1511  |
1512  |  DESCRIPTION:
1513  |                Procedure to calculate quantity variance for a paticular
1514  |                invoice. No hold or release will be put.
1515  |
1516  |  PARAMETERS
1517  |      p_invoice_id - Invoice Id
1518  |      p_base_currency_code - Base Currency Code
1519  |      p_inv_currency_code - Invoice currency code
1520  |      p_system_user - system user Id for invoice validation
1521  |      p_calling_sequence - Debugging string to indicate path of module calls
1522  |                           to beprinted out upon error.
1523  |
1524  |  PROGRAM FLOW: Loop through all the distributions and calculated Quantity
1525  |                Variance for each different po distribtutions. Update the
1526  |                corresponding distribution with line number and distribution
1527  |                line number combined.
1528  |
1529  |  KNOWN ISSUES:
1530  |
1531  |  NOTES:
1532  |
1533  |  MODIFICATION HISTORY
1534  |  Date         Author             Description of Change
1535  |
1536  *==========================================================================*/
1537 
1538 PROCEDURE Exec_Qty_Variance_Check(
1539               p_invoice_id                IN NUMBER,
1540               p_base_currency_code        IN VARCHAR2,
1541               p_inv_currency_code         IN VARCHAR2,
1542               p_system_user               IN NUMBER,
1543               p_calling_sequence          IN VARCHAR2) IS
1544 
1545     CURSOR Distribution_Cur IS
1546     SELECT   D.Invoice_Distribution_Id
1547             ,D.po_distribution_id
1548             ,D.invoice_line_number
1549             ,D.distribution_line_number
1550             ,NVL(PD.accrue_on_receipt_flag,'N')  -- l_accrue_on_receipt_flag
1551             ,nvl(PD.quantity_ordered,0)
1552                  - nvl(PD.quantity_cancelled,0)  -- l_po_qty
1553             ,nvl(PLL.price_override, 0)          -- l_po_price
1554             ,RSL.item_id                         -- l_rtxn_item_id
1555             ,PL.unit_meas_lookup_code            -- l_po_uom
1556             ,PLL.match_option                    -- l_match_option
1557     FROM    ap_invoice_distributions D,
1558             po_distributions_ap_v PD,
1559             rcv_transactions RTXN,
1560             rcv_shipment_lines RSL,
1561             po_lines PL,
1562             po_line_locations PLL
1563     WHERE  D.invoice_id = p_invoice_id
1564     AND    D.po_distribution_id = PD.po_distribution_id
1565     AND    NVL(D.match_status_flag, 'N') IN ('N', 'S', 'A')
1566     AND    NVL(D.posted_flag, 'N') IN ('N', 'P')
1567     AND    NVL(D.encumbered_flag, 'N') not in ('Y','R') --bug6921447
1568     AND    D.line_type_lookup_code IN ('ITEM', 'ACCRUAL')
1569     AND    PD.line_location_id = PLL.line_location_id
1570     AND    PL.po_header_id = PD.po_header_id
1571     AND    PLL.matching_basis = 'QUANTITY'
1572     AND    PL.po_line_id = PD.po_line_id
1573     AND    D.rcv_transaction_id = RTXN.transaction_id(+)
1574     AND    RTXN.shipment_line_id = RSL.shipment_line_id(+)
1575 
1576      --9564576 Added the below  condition
1577     AND    exists
1578 	(select 1 from ap_invoice_distributions_all aid1
1579 	 where  NVL(aid1.match_status_flag , 'N') <> 'A'
1580          and    aid1.invoice_id=D.invoice_id   /*Bug 15968233*/
1581 	 and    aid1.po_distribution_id = PD.po_distribution_id
1582 	 and    aid1.line_type_lookup_code IN ('ITEM' , 'ACCRUAL')
1583 	)
1584     ORDER BY D.po_distribution_id, D.invoice_line_number, D.distribution_line_number;
1585 
1586 
1587   l_invoice_distribution_id
1588       ap_invoice_distributions.invoice_distribution_id%TYPE;
1589   l_distribution_line_number
1590       ap_invoice_distributions.distribution_line_number%TYPE;
1591   l_invoice_line_number
1592       ap_invoice_distributions.invoice_line_number%TYPE;
1593 
1594   l_prev_po_dist_id         NUMBER(15)    := -1;
1595   l_po_dist_id              NUMBER(15);
1596   l_po_qty                  NUMBER;
1597   l_po_price                NUMBER;
1598   l_accrue_on_receipt_flag  VARCHAR2(1);
1599   l_po_UOM                  VARCHAR2(30);
1600   l_match_option            VARCHAR2(25);
1601   l_rtxn_item_id            NUMBER;
1602 
1603   l_qv                      NUMbER;
1604   l_bqv                     NUMBER;
1605   l_update_line_num         NUMBER;
1606   l_update_dist_num         NUMBER;
1607   l_po_dist_qv              NUMBER;
1608   l_po_dist_bqv             NUMBER;
1609 
1610   -- TQV
1611   l_inv_dist_id_upd  NUMBER;
1612   l_qv_upd    NUMBER;
1613   l_amount_upd    NUMBER;
1614   l_base_qv_upd    NUMBER;
1615   l_base_amount_upd  NUMBER;
1616   l_qv_ratio    NUMBER;
1617   l_base_qv_ratio  NUMBER;
1618 
1619   l_debug_loc               VARCHAR2(30) := 'Exec_Qty_Variance_Check';
1620   l_curr_calling_sequence   VARCHAR2(2000);
1621   l_debug_info              VARCHAR2(2000);
1622 
1623 BEGIN
1624 
1625   l_curr_calling_sequence := 'AP_APPROVAL_MATCHED_PKG.'||l_debug_loc||'<-'||
1626                               p_calling_sequence;
1627 
1628   IF ( AP_APPROVAL_PKG.g_debug_mode = 'Y' ) THEN
1629     g_debug_mode := 'Y';
1630   END IF;
1631 
1632   IF (g_debug_mode = 'Y') THEN
1633     AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
1634     AP_Debug_Pkg.Print(g_debug_mode, 'Invoice id: '|| TO_CHAR(p_invoice_id));
1635     AP_Debug_Pkg.Print(g_debug_mode, 'base currency code: '||
1636                        p_base_currency_code);
1637     AP_Debug_Pkg.Print(g_debug_mode, 'invoice currency code: '||
1638                        p_inv_currency_code);
1639   END IF;
1640 
1641    /*-----------------------------------------------------------------+
1642     |  Step 1 - Open Cursor and initialize data for all distribution   |
1643     |           Line and loop through for calculation                  |
1644     +-----------------------------------------------------------------*/
1645 
1646   IF (g_debug_mode = 'Y') THEN
1647     l_debug_info := 'Open Distribution_Cur';
1648     AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
1649   END IF;
1650 
1651   OPEN Distribution_Cur;
1652   LOOP
1653     FETCH Distribution_Cur
1654      INTO   l_invoice_distribution_id
1655            ,l_po_dist_id
1656            ,l_invoice_line_number
1657            ,l_distribution_line_number
1658            ,l_accrue_on_receipt_flag
1659            ,l_po_qty
1660            ,l_po_price
1661            ,l_rtxn_item_id
1662            ,l_po_uom
1663            ,l_match_option;
1664 
1665     EXIT WHEN Distribution_Cur%NOTFOUND;
1666 
1667     IF ( l_accrue_on_receipt_flag = 'N' and
1668          l_po_dist_id <> l_prev_po_dist_id ) THEN
1669 
1670    /*-----------------------------------------------------------------+
1671     | Calculate the Quantity Variance                                 |
1672     +-----------------------------------------------------------------*/
1673 
1674       IF (g_debug_mode = 'Y') THEN
1675          l_debug_info := 'Exec_Qty_Variance_Check- call Calculate_QV';
1676         AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
1677       END IF;
1678 
1679       AP_FUNDS_CONTROL_PKG.Calc_QV(
1680               p_invoice_id,
1681               l_po_dist_id,
1682               p_inv_currency_code,
1683               p_base_currency_code,
1684               l_po_price,
1685               l_po_qty,
1686               l_match_option,
1687               l_po_uom,
1688               l_rtxn_item_id,
1689               l_po_dist_qv,
1690               l_po_dist_bqv,
1691               l_update_line_num,
1692               l_update_dist_num,
1693               l_curr_calling_sequence);
1694     END IF;
1695 
1696     l_prev_po_dist_id := l_po_dist_id;
1697 
1698     /*-----------------------------------------------------------------+
1699     | Quantity variance amount is set for line that we want to update  |
1700     | only                                                             |
1701     +-----------------------------------------------------------------*/
1702 
1703     IF (g_debug_mode = 'Y') THEN
1704       l_debug_info := 'Set inv dist qv if right dist_line_num to be updated ';
1705       AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
1706     END IF;
1707 
1708     IF (l_distribution_line_number = l_update_dist_num AND
1709         l_invoice_line_number = l_update_line_num ) THEN
1710       l_qv  := l_po_dist_qv;
1711       l_bqv := l_po_dist_bqv;
1712     ELSE
1713       l_qv  := 0;
1714       l_bqv := 0;
1715     END IF;
1716 
1717     IF (g_debug_mode = 'Y') THEN
1718       l_debug_info := 'Exec_Qty_Variance_Checks-update line with dist_line_num'
1719                        || '=' || to_char(l_distribution_line_number)
1720                        || 'line_number' || to_char(l_invoice_line_number);
1721       AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
1722     END IF;
1723 
1724     UPDATE ap_invoice_distributions
1725       SET    quantity_variance = decode(nvl(quantity_variance,0)+l_qv,0,
1726                                         NULL,nvl(quantity_variance,0)+l_qv),
1727              base_quantity_variance = decode(nvl(base_quantity_variance,0)
1728                                              +l_bqv, 0, NULL,
1729                                              nvl(base_quantity_variance,0)
1730                                              +l_bqv),
1731              last_updated_by = p_system_user,
1732              last_update_login = fnd_global.login_id
1733       WHERE  invoice_id = p_invoice_id
1734       AND    invoice_line_number = l_invoice_line_number
1735       AND    distribution_line_number = l_distribution_line_number
1736     RETURNING invoice_distribution_id, quantity_variance, amount, base_quantity_variance, base_amount
1737          INTO l_inv_dist_id_upd, l_qv_upd, l_amount_upd, l_base_qv_upd, l_base_amount_upd;
1738 
1739   IF nvl(l_amount_upd,0) <> 0 and nvl(l_base_amount_upd,0) <> 0 then --bug 7533602
1740 
1741     l_qv_ratio      := l_qv_upd/l_amount_upd;
1742     l_base_qv_ratio := l_base_qv_upd/l_base_amount_upd;
1743 
1744     UPDATE  ap_invoice_distributions_all aid
1745        SET  quantity_variance      = ap_utilities_pkg.ap_round_currency
1746           (aid.amount * l_qv_ratio, p_inv_currency_code)
1747            ,base_quantity_variance = ap_utilities_pkg.ap_round_currency
1748           (aid.base_amount * l_base_qv_ratio, p_base_currency_code)
1749      WHERE  invoice_id       = p_invoice_id
1750        AND  charge_applicable_to_dist_id = l_inv_dist_id_upd
1751        AND  line_type_lookup_code   IN ('NONREC_TAX', 'TRV', 'TIPV');
1752 
1753    END IF; --bug 7533602
1754 
1755     IF (g_debug_mode = 'Y') THEN
1756       l_debug_info := 'Exec_Qty_Variance_Checks-finish update the distribution'
1757                        || 'for each distribution line';
1758       AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
1759     END IF;
1760 
1761   END LOOP;
1762   CLOSE Distribution_Cur;
1763 
1764 EXCEPTION
1765   WHEN OTHERS THEN
1766     IF (SQLCODE <> -20001) THEN
1767       FND_MESSAGE.SET_NAME('SQLAP','AP_DEBUG');
1768       FND_MESSAGE.SET_TOKEN('ERROR',SQLERRM);
1769       FND_MESSAGE.SET_TOKEN('CALLING_SEQUENCE', l_curr_calling_sequence);
1770       FND_MESSAGE.SET_TOKEN('PARAMETERS',
1771                   'Invoice_id  = '|| to_char(p_invoice_id) );
1772       FND_MESSAGE.SET_TOKEN('DEBUG_INFO',l_debug_info);
1773     END IF;
1774 
1775     IF ( Distribution_Cur%ISOPEN ) THEN
1776       CLOSE Distribution_Cur;
1777     END IF;
1778 
1779     APP_EXCEPTION.RAISE_EXCEPTION;
1780 END Exec_Qty_Variance_Check;
1781 
1782 
1783 /*============================================================================
1784  |  PUBLIC PROCEDURE  EXEC_AMT_VARIANCE_CHECK
1785  |
1786  |  DESCRIPTION:
1787  |                Procedure to calculate amount variance for a paticular
1788  |                invoice. No hold or release will be put. This procedure
1789  |                is related to new amount based matching
1790  |
1791  |  PARAMETERS
1792  |      p_invoice_id - Invoice Id
1793  |      p_base_currency_code - Base Currency Code
1794  |      p_inv_currency_code - Invoice currency code
1795  |      p_system_user - system user Id for invoice validation
1796  |      p_calling_sequence - Debugging string to indicate path of module calls
1797  |                           to beprinted out upon error.
1798  |
1799  |  PROGRAM FLOW: Loop through all the distributions and calculated Amount
1800  |                Variance for each different po distribtutions. Update the
1801  |                corresponding distribution with line number and distribution
1802  |                line number combined.
1803  |
1804  |  KNOWN ISSUES:
1805  |
1806  |  NOTES:
1807  |
1808  |  MODIFICATION HISTORY
1809  |  Date         Author             Description of Change
1810  |  August, 2004 bghose             Created
1811  |
1812  *==========================================================================*/
1813 
1814 PROCEDURE Exec_Amt_Variance_Check(
1815               p_invoice_id                IN NUMBER,
1816               p_base_currency_code        IN VARCHAR2,
1817               p_inv_currency_code         IN VARCHAR2,
1818               p_system_user               IN NUMBER,
1819               p_calling_sequence          IN VARCHAR2) IS
1820 
1821     CURSOR Distribution_Cur IS
1822     SELECT   D.Invoice_Distribution_Id
1823             ,D.po_distribution_id
1824             ,D.invoice_line_number
1825             ,D.distribution_line_number
1826             ,NVL(PD.accrue_on_receipt_flag,'N')  -- l_accrue_on_receipt_flag
1827             ,nvl(PD.amount_ordered,0)
1828                  - nvl(PD.amount_cancelled,0)    -- l_po_amt
1829             ,PLL.match_option                    -- l_match_option
1830     FROM    ap_invoice_distributions D,
1831             po_distributions_ap_v PD,
1832             rcv_transactions RTXN,
1833             rcv_shipment_lines RSL,
1834             po_lines PL,
1835             po_line_locations PLL
1836     WHERE  D.invoice_id = p_invoice_id
1837     AND    D.po_distribution_id = PD.po_distribution_id
1838     AND    NVL(D.match_status_flag, 'N') IN ('N', 'S', 'A')
1839     AND    NVL(D.posted_flag, 'N')       IN ('N', 'P')
1840     AND    NVL(D.encumbered_flag, 'N')  not in ('Y','R') --bug6921447
1841     AND    D.line_type_lookup_code IN ('ITEM', 'ACCRUAL')
1842     AND    PD.line_location_id = PLL.line_location_id
1843     AND    PL.po_header_id = PD.po_header_id
1844     AND    PL.po_line_id = PD.po_line_id
1845     AND    PLL.matching_basis = 'AMOUNT'
1846     AND    D.rcv_transaction_id = RTXN.transaction_id(+)
1847     AND    RTXN.shipment_line_id = RSL.shipment_line_id(+)
1848     ORDER BY D.po_distribution_id, D.invoice_line_number, D.distribution_line_number;
1849 
1850   l_invoice_distribution_id
1851       ap_invoice_distributions.invoice_distribution_id%TYPE;
1852   l_distribution_line_number
1853       ap_invoice_distributions.distribution_line_number%TYPE;
1854   l_invoice_line_number
1855       ap_invoice_distributions.invoice_line_number%TYPE;
1856 
1857   l_prev_po_dist_id         NUMBER(15)    := -1;
1858   l_po_dist_id              NUMBER(15);
1859   l_po_amt                  NUMBER;
1860   l_accrue_on_receipt_flag  VARCHAR2(1);
1861   l_match_option            VARCHAR2(25);
1862   l_rtxn_item_id            NUMBER;
1863 
1864   l_av                      NUMBER;
1865   l_bav                     NUMBER;
1866   l_update_line_num         NUMBER;
1867   l_update_dist_num         NUMBER;
1868   l_po_dist_av              NUMBER;
1869   l_po_dist_bav             NUMBER;
1870   l_key_value
1871       AP_INVOICE_DISTRIBUTIONS.invoice_distribution_id%TYPE;
1872 
1873   -- TAV
1874   l_inv_dist_id_upd     NUMBER;
1875   l_av_upd              NUMBER;
1876   l_amount_upd          NUMBER;
1877   l_base_av_upd         NUMBER;
1878   l_base_amount_upd     NUMBER;
1879   l_av_ratio            NUMBER;
1880   l_base_av_ratio       NUMBER;
1881 
1882   l_debug_loc               VARCHAR2(30) := 'Exec_Amt_Variance_Check';
1883   l_curr_calling_sequence   VARCHAR2(2000);
1884   l_debug_info              VARCHAR2(2000);
1885 
1886 BEGIN
1887 
1888   l_curr_calling_sequence := 'AP_APPROVAL_MATCHED_PKG.'||l_debug_loc||'<-'||
1889                               p_calling_sequence;
1890 
1891   IF ( AP_APPROVAL_PKG.g_debug_mode = 'Y' ) THEN
1892     g_debug_mode := 'Y';
1893   END IF;
1894 
1895   IF (g_debug_mode = 'Y') THEN
1896     AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
1897     AP_Debug_Pkg.Print(g_debug_mode, 'Invoice id: '|| TO_CHAR(p_invoice_id));
1898     AP_Debug_Pkg.Print(g_debug_mode, 'base currency code: '||
1899                        p_base_currency_code);
1900     AP_Debug_Pkg.Print(g_debug_mode, 'invoice currency code: '||
1901                        p_inv_currency_code);
1902   END IF;
1903 
1904    /*-----------------------------------------------------------------+
1905     |  Step 1 - Open Cursor and initialize data for all distribution   |
1906     |           Line and loop through for calculation                  |
1907     +-----------------------------------------------------------------*/
1908 
1909   IF (g_debug_mode = 'Y') THEN
1910     l_debug_info := 'Open Distribution_Cur';
1911     AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
1912   END IF;
1913 
1914   OPEN Distribution_Cur;
1915   LOOP
1916     FETCH Distribution_Cur
1917      INTO   l_invoice_distribution_id
1918            ,l_po_dist_id
1919            ,l_invoice_line_number
1920      ,l_distribution_line_number
1921            ,l_accrue_on_receipt_flag
1922            ,l_po_amt
1923            ,l_match_option;
1924 
1925     EXIT WHEN Distribution_Cur%NOTFOUND;
1926 
1927     IF ( l_accrue_on_receipt_flag = 'N' and
1928          l_po_dist_id <> l_prev_po_dist_id ) THEN
1929 
1930    /*-----------------------------------------------------------------+
1931     | Calculate the Amount Variance                                   |
1932     +-----------------------------------------------------------------*/
1933 
1934       IF (g_debug_mode = 'Y') THEN
1935          l_debug_info := 'Exec_Amt_Variance_Check- call Calculate_AV';
1936         AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
1937       END IF;
1938 
1939       AP_FUNDS_CONTROL_PKG.Calc_AV(
1940               p_invoice_id,
1941               l_po_dist_id,
1942               p_inv_currency_code,
1943               p_base_currency_code,
1944               l_po_amt,
1945               l_po_dist_av,
1946               l_po_dist_bav,
1947               l_update_line_num,
1948               l_update_dist_num,
1949               l_curr_calling_sequence);
1950     END IF;
1951 
1952     l_prev_po_dist_id := l_po_dist_id;
1953 
1954     /*-----------------------------------------------------------------+
1955     | Amount variance amount is set for line that we want to update    |
1956     | only                                                             |
1957     +-----------------------------------------------------------------*/
1958 
1959     IF (g_debug_mode = 'Y') THEN
1960       l_debug_info := 'Set inv dist av if right dist_line_num to be updated ';
1961       AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
1962     END IF;
1963 
1964     IF (l_distribution_line_number = l_update_dist_num AND
1965         l_invoice_line_number = l_update_line_num ) THEN
1966       l_av  := l_po_dist_av;
1967       l_bav := l_po_dist_bav;
1968     ELSE
1969       l_av  := 0;
1970       l_bav := 0;
1971     END IF;
1972 
1973     IF (g_debug_mode = 'Y') THEN
1974       l_debug_info := 'Exec_Amt_Variance_Checks-update line with dist_line_num'
1975                        || '=' || to_char(l_distribution_line_number)
1976                        || 'line_number' || to_char(l_invoice_line_number);
1977       AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
1978     END IF;
1979 
1980     UPDATE ap_invoice_distributions
1981       SET    amount_variance = decode(nvl(amount_variance,0)+l_av,0,
1982                                         NULL,nvl(amount_variance,0)+l_av),
1983              base_amount_variance = decode(nvl(base_amount_variance,0)
1984                                              +l_bav, 0, NULL,
1985                                              nvl(base_amount_variance,0)
1986                                              +l_bav),
1987              last_updated_by = p_system_user,
1988              last_update_login = fnd_global.login_id
1989       WHERE  invoice_id = p_invoice_id
1990       AND    invoice_line_number = l_invoice_line_number
1991       AND    distribution_line_number = l_distribution_line_number
1992     RETURNING invoice_distribution_id, amount_variance, amount, base_amount_variance, base_amount
1993          INTO l_inv_dist_id_upd, l_av_upd, l_amount_upd, l_base_av_upd, l_base_amount_upd;
1994 
1995  IF nvl(l_amount_upd,0) <> 0 and nvl(l_base_amount_upd,0) <> 0 then --bug 7533602
1996 
1997     l_av_ratio      := l_av_upd/l_amount_upd;
1998     l_base_av_ratio := l_base_av_upd/l_base_amount_upd;
1999 
2000     UPDATE  ap_invoice_distributions_all aid
2001        SET  amount_variance      = ap_utilities_pkg.ap_round_currency
2002                                         (aid.amount * l_av_ratio, p_inv_currency_code)
2003            ,base_amount_variance = ap_utilities_pkg.ap_round_currency
2004                                         (aid.base_amount * l_base_av_ratio, p_base_currency_code)
2005      WHERE  invoice_id                   = p_invoice_id
2006        AND  charge_applicable_to_dist_id = l_inv_dist_id_upd
2007        AND  line_type_lookup_code       IN ('NONREC_TAX', 'TRV', 'TIPV');
2008 
2009   END IF; --bug 7533602
2010 
2011     IF (g_debug_mode = 'Y') THEN
2012       l_debug_info := 'Exec_Amt_Variance_Checks-finish update the distribution'
2013                        || 'for each distribution line';
2014       AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
2015     END IF;
2016 
2017   END LOOP;
2018   CLOSE Distribution_Cur;
2019 
2020 EXCEPTION
2021   WHEN OTHERS THEN
2022     IF (SQLCODE <> -20001) THEN
2023       FND_MESSAGE.SET_NAME('SQLAP','AP_DEBUG');
2024       FND_MESSAGE.SET_TOKEN('ERROR',SQLERRM);
2025       FND_MESSAGE.SET_TOKEN('CALLING_SEQUENCE', l_curr_calling_sequence);
2026       FND_MESSAGE.SET_TOKEN('PARAMETERS',
2027                   'Invoice_id  = '|| to_char(p_invoice_id) );
2028       FND_MESSAGE.SET_TOKEN('DEBUG_INFO',l_debug_info);
2029     END IF;
2030 
2031     IF ( Distribution_Cur%ISOPEN ) THEN
2032       CLOSE Distribution_Cur;
2033     END IF;
2034 
2035     APP_EXCEPTION.RAISE_EXCEPTION;
2036 END Exec_Amt_Variance_Check;
2037 
2038 /*============================================================================
2039  |  PUBLIC PROCEDURE EXECUTE_MATCHED_CHECKS
2040  |
2041  |  DESCRIPTION
2042  |      Procedure to perfrom general matched checks on an invoice
2043  |      and place or release holds depending on the condition.
2044  |
2045  |  PARAMETERS
2046  |      p_invoice_id - Invoice_Id
2047  |      p_base_currency_code - system base currency code
2048  |      p_price_tol - System Price Tolerance
2049  |      p_qty_tol - System Quantity Ordered Tolerance
2050  |      p_qty_rec_tol - System Quantity Received Tolerance
2051  |      p_max_qty_ord_tol - System Max Quantity Ordered Tolerance
2052  |      p_max_qty_rec_tol - System Max Quantity Received Tolerance
2053  |      p_amt_tol - System Amount Ordered Tolerance
2054  |      p_amt_rec_tol - System Amount Received Tolerance
2055  |  p_max_amt_ord_tol - System Max Amount Ordered Tolerance
2056  |  p_max_amt_rec_tol - System Max Amount Received Tolerance
2057  |      p_ship_amt_tolerance - shipment amount tolerance
2058  |      p_rate_amt_tolerance -
2059  |      p_total_amt_tolerance -
2060  |      p_system_user - Approval Program User Id
2061  |      p_conc_flag - ('Y' or 'N') indicating whether this is called as a
2062  |                    concurrent program or not.
2063  |      p_holds - Holds Array
2064  |      p_holds_count - Holds Count Array
2065  |      p_release_count - Release Count Array
2066  |      p_calling_sequence - Debugging string to indicate path of module
2067  |                           calls to be printed out upon error.
2068  |   PROGRAM FLOW
2069  |
2070  |
2071  |  NOTES:
2072  |
2073  |  MODIFICATION HISTORY
2074  |  Date         Author             Description of Change
2075  |
2076  *==========================================================================*/
2077 
2078 PROCEDURE Execute_Matched_Checks(
2079               p_invoice_id           IN            NUMBER,
2080               p_base_currency_code   IN            VARCHAR2,
2081               p_price_tol            IN            NUMBER,
2082               p_qty_tol              IN            NUMBER,
2083               p_qty_rec_tol          IN            NUMBER,
2084               p_max_qty_ord_tol      IN            NUMBER,
2085               p_max_qty_rec_tol      IN            NUMBER,
2086         p_amt_tol         IN       NUMBER,
2087         p_amt_rec_tol       IN       NUMBER,
2088         p_max_amt_ord_tol      IN      NUMBER,
2089         p_max_amt_rec_tol      IN       NUMBER,
2090               p_goods_ship_amt_tolerance     IN            NUMBER,
2091               p_goods_rate_amt_tolerance     IN            NUMBER,
2092               p_goods_total_amt_tolerance    IN            NUMBER,
2093         p_services_ship_amt_tolerance  IN            NUMBER,
2094         p_services_rate_amt_tolerance  IN            NUMBER,
2095         p_services_total_amt_tolerance IN            NUMBER,
2096               p_system_user          IN            NUMBER,
2097               p_conc_flag            IN            VARCHAR2,
2098               p_holds                IN OUT NOCOPY AP_APPROVAL_PKG.HOLDSARRAY,
2099               p_holds_count          IN OUT NOCOPY AP_APPROVAL_PKG.COUNTARRAY,
2100               p_release_count        IN OUT NOCOPY AP_APPROVAL_PKG.COUNTARRAY,
2101               p_calling_sequence     IN            VARCHAR2) IS
2102 
2103   CURSOR Matched_Cur IS
2104   SELECT PLL.line_location_id,
2105          PLL.po_line_id,
2106          SUM(L.amount),
2107          NVL(AP_INVOICE_LINES_UTILITY_PKG.get_approval_status(p_invoice_id,L.line_number),'N'),
2108                                                                                     --bug 5182413
2109          SUM(nvl(L.quantity_invoiced,0)),
2110          PLL.price_override,              -- BUG 4123171
2111          ROUND((nvl(PLL.quantity,0) - nvl(PLL.quantity_cancelled,0)), 15),
2112          ROUND(nvl(PLL.quantity_received, 0), 15),
2113          ROUND(nvl(PLL.quantity_accepted, 0), 15),
2114          nvl(PLL.amount,0) - nvl(PLL.amount_cancelled,0), --Amount Based Matching
2115    nvl(PLL.amount_received, 0),  --Amount Based Matching
2116    nvl(PLL.amount_cancelled,0),  --Contract Payments
2117          NVL(PLL.cancel_flag, 'N'),
2118          NVL(PLL.receipt_required_flag, 'N'),
2119          NVL(PLL.inspection_required_flag, 'N'),
2120          I.invoice_currency_code,
2121          PH.currency_code,
2122          PLL.approved_flag,
2123          PLL.closed_code,
2124          decode(PLL.final_match_flag, 'Y', 'D', nvl(L.final_match_flag, 'N')), --Bug 3489536
2125          nvl(L.final_match_flag, 'N'),--Bug 5759169
2126          decode(PH.type_lookup_code, 'STANDARD', 'PO', 'RELEASE'),
2127          decode(L.po_release_id, null, PH.type_lookup_code, PR.release_type),
2128          nvl(PLL.accrue_on_receipt_flag, 'N'),
2129          DECODE(L.po_release_id, null, L.po_header_id, L.po_release_id),
2130          PH.segment1,
2131          nvl(PLL.match_option,'P'),
2132          L.rcv_transaction_id,
2133          L.unit_meas_lookup_code,
2134          RSL.item_id,
2135          decode(PLL.unit_meas_lookup_code,null,PL.unit_meas_lookup_code,PLL.unit_meas_lookup_code),   -- BUG 4184044
2136          L.discarded_flag,
2137          L.cancelled_flag,
2138          PLL.matching_basis,  -- Amount Based Matching
2139    --bugfix:4709926 added the NVL condition
2140    nvl(PLL.payment_type,'DUMMY'),-- Contract Payments: Tolerances Redesign
2141          I.invoice_type_lookup_code, --Contract Payments: Tolerances Redesign
2142          I.org_id -- Bug 5500101
2143   FROM   po_lines PL,
2144          rcv_transactions RTXN,
2145          rcv_shipment_lines RSL,
2146          ap_invoice_lines L,
2147          ap_invoices I,
2148          po_line_locations PLL,
2149          po_headers PH,
2150          po_releases PR
2151   WHERE  I.invoice_id = L.invoice_id
2152   AND    L.po_line_location_id = PLL.line_location_id
2153   AND    L.match_type in ( 'PRICE_CORRECTION', 'QTY_CORRECTION',
2154                            'ITEM_TO_PO', 'ITEM_TO_RECEIPT',
2155                            'ITEM_TO_SERVICE_PO', 'ITEM_TO_SERVICE_RECEIPT', -- ABM
2156                            'AMOUNT_CORRECTION',  -- Amount Based Matching
2157                            'PO_PRICE_ADJUSTMENT') --Retropricing
2158   AND    L.po_release_id = PR.po_release_id(+)
2159   AND    PLL.po_line_id = PL.po_line_id
2160   AND    PH.po_header_id = PL.po_header_id
2161   AND    L.rcv_transaction_id = RTXN.transaction_id(+)
2162   AND    RTXN.shipment_line_id = RSL.shipment_line_id(+)
2163   AND    (I.payment_status_flag IN ('N', 'P')
2164            OR EXISTS (SELECT 'Holds have to be released'
2165                        FROM   ap_holds H
2166                        WHERE  H.invoice_id = I.invoice_id
2167                        AND    H.release_lookup_code is null
2168                        AND    H.hold_lookup_code in
2169                                    ('QTY ORD', 'QTY REC',
2170             'AMT ORD', 'AMT REC',
2171                                     'QUALITY', 'PRICE',
2172                                     'CURRENCY DIFFERENCE',
2173                                     'REC EXCEPTION', 'PO NOT APPROVED',
2174                                     'MAX QTY REC', 'MAX QTY ORD',
2175             'MAX AMT REC', 'MAX AMT ORD',
2176                                     'FINAL MATCHING',
2177                                     'MAX SHIP AMOUNT',
2178                                     'MAX RATE AMOUNT',
2179                                     'MAX TOTAL AMOUNT'))
2180            OR EXISTS (SELECT 'Unapproved matched dist'
2181                         FROM   ap_invoice_distributions AID2
2182                         WHERE  AID2.invoice_id = I.invoice_id
2183                         AND    AID2.invoice_line_number = L.line_number
2184                         AND    nvl(AID2.match_status_flag, 'X') <> 'A'))
2185   AND     I.invoice_id = p_invoice_id
2186   GROUP BY PLL.line_location_id, L.rcv_transaction_id,
2187            nvl(PLL.match_option,'P'),PLL.po_line_id,
2188            I.invoice_currency_code,
2189            ROUND((nvl(PLL.quantity,0) - nvl(PLL.quantity_cancelled,0)), 15),
2190            PLL.quantity_received,
2191            PLL.price_override, PLL.quantity_billed, PLL.quantity_accepted,
2192            nvl(PLL.amount,0) - nvl(PLL.amount_cancelled,0),
2193            PLL.amount_received,
2194      PLL.amount_cancelled,
2195            PLL.amount_billed,
2196            PLL.cancel_flag, PLL.receipt_required_flag,
2197            PLL.inspection_required_flag,
2198            PH.currency_code,
2199            PLL.approved_flag, PLL.closed_code,
2200            decode(PLL.final_match_flag, 'Y', 'D', nvl(L.final_match_flag, 'N')),  --Bug 3489536
2201            nvl(L.final_match_flag, 'N'),--Bug 5759169
2202            PLL.accrue_on_receipt_flag,
2203            decode(PH.type_lookup_code, 'STANDARD', 'PO', 'RELEASE'),
2204            DECODE(L.po_release_id, null, L.po_header_id, L.po_release_id),
2205            decode(L.po_release_id, null, PH.type_lookup_code, PR.release_type),
2206            PH.segment1, L.unit_meas_lookup_code,RSL.item_id,
2207            decode(PLL.unit_meas_lookup_code,null,PL.unit_meas_lookup_code,PLL.unit_meas_lookup_code),    -- BUG 4184044
2208            L.discarded_flag,L.cancelled_flag,
2209            PLL.matching_basis,PLL.payment_type,I.invoice_type_lookup_code,
2210            I.org_id,
2211            NVL(AP_INVOICE_LINES_UTILITY_PKG.get_approval_status(p_invoice_id,L.line_number),'N');-- Bug 5182413
2212                                                                                   l_line_location_id            NUMBER(15);
2213   l_po_line_id                  NUMBER(15);
2214   l_inv_line_amount             NUMBER;
2215   l_adj_qty_invoiced            NUMBER;
2216   l_po_unit_price               NUMBER;
2217   l_qty_ordered                 NUMBER;
2218   l_qty_billed                  NUMBER;
2219   l_qty_received                NUMBER;
2220   l_qty_accepted                NUMBER;
2221   l_amt_ordered                 NUMBER;   -- Amount Based Matching
2222   l_amt_billed                  NUMBER;   -- Amount Based Matching
2223   l_amt_received                NUMBER;   -- Amount Based Matching
2224   l_amt_cancelled    NUMBER;
2225   l_cancel_flag                 VARCHAR2(1);
2226   l_receipt_required_flag       VARCHAR2(1);
2227   l_inspection_required_flag    VARCHAR2(1);
2228   l_inv_currency_code           VARCHAR2(15);
2229   l_po_currency_code            VARCHAR2(15);
2230   l_po_approved_flag            VARCHAR2(1);
2231   l_po_closed_code              VARCHAR2(25);
2232   l_final_match_flag            VARCHAR2(1);
2233   l_dist_final_match_flag       VARCHAR2(1);--bug5759169
2234   l_po_doc_type                 VARCHAR2(25);
2235   l_po_sub_type                 VARCHAR2(25);
2236   l_accrue_on_receipt_flag      VARCHAR2(1);
2237   l_po_header_id                NUMBER;
2238   l_po_num                      VARCHAR2(20);
2239   l_final_matching_exists       VARCHAR2(1) ;
2240   l_currency_difference_exists  VARCHAR2(1) ;
2241   l_po_not_approved_exists      VARCHAR2(1) ;
2242   l_qty_ord_error_exists        VARCHAR2(1) ;
2243   l_max_qty_ord_error_exists    VARCHAR2(1) ;
2244   l_qty_rec_error_exists        VARCHAR2(1) ;
2245   l_max_qty_rec_error_exists    VARCHAR2(1) ;
2246   l_amt_ord_error_exists        VARCHAR2(1) ;
2247   l_max_amt_ord_error_exists    VARCHAR2(1) ;
2248   l_amt_rec_error_exists        VARCHAR2(1) ;
2249   l_max_amt_rec_error_exists    VARCHAR2(1) ;
2250   l_milestone_error_exists      VARCHAR2(1) ;
2251   l_qty_overbilled_exists       VARCHAR2(1) ;
2252   l_max_ship_amt_exceeded       VARCHAR2(1) ;
2253   l_max_rate_amt_exceeded       VARCHAR2(1) ;
2254   l_max_total_amt_exceeded      VARCHAR2(1) ;
2255   l_action                      VARCHAR2(25);
2256   l_return_code                 VARCHAR2(25);
2257   l_ship_trx_amt_var            NUMBER ;
2258   l_rate_amt_var                NUMBER ;
2259   l_ship_base_amt_var           NUMBER ;
2260   l_match_option                VARCHAR2(25);
2261   l_rcv_transaction_id          NUMBER;
2262   l_ordered_po_qty              NUMBER;
2263   l_cancelled_po_qty            NUMBER;
2264   l_received_po_qty             NUMBER;
2265   l_corrected_po_qty            NUMBER;
2266   l_delivered_po_qty            NUMBER;
2267   l_rtv_po_qty                  NUMBER;
2268   l_billed_po_qty               NUMBER;
2269   l_accepted_po_qty             NUMBER;
2270   l_rejected_po_qty             NUMBER;
2271   l_ordered_txn_qty             NUMBER;
2272   l_cancelled_txn_qty           NUMBER;
2273   l_received_qty                NUMBER;
2274   l_corrected_qty               NUMBER;
2275   l_delivered_txn_qty           NUMBER;
2276   l_rtv_txn_qty                 NUMBER;
2277   l_billed_txn_qty              NUMBER;
2278   l_accepted_txn_qty            NUMBER;
2279   l_rejected_txn_qty            NUMBER;
2280   l_received_quantity_used      NUMBER;
2281   l_billed_quantity_used        NUMBER;
2282   l_accepted_quantity_used      NUMBER;
2283   l_received_amount_used        NUMBER;
2284   l_billed_amount_used          NUMBER;
2285   l_txn_uom                     VARCHAR2(25);
2286   l_po_uom                      VARCHAR2(25);
2287   l_item_id                     NUMBER;
2288   l_discarded_flag              ap_invoice_lines.discarded_flag%TYPE;
2289   l_cancelled_flag              ap_invoice_lines.cancelled_flag%TYPE;
2290   l_matching_basis              po_line_locations.matching_basis%TYPE;  -- Amount Based Matching
2291 
2292   --Contract Payments: Tolerances Redesign
2293   l_invoice_type_lookup_code    ap_invoices_all.invoice_type_lookup_code%TYPE;
2294   l_payment_type    po_line_locations_all.payment_type%TYPE;
2295   l_billed_amt      NUMBER;
2296   l_amt_delivered    NUMBER;
2297   l_amt_corrected    NUMBER;
2298   l_ret_status       VARCHAR2(100);
2299   l_msg_count         NUMBER;
2300   l_msg_data         VARCHAR2(250);
2301 
2302   l_debug_loc                   VARCHAR2(30) := 'Execute_Matched_Checks';
2303   l_curr_calling_sequence       VARCHAR2(2000);
2304   l_debug_info                  VARCHAR2(2000);
2305 
2306   -- 3488259 (3110072) Starts
2307   l_ship_amount                 NUMBER := 0;
2308   l_org_id                      NUMBER;
2309   l_fv_tol_check                VARCHAR2(1);
2310   -- 3488259 (3110072) Ends
2311 
2312   l_line_match_status_flag   VARCHAR2(25);  -- BUG 5182413
2313 
2314   -- Bug 5077550
2315   l_check_milestone_diff VARCHAR2(100);
2316   l_amt_billed_receipt                  NUMBER; --8894586
2317   l_final_match_count NUMBER := 0; --9459364
2318   l_api_name             CONSTANT VARCHAR2(200) := 'Execute_Matched_Checks';
2319 
2320 
2321 BEGIN
2322 
2323   l_curr_calling_sequence := 'AP_APPROVAL_MATCHED_PKG.'||l_debug_loc||'<-'||
2324                              p_calling_sequence;
2325 
2326   IF ( AP_APPROVAL_PKG.g_debug_mode = 'Y' ) THEN
2327     g_debug_mode := 'Y';
2328   END IF;
2329 
2330   l_action := 'UPDATE_CLOSE_STATE';
2331 
2332   -----------------------------------------
2333   l_debug_info := 'Open Matched_Cur';
2334   -----------------------------------------
2335   IF (g_debug_mode = 'Y') THEN
2336     AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
2337   END IF;
2338   IF (G_LEVEL_STATEMENT >= G_CURRENT_RUNTIME_LEVEL) THEN
2339     FND_LOG.STRING(G_LEVEL_STATEMENT,G_MODULE_NAME||l_api_name,l_debug_info);
2340   END IF;
2341 
2342   OPEN Matched_Cur;
2343   LOOP
2344 
2345     ---------------------------------------
2346     l_debug_info := 'Fetch Matched_Cur';
2347     ---------------------------------------
2348     IF (g_debug_mode = 'Y') THEN
2349       AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
2350     END IF;
2351     IF (G_LEVEL_STATEMENT >= G_CURRENT_RUNTIME_LEVEL) THEN
2352       FND_LOG.STRING(G_LEVEL_STATEMENT,G_MODULE_NAME||l_api_name,l_debug_info);
2353     END IF;
2354 
2355     FETCH Matched_Cur
2356     INTO l_line_location_id,
2357          l_po_line_id,
2358          l_inv_line_amount,
2359          l_line_match_status_flag, -- bug 5182413
2360          l_adj_qty_invoiced,
2361          l_po_unit_price,
2362          l_qty_ordered,
2363          l_qty_received,
2364          l_qty_accepted,
2365          l_amt_ordered,             -- Amount Based Matching
2366          l_amt_received,            -- Amount Based Matching
2367    l_amt_cancelled,      -- Contract Payments
2368          l_cancel_flag,
2369          l_receipt_required_flag,
2370          l_inspection_required_flag,
2371          l_inv_currency_code,
2372          l_po_currency_code,
2373          l_po_approved_flag,
2374          l_po_closed_code,
2375          l_final_match_flag,
2376    l_dist_final_match_flag,--bug5759169
2377          l_po_doc_type,
2378          l_po_sub_type,
2379          l_accrue_on_receipt_flag,
2380          l_po_header_id,
2381          l_po_num,
2382          l_match_option,
2383          l_rcv_transaction_id,
2384          l_txn_uom,
2385          l_item_id,
2386          l_po_uom,
2387          l_discarded_flag,
2388          l_cancelled_flag,
2389          l_matching_basis,         -- Amount Based Matching
2390    l_payment_type,          --Contract Payments: Tolerances Redesign
2391          l_invoice_type_lookup_code,   --Contract Payments: Tolerances Redesign
2392          l_org_id; -- 5500101
2393 
2394     EXIT WHEN Matched_Cur%NOTFOUND;
2395 
2396     l_final_matching_exists      := 'N';
2397     l_currency_difference_exists := 'N';
2398     l_po_not_approved_exists     := 'N';
2399     l_qty_ord_error_exists       := 'N';
2400     l_max_qty_ord_error_exists   := 'N';
2401     l_qty_rec_error_exists       := 'N';
2402     l_max_qty_rec_error_exists   := 'N';
2403     l_amt_ord_error_exists       := 'N';
2404     l_max_amt_ord_error_exists   := 'N';
2405     l_amt_rec_error_exists       := 'N';
2406     l_max_amt_rec_error_exists   := 'N';
2407     l_milestone_error_exists     := 'N';
2408     l_qty_overbilled_exists      := 'N';
2409     l_max_ship_amt_exceeded      := 'N';
2410     l_max_rate_amt_exceeded      := 'N';
2411     l_max_total_amt_exceeded     := 'N';
2412     l_ship_trx_amt_var           := 0;
2413     l_rate_amt_var               := 0;
2414     l_ship_base_amt_var          := 0;
2415 
2416     l_debug_info := 'Get receipt quantites for' ||
2417                       to_char(l_rcv_transaction_id);
2418 
2419     If ( l_match_option = 'R' ) Then
2420 
2421       If l_matching_basis = 'QUANTITY' Then  -- Amount Based Matching
2422 
2423         RCV_INVOICE_MATCHING_SV.get_quantities (
2424                 top_transaction_id  => l_rcv_transaction_id,  -- IN
2425                 ordered_po_qty      => l_ordered_po_qty,      -- IN OUT
2426                 cancelled_po_qty    => l_cancelled_po_qty,    -- IN OUT
2427                 received_po_qty     => l_received_po_qty,     -- IN OUT
2428                 corrected_po_qty    => l_corrected_po_qty,    -- IN OUT
2429                 delivered_po_qty    => l_delivered_po_qty,    -- IN OUT
2430                 rtv_po_qty          => l_rtv_po_qty,          -- IN OUT
2431                 billed_po_qty       => l_billed_po_qty,       -- IN OUT
2432                 accepted_po_qty     => l_accepted_po_qty,     -- IN OUT
2433                 rejected_po_qty     => l_rejected_po_qty,     -- IN OUT
2434                 ordered_txn_qty     => l_ordered_txn_qty,     -- IN OUT
2435                 cancelled_txn_qty   => l_cancelled_txn_qty,   -- IN OUT
2436                 received_txn_qty    => l_received_qty,        -- IN OUT
2437                 corrected_txn_qty   => l_corrected_qty,       -- IN OUT
2438                 delivered_txn_qty   => l_delivered_txn_qty,   -- IN OUT
2439                 rtv_txn_qty         => l_rtv_txn_qty,         -- IN OUT
2440                 billed_txn_qty      => l_billed_txn_qty,      -- IN OUT
2441                 accepted_txn_qty    => l_accepted_txn_qty,    -- IN OUT
2442                 rejected_txn_qty    => l_rejected_txn_qty);   -- IN OUT
2443 
2444       Elsif l_matching_basis = 'AMOUNT' Then
2445 
2446   --For the case of service orders, eventhough UOM is allowed on PO for certain line types
2447   --like Rate Based cannot be different on the receipt.
2448   --So we don't have to worry about the coversions between
2449   --different UOMs for the case of service order receipts.
2450 
2451   RCV_INVOICE_MATCHING_SV.Get_ReceiveAmount(
2452     P_Api_version => 1.0,
2453     P_Init_Msg_List => 'T',
2454     x_return_status => l_ret_status,
2455     x_msg_count  => l_msg_count,
2456     x_msg_data  => l_msg_data,
2457     P_receive_transaction_id =>  l_rcv_transaction_id  ,
2458     x_billed_amt  => l_amt_billed,
2459     x_received_amt    =>l_amt_received,
2460                 x_delivered_amt   =>l_amt_delivered,
2461     x_corrected_amt   =>l_amt_corrected);
2462 
2463    l_amt_billed_receipt := l_amt_billed ; --8894586
2464       End If;     -- Amount Based Matching
2465 
2466     End if;
2467 
2468     ---------------------------------------
2469     l_debug_info := 'Check PO closed code';
2470     ---------------------------------------
2471     IF (g_debug_mode = 'Y') THEN
2472       AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
2473     END IF;
2474     IF (G_LEVEL_STATEMENT >= G_CURRENT_RUNTIME_LEVEL) THEN
2475       FND_LOG.STRING(G_LEVEL_STATEMENT,G_MODULE_NAME||l_api_name,l_debug_info);
2476     END IF;
2477 
2478    /*-----------------------------------------------------------------+
2479     |  Set final_matching_exists to 'Y' when po_close_code is final   |
2480     |  and final_match_flag is not 'Done' and invoice line is Matched |
2481     |  and not discarded or cancelled. Because system does allow 0    |
2482     |  amount and 0 unit price matching. line amount <> 0 is not      |
2483     |  sufficient to determine if invoice line is an effective        |
2484     |  matching line                                                  |
2485     +-----------------------------------------------------------------*/
2486     --bug5759169.Added the below IF statement
2487     --added the code to place hold on all invoices with final_match flag as 'R'
2488     --which indicates that the invoice has been created after the
2489     --final matching is done already.
2490     --Hold is also placed on the invoice if the PO has already been closed
2491     --and if the final match flag is not equal to 'D'
2492 
2493 
2494      IF (l_dist_final_match_flag='R'
2495          --Introduced below 2 conditions for bug#9459364
2496         and NVL(l_discarded_flag, 'N' ) <> 'Y'
2497         and NVL(l_cancelled_flag, 'N' ) <> 'Y' ) THEN  --bug5759169
2498 
2499 	  --Start 9459364
2500         -- l_final_matching_exists := 'Y';  --bug5759169
2501 
2502            BEGIN
2503 		SELECT 1 INTO l_final_match_count
2504 	        FROM   ap_invoice_lines_all
2505 		WHERE  po_line_location_id  = l_line_location_id
2506 		AND  nvl(final_match_flag,'N') in ('D','Y')
2507 		AND  nvl(discarded_flag,'N')<>'Y'
2508 		AND  nvl(cancelled_flag,'N')<>'Y'
2509 		AND  rownum=1;
2510 
2511 		EXCEPTION
2512 			WHEN NO_DATA_FOUND THEN
2513 			l_final_match_count := 0;
2514            END;
2515 
2516 	IF(l_final_match_count>0) THEN
2517 		l_final_matching_exists := 'Y';
2518 	END IF;
2519      --End 9459364
2520 
2521       --Commented below ELSIF clause for bug#10327622
2522       /* --Bug8917261: Changed value not equal to Y for discarded_flag
2523          --and cancelled_flag
2524          ELSIF ((l_po_closed_code = 'FINALLY CLOSED') AND
2525            (l_final_match_flag <> 'D') AND
2526            (l_line_match_status_flag <> 'APPROVED') AND      -- BUG 5182413
2527            (NVL(l_discarded_flag, 'N' ) <> 'Y') AND
2528            (NVL(l_cancelled_flag, 'N' ) <> 'Y') )THEN
2529 
2530            l_final_matching_exists := 'Y';  */
2531 
2532        --End bug#10327622
2533 
2534     END IF;
2535 
2536 
2537     -----------------------------------------------------------------
2538     l_debug_info := 'Process FINAL MATCHING hold for shipment match';
2539     -----------------------------------------------------------------
2540     IF (g_debug_mode = 'Y') THEN
2541       AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
2542     END IF;
2543     IF (G_LEVEL_STATEMENT >= G_CURRENT_RUNTIME_LEVEL) THEN
2544       FND_LOG.STRING(G_LEVEL_STATEMENT,G_MODULE_NAME||l_api_name,l_debug_info);
2545     END IF;
2546 
2547     AP_APPROVAL_PKG.Process_Inv_Hold_Status(
2548               p_invoice_id,
2549               l_line_location_id,
2550               l_rcv_transaction_id,
2551               'FINAL MATCHING',
2552               l_final_matching_exists,
2553               null,
2554               p_system_user,
2555               p_holds,
2556               p_holds_count,
2557               p_release_count,
2558               l_curr_calling_sequence);
2559 
2560     ------------------------------------------------
2561     l_debug_info := 'Check for Currency Difference';
2562     ------------------------------------------------
2563     IF (g_debug_mode = 'Y') THEN
2564       AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
2565     END IF;
2566     IF (G_LEVEL_STATEMENT >= G_CURRENT_RUNTIME_LEVEL) THEN
2567       FND_LOG.STRING(G_LEVEL_STATEMENT,G_MODULE_NAME||l_api_name,l_debug_info);
2568     END IF;
2569 
2570     IF (l_inv_currency_code <> l_po_currency_code) THEN
2571 
2572       l_currency_difference_exists := 'Y';
2573 
2574     END IF;
2575 
2576     ----------------------------------------------------------------------
2577     l_debug_info := 'Process CURRENCY DIFFERENCE hold for shipment match';
2578     ----------------------------------------------------------------------
2579     IF (g_debug_mode = 'Y') THEN
2580       AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
2581     END IF;
2582     IF (G_LEVEL_STATEMENT >= G_CURRENT_RUNTIME_LEVEL) THEN
2583       FND_LOG.STRING(G_LEVEL_STATEMENT,G_MODULE_NAME||l_api_name,l_debug_info);
2584     END IF;
2585 
2586     AP_APPROVAL_PKG.Process_Inv_Hold_Status(
2587               p_invoice_id,
2588               l_line_location_id,
2589               l_rcv_transaction_id,
2590               'CURRENCY DIFFERENCE',
2591                l_currency_difference_exists,
2592                null,
2593                p_system_user,
2594                p_holds,
2595                p_holds_count,
2596                p_release_count,
2597                l_curr_calling_sequence);
2598 
2599     -----------------------------------------
2600     l_debug_info := 'Check PO Approval Flag';
2601     -----------------------------------------
2602     IF (g_debug_mode = 'Y') THEN
2603       AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
2604     END IF;
2605     IF (G_LEVEL_STATEMENT >= G_CURRENT_RUNTIME_LEVEL) THEN
2606       FND_LOG.STRING(G_LEVEL_STATEMENT,G_MODULE_NAME||l_api_name,l_debug_info);
2607     END IF;
2608 
2609     --Bug8971070: Corrected the conditional operator from '<>' to '='
2610     --for l_discarded_flag and l_cancelled_flag
2611     IF ((l_po_approved_flag <> 'Y') AND
2612         (NVL(l_discarded_flag, 'N' ) = 'N') AND
2613         (NVL(l_cancelled_flag, 'N' ) = 'N') )THEN
2614 
2615       l_po_not_approved_exists := 'Y';
2616 
2617     END IF;
2618 
2619     ------------------------------------------------------------------
2620     l_debug_info := 'Process PO NOT APPROVED hold for shipment match';
2621     ------------------------------------------------------------------
2622     IF (g_debug_mode = 'Y') THEN
2623       AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
2624     END IF;
2625     IF (G_LEVEL_STATEMENT >= G_CURRENT_RUNTIME_LEVEL) THEN
2626       FND_LOG.STRING(G_LEVEL_STATEMENT,G_MODULE_NAME||l_api_name,l_debug_info);
2627     END IF;
2628 
2629     AP_APPROVAL_PKG.Process_Inv_Hold_Status(
2630               p_invoice_id,
2631               l_line_location_id,
2632               l_rcv_transaction_id,
2633               'PO NOT APPROVED',
2634               l_po_not_approved_exists,
2635               null,
2636               p_system_user,
2637               p_holds,
2638               p_holds_count,
2639               p_release_count,
2640               l_curr_calling_sequence);
2641 
2642     ------------------------------------------
2643     l_debug_info := 'Check Receipt Exception';
2644     ------------------------------------------
2645     IF (g_debug_mode = 'Y') THEN
2646       AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
2647     END IF;
2648     IF (G_LEVEL_STATEMENT >= G_CURRENT_RUNTIME_LEVEL) THEN
2649       FND_LOG.STRING(G_LEVEL_STATEMENT,G_MODULE_NAME||l_api_name,l_debug_info);
2650     END IF;
2651 
2652     Check_Receipt_Exception(
2653             p_invoice_id,
2654             l_line_location_id,
2655             l_match_option,
2656             l_rcv_transaction_id,
2657             p_system_user,
2658             p_holds,
2659             p_holds_count,
2660             p_release_count,
2661             l_curr_calling_sequence);
2662 
2663     -------------------------------------------------------------
2664      l_debug_info := 'Calculate Invoice Shipment Quantity Billed';
2665     -------------------------------------------------------------
2666     IF (g_debug_mode = 'Y') THEN
2667       AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
2668     END IF;
2669     IF (G_LEVEL_STATEMENT >= G_CURRENT_RUNTIME_LEVEL) THEN
2670       FND_LOG.STRING(G_LEVEL_STATEMENT,G_MODULE_NAME||l_api_name,l_debug_info);
2671     END IF;
2672 
2673     IF (l_payment_type <> 'MILESTONE') THEN
2674 
2675        If l_matching_basis = 'QUANTITY' Then   -- Amount Based Matching
2676 
2677           Calc_Total_Shipment_Qty_Billed(
2678                 p_invoice_id,
2679             l_line_location_id,
2680             l_match_option,
2681             l_rcv_transaction_id,
2682             l_qty_billed,
2683       l_invoice_type_lookup_code, --Contract Payments
2684            l_curr_calling_sequence);
2685 
2686          -----------------------------------------
2687          l_debug_info := 'Check Quantity Ordered';
2688          -----------------------------------------
2689          IF (g_debug_mode = 'Y') THEN
2690            AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
2691          END IF;
2692          IF (G_LEVEL_STATEMENT >= G_CURRENT_RUNTIME_LEVEL) THEN
2693            FND_LOG.STRING(G_LEVEL_STATEMENT,G_MODULE_NAME||l_api_name,l_debug_info);
2694          END IF;
2695 
2696          IF (p_qty_tol IS NOT NULL) THEN
2697             IF (l_qty_billed > (p_qty_tol * l_qty_ordered)) THEN
2698 
2699                l_qty_ord_error_exists := 'Y';
2700 
2701             END IF;
2702          ELSE
2703             l_qty_ord_error_exists := 'N';
2704          END IF;
2705 
2706          ----------------------------------------------------------
2707          l_debug_info := 'Process QTY ORD hold for shipment match';
2708          ----------------------------------------------------------
2709          IF (g_debug_mode = 'Y') THEN
2710             AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
2711          END IF;
2712          IF (G_LEVEL_STATEMENT >= G_CURRENT_RUNTIME_LEVEL) THEN
2713             FND_LOG.STRING(G_LEVEL_STATEMENT,G_MODULE_NAME||l_api_name,l_debug_info);
2714          END IF;
2715 
2716          AP_APPROVAL_PKG.Process_Inv_Hold_Status(
2717               p_invoice_id,
2718               l_line_location_id,
2719               l_rcv_transaction_id,
2720               'QTY ORD',
2721               l_qty_ord_error_exists,
2722               null,
2723               p_system_user,
2724               p_holds,
2725               p_holds_count,
2726               p_release_count,
2727               l_curr_calling_sequence);
2728 
2729          -------------------------------------------------
2730          l_debug_info := 'Check Maximim Quantity Ordered';
2731          -------------------------------------------------
2732          IF (G_LEVEL_STATEMENT >= G_CURRENT_RUNTIME_LEVEL) THEN
2733            FND_LOG.STRING(G_LEVEL_STATEMENT,G_MODULE_NAME||l_api_name,l_debug_info);
2734          END IF;
2735          IF (p_max_qty_ord_tol IS NOT NULL) THEN
2736            IF (l_qty_billed > (p_max_qty_ord_tol + l_qty_ordered)) THEN
2737              l_max_qty_ord_error_exists := 'Y';
2738            END IF;
2739          ELSE
2740            l_max_qty_ord_error_exists := 'N';
2741          END IF;
2742 
2743          --------------------------------------------------------------
2744          l_debug_info := 'Process MAX QTY ORD hold for shipment match';
2745          --------------------------------------------------------------
2746          IF (g_debug_mode = 'Y') THEN
2747             AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
2748          END IF;
2749          IF (G_LEVEL_STATEMENT >= G_CURRENT_RUNTIME_LEVEL) THEN
2750            FND_LOG.STRING(G_LEVEL_STATEMENT,G_MODULE_NAME||l_api_name,l_debug_info);
2751          END IF;
2752 
2753          AP_APPROVAL_PKG.Process_Inv_Hold_Status(
2754               p_invoice_id,
2755               l_line_location_id,
2756               l_rcv_transaction_id,
2757               'MAX QTY ORD',
2758               l_max_qty_ord_error_exists,
2759               null,
2760               p_system_user,
2761               p_holds,
2762               p_holds_count,
2763               p_release_count,
2764               l_curr_calling_sequence);
2765 
2766          ------------------------------------------
2767          l_debug_info := 'Check Quantity Received ';
2768          ------------------------------------------
2769          IF (g_debug_mode = 'Y') THEN
2770             AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
2771          END IF;
2772          IF (G_LEVEL_STATEMENT >= G_CURRENT_RUNTIME_LEVEL) THEN
2773            FND_LOG.STRING(G_LEVEL_STATEMENT,G_MODULE_NAME||l_api_name,l_debug_info);
2774          END IF;
2775 
2776         /*-----------------------------------------------------------------+
2777          |  Calculate the net quantity received. the values are got from   |
2778          |  calling the PO api earlier on. the same tolerance is used to   |
2779          |  check if it needs to be put on hold. Note however that if      |
2780          |  matched to receipt, quantites are in Receipt UOM and if        |
2781          |  matching to PO quantities are in PO UOM.                       |
2782          +-----------------------------------------------------------------*/
2783 
2784          If (l_match_option = 'R') then
2785             l_received_quantity_used:= nvl(l_received_qty,0)
2786                                    + nvl(l_corrected_qty,0)
2787                                    - nvl(l_rtv_txn_qty,0);
2788             l_billed_quantity_used := nvl(l_billed_txn_qty,0);
2789 
2790          Elsif (l_match_option = 'P') then
2791 
2792             l_received_quantity_used := l_qty_received;
2793             l_billed_quantity_used := l_qty_billed;
2794 
2795          End if;
2796 
2797 
2798          IF (p_qty_rec_tol IS NOT NULL) THEN
2799            IF ((l_billed_quantity_used >(p_qty_rec_tol * l_received_quantity_used))
2800              AND (l_receipt_required_flag = 'Y')) THEN
2801 
2802              l_qty_rec_error_exists := 'Y';
2803 
2804            END IF;
2805          ELSE
2806            l_qty_rec_error_exists := 'N';
2807          END IF;
2808 
2809          ----------------------------------------------------------
2810          l_debug_info := 'Process QTY REC hold for shipment match';
2811          ----------------------------------------------------------
2812          IF (g_debug_mode = 'Y') THEN
2813             AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
2814          END IF;
2815          IF (G_LEVEL_STATEMENT >= G_CURRENT_RUNTIME_LEVEL) THEN
2816            FND_LOG.STRING(G_LEVEL_STATEMENT,G_MODULE_NAME||l_api_name,l_debug_info);
2817          END IF;
2818 
2819          AP_APPROVAL_PKG.Process_Inv_Hold_Status(
2820               p_invoice_id,
2821               l_line_location_id,
2822               l_rcv_transaction_id,
2823               'QTY REC',
2824               l_qty_rec_error_exists,
2825               null,
2826               p_system_user,
2827               p_holds,
2828               p_holds_count,
2829               p_release_count,
2830               l_curr_calling_sequence);
2831 
2832          --------------------------------------------------
2833          l_debug_info := 'Check Maximum Quantity Received';
2834          --------------------------------------------------
2835          IF (g_debug_mode = 'Y') THEN
2836            AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
2837          END IF;
2838          IF (G_LEVEL_STATEMENT >= G_CURRENT_RUNTIME_LEVEL) THEN
2839            FND_LOG.STRING(G_LEVEL_STATEMENT,G_MODULE_NAME||l_api_name,l_debug_info);
2840          END IF;
2841 
2842          IF (p_max_qty_rec_tol IS NOT NULL) THEN
2843             IF ( (l_billed_quantity_used >
2844                (p_max_qty_rec_tol + l_received_quantity_used))
2845                AND (l_receipt_required_flag = 'Y')) THEN
2846 
2847                l_max_qty_rec_error_exists := 'Y';
2848 
2849             END IF;
2850          ELSE
2851             l_max_qty_rec_error_exists := 'N';
2852          END IF;
2853 
2854          --------------------------------------------------------------
2855          l_debug_info := 'Process MAX QTY REC hold for shipment match';
2856          --------------------------------------------------------------
2857          IF (g_debug_mode = 'Y') THEN
2858             AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
2859          END IF;
2860          IF (G_LEVEL_STATEMENT >= G_CURRENT_RUNTIME_LEVEL) THEN
2861            FND_LOG.STRING(G_LEVEL_STATEMENT,G_MODULE_NAME||l_api_name,l_debug_info);
2862          END IF;
2863 
2864          AP_APPROVAL_PKG.Process_Inv_Hold_Status(
2865               p_invoice_id,
2866               l_line_location_id,
2867               l_rcv_transaction_id,
2868               'MAX QTY REC',
2869               l_max_qty_rec_error_exists,
2870               null,
2871               p_system_user,
2872               p_holds,
2873               p_holds_count,
2874               p_release_count,
2875               l_curr_calling_sequence);
2876 
2877          ------------------------------
2878          l_debug_info := 'Check Price';
2879          ------------------------------
2880          IF (g_debug_mode = 'Y') THEN
2881             AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
2882          END IF;
2883          IF (G_LEVEL_STATEMENT >= G_CURRENT_RUNTIME_LEVEL) THEN
2884            FND_LOG.STRING(G_LEVEL_STATEMENT,G_MODULE_NAME||l_api_name,l_debug_info);
2885          END IF;
2886 
2887          Check_Price(
2888               p_invoice_id,
2889               l_line_location_id,
2890               l_rcv_transaction_id,
2891               l_match_option,
2892               l_txn_uom,
2893               l_po_uom,
2894               l_item_id,
2895               l_inv_currency_code,
2896               l_po_unit_price,
2897               p_price_tol,
2898               p_system_user,
2899               p_holds,
2900               p_holds_count,
2901               p_release_count,
2902               l_curr_calling_sequence);
2903 
2904          -------------------------------------------
2905          l_debug_info := 'Check Quantity Inspected';
2906          -------------------------------------------
2907          IF (g_debug_mode = 'Y') THEN
2908             AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
2909          END IF;
2910          IF (G_LEVEL_STATEMENT >= G_CURRENT_RUNTIME_LEVEL) THEN
2911            FND_LOG.STRING(G_LEVEL_STATEMENT,G_MODULE_NAME||l_api_name,l_debug_info);
2912          END IF;
2913 
2914          IF (l_match_option = 'R') THEN
2915             l_billed_quantity_used := nvl(l_billed_txn_qty,0); -- from po api
2916             l_accepted_quantity_used := nvl(l_accepted_txn_qty,0);
2917          ELSIF (l_match_option = 'P') THEN
2918             l_billed_quantity_used := l_qty_billed; -- calculated earlier
2919             l_accepted_quantity_used := l_qty_accepted; -- from cursor
2920          END IF;
2921 
2922          IF ((l_billed_quantity_used > l_accepted_quantity_used) AND
2923              (l_inspection_required_flag = 'Y')) THEN
2924             l_qty_overbilled_exists := 'Y';
2925 
2926          END IF;
2927 
2928          ----------------------------------------------------------
2929          l_debug_info := 'Process QUALITY hold for shipment match';
2930          ----------------------------------------------------------
2931          IF (g_debug_mode = 'Y') THEN
2932             AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
2933          END IF;
2934          IF (G_LEVEL_STATEMENT >= G_CURRENT_RUNTIME_LEVEL) THEN
2935            FND_LOG.STRING(G_LEVEL_STATEMENT,G_MODULE_NAME||l_api_name,l_debug_info);
2936          END IF;
2937 
2938          AP_APPROVAL_PKG.Process_Inv_Hold_Status(
2939               p_invoice_id,
2940               l_line_location_id,
2941               l_rcv_transaction_id,
2942               'QUALITY',
2943               l_qty_overbilled_exists,
2944               NULL,
2945               p_system_user,
2946               p_holds,
2947               p_holds_count,
2948               p_release_count,
2949               l_curr_calling_sequence);
2950 
2951 
2952        --Contract Payment: Tolerances Redesign
2953        ELSIF l_matching_basis = 'AMOUNT' THEN
2954 
2955            Calc_Total_Shipment_Amt_Billed(
2956             p_invoice_id,
2957             l_line_location_id,
2958             l_match_option,
2959             l_rcv_transaction_id,
2960             l_amt_billed,
2961             l_invoice_type_lookup_code,
2962             l_curr_calling_sequence);
2963 
2964            -----------------------------------------
2965            l_debug_info := 'Check Amount Ordered';
2966            -----------------------------------------
2967            IF (g_debug_mode = 'Y') THEN
2968              AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
2969            END IF;
2970            IF (G_LEVEL_STATEMENT >= G_CURRENT_RUNTIME_LEVEL) THEN
2971              FND_LOG.STRING(G_LEVEL_STATEMENT,G_MODULE_NAME||l_api_name,l_debug_info);
2972            END IF;
2973 
2974            IF (p_amt_tol IS NOT NULL) THEN
2975               IF (l_amt_billed > (p_amt_tol * l_amt_ordered)) THEN
2976 
2977                  l_amt_ord_error_exists := 'Y';
2978 
2979               END IF;
2980            ELSE
2981               l_amt_ord_error_exists := 'N';
2982            END IF;
2983 
2984            ----------------------------------------------------------
2985            l_debug_info := 'Process AMT ORD hold for shipment match';
2986            ----------------------------------------------------------
2987            IF (g_debug_mode = 'Y') THEN
2988               AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
2989            END IF;
2990            IF (G_LEVEL_STATEMENT >= G_CURRENT_RUNTIME_LEVEL) THEN
2991              FND_LOG.STRING(G_LEVEL_STATEMENT,G_MODULE_NAME||l_api_name,l_debug_info);
2992            END IF;
2993 
2994            AP_APPROVAL_PKG.Process_Inv_Hold_Status(
2995               p_invoice_id,
2996               l_line_location_id,
2997               l_rcv_transaction_id,
2998               'AMT ORD',
2999               l_amt_ord_error_exists,
3000               null,
3001               p_system_user,
3002               p_holds,
3003               p_holds_count,
3004               p_release_count,
3005               l_curr_calling_sequence);
3006 
3007            -------------------------------------------------
3008            l_debug_info := 'Check Maximum Amount Ordered';
3009            -------------------------------------------------
3010            IF (G_LEVEL_STATEMENT >= G_CURRENT_RUNTIME_LEVEL) THEN
3011              FND_LOG.STRING(G_LEVEL_STATEMENT,G_MODULE_NAME||l_api_name,l_debug_info);
3012            END IF;
3013            IF (p_max_amt_ord_tol IS NOT NULL) THEN
3014               IF (l_amt_billed > (p_max_amt_ord_tol + l_amt_ordered)) THEN
3015                   l_max_amt_ord_error_exists := 'Y';
3016               END IF;
3017            ELSE
3018               l_max_amt_ord_error_exists := 'N';
3019            END IF;
3020 
3021            --------------------------------------------------------------
3022            l_debug_info := 'Process MAX AMT ORD hold for shipment match';
3023            --------------------------------------------------------------
3024            IF (g_debug_mode = 'Y') THEN
3025               AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
3026            END IF;
3027            IF (G_LEVEL_STATEMENT >= G_CURRENT_RUNTIME_LEVEL) THEN
3028              FND_LOG.STRING(G_LEVEL_STATEMENT,G_MODULE_NAME||l_api_name,l_debug_info);
3029            END IF;
3030 
3031            AP_APPROVAL_PKG.Process_Inv_Hold_Status(
3032               p_invoice_id,
3033               l_line_location_id,
3034               l_rcv_transaction_id,
3035               'MAX AMT ORD',
3036               l_max_amt_ord_error_exists,
3037               null,
3038               p_system_user,
3039               p_holds,
3040               p_holds_count,
3041               p_release_count,
3042               l_curr_calling_sequence);
3043 
3044            ------------------------------------------
3045            l_debug_info := 'Check Amount Received ';
3046            ------------------------------------------
3047            IF (g_debug_mode = 'Y') THEN
3048               AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
3049            END IF;
3050            IF (G_LEVEL_STATEMENT >= G_CURRENT_RUNTIME_LEVEL) THEN
3051              FND_LOG.STRING(G_LEVEL_STATEMENT,G_MODULE_NAME||l_api_name,l_debug_info);
3052            END IF;
3053 
3054            /*-----------------------------------------------------------------+
3055             |  Calculate the net amount received. the values are got from     |
3056             |  calling the PO api earlier on. the same tolerance is used to   |
3057             |  check if it needs to be put on hold.                           |
3058             +-----------------------------------------------------------------*/
3059 
3060             If (l_match_option = 'R') then
3061                l_received_amount_used:= nvl(l_amt_received,0)
3062                                        + nvl(l_amt_corrected,0) ;
3063              --  l_billed_amount_used := nvl(l_amt_billed,0);
3064 	     --  8894586 commented and added below statement
3065 	       l_billed_amount_used := nvl(l_amt_billed_receipt,0) ;--8894586
3066             Elsif (l_match_option = 'P') then
3067                l_received_amount_used := nvl(l_amt_received,0);
3068                l_billed_amount_used := nvl(l_amt_billed,0);
3069             End if;
3070 
3071 
3072             IF (p_amt_rec_tol IS NOT NULL) THEN
3073                IF ((l_billed_amount_used >(p_amt_rec_tol * l_received_amount_used))
3074                   AND (l_receipt_required_flag = 'Y')) THEN
3075                   l_amt_rec_error_exists := 'Y';
3076 
3077                END IF;
3078             ELSE
3079                l_amt_rec_error_exists := 'N';
3080             END IF;
3081 
3082             ----------------------------------------------------------
3083             l_debug_info := 'Process AMT REC hold for shipment match';
3084             ----------------------------------------------------------
3085             IF (g_debug_mode = 'Y') THEN
3086                AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
3087             END IF;
3088            IF (G_LEVEL_STATEMENT >= G_CURRENT_RUNTIME_LEVEL) THEN
3089              FND_LOG.STRING(G_LEVEL_STATEMENT,G_MODULE_NAME||l_api_name,l_debug_info);
3090            END IF;
3091 
3092             AP_APPROVAL_PKG.Process_Inv_Hold_Status(
3093               p_invoice_id,
3094               l_line_location_id,
3095               l_rcv_transaction_id,
3096               'AMT REC',
3097               l_amt_rec_error_exists,
3098               null,
3099               p_system_user,
3100               p_holds,
3101               p_holds_count,
3102               p_release_count,
3103               l_curr_calling_sequence);
3104 
3105             --------------------------------------------------
3106             l_debug_info := 'Check Maximum Amount Received';
3107             --------------------------------------------------
3108             IF (g_debug_mode = 'Y') THEN
3109                AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
3110             END IF;
3111            IF (G_LEVEL_STATEMENT >= G_CURRENT_RUNTIME_LEVEL) THEN
3112              FND_LOG.STRING(G_LEVEL_STATEMENT,G_MODULE_NAME||l_api_name,l_debug_info);
3113            END IF;
3114 
3115             IF (p_max_amt_rec_tol IS NOT NULL) THEN
3116                IF ( (l_billed_amount_used >
3117                     (p_max_amt_rec_tol + l_received_amount_used))
3118                   AND (l_receipt_required_flag = 'Y')) THEN
3119 
3120                   l_max_amt_rec_error_exists := 'Y';
3121 
3122                END IF;
3123             ELSE
3124                l_max_amt_rec_error_exists := 'N';
3125             END IF;
3126 
3127             --------------------------------------------------------------
3128             l_debug_info := 'Process MAX AMT REC hold for shipment match';
3129             --------------------------------------------------------------
3130             IF (g_debug_mode = 'Y') THEN
3131                AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
3132             END IF;
3133            IF (G_LEVEL_STATEMENT >= G_CURRENT_RUNTIME_LEVEL) THEN
3134              FND_LOG.STRING(G_LEVEL_STATEMENT,G_MODULE_NAME||l_api_name,l_debug_info);
3135            END IF;
3136 
3137             AP_APPROVAL_PKG.Process_Inv_Hold_Status(
3138                         p_invoice_id,
3139                   l_line_location_id,
3140                        l_rcv_transaction_id,
3141                  'MAX AMT REC',
3142                   l_max_amt_rec_error_exists,
3143                  null,
3144                    p_system_user,
3145                        p_holds,
3146                        p_holds_count,
3147                        p_release_count,
3148                        l_curr_calling_sequence);
3149 
3150        END IF;   -- Amount Based Matching. Matchiing Basis is QUANTITY
3151 
3152     --Contract Payments
3153     ELSIF (l_payment_type = 'MILESTONE') THEN
3154 
3155        IF (l_matching_basis = 'QUANTITY') THEN
3156 
3157            Calc_Total_Shipment_Qty_Billed(
3158                 p_invoice_id,
3159             l_line_location_id,
3160             l_match_option,
3161             l_rcv_transaction_id,
3162             l_qty_billed,
3163       l_invoice_type_lookup_code, --Contract Payments
3164            l_curr_calling_sequence);
3165 
3166            --
3167            -- Bug 5077550
3168            --
3169            l_check_milestone_diff :=
3170              Check_Milestone_Price_Qty(p_invoice_id,
3171                                            l_line_location_id,
3172                                            l_po_unit_price,
3173                                            l_curr_calling_sequence);
3174 
3175             -----------------------------------------------------------
3176             l_debug_info := 'Check for Milestone Hold for Quantity Ordered';
3177             -----------------------------------------------------------
3178             IF (g_debug_mode = 'Y') THEN
3179                AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
3180             END IF;
3181             IF (G_LEVEL_STATEMENT >= G_CURRENT_RUNTIME_LEVEL) THEN
3182               FND_LOG.STRING(G_LEVEL_STATEMENT,G_MODULE_NAME||l_api_name,l_debug_info);
3183             END IF;
3184             --
3185             -- Bug 5077550
3186             -- When the pay item type is milestone and the match basis is
3187             -- quantity, we should allow partial billing.
3188             -- we will not allow over billing
3189             -- we will not allow amount to be anything other than that of the
3190             -- value of the pay item.
3191             -- since we are supporting partial billing and rounding of
3192             -- amounts/price involved we will verify
3193             -- only the following:
3194             --   1) total quantity billed for this shipment should be less than
3195             --      that of the ordered qty.
3196             --   2) unit price should be same at the invoice line and the
3197             --      PO Shipment
3198             --   3) The quantity invoiced should be an integer and cannot
3199             --      have decimals tied to it. /*7356651 modified below if */
3200 
3201             IF (l_qty_billed > l_qty_ordered) OR
3202                (l_check_milestone_diff =
3203                 -- 'Price Difference or Quantity Has Decimals' and l_qty_billed<>0)    ..  bug8704810
3204                 'Price Difference' and l_qty_billed<>0)                                --  bug8704810
3205                THEN
3206                 l_milestone_error_exists := 'Y';
3207             ELSE
3208     l_milestone_error_exists := 'N';
3209             END IF;
3210 
3211             ----------------------------------------------------------
3212             l_debug_info := 'Process MILESTONE hold for shipment match';
3213             ----------------------------------------------------------
3214             IF (g_debug_mode = 'Y') THEN
3215                AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
3216             END IF;
3217             IF (G_LEVEL_STATEMENT >= G_CURRENT_RUNTIME_LEVEL) THEN
3218               FND_LOG.STRING(G_LEVEL_STATEMENT,G_MODULE_NAME||l_api_name,l_debug_info);
3219             END IF;
3220 
3221             AP_APPROVAL_PKG.Process_Inv_Hold_Status(
3222                 p_invoice_id,
3223                 l_line_location_id,
3224                 l_rcv_transaction_id,
3225                 'MILESTONE',
3226                 l_milestone_error_exists,
3227                 null,
3228                 p_system_user,
3229                 p_holds,
3230                 p_holds_count,
3231                 p_release_count,
3232                 l_curr_calling_sequence);
3233 
3234          -- BUG6777765 START
3235          ------------------------------------------
3236          l_debug_info := 'Check Quantity Received ';
3237          ------------------------------------------
3238 
3239 
3240          IF (g_debug_mode = 'Y') THEN
3241             AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
3242          END IF;
3243          IF (G_LEVEL_STATEMENT >= G_CURRENT_RUNTIME_LEVEL) THEN
3244             FND_LOG.STRING(G_LEVEL_STATEMENT,G_MODULE_NAME||l_api_name,l_debug_info);
3245          END IF;
3246 
3247         /*-----------------------------------------------------------------+
3248          |  Calculate the net quantity received. the values are got from   |
3249          |  calling the PO api earlier on. the same tolerance is used to   |
3250          |  check if it needs to be put on hold. Note however that if      |
3251          |  matched to receipt, quantites are in Receipt UOM and if        |
3252          |  matching to PO quantities are in PO UOM.                       |
3253          +-----------------------------------------------------------------*/
3254 
3255          If (l_match_option = 'R') then
3256             l_received_quantity_used:= nvl(l_received_qty,0)
3257                                    + nvl(l_corrected_qty,0)
3258                                    - nvl(l_rtv_txn_qty,0);
3259             l_billed_quantity_used := nvl(l_billed_txn_qty,0);
3260 
3261          Elsif (l_match_option = 'P') then
3262 
3263             l_received_quantity_used := l_qty_received;
3264             l_billed_quantity_used := l_qty_billed;
3265 
3266          End if;
3267 
3268 
3269          IF (p_qty_rec_tol IS NOT NULL) THEN
3270            IF ((l_billed_quantity_used >(p_qty_rec_tol * l_received_quantity_used))
3271              AND (l_receipt_required_flag = 'Y')) THEN
3272 
3273              l_qty_rec_error_exists := 'Y';
3274 
3275            END IF;
3276          ELSE
3277            l_qty_rec_error_exists := 'N';
3278          END IF;
3279 
3280          ----------------------------------------------------------
3281          l_debug_info := 'Process QTY REC hold for shipment match';
3282          ----------------------------------------------------------
3283          IF (g_debug_mode = 'Y') THEN
3284             AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
3285          END IF;
3286 	 IF (G_LEVEL_STATEMENT >= G_CURRENT_RUNTIME_LEVEL) THEN
3287            FND_LOG.STRING(G_LEVEL_STATEMENT,G_MODULE_NAME||l_api_name,l_debug_info);
3288          END IF;
3289 
3290          AP_APPROVAL_PKG.Process_Inv_Hold_Status(
3291               p_invoice_id,
3292               l_line_location_id,
3293               l_rcv_transaction_id,
3294               'QTY REC',
3295               l_qty_rec_error_exists,
3296               null,
3297               p_system_user,
3298               p_holds,
3299               p_holds_count,
3300               p_release_count,
3301               l_curr_calling_sequence);
3302 
3303          --BUG6777765 END
3304 
3305 
3306        ELSIF (l_matching_basis = 'AMOUNT') THEN
3307 
3308           Calc_Total_Shipment_Amt_Billed(
3309             p_invoice_id,
3310             l_line_location_id,
3311             l_match_option,
3312             l_rcv_transaction_id,
3313             l_amt_billed,
3314             l_invoice_type_lookup_code,
3315             l_curr_calling_sequence);
3316 
3317            -----------------------------------------
3318            l_debug_info := 'Check Amount Ordered';
3319            -----------------------------------------
3320            IF (g_debug_mode = 'Y') THEN
3321              AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
3322            END IF;
3323            IF (G_LEVEL_STATEMENT >= G_CURRENT_RUNTIME_LEVEL) THEN
3324              FND_LOG.STRING(G_LEVEL_STATEMENT,G_MODULE_NAME||l_api_name,l_debug_info);
3325            END IF;
3326 
3327 --Bug6830703
3328 --added the condition l_amt_billed<>0 to avoid checking
3329 --the milestone hold condition for cancellation event
3330 --because for cancellation of invoice line amount is updated to 0
3331 --this results in the unnecessary hold placement
3332 --
3333 
3334 
3335            IF (l_amt_billed<>0 and l_amt_billed <> l_amt_ordered) THEN
3336               l_milestone_error_exists := 'Y';
3337            ELSE
3338               l_milestone_error_exists := 'N';
3339            END IF;
3340 
3341            ----------------------------------------------------------
3342            l_debug_info := 'Process AMT ORD hold for shipment match';
3343            ----------------------------------------------------------
3344            IF (g_debug_mode = 'Y') THEN
3345               AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
3346            END IF;
3347 	   IF (G_LEVEL_STATEMENT >= G_CURRENT_RUNTIME_LEVEL) THEN
3348              FND_LOG.STRING(G_LEVEL_STATEMENT,G_MODULE_NAME||l_api_name,l_debug_info);
3349            END IF;
3350 
3351            AP_APPROVAL_PKG.Process_Inv_Hold_Status(
3352               p_invoice_id,
3353               l_line_location_id,
3354               l_rcv_transaction_id,
3355               'MILESTONE',
3356               l_milestone_error_exists,
3357               null,
3358               p_system_user,
3359               p_holds,
3360               p_holds_count,
3361               p_release_count,
3362               l_curr_calling_sequence);
3363 
3364 
3365          --BUG6777765 START
3366 
3367            ------------------------------------------
3368            l_debug_info := 'Check Amount Received ';
3369            ------------------------------------------
3370            IF (g_debug_mode = 'Y') THEN
3371               AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
3372            END IF;
3373 	   IF (G_LEVEL_STATEMENT >= G_CURRENT_RUNTIME_LEVEL) THEN
3374              FND_LOG.STRING(G_LEVEL_STATEMENT,G_MODULE_NAME||l_api_name,l_debug_info);
3375            END IF;
3376 
3377            /*-----------------------------------------------------------------+
3378             |  Calculate the net amount received. the values are got from     |
3379             |  calling the PO api earlier on. the same tolerance is used to   |
3380             |  check if it needs to be put on hold.                           |
3381             +-----------------------------------------------------------------*/
3382 
3383             If (l_match_option = 'R') then
3384                l_received_amount_used:= nvl(l_amt_received,0)
3385                                        + nvl(l_amt_corrected,0) ;
3386                l_billed_amount_used := nvl(l_amt_billed,0);
3387             Elsif (l_match_option = 'P') then
3388                l_received_amount_used := nvl(l_amt_received,0);
3389                l_billed_amount_used := nvl(l_amt_billed,0);
3390             End if;
3391 
3392 
3393             IF (p_amt_rec_tol IS NOT NULL) THEN
3394                IF ((l_billed_amount_used >(p_amt_rec_tol * l_received_amount_used))
3395                   AND (l_receipt_required_flag = 'Y')) THEN
3396                   l_amt_rec_error_exists := 'Y';
3397 
3398                END IF;
3399             ELSE
3400                l_amt_rec_error_exists := 'N';
3401             END IF;
3402 
3403             ----------------------------------------------------------
3404             l_debug_info := 'Process AMT REC hold for shipment match';
3405             ----------------------------------------------------------
3406             IF (g_debug_mode = 'Y') THEN
3407                AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
3408             END IF;
3409 	    IF (G_LEVEL_STATEMENT >= G_CURRENT_RUNTIME_LEVEL) THEN
3410               FND_LOG.STRING(G_LEVEL_STATEMENT,G_MODULE_NAME||l_api_name,l_debug_info);
3411             END IF;
3412 
3413             AP_APPROVAL_PKG.Process_Inv_Hold_Status(
3414               p_invoice_id,
3415               l_line_location_id,
3416               l_rcv_transaction_id,
3417               'AMT REC',
3418               l_amt_rec_error_exists,
3419               null,
3420               p_system_user,
3421               p_holds,
3422               p_holds_count,
3423               p_release_count,
3424               l_curr_calling_sequence);
3425 
3426           --BUG6777765 END
3427 
3428        END IF;  /* l_matching_basis = 'QUANTITY' */
3429 
3430     END IF;  /* l_payment_type <> 'MILESTONE' */
3431 
3432 
3433     ---------------------------------------
3434     l_debug_info := 'Check PO closed code';
3435     ---------------------------------------
3436  -- BUG 3486887 : Added parameter p_origin_doc_id=> p_invoice_id in Close_PO()
3437 
3438     IF (g_debug_mode = 'Y') THEN
3439       AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
3440     END IF;
3441     IF (G_LEVEL_STATEMENT >= G_CURRENT_RUNTIME_LEVEL) THEN
3442       FND_LOG.STRING(G_LEVEL_STATEMENT,G_MODULE_NAME||l_api_name,l_debug_info);
3443     END IF;
3444 
3445     IF (l_final_match_flag NOT IN ('Y', 'D')) THEN
3446 
3447       IF (NOT(PO_ACTIONS.Close_PO(
3448                         p_docid        => l_po_header_id,
3449                         p_doctyp       => l_po_doc_type,
3450                         p_docsubtyp    => l_po_sub_type,
3451                         p_lineid       => l_po_line_id,
3452                         p_shipid       => l_line_location_id,
3453                         p_action       => l_action,
3454                         p_reason       => NULL,
3455                         p_calling_mode => 'AP',
3456                         p_conc_flag    => p_conc_flag,
3457                         p_return_code  => l_return_code,
3458                         p_auto_close   => 'Y',
3459                         p_origin_doc_id=> p_invoice_id))) THEN
3460         APP_EXCEPTION.Raise_Exception;
3461       END IF;
3462     END IF;  -- Not a final match invoice --
3463 
3464     --------------------------------------------------
3465     l_debug_info := 'Check for ship amount tolerance';
3466     --------------------------------------------------
3467     IF (g_debug_mode = 'Y') THEN
3468       AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
3469     END IF;
3470     IF (G_LEVEL_STATEMENT >= G_CURRENT_RUNTIME_LEVEL) THEN
3471       FND_LOG.STRING(G_LEVEL_STATEMENT,G_MODULE_NAME||l_api_name,l_debug_info);
3472     END IF;
3473 
3474 
3475     IF (l_payment_type <> 'MILESTONE') THEN
3476 
3477        Calc_Ship_Total_Trx_Amt_Var(
3478             p_invoice_id,
3479             l_line_location_id,
3480             l_match_option,
3481             l_po_unit_price,
3482             l_ship_amount, -- 3488259 (3110072)
3483             l_matching_basis,
3484             l_ship_trx_amt_var,
3485             l_curr_calling_sequence,
3486             l_org_id);
3487 
3488 
3489       l_max_ship_amt_exceeded := 'N' ;   --Bug 5292808
3490 
3491       -- Bug 5292808. Modified the check for shipment amt tolerance
3492 
3493       IF (l_matching_basis = 'QUANTITY') THEN
3494 
3495          IF (p_goods_ship_amt_tolerance IS NOT NULL) THEN
3496             IF (nvl(l_ship_trx_amt_var, 0) > p_goods_ship_amt_tolerance) THEN
3497                l_max_ship_amt_exceeded := 'Y';
3498             END IF;
3499 
3500           END IF;
3501       END IF;
3502 
3503 	  /* Bug 14075976: start - Added the below code for placing
3504           'Max Ship Amount' hold based on FV tolerance setup*/
3505 	  IF l_max_ship_amt_exceeded = 'N' THEN
3506 	 ------------------------------------------------------------------------------------
3507          l_debug_info := 'l_max_ship_amt_exceeded: '||l_max_ship_amt_exceeded||' l_org_id: '||
3508 		 l_org_id;
3509          ------------------------------------------------------------------------------------
3510           IF (g_debug_mode = 'Y') THEN
3511             AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
3512           END IF;
3513           IF (G_LEVEL_STATEMENT >= G_CURRENT_RUNTIME_LEVEL) THEN
3514             FND_LOG.STRING(G_LEVEL_STATEMENT,G_MODULE_NAME||l_api_name,l_debug_info);
3515           END IF;
3516 
3517          IF FV_INSTALL.Enabled(l_org_id) THEN
3518 	    --------------------------------------------------
3519             l_debug_info := 'Calling FV_AP_MATCH_PKG.Shipment_Tolerance';
3520             --------------------------------------------------
3521             IF (g_debug_mode = 'Y') THEN
3522               AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
3523             END IF;
3524             IF (G_LEVEL_STATEMENT >= G_CURRENT_RUNTIME_LEVEL) THEN
3525               FND_LOG.STRING(G_LEVEL_STATEMENT,G_MODULE_NAME||l_api_name,l_debug_info);
3526             END IF;
3527 
3528             FV_AP_MATCH_PKG.Shipment_Tolerance(l_ship_trx_amt_var,
3529                                                l_ship_amount,
3530                                                l_fv_tol_check);
3531             IF l_fv_tol_check = 'N' THEN
3532 
3533                l_max_ship_amt_exceeded := 'Y';
3534 
3535             END IF;
3536 	    -------------------------------------------------------------------------
3537             l_debug_info := 'l_fv_tol_check: '||l_fv_tol_check||' l_max_ship_amt_exceeded: '||
3538 			l_max_ship_amt_exceeded;
3539             ----------------------------------------------------------------------------
3540             IF (g_debug_mode = 'Y') THEN
3541               AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
3542             END IF;
3543             IF (G_LEVEL_STATEMENT >= G_CURRENT_RUNTIME_LEVEL) THEN
3544               FND_LOG.STRING(G_LEVEL_STATEMENT,G_MODULE_NAME||l_api_name,l_debug_info);
3545             END IF;
3546 
3547          END IF;
3548 
3549       END IF;
3550 	  /* Bug 14075976: end */
3551 
3552 /* 5292808 commented the below check for shipment amt tolerance
3553            in case of amt based matching
3554       ELSIF (l_matching_basis = 'AMOUNT') THEN
3555 
3556          IF (p_services_ship_amt_tolerance IS NOT NULL) THEN
3557       IF (nvl(l_ship_trx_amt_var, 0) > p_services_ship_amt_tolerance) THEN
3558          l_max_ship_amt_exceeded := 'Y';
3559       ELSE
3560          l_max_ship_amt_exceeded := 'N';
3561       END IF;
3562    ELSE
3563       l_max_ship_amt_exceeded := 'N';
3564    END IF;
3565 
3566       END IF;   */
3567 
3568        -----------------------------------------------------------------------
3569        l_debug_info := 'Process MAX SHIP AMOUNT Hold for this shipment match';
3570        -----------------------------------------------------------------------
3571        IF (g_debug_mode = 'Y') THEN
3572          AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
3573        END IF;
3574        IF (G_LEVEL_STATEMENT >= G_CURRENT_RUNTIME_LEVEL) THEN
3575          FND_LOG.STRING(G_LEVEL_STATEMENT,G_MODULE_NAME||l_api_name,l_debug_info);
3576        END IF;
3577 
3578        AP_APPROVAL_PKG.Process_Inv_Hold_Status(
3579               p_invoice_id,
3580               l_line_location_id,
3581               l_rcv_transaction_id,
3582               'MAX SHIP AMOUNT',
3583               l_max_ship_amt_exceeded,
3584               NULL,
3585               p_system_user,
3586               p_holds,
3587               p_holds_count,
3588               p_release_count,
3589               l_curr_calling_sequence);
3590 
3591        -----------------------------------------------------------
3592        l_debug_info := 'Compare erv with exchange rate tolerance';
3593        -----------------------------------------------------------
3594        IF (g_debug_mode = 'Y') THEN
3595           AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
3596        END IF;
3597        IF (G_LEVEL_STATEMENT >= G_CURRENT_RUNTIME_LEVEL) THEN
3598          FND_LOG.STRING(G_LEVEL_STATEMENT,G_MODULE_NAME||l_api_name,l_debug_info);
3599        END IF;
3600 
3601        IF ((l_matching_basis = 'QUANTITY' and p_goods_rate_amt_tolerance IS NOT NULL)
3602            OR (l_matching_basis = 'AMOUNT' and p_services_rate_amt_tolerance IS NOT NULL))
3603                          THEN
3604           Calc_Max_Rate_Var(
3605               p_invoice_id,
3606               l_line_location_id,
3607               l_rcv_transaction_id,
3608               l_match_option,
3609               l_rate_amt_var,
3610               l_curr_calling_sequence);
3611 
3612    IF (l_matching_basis = 'QUANTITY') THEN
3613             IF (nvl(l_rate_amt_var, 0) > p_goods_rate_amt_tolerance) THEN
3614                l_max_rate_amt_exceeded := 'Y';
3615             ELSE
3616                l_max_rate_amt_exceeded := 'N';
3617             END IF;
3618    ELSIF (l_matching_basis = 'AMOUNT') THEN
3619             IF (nvl(l_rate_amt_var, 0) > p_services_rate_amt_tolerance) THEN
3620          l_max_rate_amt_exceeded := 'Y';
3621       ELSE
3622          l_max_rate_amt_exceeded := 'N';
3623       END IF;
3624    END IF;
3625 
3626        ELSE
3627          l_max_rate_amt_exceeded := 'N';
3628        END IF;
3629 
3630        -----------------------------------------------------------------------
3631        l_debug_info := 'Process MAX RATE AMOUNT Hold for this shipment match';
3632        -----------------------------------------------------------------------
3633        IF (g_debug_mode = 'Y') THEN
3634           AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
3635        END IF;
3636        IF (G_LEVEL_STATEMENT >= G_CURRENT_RUNTIME_LEVEL) THEN
3637          FND_LOG.STRING(G_LEVEL_STATEMENT,G_MODULE_NAME||l_api_name,l_debug_info);
3638        END IF;
3639 
3640        AP_APPROVAL_PKG.Process_Inv_Hold_Status(
3641               p_invoice_id,
3642               l_line_location_id,
3643               l_rcv_transaction_id,
3644               'MAX RATE AMOUNT',
3645               l_max_rate_amt_exceeded,
3646               NULL,
3647               p_system_user,
3648               p_holds,
3649               p_holds_count,
3650               p_release_count,
3651               l_curr_calling_sequence);
3652 
3653        --------------------------------------------------
3654        l_debug_info := 'Check for total amount tolerance';
3655        --------------------------------------------------
3656        IF (g_debug_mode = 'Y') THEN
3657           AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
3658        END IF;
3659        IF (G_LEVEL_STATEMENT >= G_CURRENT_RUNTIME_LEVEL) THEN
3660          FND_LOG.STRING(G_LEVEL_STATEMENT,G_MODULE_NAME||l_api_name,l_debug_info);
3661        END IF;
3662 
3663        IF (((l_matching_basis = 'QUANTITY' and p_goods_total_amt_tolerance IS NOT NULL) OR
3664            (l_matching_basis = 'AMOUNT' and p_services_total_amt_tolerance IS NOT NULL)) /* bug 12991841 */
3665           AND
3666           l_inv_currency_code <> p_base_currency_code) THEN
3667 
3668           Calc_Ship_Total_Base_Amt_Var(
3669             p_invoice_id,
3670             l_line_location_id,
3671             l_rcv_transaction_id,    /*Added for Bug:14726598*/
3672             l_match_option,
3673             l_po_unit_price,
3674             l_matching_basis,
3675             l_inv_currency_code,
3676             p_base_currency_code,
3677             l_ship_base_amt_var,
3678             l_curr_calling_sequence);
3679 
3680    IF (l_matching_basis = 'QUANTITY') THEN
3681             IF (nvl(l_ship_base_amt_var, 0) > p_goods_total_amt_tolerance) THEN
3682                l_max_total_amt_exceeded := 'Y';
3683             ELSE
3684                l_max_total_amt_exceeded := 'N';
3685             END IF;
3686          ELSIF (l_matching_basis = 'AMOUNT') THEN
3687             IF (nvl(l_ship_base_amt_var, 0) > p_services_total_amt_tolerance) THEN
3688                l_max_total_amt_exceeded := 'Y';
3689             ELSE
3690                l_max_total_amt_exceeded := 'N';
3691             END IF;
3692    END IF;
3693 
3694        ELSE
3695          l_max_total_amt_exceeded := 'N';
3696        END IF;
3697 
3698        -----------------------------------------------------------------------
3699        l_debug_info := 'Process MAX TOTAL AMOUNT Hold for this shipment match';
3700        -----------------------------------------------------------------------
3701        IF (g_debug_mode = 'Y') THEN
3702          AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
3703        END IF;
3704        IF (G_LEVEL_STATEMENT >= G_CURRENT_RUNTIME_LEVEL) THEN
3705          FND_LOG.STRING(G_LEVEL_STATEMENT,G_MODULE_NAME||l_api_name,l_debug_info);
3706        END IF;
3707 
3708        AP_APPROVAL_PKG.Process_Inv_Hold_Status(
3709               p_invoice_id,
3710               l_line_location_id,
3711               l_rcv_transaction_id,
3712               'MAX TOTAL AMOUNT',
3713               l_max_total_amt_exceeded,
3714               null,
3715               p_system_user,
3716               p_holds,
3717               p_holds_count,
3718               p_release_count,
3719               l_curr_calling_sequence);
3720 
3721     END IF; /*l_payment_type <> 'MILESTONE' */
3722 
3723   END LOOP;
3724 
3725   CLOSE Matched_Cur;
3726 
3727 EXCEPTION
3728   WHEN OTHERS THEN
3729     IF (SQLCODE <> -20001) THEN
3730       FND_MESSAGE.SET_NAME('SQLAP','AP_DEBUG');
3731       FND_MESSAGE.SET_TOKEN('ERROR',SQLERRM);
3732       FND_MESSAGE.SET_TOKEN('CALLING_SEQUENCE', l_curr_calling_sequence);
3733       FND_MESSAGE.SET_TOKEN('PARAMETERS',
3734                   'Invoice_id  = '|| to_char(p_invoice_id)
3735               ||', Dist_line_num = '|| to_char(p_price_tol)
3736               ||', Packet_id = '|| to_char(p_qty_tol)
3737               ||', Fundscheck mode = '|| to_char(p_qty_rec_tol)
3738               ||', Partial_reserv_flag = '|| to_char(p_max_qty_ord_tol)
3739         ||', Max QTY REC Tol = '|| to_char(p_max_qty_rec_tol));
3740       FND_MESSAGE.SET_TOKEN('DEBUG_INFO',l_debug_info);
3741     END IF;
3742     APP_EXCEPTION.RAISE_EXCEPTION;
3743 END Execute_Matched_Checks;
3744 
3745 
3746 /*============================================================================
3747  |  PUBLIC PROCEDURE  Get_PO_Closed_Code
3748  |
3749  |  DESCRIPTION:
3750  |              Procedure to retrieve the PO Closed Code for a given
3751  |              line_location_id after the Close_PO API has been  called.
3752  |
3753  |  CALLS PROCEDURES / FUNCTIONS (local to this package body)
3754  |
3755  |  PARAMETERS
3756  |
3757  |  MODIFICATION HISTORY
3758  |  Date         Author             Description of Change
3759  |
3760  *==========================================================================*/
3761 
3762 PROCEDURE Get_PO_Closed_Code(
3763               p_line_location_id    IN            NUMBER,
3764               p_po_closed_code      IN OUT NOCOPY VARCHAR2,
3765               p_calling_sequence    IN            VARCHAR2) IS
3766 
3767   l_debug_loc              VARCHAR2(30) := 'Get_PO_Closed_Code';
3768   l_curr_calling_sequence  VARCHAR2(2000);
3769 BEGIN
3770 
3771   l_curr_calling_sequence := 'AP_APPROVAL_MATCHED_PKG.'||l_debug_loc ||'<-'||
3772                               p_calling_sequence;
3773 
3774   SELECT   PLL.closed_code
3775   INTO     p_po_closed_code
3776   FROM     po_line_locations PLL
3777   WHERE    line_location_id = p_line_location_id;
3778 
3779 EXCEPTION
3780   WHEN NO_DATA_FOUND THEN
3781     p_po_closed_code := null;
3782     return;
3783   WHEN OTHERS THEN
3784     IF (SQLCODE <> -20001) THEN
3785       FND_MESSAGE.SET_NAME('SQLAP','AP_DEBUG');
3786       FND_MESSAGE.SET_TOKEN('ERROR',SQLERRM);
3787       FND_MESSAGE.SET_TOKEN('CALLING_SEQUENCE', l_curr_calling_sequence);
3788       FND_MESSAGE.SET_TOKEN('PARAMETERS',
3789                   'Invoice_id  = '|| to_char(p_line_location_id));
3790     END IF;
3791     APP_EXCEPTION.RAISE_EXCEPTION;
3792 END Get_PO_Closed_Code;
3793 
3794 
3795 /*============================================================================
3796  |  FUNCTION INV_HAS_HOLDS_OTHER_THAN
3797  |
3798  |  DESCRIPTION:
3799  |              Function that indicates whether an invoice has other holds
3800  |              other than the 2 hold_codes
3801  |
3802  *==========================================================================*/
3803 
3804 FUNCTION Inv_Has_Holds_Other_Than(
3805              p_invoice_id       IN NUMBER,
3806              p_hold_code        IN VARCHAR2,
3807              p_hold_code2       IN VARCHAR2,
3808              p_calling_sequence IN VARCHAR2) RETURN BOOLEAN IS
3809 
3810   l_holds_exist            VARCHAR2(1);
3811   l_debug_loc              VARCHAR2(30) := 'Inv_Has_Holds_Other_Than';
3812   l_curr_calling_sequence  VARCHAR2(2000);
3813 BEGIN
3814 
3815   l_curr_calling_sequence := 'AP_APPROVAL_MATCHED_PKG.'||l_debug_loc||'<-'||
3816                              p_calling_sequence;
3817 
3818   SELECT 'Y'
3819   INTO   l_holds_exist
3820   FROM   sys.dual
3821   WHERE  EXISTS (SELECT DISTINCT 'Invoice has unreleased holds'
3822                    FROM ap_holds AH
3823                   WHERE AH.invoice_id = p_invoice_id
3824                    AND AH.hold_lookup_code NOT IN (p_hold_code, p_hold_code2)
3825                    AND AH.release_lookup_code IS NULL);
3826 
3827   IF (l_holds_exist = 'Y') THEN
3828     return(TRUE);
3829   END IF;
3830 
3831 EXCEPTION
3832   WHEN NO_DATA_FOUND THEN
3833     return(FALSE);
3834   WHEN OTHERS THEN
3835     IF (SQLCODE <> -20001) THEN
3836       FND_MESSAGE.SET_NAME('SQLAP','AP_DEBUG');
3837       FND_MESSAGE.SET_TOKEN('ERROR',SQLERRM);
3838       FND_MESSAGE.SET_TOKEN('CALLING_SEQUENCE', l_curr_calling_sequence);
3839       FND_MESSAGE.SET_TOKEN('PARAMETERS',
3840                   'Invoice_id  = '|| to_char(p_invoice_id)
3841               ||', Hold Code1 = '|| p_hold_code
3842               ||', Hold Code2 = '|| p_hold_code2);
3843     END IF;
3844     APP_EXCEPTION.RAISE_EXCEPTION;
3845 END Inv_Has_Holds_Other_Than;
3846 
3847 /*============================================================================
3848  |  FUNCTION    INV_HAS_UNRELEASED_HOLDS
3849  |
3850  |  DESCRIPTION:
3851  |              Function that indicates that an invoice has the two holds
3852  |              passed in and they haven't been released
3853  |
3854  *==========================================================================*/
3855 
3856 FUNCTION Inv_Has_Unreleased_Holds(
3857              p_invoice_id       IN NUMBER,
3858              p_hold_code        IN VARCHAR2,
3859              p_hold_code2       IN VARCHAR2,
3860              p_calling_sequence IN VARCHAR2) RETURN BOOLEAN IS
3861 
3862   l_holds_exist            VARCHAR2(1) := 'N';
3863   l_debug_loc              VARCHAR2(30) := 'Inv_Has_Unreleased_Holds';
3864   l_curr_calling_sequence  VARCHAR2(2000);
3865 BEGIN
3866 
3867   l_curr_calling_sequence := 'AP_APPROVAL_MATCHED_PKG.'||l_debug_loc||'<-'||
3868                              p_calling_sequence;
3869 
3870   SELECT 'Y'
3871     INTO  l_holds_exist
3872     FROM  sys.dual
3873    WHERE  EXISTS (SELECT DISTINCT 'Invoice has unreleased holds'
3874                     FROM ap_holds AH
3875                    WHERE AH.invoice_id = p_invoice_id
3876                      AND AH.hold_lookup_code IN (p_hold_code, p_hold_code2)
3877                      AND AH.release_lookup_code IS NULL);
3878 
3879   IF (l_holds_exist = 'Y') THEN
3880     return(TRUE);
3881   END IF;
3882 
3883 EXCEPTION
3884   WHEN NO_DATA_FOUND THEN
3885     return(FALSE);
3886   WHEN OTHERS THEN
3887     IF (SQLCODE <> -20001) THEN
3888       FND_MESSAGE.SET_NAME('SQLAP','AP_DEBUG');
3889       FND_MESSAGE.SET_TOKEN('ERROR',SQLERRM);
3890       FND_MESSAGE.SET_TOKEN('CALLING_SEQUENCE', l_curr_calling_sequence);
3891       FND_MESSAGE.SET_TOKEN('PARAMETERS',
3892                   'Invoice_id  = '|| to_char(p_invoice_id)
3893               ||', Hold Code1 = '|| p_hold_code
3894               ||', Hold Code2 = '|| p_hold_code2);
3895     END IF;
3896     APP_EXCEPTION.RAISE_EXCEPTION;
3897 END Inv_Has_Unreleased_Holds;
3898 
3899 
3900 /*============================================================================
3901  |  PROCEDURE  GET_SHIPMENT_QTY_DELIVERED
3902  |
3903  |  DESCRIPTION:
3904  |              Procedure given a line_location_id retrieves the
3905  |              quantity_delivered for that shipment.
3906  |
3907  *==========================================================================*/
3908 
3909 PROCEDURE Get_Shipment_Qty_Delivered(
3910               p_line_location_id    IN            NUMBER,
3911               p_qty_delivered       IN OUT NOCOPY NUMBER,
3912               p_calling_sequence    IN            VARCHAR2) IS
3913 
3914   l_debug_loc              VARCHAR2(30) := 'Get_Shipment_Qty_Delivered';
3915   l_curr_calling_sequence  VARCHAR2(2000);
3916 BEGIN
3917 
3918 
3919   l_curr_calling_sequence := 'AP_APPROVAL_MATCHED_PKG.'||l_debug_loc||'<-'||
3920                               p_calling_sequence;
3921 
3922   SELECT   ROUND(SUM(nvl(PD.quantity_delivered, 0)), 5)
3923   INTO     p_qty_delivered
3924   FROM     po_distributions_ap_v PD
3925   WHERE    PD.line_location_id = p_line_location_id;
3926 
3927 EXCEPTION
3928   WHEN NO_DATA_FOUND THEN
3929     p_qty_delivered := NULL;
3930     return;
3931   WHEN OTHERS THEN
3932     IF (SQLCODE <> -20001) THEN
3933       FND_MESSAGE.SET_NAME('SQLAP','AP_DEBUG');
3934       FND_MESSAGE.SET_TOKEN('ERROR',SQLERRM);
3935       FND_MESSAGE.SET_TOKEN('CALLING_SEQUENCE', l_curr_calling_sequence);
3936       FND_MESSAGE.SET_TOKEN('PARAMETERS',
3937                   'Invoice_id  = '|| to_char(p_line_location_id));
3938     END IF;
3939     APP_EXCEPTION.RAISE_EXCEPTION;
3940 END Get_Shipment_Qty_Delivered;
3941 
3942 /*============================================================================
3943  |  PROCEDURE  UPDATE_FINAL_MATCH_FLAG
3944  |
3945  |  DESCRIPTION:
3946  |              Procedure to update the final_match_flag to a given value for
3947  |              a invoice_distribution
3948  |
3949  *==========================================================================*/
3950 
3951 --BugFix 3489536.Added the parameter p_invoice_id to the function call
3952 PROCEDURE Update_Final_Match_Flag(
3953               p_line_location_id  IN NUMBER,
3954               p_final_match_flag  IN VARCHAR2,
3955               p_calling_sequence  IN VARCHAR2,
3956               p_invoice_id        IN NUMBER) IS
3957 
3958   l_debug_loc              VARCHAR2(30) := 'Update_Final_Match_Flag';
3959   l_curr_calling_sequence  VARCHAR2(2000);
3960 BEGIN
3961 
3962   l_curr_calling_sequence := 'AP_APPROVAL_MATCHED_PKG.'||l_debug_loc||'<-'||
3963                              p_calling_sequence;
3964 
3965   UPDATE   ap_invoice_distributions AID
3966      SET   final_match_flag = p_final_match_flag
3967    WHERE   AID.invoice_id = p_invoice_id  -- Bug 3489536
3968    AND     AID.po_distribution_id IN
3969               (SELECT PD.po_distribution_id
3970                FROM   po_distributions_ap_v PD
3971                WHERE  line_location_id = p_line_location_id);
3972 
3973   UPDATE   ap_invoice_lines AIL
3974      SET   final_match_flag = p_final_match_flag
3975    WHERE   AIL.po_line_location_id = p_line_location_id
3976    AND     AIL.invoice_id=p_invoice_id;--bug5759169
3977 
3978 EXCEPTION
3979   WHEN OTHERS THEN
3980     IF (SQLCODE <> -20001) THEN
3981       FND_MESSAGE.SET_NAME('SQLAP','AP_DEBUG');
3982       FND_MESSAGE.SET_TOKEN('ERROR',SQLERRM);
3983       FND_MESSAGE.SET_TOKEN('CALLING_SEQUENCE', l_curr_calling_sequence);
3984       FND_MESSAGE.SET_TOKEN('PARAMETERS',
3985                   'Invoice_id  = '|| to_char(p_line_location_id));
3986     END IF;
3987     APP_EXCEPTION.RAISE_EXCEPTION;
3988 END Update_Final_Match_Flag;
3989 
3990 
3991 /*============================================================================
3992  |  PUBLIC PROCEDURE  EXEC_PO_FINAL_CLOSE
3993  |
3994  |  DESCRIPTION:
3995  |                Procedure that performs po final close on an invoice
3996  |                and places or releases 'CANT CLOSE PO' and/oR
3997  |                'CANT TRY PO CLOSE' holds depending on the condition.
3998  |
3999  |   PROGRAM FLOW
4000  |
4001  | FOR each 'CANT CLOSE PO' hold associated with distributions
4002  |     where final_match_flag <> 'Y' DO
4003  |     Release 'CANT CLOSE PO' hold for this match
4004  |    AND
4005  | FOR each match where final_match_flag = 'Y' and the sum of the
4006  |     distribution amounts is 0 (the final match has been reversed)
4007  |     and the invoice is on 'CANT TRY PO CLOSE' hold DO
4008  |     Release 'CANT TRY PO CLOSE' hold for this match
4009  | END FOR
4010  |
4011  | FOR each 'not-yet-done' final match on the invoice DO
4012  |     IF first_final_match = TRUE THEN
4013  |        first_final_match := FALSE
4014  |        at_least_one_final_match := TRUE
4015  |        IF the invoice has unreleased holds (other than either
4016  |                                         of the 2 holds above) THEN
4017  |           IF the invoice doesn't have any unreleased
4018  |                                         'CANT CLOSE PO' or
4019  |                             'CANT TRY PO CLOSE' holds THEN
4020  |                 Invoice should have 'CANT TRY PO CLOSE' hold
4021  |           END IF
4022  |             Break out of FOR loop
4023  |       END IF
4024  |     END IF
4025  |     Get quantity delivered for this PO shipment
4026  |     IF ((accrue_on_receipt_flag = 'N') OR
4027  |           (quantity_delivered >= quantity_received)) THEN
4028  |         IF call to PO Final Close returns failure THEN
4029  |             Raise Exception
4030  |         END IF;
4031  |         IF the Final Close failed THEN
4032  |           Invoice should be on 'CANT CLOSE PO' hold
4033  |              for this match,
4034  |         ELSE (PO Final Close succeeded)
4035  |             Get the PO closed code for this shipment
4036  |             IF closed_code = 'FINALLY CLOSED' THEN
4037  |               Update final_match_flag to 'D' for
4038  |               ALL invoice distributions matched to
4039  |                this PO shipment
4040  |             ELSE (closed_code <> 'FINALLY CLOSED')
4041  |               Raise Exception
4042  |             END IF
4043  |          END IF
4044  |     ELSE (quantity_delivered < quantity_received)
4045  |         Invoice should be on 'CANT TRY PO CLOSE' hold
4046  |   Exit Loop;
4047  |     END IF
4048  |
4049  |     Process Inv Hold Status for 'CANT CLOSE PO' hold - place a hold if
4050  |     condition exists and this invoice shipment match doesn't already have
4051  |     hold, or release if invoice has the hold and contiton doesn't exists.
4052  |
4053  | END LOOP;
4054  |
4055  | IF at_least_one_final_match == FALSE THEN
4056  |   Invoice shouldn't be on 'CANT TRY PO CLOSE' hold
4057  | END IF
4058  |
4059  | Process Invoice Hold Status for 'CANT TRY PO CLOSE' hold - place a hold if
4060  | condition exists and this invoice doesn't already have the hold, or release
4061  | the hold if invoice has the hold and condition doesn't exist.
4062  |
4063  |  KNOWN ISSUES:
4064  |
4065  |  NOTES:
4066  |
4067  |  MODIFICATION HISTORY
4068  |  Date         Author             Description of Change
4069  |
4070  *==========================================================================*/
4071 
4072 PROCEDURE Exec_PO_Final_Close(
4073               p_invoice_id        IN            NUMBER,
4074               p_system_user       IN            NUMBER,
4075               p_conc_flag         IN            VARCHAR2,
4076               p_holds             IN OUT NOCOPY AP_APPROVAL_PKG.HOLDSARRAY,
4077               p_holds_count       IN OUT NOCOPY AP_APPROVAL_PKG.COUNTARRAY,
4078               p_release_count     IN OUT NOCOPY AP_APPROVAL_PKG.COUNTARRAY,
4079               p_calling_sequence  IN            VARCHAR2) IS
4080 
4081    /*-----------------------------------------------------------------+
4082     |  1. Select each 'CANT CLOSE PO' hold associated with            |
4083     |     distributions where final_match_flag <> 'Y'                 |
4084     |  2. SELECT each match where final_match_flag = 'Y' and the sum  |
4085     |     of the distribution amount is 0                             |
4086     |     (final match has been reversed ) and the invoice is on      |
4087     |     'CANT TRY PO CLOSE' hold  - To release                      |
4088     +-----------------------------------------------------------------*/
4089 
4090   CURSOR Final_Match_Release_Cur IS
4091   SELECT PD.line_location_id,
4092          'CANT CLOSE PO'
4093     FROM ap_invoice_distributions AID,
4094          ap_holds AH,
4095          po_distributions_ap_v PD,
4096          po_line_locations PLL                                                             --Bug 3489536
4097    WHERE AH.invoice_id = p_invoice_id
4098      AND AH.hold_lookup_code = 'CANT CLOSE PO'
4099      AND AH.release_lookup_code IS NULL
4100      AND AH.invoice_id = AID.invoice_id
4101      AND AID.po_distribution_id = PD.po_distribution_id
4102      AND PLL.line_location_id   = PD.line_location_id                                      --Bug 3489536
4103      AND decode(PLL.final_match_flag, 'Y', 'D', NVL(AID.final_match_flag, 'N')) <> 'Y'     --Bug 3489536
4104      -- AND NVL(AID.final_match_flag, 'N') <> 'Y'--3489536
4105     GROUP BY PD.line_location_id
4106   UNION
4107   SELECT  PD.line_location_id,
4108           'CANT TRY PO CLOSE'
4109     FROM  ap_invoice_distributions AID,
4110           ap_holds AH,
4111           po_distributions_ap_v PD,
4112          po_line_locations PLL                                                             --Bug 3489536
4113    WHERE  AH.invoice_id = p_invoice_id
4114      AND  AH.hold_lookup_code = 'CANT TRY PO CLOSE'
4115      AND  AH.release_lookup_code IS NULL
4116      AND  AH.invoice_id = AID.invoice_id
4117      AND  AID.po_distribution_id = PD.po_distribution_id
4118      AND  AID.final_match_flag = 'Y'
4119      AND  PLL.line_location_id   = PD.line_location_id                                      --Bug 3489536
4120      AND  decode(PLL.final_match_flag, 'Y', 'D', NVL(AID.final_match_flag, 'N')) = 'Y'      --Bug 3489536
4121      GROUP BY  PD.line_location_id
4122      HAVING    SUM(AID.amount) = 0;
4123 
4124 -------------------------------------------------------
4125 -- Select each match with a not-yet-done Final Match --
4126 -------------------------------------------------------
4127 
4128   CURSOR Final_Match_Cur IS
4129   SELECT PLL.line_location_id,
4130          PLL.po_line_id,
4131          ROUND(NVL(PLL.quantity_received, 0), 5),
4132          DECODE(PH.type_lookup_code, 'STANDARD', 'PO', 'RELEASE'),
4133          DECODE(PD.po_release_id, NULL, PH.type_lookup_code,
4134                 PR.release_type),
4135          NVL(PLL.accrue_on_receipt_flag, 'N'),
4136          DECODE(PD.po_release_id, NULL, PD.po_header_id,
4137                 PD.po_release_id),
4138          PH.segment1,
4139          MAX(aid.accounting_date) Accounting_date
4140     FROM po_distributions_ap_v PD,
4141          ap_invoice_distributions AID,
4142          po_line_locations PLL,
4143          po_headers PH,
4144          po_releases PR
4145    WHERE AID.invoice_id = p_invoice_id
4146      AND AID.final_match_flag = 'Y'
4147      AND AID.po_distribution_id = PD.po_distribution_id
4148      AND PD.line_location_id = PLL.line_location_id
4149      AND PD.po_release_id = PR.po_release_id(+)
4150      AND PLL.po_header_id = PH.po_header_id
4151      AND decode(PLL.final_match_flag, 'Y', 'D', NVL(AID.final_match_flag, 'N')) = 'Y'     --Bug 3489536
4152      -- Bug 5441016. made the last condition to be = , was <> before
4153      GROUP BY  PLL.line_location_id,
4154                PLL.po_line_id,
4155                ROUND(NVL(PLL.quantity_received, 0), 5),
4156                DECODE(PH.type_lookup_code, 'STANDARD', 'PO', 'RELEASE'),
4157                DECODE(PD.po_release_id, NULL, PH.type_lookup_code,
4158                       PR.release_type),
4159                NVL(PLL.accrue_on_receipt_flag, 'N'),
4160                DECODE(PD.po_release_id, NULL, PD.po_header_id,
4161                       PD.po_release_id),
4162                PH.segment1
4163      HAVING    SUM(AID.amount) <> 0;
4164 
4165 
4166   l_line_location_id            NUMBER(15);
4167   l_hold_code                   VARCHAR2(25);
4168   l_cant_po_close_exists        VARCHAR2(1);
4169   l_cant_try_po_close_exists    VARCHAR2(1);
4170   l_first_final_match           BOOLEAN := TRUE;
4171   l_at_least_one_final_match    BOOLEAN := FALSE;
4172   l_po_line_id                  NUMBER(15);
4173   l_qty_delivered               NUMBER;
4174   l_qty_received                NUMBER;
4175   l_po_doc_type                 VARCHAR2(25);
4176   l_po_sub_type                 VARCHAR2(25);
4177   l_accrue_on_receipt_flag      VARCHAR2(1);
4178   l_po_header_id                VARCHAR2(15);
4179   l_return_code                 VARCHAR2(30);
4180   l_po_num                      VARCHAR2(20);
4181   l_po_closed_code              VARCHAR2(30);
4182   l_action                      VARCHAR2(25);
4183   l_debug_loc                   VARCHAR2(30) := 'Exec_PO_Final_Close';
4184   l_curr_calling_sequence       VARCHAR2(2000);
4185   l_debug_info                  VARCHAR2(2000);
4186   l_inv_accounting_date         DATE;
4187   error                         EXCEPTION;
4188 
4189  -- Start Bug 3489536
4190   l_ret_status                  VARCHAR2(100);
4191   l_msg_count                   NUMBER;
4192   l_msg_data                    VARCHAR2(4000);
4193   l_po_line_loc_tab             PO_TBL_NUMBER;
4194   l_po_api_exc                  EXCEPTION;
4195   -- End Bug 3489536
4196 
4197 BEGIN
4198 
4199   l_curr_calling_sequence := 'AP_APPROVAL_MATCHED_PKG.'||l_debug_loc||'<-'||
4200                              p_calling_sequence;
4201 
4202   IF ( AP_APPROVAL_PKG.g_debug_mode = 'Y' ) THEN
4203     g_debug_mode := 'Y';
4204   END IF;
4205 
4206   l_cant_try_po_close_exists := 'N';
4207   l_action := 'FINALLY CLOSE';
4208 
4209   -----------------------------------------------
4210   l_debug_info := 'Open Final_Match_Release_Cur';
4211   -----------------------------------------------
4212   IF (g_debug_mode = 'Y') THEN
4213     AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
4214   END IF;
4215 
4216   OPEN Final_Match_Release_Cur;
4217   LOOP
4218 
4219     ------------------------------------------------
4220     l_debug_info := 'Fetch Final_Match_Release_Cur';
4221     ------------------------------------------------
4222     IF (g_debug_mode = 'Y') THEN
4223       AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
4224     END IF;
4225 
4226     FETCH Final_Match_Release_Cur
4227      INTO l_line_location_id,
4228           l_hold_code;
4229     EXIT WHEN Final_Match_Release_Cur%NOTFOUND;
4230 
4231     -------------------------------------------------------------------------
4232     -- Release 'CANT PO CLOSE' or 'CANT TRY PO CLOSE' hold for this match  --
4233     -------------------------------------------------------------------------
4234     AP_APPROVAL_PKG.Release_Hold(
4235             p_invoice_id,
4236             l_line_location_id,
4237             '', -- rcv_transaction_id
4238             l_hold_code,
4239             p_holds,
4240             p_release_count,
4241             l_curr_calling_sequence);
4242   END LOOP;
4243   CLOSE Final_Match_Release_Cur;
4244 
4245 
4246   -----------------------------------------
4247   l_debug_info := 'Open Final_Match_Cur';
4248   -----------------------------------------
4249   IF (g_debug_mode = 'Y') THEN
4250     AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
4251   END IF;
4252 
4253   OPEN Final_Match_Cur;
4254   LOOP
4255 
4256     l_cant_po_close_exists := 'N';
4257     ---------------------------------------
4258     l_debug_info := 'Fetch Final_Match_Cur';
4259     ---------------------------------------
4260 
4261     Fetch Final_Match_Cur
4262      INTO l_line_location_id,
4263           l_po_line_id,
4264           l_qty_received,
4265           l_po_doc_type,
4266           l_po_sub_type,
4267           l_accrue_on_receipt_flag,
4268           l_po_header_id,
4269           l_po_num,
4270           l_inv_accounting_date;
4271     EXIT WHEN Final_Match_Cur%NOTFOUND;
4272 
4273    ------------------------------------------------------------
4274    --  FOR each 'not-yet-done' final match on the invoice DO --
4275    ------------------------------------------------------------
4276 
4277     IF (l_first_final_match) THEN
4278       l_first_final_match := FALSE;
4279       l_at_least_one_final_match := TRUE;
4280 
4281       IF ( Inv_Has_Holds_Other_Than(
4282                p_invoice_id,
4283                'CANT CLOSE PO',
4284                'CANT TRY PO CLOSE',
4285                l_curr_calling_sequence)) THEN
4286         l_cant_try_po_close_exists := 'Y';
4287         EXIT; -- drop out of the loop
4288       END IF;
4289     END IF; -- l_first_final_match = TRUE --
4290 
4291     ------------------------------------------------
4292     l_debug_info := 'Start Final Match Processing';
4293     ------------------------------------------------
4294     IF (g_debug_mode = 'Y') THEN
4295       AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
4296     END IF;
4297 
4298     Get_Shipment_Qty_Delivered(
4299         l_line_location_id,
4300         l_qty_delivered,
4301         l_curr_calling_sequence);
4302 
4303     IF ( (l_accrue_on_receipt_flag = 'N') OR
4304          (l_qty_delivered >= l_qty_received) ) THEN
4305 
4306       --------------------------------------------------------
4307       -- Not accrue_on_receipt and l_quantity_delivered >=  --
4308       -- l_quantity_received so ...                         --
4309       --------------------------------------------------------
4310       l_debug_info := 'Call PO Close API';
4311       ------------------------------------
4312 
4313  -- BUG 3486887 : Added parameter p_origin_doc_id=> p_invoice_id in Close_PO()
4314 
4315       IF (g_debug_mode = 'Y') THEN
4316         AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
4317       END IF;
4318 
4319       IF (NOT(PO_ACTIONS.Close_PO(
4320                    p_docid        => l_po_header_id,
4321                    p_doctyp       => l_po_doc_type,
4322                    p_docsubtyp    => l_po_sub_type,
4323                    p_lineid       => l_po_line_id,
4324                    p_shipid       => l_line_location_id,
4325                    p_action       => l_action,
4326                    p_reason       => NULL,
4327                    p_calling_mode => 'AP',
4328                    p_conc_flag    => p_conc_flag,
4329                    p_return_code  => l_return_code,
4330                    p_auto_close   => 'N',
4331                    p_action_date  => l_inv_accounting_date,
4332                    p_origin_doc_id=> p_invoice_id)))
4333          THEN APP_EXCEPTION.Raise_Exception;
4334       END IF;
4335 
4336       -----------------------------------------------
4337       l_debug_info := 'Process PO Close retrun code';
4338       -----------------------------------------------
4339       IF (g_debug_mode = 'Y') THEN
4340         AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
4341       END IF;
4342 
4343       IF (l_return_code IN ('SUBMISSION_FAILED', 'STATE_FAILED')) THEN
4344 
4345         -------------------------------------------------
4346         l_debug_info := 'PO Closed with failure';
4347         -------------------------------------------------
4348         IF (g_debug_mode = 'Y') THEN
4349           AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
4350         END IF;
4351 
4352         l_cant_po_close_exists := 'Y';
4353       ELSE
4354         -------------------------------------------------
4355         l_debug_info := 'Get PO Closed Code after success';
4356         -------------------------------------------------
4357         IF (g_debug_mode = 'Y') THEN
4358           AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
4359         END IF;
4360 
4361         Get_PO_Closed_Code(
4362             l_line_location_id,
4363             l_po_closed_code,
4364             l_curr_calling_sequence);
4365 
4366         IF (l_po_closed_code = 'FINALLY CLOSED') THEN
4367           -------------------------------------------------------------
4368           l_debug_info := 'Update Inv Dist/Line Final_Match_Flag to D';
4369           -------------------------------------------------------------
4370           IF (g_debug_mode = 'Y') THEN
4371             AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
4372           END IF;
4373 
4374             -- Start Bug 3489536
4375 
4376              l_po_line_loc_tab := po_tbl_number();
4377              l_po_line_loc_tab.extend;
4378              l_po_line_loc_tab(l_po_line_loc_tab.last) := l_line_location_id;
4379 
4380  --bug 7696098 removed the quotes in  p_api_version => '1.0'
4381              PO_AP_INVOICE_MATCH_GRP.set_final_match_flag
4382                                 (p_api_version          => 1.0,
4383                                  p_entity_type          => 'PO_LINE_LOCATIONS',
4384                                  p_entity_id_tbl        => l_po_line_loc_tab,
4385                                  p_final_match_flag     => 'Y',
4386                                  p_init_msg_list        => FND_API.G_FALSE ,
4387                                  p_commit               => FND_API.G_FALSE ,
4388                                  x_ret_status           => l_ret_status,
4389                                  x_msg_count            => l_msg_count,
4390                                  x_msg_data             => l_msg_data);
4391 
4392              IF l_ret_status = FND_API.G_RET_STS_SUCCESS THEN
4393 
4394 
4395                Update_Final_Match_Flag(l_line_location_id, 'D',
4396                                              l_curr_calling_sequence, p_invoice_id);
4397 
4398              ELSE
4399 
4400                 l_cant_po_close_exists := 'Y';
4401 
4402              END IF;
4403 
4404              -- End Bug 3489536
4405 
4406         ELSE
4407           -------------------------------------------------------------
4408           l_debug_info := 'Error l_po_closed_code not finally closed';
4409           -------------------------------------------------------------
4410           IF (g_debug_mode = 'Y') THEN
4411             AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
4412           END IF;
4413 
4414           Raise Error;
4415 
4416         END IF; -- l_po_closed_code <> 'FINALLY CLOSED' --
4417       END IF; -- PO Final Close Succeeded --
4418 
4419     ELSIF ( l_qty_delivered < l_qty_received ) THEN
4420 
4421       ------------------------------------------------------------
4422       -- Quantity_delivered < quantity_received so place inv on --
4423       -- CANT TRY PO CLOSE hold                                 --
4424       ------------------------------------------------------------
4425       l_cant_try_po_close_exists := 'Y';
4426 
4427       EXIT;  -- drop out of loop
4428 
4429     END IF;
4430 
4431     --------------------------------------------------------------
4432     l_debug_info := 'Process the CANT CLOSE PO hold status';
4433     --------------------------------------------------------------
4434     IF (g_debug_mode = 'Y') THEN
4435       AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
4436     END IF;
4437 
4438     AP_APPROVAL_PKG.Process_Inv_Hold_Status(
4439             p_invoice_id,
4440             l_line_location_id,
4441             null,
4442             'CANT CLOSE PO',
4443             l_cant_po_close_exists,
4444             null,
4445             p_system_user,
4446             p_holds,
4447             p_holds_count,
4448             p_release_count,
4449             p_calling_sequence);
4450 
4451   END LOOP;
4452 
4453   ----------------------------------------
4454   l_debug_info := 'CLOSE Final_Match_Cur';
4455   ----------------------------------------
4456   IF (g_debug_mode = 'Y') THEN
4457     AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
4458   END IF;
4459 
4460   CLOSE Final_Match_Cur;
4461 
4462   IF (NOT l_at_least_one_final_match) THEN
4463 
4464     l_cant_try_po_close_exists := 'N';
4465 
4466   END IF;
4467 
4468   ------------------------------------------------------------------------
4469   l_debug_info := 'Process CANT TRY PO CLOSE hold status for the invoice';
4470   ------------------------------------------------------------------------
4471   IF (g_debug_mode = 'Y') THEN
4472     AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
4473   END IF;
4474 
4475   AP_APPROVAL_PKG.Process_Inv_Hold_Status(
4476           p_invoice_id,
4477           null,
4478           null,
4479           'CANT TRY PO CLOSE',
4480           l_cant_try_po_close_exists,
4481           null,
4482           p_system_user,
4483           p_holds,
4484           p_holds_count,
4485           p_release_count,
4486           p_calling_sequence);
4487 
4488 EXCEPTION
4489   WHEN Error THEN
4490       FND_MESSAGE.SET_NAME('SQLAP','AP_DEBUG');
4491       FND_MESSAGE.SET_TOKEN('ERROR',SQLERRM);
4492       FND_MESSAGE.SET_TOKEN('CALLING_SEQUENCE', l_curr_calling_sequence);
4493       FND_MESSAGE.SET_TOKEN('PARAMETERS',
4494                   'Invoice_id  = '|| to_char(p_invoice_id));
4495       FND_MESSAGE.SET_TOKEN('DEBUG_INFO',l_debug_info);
4496     APP_EXCEPTION.RAISE_EXCEPTION;
4497   WHEN OTHERS THEN
4498     IF (SQLCODE <> -20001) THEN
4499       FND_MESSAGE.SET_NAME('SQLAP','AP_DEBUG');
4500       FND_MESSAGE.SET_TOKEN('ERROR',SQLERRM);
4501       FND_MESSAGE.SET_TOKEN('CALLING_SEQUENCE', l_curr_calling_sequence);
4502       FND_MESSAGE.SET_TOKEN('PARAMETERS',
4503                   'Invoice_id  = '|| to_char(p_invoice_id));
4504       FND_MESSAGE.SET_TOKEN('DEBUG_INFO',l_debug_info);
4505     END IF;
4506     APP_EXCEPTION.RAISE_EXCEPTION;
4507 END Exec_PO_Final_Close;
4508 
4509 
4510 /*============================================================================
4511  |  PROCEDURE  CHECK_RECEIPT_EXCEPTION
4512  |
4513  |  DESCRIPTION:
4514  |               For a given invoice shipment match check if there should be a
4515  |               'RECEIPT EXCEPTION' hold and place or release the hold
4516  |               depending on the conditon.
4517  |
4518  *==========================================================================*/
4519 
4520 PROCEDURE Check_Receipt_Exception(
4521               p_invoice_id          IN            NUMBER,
4522               p_line_location_id    IN            NUMBER,
4523               p_match_option        IN            VARCHAR2,
4524               p_rcv_transaction_id  IN            NUMBER,
4525               p_system_user         IN            NUMBER,
4526               p_holds               IN OUT NOCOPY AP_APPROVAL_PKG.HOLDSARRAY,
4527               p_holds_count         IN OUT NOCOPY AP_APPROVAL_PKG.COUNTARRAY,
4528               p_release_count       IN OUT NOCOPY AP_APPROVAL_PKG.COUNTARRAY,
4529               p_calling_sequence    IN            VARCHAR2) IS
4530 
4531   l_rec_exception_exists   VARCHAR2(1) := 'N';
4532   l_rec_exception_count    NUMBER := 0;
4533   l_debug_loc              VARCHAR2(30) := 'Check_Recipt_Exception';
4534   l_curr_calling_sequence  VARCHAR2(2000);
4535   l_debug_info             VARCHAR2(100);
4536 
4537 BEGIN
4538 
4539   l_curr_calling_sequence := 'AP_APPROVAL_MATCHED_PKG.'||l_debug_loc||'<-'||
4540                              p_calling_sequence;
4541 
4542   IF g_debug_mode = 'Y' THEN
4543     l_debug_info := 'Check if Rec Exception Exists';
4544     AP_Debug_Pkg.Print(g_debug_mode, l_debug_info);
4545   END IF;
4546 
4547    /*-----------------------------------------------------------------+
4548     | Query is done at invoice line level for release 11.6 trying to  |
4549     | gain a bit performance. Query was done at distribution level    |
4550     | for release 11.5                                                |
4551     +-----------------------------------------------------------------*/
4552 
4553   IF (p_match_option = 'P') THEN
4554     BEGIN
4555       SELECT count(*)
4556       INTO   l_rec_exception_count
4557       FROM   rcv_transactions rt,
4558              ap_invoice_lines ail
4559       WHERE  rt.receipt_exception_flag = 'Y'
4560       AND    rt.transaction_type = 'RECEIVE'
4561       AND    rt.po_line_location_id = ail.po_line_location_id
4562       AND    ail.po_line_location_id = p_line_location_id
4563       AND    ail.invoice_id = p_invoice_id ;
4564 
4565     EXCEPTION
4566        WHEN NO_DATA_FOUND THEN
4567           null;
4568     END;
4569     IF ( l_rec_exception_count > 0 ) THEN
4570       l_rec_exception_exists := 'y';
4571     END IF;
4572   ELSIF (p_match_option = 'R') THEN
4573     BEGIN
4574       SELECT 'Y'
4575         INTO l_rec_exception_exists
4576         FROM rcv_transactions rtxn
4577        WHERE rtxn.transaction_id = p_rcv_transaction_id
4578          AND rtxn.receipt_exception_flag = 'Y';
4579 
4580     EXCEPTION
4581       WHEN NO_DATA_FOUND Then
4582         null;
4583     END;
4584   END IF;
4585 
4586   IF g_debug_mode = 'Y' THEN
4587     l_debug_info := 'Process Invoice Hold Status for REC EXCEPTION';
4588     AP_Debug_Pkg.Print(g_debug_mode, l_debug_info);
4589   END IF;
4590 
4591   AP_APPROVAL_PKG.Process_Inv_Hold_Status(
4592           p_invoice_id,
4593           p_line_location_id,
4594           p_rcv_transaction_id,
4595           'REC EXCEPTION',
4596           l_rec_exception_exists,
4597           null,
4598           p_system_user,
4599           p_holds,
4600           p_holds_count,
4601           p_release_count,
4602           l_curr_calling_sequence);
4603 
4604 EXCEPTION
4605   WHEN OTHERS THEN
4606     IF (SQLCODE <> -20001) THEN
4607       FND_MESSAGE.SET_NAME('SQLAP','AP_DEBUG');
4608       FND_MESSAGE.SET_TOKEN('ERROR',SQLERRM);
4609       FND_MESSAGE.SET_TOKEN('CALLING_SEQUENCE', l_curr_calling_sequence);
4610       FND_MESSAGE.SET_TOKEN('PARAMETERS',
4611                   'Invoice_id  = '|| to_char(p_invoice_id)
4612               ||', Line Location Id = '|| to_char(p_line_location_id));
4613       FND_MESSAGE.SET_TOKEN('DEBUG_INFO',l_debug_info);
4614     END IF;
4615     APP_EXCEPTION.RAISE_EXCEPTION;
4616 END Check_Receipt_Exception;
4617 
4618 
4619 /*============================================================================
4620  |  PROCEDURE  CHECK_PRICE
4621  |
4622  |  DESCRIPTION:
4623  |
4624  |     For a given invoice shipment match, check for price error
4625  |     and place or release the 'PRICE' hold depending on the condition.
4626  |     1. Try to determine if the passed in invoice is base match only or it
4627  |        is trying to correct some other invoices.
4628  |     2. if no correctings get involved, we call function to check price of
4629  |        this invoice only
4630  |     3. if there are correctings, we need to loop through a list of
4631  |        invoices this invoice is trying to correct, and check the price of
4632  |        those invoice one by one to see if any hold needs to be put as a
4633  |        result of this passed in invoice.
4634  |
4635  |  MODIFICATION HISTORY
4636  |  Date         Author             Description of Change
4637  |
4638  *==========================================================================*/
4639 
4640 PROCEDURE Check_Price(
4641           p_invoice_id            IN NUMBER,
4642           p_line_location_id      IN NUMBER,
4643           p_rcv_transaction_id    IN NUMBER,
4644           p_match_option          IN VARCHAR2,
4645           p_txn_uom               IN VARCHAR2,
4646           p_po_uom                IN VARCHAR2,
4647           p_item_id               IN NUMBER,
4648           p_invoice_currency_code IN VARCHAR2,
4649           p_po_unit_price         IN NUMBER,
4650           p_price_tolerance       IN NUMBER,
4651           p_system_user           IN NUMBER,
4652           p_holds                 IN OUT NOCOPY AP_APPROVAL_PKG.HOLDSARRAY,
4653           p_holds_count           IN OUT NOCOPY AP_APPROVAL_PKG.COUNTARRAY,
4654           p_release_count         IN OUT NOCOPY AP_APPROVAL_PKG.COUNTARRAY,
4655           p_calling_sequence      IN VARCHAR2) IS
4656 
4657 
4658   l_price_error_exists          VARCHAR2(1):='N';
4659   l_debug_loc                   VARCHAR2(30) := 'Check_Price';
4660   l_curr_calling_sequence       VARCHAR2(2000);
4661   l_debug_info                  VARCHAR2(2000);
4662 
4663   l_correction_count            NUMBER;
4664   l_check_other_inv_price_flag  VARCHAR2(1);
4665   l_base_invoice_id             NUMBER;
4666 
4667    /*-----------------------------------------------------------------+
4668     |  A list of invoices this invoice  is trying to correct          |
4669     |  We are considering both qty correction and price correction    |
4670     |  because both will affect the average price for the AMOUNT part |
4671     +-----------------------------------------------------------------*/
4672 
4673   CURSOR corrected_invoices IS
4674   SELECT distinct corrected_inv_id
4675     FROM ap_invoice_lines AIL
4676    WHERE AIL.invoice_id = p_invoice_id
4677      AND (  ( AIL.po_line_location_id is not null and
4678               AIL.po_line_location_id = p_line_location_id )
4679           OR( AIL.rcv_transaction_id is not null and
4680               AIL.rcv_transaction_id = p_rcv_transaction_id) )
4681      AND AIL.corrected_inv_id is not null
4682      AND AIL.corrected_inv_id <> p_invoice_id;
4683 
4684 BEGIN
4685 
4686   l_curr_calling_sequence := 'AP_APPROVAL_MATCHED_PKG.'||l_debug_loc||'<-'||
4687                               p_calling_sequence;
4688 
4689   ---------------------------------------------------------
4690   l_debug_info := 'Check if invoice is a price correction';
4691   ---------------------------------------------------------
4692   IF (g_debug_mode = 'Y') THEN
4693     AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
4694   END IF;
4695 
4696    /*-----------------------------------------------------------------+
4697     |  To check if the match is a base match only or has corrections  |
4698     |  that trying to correct other invoices which not includes       |
4699     |  itself.                                                        |
4700     |  Qty correction or price correction both affect average price   |
4701    +------------------------------------------------------------------*/
4702 
4703   SELECT count(*)
4704     INTO l_correction_count
4705     FROM ap_invoice_lines AIL
4706    WHERE AIL.invoice_id = p_invoice_id
4707      AND po_line_location_id = p_line_location_id
4708      AND corrected_inv_id is not null
4709      AND corrected_inv_id <> p_invoice_id;
4710 
4711   IF ( l_correction_count = 0 ) THEN
4712     l_check_other_inv_price_flag := 'N';
4713   ELSE
4714     l_check_other_inv_price_flag := 'Y';
4715   END IF;
4716 
4717    /*-----------------------------------------------------------------+
4718     |  If it is a base match only or a base match with 1 or more      |
4719     |  correction lines. It does not have any correcting lines which  |
4720     |  try to correct other invoices. In this case, price check is    |
4721     |  needed to be done only to this invoice ( with p_invoice_id )   |
4722     +-----------------------------------------------------------------*/
4723 
4724     IF l_check_other_inv_price_flag = 'N' THEN
4725 
4726        CHECK_AVERAGE_PRICE(
4727              p_invoice_id  ,
4728              p_line_location_id  ,
4729              p_match_option,
4730              p_txn_uom ,
4731              p_po_uom ,
4732              P_item_id,
4733              p_price_tolerance ,
4734              p_po_unit_price  ,
4735              p_invoice_currency_code ,
4736              l_price_error_exists,
4737              p_calling_sequence);
4738 
4739     END IF;
4740 
4741    /*-----------------------------------------------------------------+
4742     |  If it is a match with correctings that are trying to correct   |
4743     |  other invoice. In this case, a list of invoices are affected   |
4744     |  by this invoice. We need to check if the average price of the  |
4745     |  corrected invoices which are matching to this po shipment      |
4746     |  exceeded price tolerance. If yes, the hold needs to be put on  |
4747     |  originating invoice                                            |
4748     +-----------------------------------------------------------------*/
4749 
4750   IF ( l_check_other_inv_price_flag = 'Y'  and
4751        l_price_error_exists = 'N' ) THEN
4752 
4753     OPEN corrected_invoices;
4754     LOOP
4755       FETCH corrected_invoices
4756        INTO l_base_invoice_id;
4757        EXIT WHEN corrected_invoices%NOTFOUND OR l_price_error_exists = 'Y';
4758 
4759       CHECK_AVERAGE_PRICE(
4760             l_base_invoice_id,
4761             p_line_location_id,
4762             p_match_option,
4763             p_txn_uom ,
4764             p_po_uom ,
4765             p_item_id,
4766             p_price_tolerance,
4767             p_po_unit_price,
4768             p_invoice_currency_code,
4769             l_price_error_exists,
4770             p_calling_sequence);
4771     END LOOP;
4772     CLOSE corrected_invoices;
4773   END IF;
4774 
4775   --------------------------------------
4776   l_debug_info := 'Process PRICE hold ';
4777   --------------------------------------
4778   IF (g_debug_mode = 'Y') THEN
4779     AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
4780   END IF;
4781 
4782   AP_APPROVAL_PKG.Process_Inv_Hold_Status(
4783                 p_invoice_id,
4784                 p_line_location_id,
4785                 p_rcv_transaction_id,
4786                 'PRICE',
4787                 l_price_error_exists,
4788                 null,
4789                 p_system_user,
4790                 p_holds,
4791                 p_holds_count,
4792                 p_release_count,
4793                 l_curr_calling_sequence);
4794 
4795 EXCEPTION
4796   WHEN OTHERS THEN
4797     IF (SQLCODE <> -20001) THEN
4798       FND_MESSAGE.SET_NAME('SQLAP','AP_DEBUG');
4799       FND_MESSAGE.SET_TOKEN('ERROR',SQLERRM);
4800       FND_MESSAGE.SET_TOKEN('CALLING_SEQUENCE', l_curr_calling_sequence);
4801       FND_MESSAGE.SET_TOKEN('PARAMETERS',
4802                   'Invoice_id  = '|| to_char(p_invoice_id)
4803               ||', Line_Location_id = '|| to_char(p_line_location_id)
4804               ||', Inv_Currency_Code= '|| p_invoice_currency_code
4805               ||', rcv_transaction_id = '|| to_char(p_rcv_transaction_id)
4806               ||', PO_Unit_Price = '|| to_char(p_po_unit_price)
4807               ||', Price_Tolerance = '|| to_char(p_price_tolerance));
4808       FND_MESSAGE.SET_TOKEN('DEBUG_INFO',l_debug_info);
4809     END IF;
4810 
4811     IF ( corrected_invoices%ISOPEN ) THEN
4812       CLOSE corrected_invoices;
4813     END IF;
4814 
4815     APP_EXCEPTION.RAISE_EXCEPTION;
4816 END Check_Price;
4817 
4818 
4819 /*============================================================================
4820  |  PROCEDURE CHECK_AVERAGE_PRICE
4821  |
4822  |  DESCRIPTION
4823  |      Procedure to calculate the average price for a po matched invoice.
4824  |
4825  |  PROGRAM FLOW
4826  |      It sums up all the base match without any correction to other invoices
4827  |      and the lines that are trying to correct it.
4828  |
4829  |  KNOWN ISSUES:
4830  |
4831  |  NOTES:
4832  |      1. Ensure that we don't divide by zero. if l_sum_qty_invoiced is
4833  |        zero we still need to place a hold if there is an outstanding
4834  |        amount left that is matched. this could happen when an invoice
4835  |        is po matched a credit memo matched to the invoice backs out
4836  |        the quantity and a price correction is entered against the
4837  |        invoice for a positive amount, in this case the total quantity
4838  |        is zero but a price hold should still be placed if using price
4839  |        tolerances.
4840  |
4841  |      2. calculate at invoice line level
4842  |
4843  |      3. We might have a situation that two invoice lines match to different
4844  |         receipts which are against the same PO shipment. We need to be
4845  |         careful when try to do the UOM conversion. Although we only
4846  |         concern the po shipment when we calculate the average price.
4847  |
4848  |      4. PRICE CORRECTION will not affect the total Quantity Invoiced
4849  |
4850  |  MODIFICATION HISTORY
4851  |  Date         Author             Description of Change
4852  |
4853  *==========================================================================*/
4854 
4855 PROCEDURE CHECK_AVERAGE_PRICE(
4856               p_invoice_id            IN            NUMBER,
4857               p_line_location_id      IN            NUMBER,
4858               p_match_option          IN            VARCHAR2,
4859               p_txn_uom               IN            VARCHAR2,
4860               p_po_uom                IN            VARCHAR2,
4861               p_item_id               IN            NUMBER,
4862               p_price_tolerance       IN            NUMBER ,
4863               p_po_unit_price         IN            NUMBER ,
4864               p_invoice_currency_code IN            VARCHAR2,
4865               p_price_error_exists    IN OUT NOCOPY VARCHAR2,
4866               p_calling_sequence      IN            VARCHAR2) IS
4867 
4868   l_sum_pc_inv_amount     NUMBER;
4869   l_sum_qty_invoiced      NUMBER;
4870   l_avg_price             NUMBER ;
4871   l_qty_ratio             NUMBER;
4872   l_total_price_variance  NUMBER;
4873   l_debug_info            varchar2(100);
4874   l_curr_calling_sequence varchar2(2000);
4875 
4876 BEGIN
4877 
4878   l_curr_calling_sequence := 'CHECK_AVERAGE_PRICE <- '||
4879                               p_calling_sequence;
4880 
4881   ---------------------------------------------------------------
4882   l_debug_info := 'calculate average price for a invoice ';
4883   ---------------------------------------------------------------
4884   IF (g_debug_mode = 'Y') THEN
4885     AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
4886   END IF;
4887 
4888   IF ( p_match_option = 'P' ) THEN
4889 
4890      ---------------------------------------------------------------
4891      l_debug_info := 'CHECK_AVERAGE_PRICE <- match to PO';
4892      ---------------------------------------------------------------
4893 
4894      IF (g_debug_mode = 'Y') THEN
4895        AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
4896      END IF;
4897 
4898     SELECT sum( decode( nvl(AIL.unit_price,0) * nvl(AIL.quantity_invoiced,0),
4899                       0, nvl(AIL.amount, 0),
4900                       nvl(AIL.unit_price,0) * nvl(AIL.quantity_invoiced,0) ) ),
4901            sum( decode( AIL.match_type, 'PRICE_CORRECTION', 0,
4902                         nvl(AIL.quantity_invoiced,0)) )
4903     INTO l_sum_pc_inv_amount,
4904          l_sum_qty_invoiced
4905     FROM ap_invoice_lines AIL
4906     WHERE AIL.po_line_location_id  = p_line_location_id
4907     AND  ( AIL.corrected_inv_id = p_invoice_id
4908           OR (AIL.invoice_id = p_invoice_id and
4909               AIL.corrected_inv_id is null) )
4910          and nvl(AIL.discarded_flag,'N') = 'N'       --for the bug 6882864
4911          and AIL.line_type_lookup_code = 'ITEM';     --for the bug 9686240
4912   ELSE
4913     ------------------------------------------------------------------
4914      l_debug_info := 'Check_Average_Price - get qty ratio match to R';
4915     ------------------------------------------------------------------
4916 
4917     IF (p_txn_uom <> p_po_uom) THEN
4918       l_qty_ratio := po_uom_s.po_uom_convert(
4919                            p_txn_uom,
4920                            p_po_uom,
4921                            p_item_id);
4922     ELSE
4923       l_qty_ratio := 1;
4924     END IF;
4925 
4926      ---------------------------------------------------------------
4927      l_debug_info := 'CHECK_AVERAGE_PRICE <- match to receipt';
4928      ---------------------------------------------------------------
4929 
4930      IF (g_debug_mode = 'Y') THEN
4931        AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
4932      END IF;
4933 
4934       -- bug8518421
4935      SELECT sum (decode(nvl(AIL.unit_price,0) * nvl(AIL.quantity_invoiced,0),
4936                        0, NVL(AIL.amount, 0),
4937                        nvl(AIL.unit_price,0) * nvl(AIL.quantity_invoiced,0)
4938                       )
4939                 ),
4940            sum (decode( AIL.match_type, 'PRICE_CORRECTION', 0,
4941                            (nvl(AIL.quantity_invoiced,0) * l_qty_ratio)
4942                        )
4943                )
4944     INTO l_sum_pc_inv_amount,
4945          l_sum_qty_invoiced
4946     FROM ap_invoice_lines AIL
4947     WHERE AIL.po_line_location_id  = p_line_location_id
4948     AND  ( AIL.corrected_inv_id = p_invoice_id
4949            OR (AIL.invoice_id = p_invoice_id and
4950                AIL.corrected_inv_id is null) )
4951     AND nvl(AIL.discarded_flag,'N') = 'N'    --for the bug 6908761
4952     and AIL.line_type_lookup_code = 'ITEM';  --for the bug 9686240
4953 
4954   END IF;
4955 
4956   IF (l_sum_qty_invoiced is null and l_sum_pc_inv_amount is null)   THEN -- Bug 7161683
4957     p_price_error_exists := 'N';
4958     return;
4959   END IF;
4960 
4961 
4962   IF (l_sum_qty_invoiced <> 0) THEN
4963     l_avg_price := l_sum_pc_inv_amount / l_sum_qty_invoiced ;
4964   ELSIF (l_sum_qty_invoiced = 0 and l_sum_pc_inv_amount = 0) THEN
4965     l_avg_price := 0;
4966   ELSIF (p_price_tolerance is not null) THEN
4967     p_price_error_exists := 'Y';
4968   END IF;
4969 
4970   IF (l_sum_qty_invoiced > 0) THEN
4971   /* Start of fix for bug8474680 */
4972   /*  l_total_price_variance := nvl(ap_utilities_pkg.ap_round_currency(
4973                                       l_avg_price -
4974                                       (p_price_tolerance * p_po_unit_price),
4975                                        p_invoice_currency_code), 0); */
4976    l_total_price_variance := nvl(l_avg_price -
4977                               (p_price_tolerance * p_po_unit_price),0);
4978  /*End of fix for bug8474680 */
4979   ELSE
4980     l_total_price_variance := 0;
4981   END IF;
4982 
4983   IF ((l_total_price_variance > 0) AND (p_price_tolerance IS NOT NULL)) THEN
4984     p_price_error_exists := 'Y';
4985   END IF;
4986 
4987 EXCEPTION
4988   WHEN OTHERS THEN
4989     IF (SQLCODE <> -20001) THEN
4990       FND_MESSAGE.SET_NAME('SQLAP','AP_DEBUG');
4991       FND_MESSAGE.SET_TOKEN('ERROR',SQLERRM);
4992       FND_MESSAGE.SET_TOKEN('CALLING_SEQUENCE', l_curr_calling_sequence);
4993       FND_MESSAGE.SET_TOKEN('PARAMETERS',
4994                   'Invoice_id  = '|| to_char(p_invoice_id)
4995               ||', Line_Location_id = '|| to_char(p_line_location_id)
4996               ||', Inv_Currency_Code= '|| p_invoice_currency_code
4997               ||', PO_Unit_Price = '|| to_char(p_po_unit_price)
4998               ||', Price_Tolerance = '|| to_char(p_price_tolerance));
4999       FND_MESSAGE.SET_TOKEN('DEBUG_INFO',l_debug_info);
5000     END IF;
5001     APP_EXCEPTION.RAISE_EXCEPTION;
5002 
5003 END CHECK_AVERAGE_PRICE;
5004 
5005 
5006 /*============================================================================
5007  |  PROCEDURE CALC_TOTAL_SHIPMENT_QTY_BILLED
5008  |
5009  |  DESCRIPTION:
5010  |    Procedure given an invoice id and line_location_id calculateds the
5011  |    the quantity billed affected by this invoice via matching to the given
5012  |    shipment. If the net Quantity billed via this invoice is 0, means no
5013  |    net effect from this invoice, just return the total quantity billed of
5014  |    the system that currently recorded.
5015  |
5016  |  PARAMETERS
5017  |    p_invoice_id - The invoice being validated
5018  |    p_line_location_id - po shimpent line
5019  |    p_match_option - 'R' or 'P'
5020  |    p_rcv_transaction_id - for receipt matching
5021  |    p_qty_billed - out for the total qty billed
5022  |    p_calling_sequence - calling sequence for debug
5023  |
5024  |  PROGRAM FLOW
5025  |    It determine if the invoice line is Quantity correction or Regular base
5026  |    match. Then it will calculate the total quantiy billed. If it is not a
5027  |    correction, in case of the sum of its base match sum up to 0, total qty
5028  |    billed by this invoice is 0. Otherwise, it should be the sum of any
5029  |    invoice that has been matched to this shipment. It applies to both PO
5030  |    match or receipt match.
5031  |
5032  |  KNOWN ISSUES:
5033  |
5034  |  NOTES:
5035  |    Quantity Billed via this invoice = 0 MEANS
5036  |      1) Invoice base matches against shipment + any QTY corrections
5037  |         against this base matches is 0  and
5038  |      2) Invoice QTY Corrections + Base Matches and its other corrections
5039  |         against this shipment is 0
5040  |
5041  |  MODIFICATION HISTORY
5042  |  Date         Author             Description of Change
5043  |
5044  *==========================================================================*/
5045 
5046 PROCEDURE Calc_Total_Shipment_Qty_Billed(
5047               p_invoice_id         IN            NUMBER,
5048               p_line_location_id   IN            NUMBER,
5049               p_match_option       IN            VARCHAR2,
5050               p_rcv_transaction_id IN            NUMBER,
5051               p_qty_billed         IN OUT NOCOPY NUMBER,
5052         p_invoice_type_lookup_code IN      VARCHAR2,
5053               p_calling_sequence   IN            VARCHAR2) IS
5054 
5055   l_debug_loc              VARCHAR2(30) := 'Calc_Total_Shipment_Qty_Billed';
5056   l_curr_calling_sequence  VARCHAR2(2000);
5057   l_inv_qty_billed         NUMBER;
5058   l_corrected_invoice_id   NUMBER;
5059 
5060 BEGIN
5061 
5062   l_curr_calling_sequence := 'AP_APPROVAL_MATCHED_PKG.'||l_debug_loc||'<-'||
5063                               p_calling_sequence;
5064 
5065    Calc_Shipment_Qty_Billed(
5066        p_invoice_id,
5067        p_line_location_id,
5068        p_match_option,
5069        p_rcv_transaction_id,
5070        l_inv_qty_billed,
5071        l_curr_calling_sequence);
5072 /*
5073    SELECT ROUND(DECODE(l_inv_qty_billed,0,
5074                        0, NVL(DECODE(p_invoice_type_lookup_code,'PREPAYMENT',
5075                       PLL.quantity_financed,PLL.quantity_billed)
5076                   ,0)
5077           )
5078     ,5)
5079      INTO p_qty_billed
5080      FROM po_line_locations PLL
5081     WHERE PLL.line_location_id = p_line_location_id;
5082 */
5083 
5084 --bug 9309310
5085    SELECT ROUND(DECODE(l_inv_qty_billed,0,
5086                        0, (nvl(pll.quantity_financed,0) + nvl(pll.quantity_billed,0) - nvl(pll.quantity_recouped,0))
5087                       )
5088                 ,15)
5089      INTO p_qty_billed
5090      FROM po_line_locations PLL
5091     WHERE PLL.line_location_id = p_line_location_id;
5092 
5093 EXCEPTION
5094   WHEN OTHERS THEN
5095     IF (SQLCODE <> -20001) THEN
5096       FND_MESSAGE.SET_NAME('SQLAP','AP_DEBUG');
5097       FND_MESSAGE.SET_TOKEN('ERROR',SQLERRM);
5098       FND_MESSAGE.SET_TOKEN('CALLING_SEQUENCE', l_curr_calling_sequence);
5099       FND_MESSAGE.SET_TOKEN('PARAMETERS',
5100                   'Invoice_id  = '|| to_char(p_invoice_id)
5101               ||', Dist_line_num = '|| to_char(p_line_location_id));
5102     END IF;
5103     APP_EXCEPTION.RAISE_EXCEPTION;
5104 END Calc_Total_Shipment_Qty_Billed;
5105 
5106 
5107 /*============================================================================
5108  |  PROCEDURE CALC_SHIPMENT_QTY_BILLED
5109  |
5110  |  DESCRIPTION:
5111  |    Procedure given an invoice id and line_location_id calculates the
5112  |    quantity billed between this match.
5113  |
5114  |  PARAMETERS
5115  |    p_invoice_id - The invoice being validated
5116  |    p_line_location_id - po shimpent line
5117  |    p_match_option - 'R' or 'P'
5118  |    p_rcv_transaction_id - for receipt matching
5119  |    p_qty_billed - out for the total qty billed by this invoice
5120  |    p_calling_sequence - calling sequence for debug
5121  |
5122  |  PROGRAM FLOW
5123  |    It sums up the quantity billed via BASE MATCH of this invoice and all its
5124  |    quantity corrections to this invoice for a particular shipment;
5125  |    If there is an QUANTITY CORRECTION line exists in this invoice, we need
5126  |    to sum up the quantity billed via BASE MATCH and QUANTITY CORRECTION of all
5127  |    the invoices it was trying to correct for this shipment, plus the
5128  |    QUANTITY CORRECTION line of this invoce itself. Please note, there might
5129  |    a case that this invoice has one correcting line which is trying to correct
5130  |    itself, with our query, it will be included.
5131  |
5132  |  KNOWN ISSUES:
5133  |
5134  |  NOTES:
5135  |
5136  |  MODIFICATION HISTORY
5137  |  Date         Author             Description of Change
5138  |
5139  *===========================================================================*/
5140 
5141 
5142 PROCEDURE Calc_Shipment_Qty_Billed(
5143               p_invoice_id         IN            NUMBER,
5144               p_line_location_id   IN            NUMBER,
5145               p_match_option       IN            VARCHAR2,
5146               p_rcv_transaction_id IN            NUMBER,
5147               p_qty_billed         IN OUT NOCOPY NUMBER,
5148               p_calling_sequence   IN            VARCHAR2) IS
5149 
5150   l_debug_loc              VARCHAR2(30) := 'Calc_Shipment_Qty_Billed';
5151   l_curr_calling_sequence  VARCHAR2(2000);
5152 
5153 BEGIN
5154 
5155   l_curr_calling_sequence := 'AP_APPROVAL_MATCHED_PKG.'||l_debug_loc||'<-'||
5156                               p_calling_sequence;
5157 
5158    /*-----------------------------------------------------------------+
5159     |  The Meaning fo the following query conditions indicates:-      |
5160     |    Query condition 1 - all the base match lines of this         |
5161     |                        invoice itself with p_invoice_id         |
5162     |    Query condition 2 - all the qty correction lines against this|
5163     |                        particular invoice itself (p_invoice_id) |
5164     |    Query condition 3 - all the base match lines of a list of    |
5165     |                        invoices that invoice with p_invoice_id  |
5166     |                        is trying to do quantity correction      |
5167     |    Query condition 4 - all the qty correction lines trying to   |
5168     |                        correct a list of invoices that invoice  |
5169     |                        with p_invoice_id is trying to do        |
5170     |                        quantity corrections                     |
5171     +-----------------------------------------------------------------*/
5172 
5173   IF (p_match_option = 'P') THEN
5174 
5175 
5176      SELECT nvl(trunc(sum(quantity_invoiced),5),0) --7021414
5177       INTO p_qty_billed
5178       FROM ap_invoice_lines L
5179      WHERE L.po_line_location_id = p_line_location_id
5180       AND  (   (L.invoice_id = p_invoice_id and
5181                 L.match_type = 'ITEM_TO_PO' )           -- query condition 1
5182             or (L.corrected_inv_id = p_invoice_id and
5183                 L.match_type = 'QTY_CORRECTION')        -- query condition 2
5184             or (L.invoice_id IN
5185                            ( SELECT corrected_inv_id
5186                                FROM ap_invoice_lines L2
5187                               WHERE L2.invoice_id = p_invoice_id
5188                                 AND L2.po_line_location_id = p_line_location_id
5189                                 AND L2.match_type = 'QTY_CORRECTION') and
5190                 L.match_type = 'ITEM_TO_PO' )           -- query condition 3
5191             or ( L.corrected_inv_id IN
5192                             ( SELECT corrected_inv_id
5193                                 FROM ap_invoice_lines L3
5194                                WHERE L3.invoice_id = p_invoice_id
5195                                  AND L3.po_line_location_id = p_line_location_id
5196                                  AND L3.match_type = 'QTY_CORRECTION') and
5197                 L.match_type = 'QTY_CORRECTION' ) )   -- query condition 4
5198       AND nvl(L.discarded_flag,'N')='N'; --bug 7021414
5199 
5200 
5201   ELSIF (p_match_option = 'R') THEN
5202 
5203 
5204     SELECT nvl(trunc(sum(quantity_invoiced),5),0)
5205       INTO p_qty_billed
5206       FROM ap_invoice_lines L
5207      WHERE L.po_line_location_id = p_line_location_id
5208       AND  (   (L.invoice_id = p_invoice_id and
5209                 L.match_type = 'ITEM_TO_RECEIPT' )        -- query condition 1
5210             or (L.corrected_inv_id = p_invoice_id and
5211                 L.match_type = 'QTY_CORRECTION')          -- query condition 2
5212             or (L.invoice_id IN
5213                            ( SELECT corrected_inv_id
5214                                FROM ap_invoice_lines L2
5215                               WHERE L2.invoice_id = p_invoice_id
5216                                 AND L2.po_line_location_id = p_line_location_id
5217                                 AND L2.match_type = 'QTY_CORRECTION') and
5218                 L.match_type = 'ITEM_TO_RECEIPT' )         -- query condition 3
5219             or (L.corrected_inv_id IN
5220                            ( SELECT corrected_inv_id
5221                                FROM ap_invoice_lines L3
5222                               WHERE L3.invoice_id = p_invoice_id
5223                                 AND L3.po_line_location_id = p_line_location_id
5224                                 AND L3.match_type = 'QTY_CORRECTION') and
5225                 L.match_type = 'QTY_CORRECTION' ) )      -- query condition 4
5226        AND nvl(L.discarded_flag,'N')='N'; --bug 7021414
5227 
5228   END IF;
5229 
5230 EXCEPTION
5231   WHEN OTHERS THEN
5232     IF (SQLCODE <> -20001) THEN
5233       FND_MESSAGE.SET_NAME('SQLAP','AP_DEBUG');
5234       FND_MESSAGE.SET_TOKEN('ERROR',SQLERRM);
5235       FND_MESSAGE.SET_TOKEN('CALLING_SEQUENCE', l_curr_calling_sequence);
5236       FND_MESSAGE.SET_TOKEN('PARAMETERS',
5237                   'Invoice_id  = '|| to_char(p_invoice_id)
5238               ||', po_line_location_id = '|| to_char(p_line_location_id));
5239     END IF;
5240     APP_EXCEPTION.RAISE_EXCEPTION;
5241 END Calc_Shipment_Qty_Billed;
5242 
5243 
5244 
5245 /*============================================================================
5246  |  PROCEDURE CALC_TOTAL_SHIPMENT_AMT_BILLED
5247  |
5248  |  DESCRIPTION:
5249  |    Procedure given an invoice id and line_location_id calculateds the
5250  |    the amount billed affected by this invoice via matching to the given
5251  |    shipment. If the net Amount billed via this invoice is 0, means no
5252  |    net effect from this invoice, just return the total amount billed of
5253  |    the system that currently recorded.
5254  |
5255  |  PARAMETERS
5256  |    p_invoice_id - The invoice being validated
5257  |    p_line_location_id - po shimpent line
5258  |    p_match_option - 'R' or 'P'
5259  |    p_rcv_transaction_id - for receipt matching
5260  |    p_amt_billed - out for the total amt billed
5261  |    p_invoice_type_lookup_code - in for invoice_type
5262  |    p_calling_sequence - calling sequence for debug
5263  |
5264  |  PROGRAM FLOW
5265  |    It determine if the invoice line is Amount correction or Regular base
5266  |    match. Then it will calculate the total amount billed. If it is not a
5267  |    correction, in case of the sum of its base match sum up to 0, total amt
5268  |    billed by this invoice is 0. Otherwise, it should be the sum of any
5269  |    invoice that has been matched to this shipment. It applies to both PO
5270  |    match or receipt match.
5271  |
5272  |  KNOWN ISSUES:
5273  |
5274  |  NOTES:
5275  |    Amount Billed via this invoice = 0 MEANS
5276  |      1) Invoice base matches against shipment + any AMT corrections
5277  |         against this base matches is 0  and
5278  |      2) Invoice AMT Corrections + Base Matches and its other corrections
5279  |         against this shipment is 0
5280  |
5281  |  MODIFICATION HISTORY
5282  |  Date         Author             Description of Change
5283  |  19-Apr-2005  Surekha Myadam    Created
5284  *==========================================================================*/
5285 
5286 PROCEDURE Calc_Total_Shipment_Amt_Billed(
5287               p_invoice_id         IN            NUMBER,
5288               p_line_location_id   IN            NUMBER,
5289               p_match_option       IN            VARCHAR2,
5290               p_rcv_transaction_id IN            NUMBER,
5291               p_amt_billed         IN OUT NOCOPY NUMBER,
5292         p_invoice_type_lookup_code IN      VARCHAR2,
5293               p_calling_sequence   IN            VARCHAR2) IS
5294 
5295   l_debug_loc              VARCHAR2(30) ;
5296   l_curr_calling_sequence  VARCHAR2(2000);
5297   l_inv_amt_billed         NUMBER;
5298   l_corrected_invoice_id   NUMBER;
5299 
5300 BEGIN
5301 
5302   l_debug_loc := 'Calc_Total_Shipment_Qty_Billed';
5303   l_curr_calling_sequence := 'AP_APPROVAL_MATCHED_PKG.'||l_debug_loc||'<-'||
5304                               p_calling_sequence;
5305 
5306    Calc_Shipment_Amt_Billed(
5307        p_invoice_id,
5308        p_line_location_id,
5309        p_match_option,
5310        p_rcv_transaction_id,
5311        l_inv_amt_billed,
5312        l_curr_calling_sequence);
5313 /*
5314    SELECT ROUND(DECODE(l_inv_amt_billed,0,
5315                        0, NVL(DECODE(p_invoice_type_lookup_code,'PREPAYMENT',
5316                       PLL.amount_financed,PLL.amount_billed)
5317                   ,0)
5318           )
5319     ,5)
5320      INTO p_amt_billed
5321      FROM po_line_locations PLL
5322     WHERE PLL.line_location_id = p_line_location_id;
5323 */
5324 
5325    SELECT ROUND(DECODE(l_inv_amt_billed,0,
5326                        0, (nvl(PLL.amount_financed,0) + nvl(PLL.amount_billed,0) - nvl(PLL.amount_recouped,0))
5327                       )
5328                 ,5)
5329      INTO p_amt_billed
5330      FROM po_line_locations PLL
5331     WHERE PLL.line_location_id = p_line_location_id;
5332 
5333 EXCEPTION
5334   WHEN OTHERS THEN
5335     IF (SQLCODE <> -20001) THEN
5336       FND_MESSAGE.SET_NAME('SQLAP','AP_DEBUG');
5337       FND_MESSAGE.SET_TOKEN('ERROR',SQLERRM);
5338       FND_MESSAGE.SET_TOKEN('CALLING_SEQUENCE', l_curr_calling_sequence);
5339       FND_MESSAGE.SET_TOKEN('PARAMETERS',
5340                   'Invoice_id  = '|| to_char(p_invoice_id)
5341               ||', Dist_line_num = '|| to_char(p_line_location_id));
5342     END IF;
5343     APP_EXCEPTION.RAISE_EXCEPTION;
5344 END Calc_Total_Shipment_Amt_Billed;
5345 
5346 
5347 /*============================================================================
5348  |  PROCEDURE CALC_SHIPMENT_AMT_BILLED
5349  |
5350  |  DESCRIPTION:
5351  |    Procedure given an invoice id and line_location_id calculates the
5352  |    amount billed between this match.
5353  |
5354  |  PARAMETERS
5355  |    p_invoice_id - The invoice being validated
5356  |    p_line_location_id - po shimpent line
5357  |    p_match_option - 'R' or 'P'
5358  |    p_rcv_transaction_id - for receipt matching
5359  |    p_amt_billed - out for the total amt billed by this invoice
5360  |    p_calling_sequence - calling sequence for debug
5361  |
5362  |  PROGRAM FLOW
5363  |    It sums up the amount billed via BASE MATCH of this invoice and all its
5364  |    amount corrections to this invoice for a particular shipment;
5365  |    If there is an AMOUNT CORRECTION line exists in this invoice, we need
5366  |    to sum up the amount billed via BASE MATCH and AMOUNT CORRECTION of all
5367  |    the invoices it was trying to correct for this shipment, plus the
5368  |    AMOUNT CORRECTION line of this invoce itself. Please note, there might
5369  |    a case that this invoice has one correcting line which is trying to correct
5370  |    itself, with our query, it will be included.
5371  |
5372  |  KNOWN ISSUES:
5373  |
5374  |  NOTES:
5375  |
5376  |  MODIFICATION HISTORY
5377  |  Date         Author             Description of Change
5378  | 19-Apr-2005   Surekha Myadam    Created
5379  *===========================================================================*/
5380 PROCEDURE Calc_Shipment_Amt_Billed(
5381               p_invoice_id         IN            NUMBER,
5382               p_line_location_id   IN            NUMBER,
5383               p_match_option       IN            VARCHAR2,
5384               p_rcv_transaction_id IN            NUMBER,
5385               p_amt_billed         IN OUT NOCOPY NUMBER,
5386               p_calling_sequence   IN            VARCHAR2) IS
5387 
5388   l_debug_loc              VARCHAR2(30) ;
5389   l_curr_calling_sequence  VARCHAR2(2000);
5390 
5391 BEGIN
5392 
5393   l_debug_loc := 'Calc_Shipment_Amt_Billed';
5394   l_curr_calling_sequence := 'AP_APPROVAL_MATCHED_PKG.'||l_debug_loc||'<-'||
5395                               p_calling_sequence;
5396 
5397    /*-----------------------------------------------------------------+
5398     |  The Meaning fo the following query conditions indicates:-      |
5399     |    Query condition 1 - all the base match lines of this         |
5400     |                        invoice itself with p_invoice_id         |
5401     |    Query condition 2 - all the amt correction lines against this|
5402     |                        particular invoice itself (p_invoice_id) |
5403     |    Query condition 3 - all the base match lines of a list of    |
5404     |                        invoices that invoice with p_invoice_id  |
5405     |                        is trying to do amount correction        |
5406     |    Query condition 4 - all the amt correction lines trying to   |
5407     |                        correct a list of invoices that invoice  |
5408     |                        with p_invoice_id is trying to do        |
5409     |                        amount corrections                       |
5410     +-----------------------------------------------------------------*/
5411 
5412   IF (p_match_option = 'P') THEN
5413 
5414 
5415      SELECT trunc(sum(amount),5)
5416       INTO p_amt_billed
5417       FROM ap_invoice_lines L
5418      WHERE L.po_line_location_id = p_line_location_id
5419       AND  (   (L.invoice_id = p_invoice_id and
5420                 L.match_type = 'ITEM_TO_PO' )           -- query condition 1
5421             or (L.corrected_inv_id = p_invoice_id and
5422                 L.match_type = 'AMOUNT_CORRECTION')        -- query condition 2
5423             or (L.invoice_id IN
5424                            ( SELECT corrected_inv_id
5425                                FROM ap_invoice_lines L2
5426                               WHERE L2.invoice_id = p_invoice_id
5427                                 AND L2.po_line_location_id = p_line_location_id
5428                                 AND L2.match_type = 'AMOUNT_CORRECTION') and
5429                 L.match_type = 'ITEM_TO_PO' )           -- query condition 3
5430             or ( L.corrected_inv_id IN
5431                             ( SELECT corrected_inv_id
5432                                 FROM ap_invoice_lines L3
5433                                WHERE L3.invoice_id = p_invoice_id
5434                                  AND L3.po_line_location_id = p_line_location_id
5435                                  AND L3.match_type = 'AMOUNT_CORRECTION') and
5436                 L.match_type = 'AMOUNT_CORRECTION' ) );   -- query condition 4
5437 
5438 
5439   ELSIF (p_match_option = 'R') THEN
5440 
5441 
5442     SELECT trunc(sum(amount),5)
5443       INTO p_amt_billed
5444       FROM ap_invoice_lines L
5445      WHERE L.po_line_location_id = p_line_location_id
5446       AND  (   (L.invoice_id = p_invoice_id and
5447                 L.match_type = 'ITEM_TO_RECEIPT' )        -- query condition 1
5448             or (L.corrected_inv_id = p_invoice_id and
5449                 L.match_type = 'AMOUNT_CORRECTION')          -- query condition 2
5450             or (L.invoice_id IN
5451                            ( SELECT corrected_inv_id
5452                                FROM ap_invoice_lines L2
5453                               WHERE L2.invoice_id = p_invoice_id
5454                                 AND L2.po_line_location_id = p_line_location_id
5455                                 AND L2.match_type = 'AMOUNT_CORRECTION') and
5456                 L.match_type = 'ITEM_TO_RECEIPT' )         -- query condition 3
5457             or (L.corrected_inv_id IN
5458                            ( SELECT corrected_inv_id
5459                                FROM ap_invoice_lines L3
5460                               WHERE L3.invoice_id = p_invoice_id
5461                                 AND L3.po_line_location_id = p_line_location_id
5462                                 AND L3.match_type = 'AMOUNT_CORRECTION') and
5463                 L.match_type = 'AMOUNT_CORRECTION' ) );      -- query condition 4
5464 
5465   END IF;
5466 
5467 EXCEPTION
5468   WHEN OTHERS THEN
5469     IF (SQLCODE <> -20001) THEN
5470       FND_MESSAGE.SET_NAME('SQLAP','AP_DEBUG');
5471       FND_MESSAGE.SET_TOKEN('ERROR',SQLERRM);
5472       FND_MESSAGE.SET_TOKEN('CALLING_SEQUENCE', l_curr_calling_sequence);
5473       FND_MESSAGE.SET_TOKEN('PARAMETERS',
5474                   'Invoice_id  = '|| to_char(p_invoice_id)
5475               ||', po_line_location_id = '|| to_char(p_line_location_id));
5476     END IF;
5477     APP_EXCEPTION.RAISE_EXCEPTION;
5478 END Calc_Shipment_Amt_Billed;
5479 
5480 
5481 
5482 /*============================================================================
5483  |  PROCEDURE  CALC_SHIP_TOTAL_TRX_AMT_VAR
5484  |
5485  |  DESCRIPTION:
5486  |                Procedure that given a shipment it calculates total amount
5487  |                invoiced against the shipment in transaction currency minus
5488  |                the valid po qty (ordered-cancelled) times its unit price.
5489  |
5490  |  PROGRAM FLOW
5491  |    It will calculate the total amount billed. If it is 0, return 0,
5492  |    Otherwise, it should be the sum of any invoice that has been matched
5493  |    to this shipment. It applies to both PO match or receipt match.
5494  |
5495  |  NOTES:
5496  |         It should all be in the same currency. since we can not do
5497  |         cross-curr matching.
5498  |        -----------------------------------------------------------------
5499  |        -- If the total matched to the shipment from this invoice      --
5500  |        -- is 0, then return with 0 since this invoice should not be   --
5501  |        -- placed on max shipment hold.                                --
5502  |        -- Otherwise, move on to calculating the full shipment amount  --
5503  |        -- transactional currency matched to this shipment.            --
5504  |        -----------------------------------------------------------------
5505  |  MODIFICATION HISTORY
5506  |  Date         Author             Description of Change
5507  *==========================================================================*/
5508 
5509 PROCEDURE Calc_Ship_Total_Trx_Amt_Var(
5510              p_invoice_id         IN            NUMBER,
5511              p_line_location_id   IN            NUMBER,
5512              p_match_option       IN            VARCHAR2,
5513              p_po_price           IN            NUMBER,
5514              p_ship_amount        OUT NOCOPY    NUMBER, -- 3488259 (3110072)
5515              p_match_basis        IN            VARCHAR2,  -- Amount Based Matching
5516              p_ship_trx_amt_var   IN OUT NOCOPY NUMBER,
5517              p_calling_sequence   IN            VARCHAR2,
5518              p_org_id             IN            NUMBER) IS -- 5500101
5519 
5520   l_debug_loc                   VARCHAR2(30) := 'Calc_Ship_Total_Trx_Amt_Var';
5521   l_debug_info                  VARCHAR2(2000);
5522   l_curr_calling_sequence       VARCHAR2(2000);
5523   l_po_total                    NUMBER;
5524   l_ship_trx_amt                NUMBER;
5525   l_freight_total               NUMBER; -- 3488259 (3110072)
5526 
5527 BEGIN
5528 
5529   l_curr_calling_sequence := 'AP_APPROVAL_MATCHED_PKG.'||l_debug_loc||'<-'||
5530                              p_calling_sequence;
5531   --------------------------------------------------------
5532   l_debug_info := 'Calculate Shipment Total for the invoice';
5533   --------------------------------------------------------
5534   IF (g_debug_mode = 'Y') THEN
5535     AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
5536   END IF;
5537 
5538    /*-----------------------------------------------------------------+
5539     |  Calculate the total shipment transaction amt billed by this    |
5540     |  invoice and its corrections. If it is 0, further check is      |
5541     |  not needed.                                                    |
5542     +-----------------------------------------------------------------*/
5543 
5544   Calc_Ship_Trx_Amt(
5545       p_invoice_id,
5546       p_line_location_id,
5547       p_match_option,
5548       l_ship_trx_amt,
5549       l_curr_calling_sequence);
5550 
5551   IF ( l_ship_trx_amt = 0  ) THEN
5552     -----------------------------------------------------------------
5553     l_debug_info := 'Calc_Ship_Total_Trx_Amt_Var->shipment amt is 0';
5554     -----------------------------------------------------------------
5555     IF (g_debug_mode = 'Y') THEN
5556       AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
5557     END IF;
5558     p_ship_trx_amt_var := 0;
5559   ELSE
5560     IF p_match_basis  = 'QUANTITY' THEN  -- Amount Based Matching
5561       SELECT DECODE(FC.minimum_accountable_unit, NULL,
5562                   ROUND(((NVL(PLL.quantity, 0) -
5563                           NVL(PLL.quantity_cancelled, 0)) * p_po_price),
5564                         FC.precision),
5565                   ROUND(((NVL(PLL.quantity, 0) -
5566                           NVL(PLL.quantity_cancelled, 0))* p_po_price)
5567                         / FC.minimum_accountable_unit)
5568                         * FC.minimum_accountable_unit)
5569       INTO   l_po_total
5570       FROM   fnd_currencies FC,
5571            po_line_locations PLL,
5572            po_headers PH
5573       WHERE  PLL.line_location_id = p_line_location_id
5574       AND   PH.po_header_id = PLL.po_header_id
5575       AND   FC.currency_code = PH.currency_code;
5576 
5577     ELSE  /* for match_basis 'AMOUNT' need to get amounts on po_shipments
5578          rather than multiplying quantity_invoiced and unit_price */
5579 
5580       SELECT DECODE(FC.minimum_accountable_unit, null,
5581                      ROUND((NVL(PLL.amount, 0) -
5582                              NVL(PLL.amount_cancelled, 0)),
5583                            FC.precision),
5584                      ROUND((NVL(PLL.amount, 0) -
5585                              NVL(PLL.amount_cancelled, 0))
5586                            / FC.minimum_accountable_unit)
5587                            * FC.minimum_accountable_unit)
5588       INTO   l_po_total
5589       FROM   fnd_currencies FC, po_line_locations PLL, po_headers PH
5590       WHERE  PLL.line_location_id = p_line_location_id
5591       AND    PH.po_header_id = PLL.po_header_id
5592       AND    FC.currency_code = PH.currency_code;
5593 
5594     END IF; --p_match_basis = 'QUANTITY'. AMount Based Matching
5595 
5596     --Contract Payments: Added the decode clause
5597     SELECT SUM(decode(PD.distribution_type,'PREPAYMENT',
5598               nvl(PD.amount_financed,0),
5599           nvl(PD.amount_billed,0)
5600          )
5601          )
5602     INTO   p_ship_trx_amt_var
5603     FROM   po_distributions_ap_v PD
5604     WHERE  PD.line_location_id = p_line_location_id;
5605 
5606     p_ship_trx_amt_var := p_ship_trx_amt_var - l_po_total;
5607 
5608   END IF;
5609 
5610 
5611   IF FV_INSTALL.Enabled(p_org_id) THEN -- 5500101
5612 
5613     BEGIN
5614 
5615      SELECT     nvl(sum(nvl(AIDF.amount,0)),0)
5616      INTO       l_freight_total
5617      FROM       ap_invoice_distributions AIDF,
5618                 ap_invoice_distributions AIDI,
5619                 po_distributions_all POD
5620      WHERE      AIDF.charge_applicable_to_dist_id = AIDI.invoice_distribution_id
5621      AND        AIDF.line_type_lookup_code = 'FREIGHT'
5622      AND        AIDI.line_type_lookup_code = 'ITEM'
5623      AND        AIDI.po_distribution_id = POD.po_distribution_id
5624      AND        POD.line_location_id = p_line_location_id;
5625 
5626     EXCEPTION
5627          WHEN NO_DATA_FOUND THEN
5628               l_freight_total := 0;
5629          WHEN OTHERS THEN
5630               l_freight_total := 0;
5631 
5632     END;
5633 
5634      p_ship_trx_amt_var := p_ship_trx_amt_var + l_freight_total;
5635      p_ship_amount := l_po_total;
5636 
5637   END IF;
5638 
5639     -- 3488259 (3110072) Ends
5640 
5641 EXCEPTION
5642   WHEN OTHERS THEN
5643     IF (SQLCODE <> -20001) THEN
5644       FND_MESSAGE.SET_NAME('SQLAP','AP_DEBUG');
5645       FND_MESSAGE.SET_TOKEN('ERROR',SQLERRM);
5646       FND_MESSAGE.SET_TOKEN('CALLING_SEQUENCE', l_curr_calling_sequence);
5647       FND_MESSAGE.SET_TOKEN('PARAMETERS',
5648                   'Invoice_id  = '|| to_char(p_invoice_id)
5649               ||', Shipment_id = '|| to_char(p_line_location_id));
5650     END IF;
5651     APP_EXCEPTION.RAISE_EXCEPTION;
5652 END Calc_Ship_Total_Trx_Amt_Var;
5653 
5654 /*============================================================================
5655  |  PROCEDURE  CALC_SHIP_TRX_AMT
5656  |
5657  |  DESCRIPTION:
5658  |                Procedure that given a shipment it calculates total amount
5659  |                invoiced against the shipment by this particular invoice
5660  |                in transaction currency.
5661  |
5662  |  PROGRAM FLOW
5663  |    It sums up the amount billed via BASE MATCH of this invoice and all its
5664  |    qty/price corrections to this invoice for a particular shipment;
5665  |    If there is an QTY/PRICE CORRECTION line exists in this invoice, we need
5666  |    to sum up the amount billed via BASE MATCH and QTY/PRICE CORRECTIONS of
5667  |    all the invoices it was trying to correct for this shipment, plus the
5668  |    QTY/PRICE CORRECTION line of this invoce itself. Please note, there might
5669  |    a case that this invoice has one correcting line which is trying to
5670  |    correct itself, with our query, it will be included.
5671  |
5672  |  NOTES:
5673  |    1. It should all be in the same currency. since we can not do
5674  |       cross-curr matching.
5675  |    2. both Quantity correction and Price correction should be considered
5676  |       when calculate the amount.
5677  |
5678  |  MODIFICATION HISTORY
5679  |  Date         Author             Description of Change
5680  *==========================================================================*/
5681 
5682 PROCEDURE Calc_Ship_Trx_Amt(
5683               p_invoice_id         IN            NUMBER,
5684               p_line_location_id   IN            NUMBER,
5685               p_match_option       IN            VARCHAR2,
5686               p_ship_trx_amt       IN OUT NOCOPY NUMBER,
5687               p_calling_sequence   IN            VARCHAR2) IS
5688 
5689   l_debug_loc                   VARCHAR2(30) := 'Calc_Ship_Trx_Amt';
5690   l_debug_info                  VARCHAR2(2000);
5691   l_curr_calling_sequence       VARCHAR2(2000);
5692 
5693 BEGIN
5694 
5695   l_curr_calling_sequence := 'AP_APPROVAL_MATCHED_PKG.'||l_debug_loc||'<-'||
5696                              p_calling_sequence;
5697   ------------------------------------------------------------------
5698   l_debug_info := 'Calculate Shipment Total amount for the invoice';
5699   --------------------------------------------------------------=---
5700   IF (g_debug_mode = 'Y') THEN
5701     AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
5702   END IF;
5703 
5704    /*-----------------------------------------------------------------+
5705     |  The Meaning fo the following query conditions indicates:-      |
5706     |    Query condition 1 - all the base match lines of this         |
5707     |                        invoice itself with p_invoice_id         |
5708     |    Query condition 2 - all the qty/price correction lines       |
5709     |                        against this particular invoice itself   |
5710     |                        (p_invoice_id)                           |
5711     |    Query condition 3 - all the base match lines of a list of    |
5712     |                        invoices that invoice with p_invoice_id  |
5713     |                        is trying to do qty/price correction     |
5714     |    Query condition 4 - all the qty/price correction lines       |
5715     |                        trying to correct a list of invoices     |
5716     |                        that invoice with p_invoice_id is trying |
5717     |                        to do corrections                        |
5718     +-----------------------------------------------------------------*/
5719 
5720   IF (p_match_option = 'P') THEN
5721 
5722     -------------------------------------------------------
5723     l_debug_info := 'Calc_Ship_Trx_Amt - Match to PO';
5724     -------------------------------------------------------
5725 
5726     IF (g_debug_mode = 'Y') THEN
5727       AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
5728     END IF;
5729 
5730     SELECT sum( NVL(L.amount, 0) )
5731       INTO p_ship_trx_amt
5732       FROM ap_invoice_lines L
5733      WHERE L.po_line_location_id = p_line_location_id
5734       AND  (   (L.invoice_id = p_invoice_id and
5735                 L.match_type IN ('ITEM_TO_PO',           -- query condition 1
5736                                  'ITEM_TO_SERVICE_PO'))  -- Amount Based Matching
5737             or (L.corrected_inv_id = p_invoice_id )      -- query condition 2
5738             or (L.invoice_id IN
5739                            ( SELECT corrected_inv_id
5740                                FROM ap_invoice_lines L2
5741                               WHERE L2.po_line_location_id = p_line_location_id
5742                                 AND L2.invoice_id = p_invoice_id
5743                                 AND L2.corrected_inv_id is not null ) and
5744                 L.match_type IN ('ITEM_TO_PO',            -- query condition 3
5745                                  'ITEM_TO_SERVICE_PO'))   -- Amount Based Matching
5746             or (L.corrected_inv_id IN
5747                            ( SELECT corrected_inv_id
5748                                FROM ap_invoice_lines L3
5749                               WHERE L3.po_line_location_id = p_line_location_id
5750                                 AND L3.invoice_id = p_invoice_id
5751                                 AND L3.corrected_inv_id is not null ) ) );
5752                                                          -- query condition 4
5753 
5754   ELSIF (p_match_option = 'R') THEN
5755 
5756     -------------------------------------------------------
5757     l_debug_info := 'Calc_Ship_Trx_Amt - Match to RECEIPT';
5758     -------------------------------------------------------
5759 
5760     IF (g_debug_mode = 'Y') THEN
5761       AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
5762     END IF;
5763 
5764     SELECT sum(NVL(L.amount, 0))
5765       INTO p_ship_trx_amt
5766       FROM ap_invoice_lines L
5767      WHERE L.po_line_location_id = p_line_location_id
5768       AND  (   (L.invoice_id = p_invoice_id and
5769                 L.match_type IN ('ITEM_TO_RECEIPT',      -- query condition 1
5770                                  'ITEM_TO_SERVICE_RECEIPT')) -- Amount Based Matching
5771             or (L.corrected_inv_id = p_invoice_id )      -- query condition 2
5772             or (L.invoice_id IN
5773                            ( SELECT corrected_inv_id
5774                                FROM ap_invoice_lines L2
5775                               WHERE L2.po_line_location_id = p_line_location_id
5776                                 AND L2.invoice_id = p_invoice_id
5777                                 AND L2.corrected_inv_id is not null ) and
5778                 L.match_type IN ('ITEM_TO_RECEIPT',        -- query condition 3
5779                                  'ITEM_TO_SERVICE_RECEIPT')) -- Amount Based Matching
5780             or (L.corrected_inv_id IN
5781                            ( SELECT corrected_inv_id
5782                                FROM ap_invoice_lines L3
5783                               WHERE L3.po_line_location_id = p_line_location_id
5784                                 AND L3.invoice_id = p_invoice_id
5785                                 AND L3.corrected_inv_id is not null ) ) );
5786                                                          -- query condition 4
5787   END IF;
5788 
5789 EXCEPTION
5790   WHEN OTHERS THEN
5791     IF (SQLCODE <> -20001) THEN
5792       FND_MESSAGE.SET_NAME('SQLAP','AP_DEBUG');
5793       FND_MESSAGE.SET_TOKEN('ERROR',SQLERRM);
5794       FND_MESSAGE.SET_TOKEN('CALLING_SEQUENCE', l_curr_calling_sequence);
5795       FND_MESSAGE.SET_TOKEN('PARAMETERS',
5796                   'Invoice_id  = '|| to_char(p_invoice_id)
5797               ||', Shipment_id = '|| to_char(p_line_location_id));
5798     END IF;
5799     APP_EXCEPTION.RAISE_EXCEPTION;
5800 END Calc_Ship_Trx_Amt;
5801 
5802 
5803 /*=============================================================================
5804  |  PROCEDURE  CALC_MAX_RATE_VAR
5805  |
5806  |  DESCRIPTION:
5807  |                Procedure that given a shipment, finds the erv for the
5808  |                shipment in an invoice
5809  |
5810  |   PROGRAM FLOW
5811  |
5812  |  KNOWN ISSUES:
5813  |
5814  |  NOTES:
5815  |
5816  |  MODIFICATION HISTORY
5817  |  Date         Author             Description of Change
5818  |
5819  *============================================================================*/
5820 
5821 PROCEDURE Calc_Max_Rate_Var(
5822               p_invoice_id         IN            NUMBER,
5823               p_line_location_id   IN            NUMBER,
5824               p_rcv_transaction_id IN            NUMBER,
5825               p_match_option       IN            VARCHAR2,
5826               p_rate_amt_var       IN OUT NOCOPY NUMBER,
5827               p_calling_sequence   IN            VARCHAR2) IS
5828 
5829   l_debug_loc                   VARCHAR2(30) := 'Calc_Max_Rate_Var';
5830   l_debug_info                  VARCHAR2(2000);
5831   l_curr_calling_sequence       VARCHAR2(2000);
5832 
5833 BEGIN
5834 
5835   l_curr_calling_sequence := 'AP_APPROVAL_MATCHED_PKG.'||l_debug_loc||'<-'||
5836                               p_calling_sequence;
5837 
5838   -------------------------------------------------------------------------
5839   l_debug_info := 'Calculate ERV total for Shipment/receipt in the invoice';
5840   -------------------------------------------------------------------------
5841 
5842   IF g_debug_mode = 'Y' THEN
5843     AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
5844     AP_Debug_Pkg.Print(g_debug_mode, 'Invoice id: '|| TO_CHAR(p_invoice_id));
5845     AP_Debug_Pkg.Print(g_debug_mode, 'line location id: '||
5846                        TO_CHAR(p_line_location_id));
5847   END IF;
5848 
5849   IF (p_match_option = 'P') THEN
5850 
5851     -------------------------------------------------------
5852     l_debug_info := 'Calc_Max_Rate_Var - Match to RECEIPT';
5853     -------------------------------------------------------
5854     IF (g_debug_mode = 'Y') THEN
5855       AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
5856     END IF;
5857 
5858     SELECT SUM( NVL(D.base_amount, 0))
5859       INTO p_rate_amt_var
5860       FROM ap_invoice_distributions D, po_distributions_ap_v PD
5861      WHERE D.po_distribution_id = PD.po_distribution_id
5862        AND PD.line_location_id = p_line_location_id
5863        AND D.invoice_id = p_invoice_id
5864        AND D.line_type_lookup_code = 'ERV';
5865 
5866   ELSIF (p_match_option = 'R') THEN
5867 
5868     -------------------------------------------------------
5869     l_debug_info := 'Calc_Max_Rate_Var - Match to RECEIPT';
5870     -------------------------------------------------------
5871     IF (g_debug_mode = 'Y') THEN
5872       AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
5873     END IF;
5874 
5875     SELECT SUM(NVL(D.base_amount, 0))
5876       INTO p_rate_amt_var
5877       FROM ap_invoice_distributions D
5878      WHERE D.rcv_transaction_id = p_rcv_transaction_id
5879        AND D.invoice_id = p_invoice_id
5880        AND D.line_type_lookup_code = 'ERV';
5881 
5882   END IF;
5883 
5884 EXCEPTION
5885   WHEN OTHERS THEN
5886     IF (SQLCODE <> -20001) THEN
5887       FND_MESSAGE.SET_NAME('SQLAP','AP_DEBUG');
5888       FND_MESSAGE.SET_TOKEN('ERROR',SQLERRM);
5889       FND_MESSAGE.SET_TOKEN('CALLING_SEQUENCE', l_curr_calling_sequence);
5890       FND_MESSAGE.SET_TOKEN('PARAMETERS',
5891                   'Invoice_id  = '|| to_char(p_invoice_id)
5892               ||', Shipment_id = '|| to_char(p_line_location_id));
5893     END IF;
5894     APP_EXCEPTION.RAISE_EXCEPTION;
5895 END Calc_Max_Rate_Var;
5896 
5897 
5898 /*=============================================================================
5899  |  PROCEDURE  CALC_SHIP_TOTAL_BASE_AMT_VAR
5900  |
5901  |  DESCRIPTION:
5902  |                Procedure that given a shipment, it calculates total amount
5903  |                invoiced against the shipment in base currency minus the
5904  |                valid po qty (ordered-cancelled) times its unit price at
5905  |                base currency.
5906  |
5907  |  PROGRAM FLOW
5908  |    It will calculate the total BASE amount billed. If it is 0, return 0,
5909  |    Otherwise, it should be the sum of any invoice that has been matched
5910  |    to this shipment. It applies to both PO match or receipt match.
5911  |
5912  |  NOTES:
5913  |
5914  |  MODIFICATION HISTORY
5915  |  Date         Author             Description of Change
5916  |
5917  *============================================================================*/
5918 
5919 PROCEDURE Calc_Ship_Total_Base_Amt_Var(
5920               p_invoice_id         IN            NUMBER,
5921               p_line_location_id   IN            NUMBER,
5922               p_rcv_transaction_id   IN            NUMBER, /* Added for Bug:14726598*/
5923               p_match_option       IN            VARCHAR2,
5924               p_po_price           IN            NUMBER,
5925               p_match_basis        IN            VARCHAR2,
5926               p_inv_curr_code      IN            VARCHAR2,
5927               p_base_curr_code     IN            VARCHAR2,
5928               p_ship_base_amt_var  IN OUT NOCOPY NUMBER,
5929               p_calling_sequence   IN            VARCHAR2) IS
5930 
5931   l_debug_loc                   VARCHAR2(30) := 'Calc_Ship_Total_Base_Amt_Var';
5932   l_debug_info                  VARCHAR2(2000);
5933   l_curr_calling_sequence       VARCHAR2(2000);
5934   l_po_total                    NUMBER;
5935   l_ship_trx_base_amt           NUMBER;
5936   rcv_total                     NUMBER; /*Added for Bug:14726598*/
5937 
5938 BEGIN
5939 
5940   l_curr_calling_sequence := 'AP_APPROVAL_MATCHED_PKG.'||l_debug_loc||'<-'||
5941                               p_calling_sequence;
5942 
5943   ----------------------------------------------------------------
5944   l_debug_info := 'Calculate Base Shipment Total for the invoice';
5945   ----------------------------------------------------------------
5946 
5947   IF g_debug_mode = 'Y' THEN
5948     AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
5949   END IF;
5950 
5951    /*-----------------------------------------------------------------+
5952     |  Calculate the total shipment transaction amt billed by this    |
5953     |  invoice and its corrections. If it is 0, further check is      |
5954     |  not needed.                                                    |
5955     +-----------------------------------------------------------------*/
5956 
5957   Calc_Ship_Trx_Base_Amt(
5958       p_invoice_id,
5959       p_line_location_id,
5960       p_rcv_transaction_id,                         /*Added for Bug 14726598 as additional fix*/
5961       p_match_option,
5962       p_inv_curr_code,
5963       p_base_curr_code,
5964       l_ship_trx_base_amt,
5965       l_curr_calling_sequence);
5966 
5967   l_ship_trx_base_amt := AP_UTILITIES_PKG.Ap_Round_Currency(
5968                              l_ship_trx_base_amt,
5969                              p_base_curr_code);
5970 
5971 
5972   IF ( l_ship_trx_base_amt = 0 ) THEN
5973     ---------------------------------------------------------------------------
5974     l_debug_info := 'Calc_Ship_Total_base_Trx_Amt_Var->base shipment amt is 0';
5975     ---------------------------------------------------------------------------
5976     IF (g_debug_mode = 'Y') THEN
5977       AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
5978     END IF;
5979 
5980     p_ship_base_amt_var := 0;
5981 
5982   ELSE
5983 
5984     ---------------------------------------------------------------------------
5985     l_debug_info := 'Calc_Ship_Total_base_Trx_Amt_Var->base shipment amt <> 0';
5986     ---------------------------------------------------------------------------
5987     IF (g_debug_mode = 'Y') THEN
5988       AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
5989     END IF;
5990 
5991     --Amount-Based Matching Project, added the IF condition
5992 
5993    --match_basis ='QUANTITY'--
5994 
5995     IF (p_match_basis ='QUANTITY') THEN
5996       IF (p_match_option='P') THEN                 /*If condition added for Bug:14726598 */
5997         SELECT SUM((NVL(PD.quantity_ordered, 0) -
5998                   NVL(PD.quantity_cancelled, 0)) * p_po_price
5999                   * DECODE(p_inv_curr_code, p_base_curr_code,1, PD.rate))
6000         INTO   l_po_total
6001         FROM   po_distributions_ap_v PD
6002         WHERE  PD.line_location_id = p_line_location_id;
6003 
6004        --Bug6824860 this SQl should not consider lines which are not matched, but
6005      --have PO dist ID stamped,
6006     --for instance, the Tax lines(passed as MISC lines) to AP by India
6007     --Localization, non-rec tax lines in AP. India localization
6008     --passes NOT MATCHED as match_type for misc lines, while AP uses
6009     --NOT_MATCHED, hence adding both in match_type condition
6010 
6011        SELECT SUM(DECODE(p_inv_curr_code, p_base_curr_code, nvl(D.amount,0),
6012                nvl(D.base_amount,D.amount/*,(D.amount * DECODE(I.exchange_rate, null,
6013                                              PD.rate, I.exchange_rate))*/)))  /*commented in bug: 14726598 as additional fix*/
6014           INTO   p_ship_base_amt_var
6015           FROM   ap_invoice_distributions D
6016                  , po_distributions_ap_v PD
6017                  , ap_invoices I
6018            , ap_invoice_lines L --Bug6824860
6019           WHERE  D.po_distribution_id = PD.po_distribution_id
6020           AND    PD.line_location_id = p_line_location_id
6021           AND    D.invoice_id = I.invoice_id
6022           AND     L.invoice_id = I.invoice_id --Bug6824860
6023           AND    L.line_number = D.invoice_line_number --Bug6824860
6024           AND     L.match_type not in ('NOT MATCHED','NOT_MATCHED'); --Bug6824860
6025 
6026          p_ship_base_amt_var := AP_UTILITIES_PKG.Ap_Round_Currency( p_ship_base_amt_var -l_po_total,p_base_curr_code);
6027      /*Bug:14726598 Start*/
6028       ELSE               /* Bug: 14726598:Following code is added to fetch PO Base Amount for reciept matched invoices based on exchange rate of reciepts for quantity type po match */
6029         SELECT SUM((NVL(RT.quantity, 0)) * p_po_price* DECODE(p_inv_curr_code, p_base_curr_code,1,RT.currency_conversion_rate))
6030         INTO   rcv_total
6031         FROM   rcv_transactions RT
6032         WHERE  RT.transaction_id=p_rcv_transaction_id;
6033 
6034         SELECT SUM(DECODE(p_inv_curr_code, p_base_curr_code, nvl(D.amount,0),nvl(D.base_amount,D.amount)))
6035         INTO   p_ship_base_amt_var
6036         FROM   ap_invoice_distributions D
6037                , ap_invoices I
6038                , ap_invoice_lines L
6039                ,rcv_transactions  RT
6040         WHERE  D.rcv_transaction_id = RT.transaction_id
6041         AND    RT.transaction_id=p_rcv_transaction_id
6042         AND    D.invoice_id = I.invoice_id
6043         AND     L.invoice_id = I.invoice_id --Bug6824860
6044         AND    L.line_number = D.invoice_line_number --Bug6824860
6045         AND     L.match_type not in ('NOT MATCHED','NOT_MATCHED');
6046 
6047          p_ship_base_amt_var := AP_UTILITIES_PKG.Ap_Round_Currency(p_ship_base_amt_var - rcv_total,p_base_curr_code);
6048       /*Bug:14726598 End*/
6049       END IF;
6050   ELSE
6051        --match_basis ='AMOUNT'--
6052 
6053       IF (p_match_option='P') THEN                 /*If condition added for Bug:14726598 */
6054           SELECT SUM((NVL(PD.amount_ordered, 0) -
6055                      NVL(PD.amount_cancelled, 0))
6056                       * DECODE(p_inv_curr_code, p_base_curr_code,1,
6057                         PD.rate))
6058           INTO   l_po_total
6059           FROM   po_distributions_ap_v PD
6060           WHERE  PD.line_location_id = p_line_location_id;
6061 
6062            --Bug6824860 this SQl should not consider lines which are not matched, but
6063      --have PO dist ID stamped,
6064     --for instance, the Tax lines(passed as MISC lines) to AP by India
6065     --Localization, non-rec tax lines in AP. India localization
6066     --passes NOT MATCHED as match_type for misc lines, while AP uses
6067     --NOT_MATCHED, hence adding both in match_type condition
6068 
6069            SELECT SUM(DECODE(p_inv_curr_code, p_base_curr_code, nvl(D.amount,0),
6070                nvl(D.base_amount,D.amount/*,(D.amount * DECODE(I.exchange_rate, null,
6071                                              PD.rate, I.exchange_rate))*/)))  /*commented in bug: 14726598 as additional fix*/
6072           INTO   p_ship_base_amt_var
6073           FROM   ap_invoice_distributions D
6074                  , po_distributions_ap_v PD
6075                  , ap_invoices I
6076            , ap_invoice_lines L --Bug6824860
6077           WHERE  D.po_distribution_id = PD.po_distribution_id
6078           AND    PD.line_location_id = p_line_location_id
6079           AND    D.invoice_id = I.invoice_id
6080           AND     L.invoice_id = I.invoice_id --Bug6824860
6081           AND    L.line_number = D.invoice_line_number --Bug6824860
6082           AND     L.match_type not in ('NOT MATCHED','NOT_MATCHED'); --Bug6824860
6083 
6084           p_ship_base_amt_var := AP_UTILITIES_PKG.Ap_Round_Currency( p_ship_base_amt_var -l_po_total,p_base_curr_code);
6085       /*Bug:14726598 Start*/
6086      ELSE    /* Bug: 14726598:Following code is added to fetch PO Base Amount for reciept matched invoices based on exchange rate of reciepts  for amount type po match */
6087            SELECT SUM((NVL(RT.amount, 0)) * DECODE(p_inv_curr_code, p_base_curr_code,1,RT.currency_conversion_rate))
6088            INTO   rcv_total
6089            FROM   rcv_transactions RT
6090            WHERE  RT.transaction_id=p_rcv_transaction_id;
6091 
6092             SELECT SUM(DECODE(p_inv_curr_code, p_base_curr_code, nvl(D.amount,0),nvl(D.base_amount,D.amount)))
6093             INTO   p_ship_base_amt_var
6094             FROM   ap_invoice_distributions D
6095                    , ap_invoices I
6096                    , ap_invoice_lines L
6097                    ,rcv_transactions  RT
6098             WHERE  D.rcv_transaction_id = RT.transaction_id
6099             AND    RT.transaction_id=p_rcv_transaction_id
6100             AND    D.invoice_id = I.invoice_id
6101             AND     L.invoice_id = I.invoice_id --Bug6824860
6102             AND    L.line_number = D.invoice_line_number --Bug6824860
6103             AND     L.match_type not in ('NOT MATCHED','NOT_MATCHED');
6104 
6105             p_ship_base_amt_var := AP_UTILITIES_PKG.Ap_Round_Currency(p_ship_base_amt_var - rcv_total,p_base_curr_code);
6106 
6107     END IF;
6108       /*Bug:14726598 End*/
6109 
6110   END IF;  -- Amount Based Matching If condition ends
6111 
6112   END IF;
6113 
6114 EXCEPTION
6115   WHEN OTHERS THEN
6116     IF (SQLCODE <> -20001) THEN
6117       FND_MESSAGE.SET_NAME('SQLAP','AP_DEBUG');
6118       FND_MESSAGE.SET_TOKEN('ERROR',SQLERRM);
6119       FND_MESSAGE.SET_TOKEN('CALLING_SEQUENCE', l_curr_calling_sequence);
6120       FND_MESSAGE.SET_TOKEN('PARAMETERS',
6121                   'Invoice_id  = '|| to_char(p_invoice_id)
6122               ||', Shipment_id = '|| to_char(p_line_location_id));
6123     END IF;
6124     APP_EXCEPTION.RAISE_EXCEPTION;
6125 END Calc_Ship_Total_Base_Amt_Var;
6126 
6127 /*============================================================================
6128  |  PROCEDURE  CALC_SHIP_TRX_BASE_AMT
6129  |
6130  |  DESCRIPTION:
6131  |                Procedure that given a shipment it calculates total base amt
6132  |                invoiced against the shipment by this particular invoice and
6133  |                its corrections in transaction currency.
6134  |
6135  |  PROGRAM FLOW
6136  |    It sums up the BASE amount billed via BASE MATCH of this invoice and all
6137  |    its QTY/PRICE CORRECTIONS to this invoice for a particular shipment;
6138  |    If there is an QTY/PRICE CORRECTION line exists in this invoice, we need
6139  |    to sum up the base amount billed via BASE MATCH and QTY/PRICE CORRECTIONS
6140  |    of all the invoices it was trying to correct for this shipment, plus the
6141  |    QTY/PRICE CORRECTION line of this invoce itself. Please note, there might
6142  |    bbe a case that this invoice has one correcting line which is trying to
6143  |    correct itself, with our query, it should be included.
6144  |
6145  |  NOTES:
6146  |         It should all be in the same currency. since we can not do
6147  |         cross-curr matching.
6148  |  MODIFICATION HISTORY
6149  |  Date         Author             Description of Change
6150  *==========================================================================*/
6151 
6152 PROCEDURE Calc_Ship_Trx_Base_Amt(
6153               p_invoice_id         IN            NUMBER,
6154               p_line_location_id   IN            NUMBER,
6155               p_rcv_transaction_id   IN            NUMBER,  /*Added for Bug 14726598 as additional fix*/
6156               p_match_option       IN            VARCHAR2,
6157               p_inv_curr_code      IN            VARCHAR2,
6158               p_base_curr_code     IN            VARCHAR2,
6159               p_ship_base_amt      IN OUT NOCOPY NUMBER,
6160               p_calling_sequence   IN            VARCHAR2) IS
6161 
6162   l_debug_loc                   VARCHAR2(30) := 'Calc_Ship_Trx_Base_Amt';
6163   l_debug_info                  VARCHAR2(2000);
6164   l_curr_calling_sequence       VARCHAR2(2000);
6165 
6166 BEGIN
6167 
6168   l_curr_calling_sequence := 'AP_APPROVAL_MATCHED_PKG.'||l_debug_loc||'<-'||
6169                              p_calling_sequence;
6170   ------------------------------------------------------------------
6171   l_debug_info := 'Calculate base Shipment amount  for the invoice';
6172   ------------------------------------------------------------------
6173 
6174   IF g_debug_mode = 'Y' THEN
6175     AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
6176   END IF;
6177 
6178 
6179    /*-----------------------------------------------------------------+
6180     |  The Meaning fo the following query conditions indicates:-      |
6181     |    Query condition 1 - all the base match lines of this         |
6182     |                        invoice itself with p_invoice_id         |
6183     |    Query condition 2 - all the qty/price correction lines of    |
6184     |                        this particular invoice itself           |
6185     |                        (p_invoice_id)                           |
6186     |    Query condition 3 - all the base match lines of a list of    |
6187     |                        invoices that invoice with p_invoice_id  |
6188     |                        is trying to do qty/price correction     |
6189     |    Query condition 4 - all the qty/price correction lines       |
6190     |                        trying to correct a list of invoices     |
6191     |                        that this invoice with p_invoice_id is   |
6192     |                        trying to do qty/price corrections       |
6193     +-----------------------------------------------------------------*/
6194 
6195   IF (p_match_option = 'P') THEN
6196 
6197     ----------------------------------------------------------
6198     l_debug_info := 'Calc_Ship_BASE_Trx_Amt - Match to PO';
6199     ----------------------------------------------------------
6200 
6201     IF (g_debug_mode = 'Y') THEN
6202       AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
6203     END IF;
6204 
6205     SELECT SUM( DECODE( p_inv_curr_code
6206                        ,p_base_curr_code
6207                        ,nvl(L.amount,0)
6208                        ,nvl(L.base_amount, (L.amount * AI.exchange_rate )) )
6209                )
6210       INTO p_ship_base_amt
6211       FROM ap_invoice_lines L,
6212            ap_invoices AI
6213      WHERE AI.invoice_id = L.invoice_id
6214       AND  L.po_line_location_id = p_line_location_id
6215       AND  (   (L.invoice_id = p_invoice_id and
6216                 L.match_type IN ('ITEM_TO_PO',           -- query condition 1
6217                                  'ITEM_TO_SERVICE_PO'))  -- Amount Based Matching
6218             or (L.corrected_inv_id = p_invoice_id )      -- query condition 2
6219             or (L.invoice_id IN
6220                            ( SELECT corrected_inv_id
6221                                FROM ap_invoice_lines L2
6222                               WHERE L2.po_line_location_id = p_line_location_id
6223                                 AND L2.invoice_id = p_invoice_id
6224                                 AND L2.corrected_inv_id is not null ) and
6225                 L.match_type IN ('ITEM_TO_PO',           -- query condition 3
6226                                  'ITEM_TO_SERVICE_PO'))  -- Amount Based Matching
6227             or (L.corrected_inv_id IN
6228                            ( SELECT corrected_inv_id
6229                                FROM ap_invoice_lines L3
6230                               WHERE L3.po_line_location_id = p_line_location_id
6231                                 AND L3.invoice_id = p_invoice_id
6232                                 AND L3.corrected_inv_id is not null ) ) );
6233                                                         -- query condition 4
6234 
6235   ELSIF (p_match_option = 'R') THEN
6236 
6237     ------------------------------------------------------------
6238     l_debug_info := 'Calc_Ship_Trx_BASE_Amt - Match to RECEIPT';
6239     ------------------------------------------------------------
6240 
6241     IF (g_debug_mode = 'Y') THEN
6242       AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
6243     END IF;
6244 
6245     SELECT SUM( DECODE( p_inv_curr_code
6246                        ,p_base_curr_code
6247                        ,nvl(L.amount,0)
6248                        ,nvl(L.base_amount, (L.amount * AI.exchange_rate )) )
6249                )
6250       INTO p_ship_base_amt
6251       FROM ap_invoice_lines L,
6252            ap_invoices AI
6253      WHERE AI.invoice_id = L.invoice_id
6254      AND  L.rcv_transaction_id = p_rcv_transaction_id   /*Added for Bug 14726598 as additional fix*/
6255       AND  (   (L.invoice_id = p_invoice_id and
6256                 L.match_type IN ('ITEM_TO_RECEIPT',      -- query condition 1
6257                                  'ITEM_TO_SERVICE_RECEIPT')) -- Amount Based Matching
6258             or (L.corrected_inv_id = p_invoice_id )      -- query condition 2
6259             or (L.invoice_id IN
6260                            ( SELECT corrected_inv_id
6261                                FROM ap_invoice_lines L2
6262                               WHERE L2.po_line_location_id = p_line_location_id
6263                                 AND L2.invoice_id = p_invoice_id
6264                                 AND L2.corrected_inv_id is not null ) and
6265                 L.match_type  IN ('ITEM_TO_RECEIPT',      -- query condition 3
6266                                  'ITEM_TO_SERVICE_RECEIPT')) -- Amount Based Matching
6267             or (L.corrected_inv_id IN
6268                            ( SELECT corrected_inv_id
6269                                FROM ap_invoice_lines L3
6270                               WHERE L3.po_line_location_id = p_line_location_id
6271                                 AND L3.invoice_id = p_invoice_id
6272                                 AND L3.corrected_inv_id is not null ) ) );
6273                                                          -- query condition 4
6274   END IF;
6275 
6276 EXCEPTION
6277   WHEN OTHERS THEN
6278     IF (SQLCODE <> -20001) THEN
6279       FND_MESSAGE.SET_NAME('SQLAP','AP_DEBUG');
6280       FND_MESSAGE.SET_TOKEN('ERROR',SQLERRM);
6281       FND_MESSAGE.SET_TOKEN('CALLING_SEQUENCE', l_curr_calling_sequence);
6282       FND_MESSAGE.SET_TOKEN('PARAMETERS',
6283                   'Invoice_id  = '|| to_char(p_invoice_id)
6284               ||', Shipment_id = '|| to_char(p_line_location_id));
6285     END IF;
6286     APP_EXCEPTION.RAISE_EXCEPTION;
6287 END Calc_Ship_Trx_Base_Amt;
6288 
6289 --Bug 5077550
6290 
6291 FUNCTION Check_Milestone_Price_Qty(
6292               p_invoice_id         IN            NUMBER,
6293               p_line_location_id   IN            NUMBER,
6294               p_po_unit_price      IN            NUMBER,
6295               p_calling_sequence   IN            VARCHAR2) RETURN VARCHAR2 IS
6296 
6297   l_debug_loc              VARCHAR2(30) := 'Calc_Milestone_Price_Qty';
6298   l_curr_calling_sequence  VARCHAR2(2000);
6299   l_check                  VARCHAR2(100);
6300 
6301 BEGIN
6302 
6303   l_curr_calling_sequence := 'AP_APPROVAL_MATCHED_PKG.'||l_debug_loc||'<-'||
6304                               p_calling_sequence;
6305 
6306   BEGIN
6307     -- bug8704810
6308     -- SELECT 'Price Difference or Quantity Has Decimals'    ..  bug8704810
6309     SELECT 'Price Difference'                                --  bug8704810
6310     INTO   l_check
6311     FROM   ap_invoice_lines_all
6312     WHERE  invoice_id = p_invoice_id
6313     AND    po_line_location_id = p_line_location_id
6314     AND    unit_price <> p_po_unit_price;
6315 
6316   EXCEPTION
6317     WHEN NO_DATA_FOUND THEN
6318       l_check := 'No Price or Quantity Issues';
6319     WHEN TOO_MANY_ROWS THEN
6320       -- l_check := 'Price Difference or Quantity Has Decimals';    ..  bug8704810
6321       l_check := 'Price Difference';                                --  bug8704810
6322     WHEN OTHERS THEN
6323       IF (SQLCODE <> -20001) THEN
6324         FND_MESSAGE.SET_NAME('SQLAP','AP_DEBUG');
6325         FND_MESSAGE.SET_TOKEN('ERROR',SQLERRM);
6326         FND_MESSAGE.SET_TOKEN('CALLING_SEQUENCE', l_curr_calling_sequence);
6327         FND_MESSAGE.SET_TOKEN('PARAMETERS',
6328                     'Invoice_id  = '|| to_char(p_invoice_id));
6329       END IF;
6330       APP_EXCEPTION.RAISE_EXCEPTION;
6331   END;
6332 
6333   return (l_check);
6334 
6335 EXCEPTION
6336   WHEN OTHERS THEN
6337     IF (SQLCODE <> -20001) THEN
6338       FND_MESSAGE.SET_NAME('SQLAP','AP_DEBUG');
6339       FND_MESSAGE.SET_TOKEN('ERROR',SQLERRM);
6340       FND_MESSAGE.SET_TOKEN('CALLING_SEQUENCE', l_curr_calling_sequence);
6341       FND_MESSAGE.SET_TOKEN('PARAMETERS',
6342                   'Invoice_id  = '|| to_char(p_invoice_id));
6343     END IF;
6344     APP_EXCEPTION.RAISE_EXCEPTION;
6345 END Check_Milestone_Price_Qty;
6346 
6347 -- 7299826 EnC Project
6348 PROCEDURE exec_pay_when_paid_check(p_invoice_id        IN NUMBER,
6349                                     p_system_user      IN NUMBER,
6350                                     p_holds            IN OUT NOCOPY AP_APPROVAL_PKG.holdsarray,
6351                                     p_holds_count      IN OUT NOCOPY AP_APPROVAL_PKG.countarray,
6352                                     p_release_count    IN OUT NOCOPY AP_APPROVAL_PKG.countarray,
6353                                     p_calling_sequence IN VARCHAR2) IS
6354 
6355   l_debug_loc               VARCHAR2(30) := 'exec_pay_when_paid_check';
6356   l_curr_calling_sequence   VARCHAR2(2000);
6357   l_debug_info              VARCHAR2(100);
6358   l_api_version             NUMBER := 1.0;
6359   l_hold_required           VARCHAR2(1) := 'N';
6360   l_return_status           VARCHAR2(1);
6361   l_msg_count               NUMBER;
6362   l_msg_data                varchar2(2000);
6363 
6364 BEGIN
6365 
6366   l_curr_calling_sequence := 'AP_APPROVAL_MATCHED_PKG.'||l_debug_loc||'<-'||
6367                               p_calling_sequence;
6368 
6369   Print_Debug(l_debug_loc,  'exec_pay_when_paid_check - begin for invoice_id : '|| p_invoice_id);
6370 
6371   FOR i IN (SELECT DISTINCT po_header_id
6372               FROM ap_invoice_lines
6373              WHERE invoice_id = p_invoice_id
6374                AND po_header_id is NOT NULL)
6375   LOOP
6376 
6377    Print_Debug(l_debug_loc,  'pay when paid check for po_heade_id : '||i.po_header_id );
6378    po_invoice_hold_check.pay_when_paid(p_api_version   => l_api_version,
6379                                        p_po_header_id  => i.po_header_id,
6380                                        p_invoice_id    => p_invoice_id,
6381                                        x_return_status => l_return_status,
6382                                        x_msg_count     => l_msg_count,
6383                                        x_msg_data      => l_msg_data,
6384                                        x_pay_when_paid => l_hold_required);
6385 
6386    IF l_return_status <> FND_API.G_RET_STS_SUCCESS  THEN
6387       Print_Debug(l_debug_loc, 'error occured while pay when paid check for po_heade_id : '||i.po_header_id );
6388       APP_EXCEPTION.raise_exception;
6389    END IF;
6390 
6391    EXIT WHEN l_hold_required = 'Y';
6392 
6393   END LOOP;
6394 
6395   Print_Debug(l_debug_loc,  'pay when paid hold required for invoice id : '||p_invoice_id||' - '||l_hold_required );
6396 
6397   AP_APPROVAL_PKG.process_inv_hold_status(p_invoice_id,
6398                                           NULL,
6399                                           NULL,
6400                                           'Pay When Paid',
6401                                           l_hold_required,
6402                                           NULL,
6403                                           p_system_user,
6404                                           p_holds,
6405                                           p_holds_count,
6406                                           p_release_count,
6407                                           p_calling_sequence);
6408 
6409    Print_Debug(l_debug_loc,  'exec_pay_when_paid_check - end for invoice_id : '|| p_invoice_id);
6410 
6411 EXCEPTION
6412   WHEN OTHERS THEN
6413     IF (SQLCODE <> -20001) THEN
6414       FND_MESSAGE.set_name('SQLAP','AP_DEBUG');
6415       FND_MESSAGE.set_token('ERROR',SQLERRM);
6416       FND_MESSAGE.set_token('CALLING_SEQUENCE', l_curr_calling_sequence);
6417       FND_MESSAGE.set_token('PARAMETERS', 'Invoice_id  = '|| to_char(p_invoice_id) );
6418       FND_MESSAGE.set_token('DEBUG_INFO',l_debug_info);
6419     END IF;
6420 
6421     APP_EXCEPTION.raise_exception;
6422 
6423 END exec_pay_when_paid_check;
6424 
6425 -- 7299826 EnC Project
6426 PROCEDURE exec_po_deliverable_check(p_invoice_id       IN NUMBER,
6427                                     p_system_user      IN NUMBER,
6428                                     p_holds            IN OUT NOCOPY AP_APPROVAL_PKG.holdsarray,
6429                                     p_holds_count      IN OUT NOCOPY AP_APPROVAL_PKG.countarray,
6430                                     p_release_count    IN OUT NOCOPY AP_APPROVAL_PKG.countarray,
6431                                     p_calling_sequence IN VARCHAR2
6432                                     ) IS
6433 
6434   l_debug_loc               VARCHAR2(30) := 'exec_po_deliverable_check';
6435   l_curr_calling_sequence   VARCHAR2(2000);
6436   l_debug_info              VARCHAR2(100);
6437   l_api_version             NUMBER := 1.0;
6438   l_hold_required           VARCHAR2(1) := 'N';
6439   l_return_status           VARCHAR2(1);
6440   l_msg_count               NUMBER;
6441   l_msg_data                varchar2(2000);
6442 
6443 BEGIN
6444 
6445   l_curr_calling_sequence := 'AP_APPROVAL_MATCHED_PKG.'||l_debug_loc||'<-'||
6446                               p_calling_sequence;
6447 
6448   Print_Debug(l_debug_loc,'exec_po_deliverable_check - begin for invoice_id : '|| p_invoice_id);
6449 
6450   FOR i IN (SELECT DISTINCT po_header_id
6451               FROM ap_invoice_lines
6452              WHERE invoice_id = p_invoice_id
6453                AND po_header_id is NOT NULL)
6454   LOOP
6455 
6456     Print_Debug(l_debug_loc,  'po deliverable check for po_heade_id : '||i.po_header_id );
6457     po_invoice_hold_check.deliverable_overdue_check(p_api_version   => l_api_version,
6458                                                    p_po_header_id  => i.po_header_id,
6459                                                    p_invoice_id    => p_invoice_id,
6460                                                    x_return_status => l_return_status,
6461                                                    x_msg_count     => l_msg_count,
6462                                                    x_msg_data      => l_msg_data,
6463                                                    x_hold_required => l_hold_required);
6464 
6465     IF l_return_status <> FND_API.G_RET_STS_SUCCESS  THEN
6466       Print_Debug(l_debug_loc, 'error occured while po deliverable check for po_heade_id : '||i.po_header_id );
6467       APP_EXCEPTION.raise_exception;
6468     END IF;
6469 
6470     EXIT WHEN l_hold_required = 'Y';
6471 
6472   END LOOP;
6473 
6474   Print_Debug(l_debug_loc, 'po deliverable hold required for invoice id : '||p_invoice_id||' - '||l_hold_required );
6475 
6476   AP_APPROVAL_PKG.process_inv_hold_status(p_invoice_id,
6477                                           NULL,
6478                                           NULL,
6479                                           'PO Deliverable',
6480                                           l_hold_required,
6481                                           NULL,
6482                                           p_system_user,
6483                                           p_holds,
6484                                           p_holds_count,
6485                                           p_release_count,
6486                                           p_calling_sequence);
6487 
6488   AP_Debug_Pkg.Print(g_debug_mode, 'exec_po_deliverable_check - end for invoice_id : '|| p_invoice_id);
6489 
6490 EXCEPTION
6491   WHEN OTHERS THEN
6492     IF (SQLCODE <> -20001) THEN
6493       FND_MESSAGE.set_name('SQLAP','AP_DEBUG');
6494       FND_MESSAGE.set_token('ERROR',SQLERRM);
6495       FND_MESSAGE.set_token('CALLING_SEQUENCE', l_curr_calling_sequence);
6496       FND_MESSAGE.set_token('PARAMETERS', 'Invoice_id  = '|| to_char(p_invoice_id) );
6497       FND_MESSAGE.set_token('DEBUG_INFO',l_debug_info);
6498     END IF;
6499 
6500     APP_EXCEPTION.raise_exception;
6501 
6502 END exec_po_deliverable_check;
6503 
6504 -- 7299826 EnC Project
6505 Procedure Print_Debug(
6506 		p_api_name		  IN VARCHAR2,
6507 		p_debug_info		IN VARCHAR2) IS
6508 BEGIN
6509 
6510   IF AP_APPROVAL_PKG.g_debug_mode = 'Y' THEN
6511     AP_Debug_Pkg.Print('Y', p_debug_info );
6512   END IF;
6513 
6514   IF (FND_LOG.LEVEL_STATEMENT >= FND_LOG.G_CURRENT_RUNTIME_LEVEL) THEN
6515     FND_LOG.STRING(FND_LOG.LEVEL_STATEMENT, 'AP.PLSQL.AP_APPROVAL_MATCHED_PKG'||p_api_name,p_debug_info);
6516   END IF;
6517 
6518 END Print_Debug;
6519 
6520 
6521 --for CLM project - bug 9494400
6522 
6523 PROCEDURE exec_partial_funds_check (p_invoice_id       IN NUMBER,
6524                                     p_system_user      IN NUMBER,
6525                                     p_holds            IN OUT NOCOPY
6526 AP_APPROVAL_PKG.holdsarray,
6527                                     p_holds_count      IN OUT NOCOPY
6528 AP_APPROVAL_PKG.countarray,
6529                                     p_release_count    IN OUT NOCOPY
6530 AP_APPROVAL_PKG.countarray,
6531                                     p_calling_sequence IN VARCHAR2)
6532 IS
6533 
6534   --BUG# 9868268
6535   CURSOR Matched_Shpmnts_Cur IS
6536   select distinct po_line_location_id
6537   from   ap_invoice_lines
6538   where invoice_id = p_invoice_id
6539    and po_line_location_id is not null --Bug16406697
6540    and line_type_lookup_code not in ('TAX','PREPAY');
6541 
6542   l_line_location_id    PO_LINE_LOCATIONS_ALL.LINE_LOCATION_ID%TYPE;
6543 
6544   --End9868268
6545 
6546   l_debug_loc              VARCHAR2(30):='exec_partial_funds_check';
6547   l_curr_calling_sequence  VARCHAR2(2000);
6548   l_debug_info             VARCHAR2(1000);
6549   l_api_version            NUMBER := 1.0;
6550   l_hold_required          VARCHAR2(1) := 'N';
6551   l_return_status          VARCHAR2(1);
6552   l_msg_count              NUMBER;
6553   l_msg_data               varchar2(2000);
6554 
6555 l_distribution_type        PO_DISTRIBUTIONS_ALL.destination_type_code%TYPE ;
6556 l_accrue_on_receipt_flag   PO_DISTRIBUTIONS_ALL.accrue_on_receipt_flag%TYPE ;
6557 l_code_combination_id      PO_DISTRIBUTIONS_ALL.code_combination_id%TYPE ;
6558 l_budget_account_id        PO_DISTRIBUTIONS_ALL.budget_account_id%TYPE ;
6559 l_partial_funded_flag      PO_DISTRIBUTIONS_ALL.partial_funded_flag%TYPE ;
6560 l_funded_value             PO_DISTRIBUTIONS_ALL.funded_value%TYPE ;
6561 l_quantity_funded          PO_DISTRIBUTIONS_ALL.quantity_funded%TYPE ;
6562 l_amount_funded            PO_DISTRIBUTIONS_ALL.amount_funded%TYPE ;
6563 l_quantity_delivered       PO_DISTRIBUTIONS_ALL.quantity_delivered%TYPE ;
6564 l_amount_delivered         PO_DISTRIBUTIONS_ALL.amount_delivered%TYPE ;
6565 l_quantity_billed          PO_DISTRIBUTIONS_ALL.quantity_billed%TYPE ;
6566 l_amount_billed            PO_DISTRIBUTIONS_ALL.amount_billed%TYPE ;
6567 l_matching_basis           PO_LINE_LOCATIONS.matching_basis%TYPE;
6568 l_quantity_received        PO_LINE_LOCATIONS.quantity_received%TYPE;
6569 l_amount_received          PO_LINE_LOCATIONS.amount_received%TYPE;
6570 l_hold_name                VARCHAR2(30);
6571 l_unit_meas_lookup_code    PO_LINE_LOCATIONS_ALL.unit_meas_lookup_code%TYPE;
6572 l_quantity_cancelled       PO_DISTRIBUTIONS_ALL.quantity_cancelled%TYPE ;
6573 l_amount_cancelled         PO_DISTRIBUTIONS_ALL.amount_cancelled%TYPE ;
6574 l_po_header_id             ap_invoice_lines_all.po_header_id%TYPE;
6575 
6576 
6577 BEGIN
6578 
6579   l_curr_calling_sequence := 'AP_APPROVAL_MATCHED_PKG.'||
6580    l_debug_loc||'<-'||p_calling_sequence;
6581    Print_Debug(l_debug_loc,  'exec_partial_funds_check - begin for invoice_id :
6582     '|| p_invoice_id);
6583 
6584     IF (AP_CLM_PVT_PKG.is_clm_installed = 'Y' )then
6585     --PO Matched, Non Tax distributions of the Invoice
6586 
6587   --start bug#9868268
6588    OPEN Matched_Shpmnts_Cur;
6589    LOOP
6590 
6591     ---------------------------------------
6592     l_debug_info := 'Fetch Matched_Cur';
6593     ---------------------------------------
6594     IF (g_debug_mode = 'Y') THEN
6595       AP_Debug_Pkg.Print(g_debug_mode, l_debug_info );
6596     END IF;
6597 
6598     FETCH Matched_Shpmnts_Cur
6599     INTO l_line_location_id;
6600 
6601     EXIT WHEN Matched_Shpmnts_Cur%NOTFOUND;
6602 
6603 
6604      l_hold_required := 'N';
6605 
6606      For rec_part_funds_check in (select distinct aid.po_distribution_id
6607                                   from ap_invoice_distributions aid,
6608 				       ap_invoice_lines ail
6609                                   where  ail.po_line_location_id =l_line_location_id
6610 				    and  ail.invoice_id = P_INVOICE_ID
6611                                     and ail.invoice_id = aid.invoice_id
6612 				    and ail.line_number = aid.invoice_line_number
6613                                     and aid.po_distribution_id is not null --Bug16406697
6614 			            and aid.line_type_lookup_code not in ('REC_TAX',
6615                                               'NONREC_TAX','TERV','TIPV','TRV','PREPAY'))
6616      LOOP
6617 
6618      IF(l_hold_required = 'N')THEN
6619 
6620        --End bug#9868268
6621 
6622      Print_Debug(l_debug_loc,  'exec_partial_funds_check - po_distribution_id: '||
6623                  rec_part_funds_check.po_distribution_id);
6624 
6625     --Call the Partial Funding Information API
6626         AP_CLM_PVT_PKG.Get_Funding_Info(
6627          P_PO_DISTRIBUTION_ID     =>  rec_part_funds_check.po_distribution_id
6628         ,X_DISTRIBUTION_TYPE      =>  l_distribution_type
6629         ,X_MATCHING_BASIS         =>  l_matching_basis
6630         ,X_ACCRUE_ON_RECEIPT_FLAG =>  l_accrue_on_receipt_flag
6631         ,X_CODE_COMBINATION_ID    =>  l_code_combination_id
6632         ,X_BUDGET_ACCOUNT_ID      =>  l_budget_account_id
6633         ,X_PARTIAL_FUNDED_FLAG    =>  l_partial_funded_flag
6634         ,x_UNIT_MEAS_LOOKUP_CODE  =>  l_unit_meas_lookup_code
6635         ,X_FUNDED_VALUE           =>  l_funded_value
6636         ,X_QUANTITY_FUNDED        =>  l_quantity_funded
6637         ,X_AMOUNT_FUNDED          =>  l_amount_funded
6638         ,X_QUANTITY_RECEIVED      =>  l_quantity_received
6639         ,X_AMOUNT_RECEIVED        =>  l_amount_received
6640         ,X_QUANTITY_DELIVERED     =>  l_quantity_delivered
6641         ,X_AMOUNT_DELIVERED       =>  l_amount_delivered
6642         ,X_QUANTITY_BILLED        =>  l_quantity_billed
6643         ,X_AMOUNT_BILLED          =>  l_amount_billed
6644         ,x_QUANTITY_CANCELLED     =>  l_quantity_cancelled
6645         ,X_AMOUNT_CANCELLED       =>  l_amount_cancelled
6646         ,X_RETURN_STATUS          =>  l_return_status    );
6647 
6648 
6649     IF L_return_status <> FND_API.G_RET_STS_SUCCESS THEN
6650         l_debug_info := 'Partial funds check failed:
6651 	AP_INTG_DOCUMENT_FUNDS_GRP.Get_Funding_Info returned invalid status.';
6652         Print_Debug(l_debug_loc,  l_debug_info);
6653         --start bug#9868268
6654 	 IF (Matched_Shpmnts_Cur%ISOPEN ) THEN
6655              CLOSE Matched_Shpmnts_Cur;
6656          END IF;
6657 	 --end bug#9868268
6658         APP_EXCEPTION.raise_exception;
6659     END IF    ;
6660 
6661 
6662     IF l_partial_funded_flag = 'Y' THEN
6663 
6664         IF l_matching_basis = 'QUANTITY' THEN
6665            l_hold_name :='Quantity Funded';
6666            IF l_quantity_billed > l_quantity_funded THEN
6667                 l_hold_required := 'Y'   ;
6668            END IF;
6669         ELSIF l_matching_basis = 'AMOUNT' THEN
6670               l_hold_name :='Amount Funded';
6671               IF l_amount_billed > l_amount_funded THEN
6672                 l_hold_required := 'Y';
6673               END IF;
6674         END IF;
6675 
6676     END IF;
6677 
6678       IF l_hold_required = 'Y' THEN
6679           Print_Debug(l_debug_loc,  'exec_partial_funds_check - Hold
6680 	      Name'||l_hold_name|| 'required for invoice_id : '|| p_invoice_id);
6681       END IF;
6682 
6683    END IF;
6684    END LOOP;
6685 
6686   --Start bug#9868268
6687    --Introduced below call here
6688      AP_APPROVAL_PKG.process_inv_hold_status(  p_invoice_id,
6689                                               l_line_location_id, --Bug#9868268 NULL,
6690                                               NULL,
6691                                               l_hold_name,
6692                                               l_hold_required,
6693                                               NULL,
6694                                               p_system_user,
6695                                               p_holds,
6696                                               p_holds_count,
6697                                               p_release_count,
6698                                               p_calling_sequence);
6699 
6700 
6701     END LOOP;
6702     Close Matched_Shpmnts_Cur;
6703   END IF;
6704 
6705   --End bug#9868268
6706 
6707   --Commented below call here and introduced above for bug#9868268
6708   /*  AP_APPROVAL_PKG.process_inv_hold_status(p_invoice_id,
6709                                               NULL,
6710                                               NULL,
6711                                               l_hold_name,
6712                                               l_hold_required,
6713                                               NULL,
6714                                               p_system_user,
6715                                               p_holds,
6716                                               p_holds_count,
6717                                               p_release_count,
6718                                               p_calling_sequence); */
6719 
6720 EXCEPTION
6721   WHEN OTHERS THEN
6722         l_debug_info := 'Partial funds check failed';
6723         Print_Debug(l_debug_loc,  l_debug_info);
6724 	 --start bug#9868268
6725          IF (Matched_Shpmnts_Cur%ISOPEN ) THEN
6726              CLOSE Matched_Shpmnts_Cur;
6727          END IF;
6728 	 --End bug#9868268
6729          APP_EXCEPTION.raise_exception;
6730 END exec_partial_funds_check;
6731 --end for CLM project - bug 9494400
6732 
6733 
6734 END AP_APPROVAL_MATCHED_PKG;