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