DBA Data[Home] [Help]

PACKAGE BODY: APPS.PA_CMT_UTILS

Source


1 PACKAGE BODY PA_CMT_UTILS AS
2 /* $Header: PAXCMTUB.pls 120.23.12020000.2 2012/07/19 10:03:31 admarath ship $ */
3 g_accrue_on_receipt_flag varchar2(1);  /*bug 5946201*/
4 /* Function : get_rcpt_qty
5    Return   : Returns the commitment quantity not yet interfaced to PA
6    IN parameters: PO Distribution Id,
7                   PO Distribution's Qty Ordered,
8                   PO Distribution's Qty Canceled,
9                   PO Distribution's Qty Billed and
10                   Calling module :  PO or AP
11    Logic:
12          If called from the PO view, the function first retrieves the total
13          receipt quantity already interfaced to PA.  If the receipt qty is 0 then the
14          total PO commitment quantity is equal to (qty ordered - qty canceled - qty billed).
15          If receipt quantity is greater than 0 then the greatest of receipt quantity and qty billed
16          will be subtracted from the total PO quantity (qty ordered - qty canceled)
17          If called from the AP view, the total quantity invoiced (pa_quantity)  and number of invoice
18          distributions created for a specific PO distribution is selected. If the receipt quantity is
19          0 then quantity invoiced equals the total invoice quantity divided by the number of invoices.
20          If receipt quantity greater than 0 then the greatest of receipt quantity and total invoice
21          quantity is distributed to the number of invoices.
22 */
23 
24 FUNCTION get_rcpt_qty(p_po_dist in number,
25                       p_qty_ordered in number,
26                       p_qty_cancel in number,
27                       p_qty_billed in number,
31                       p_project_id in number,
28                       p_module in varchar2,
29                       --Pa.M Added below parameters
30                       p_po_line_id in number,
32                       p_task_id in number,
33                       p_ccid in number,
34                       -- Bug 3556021 : Added for retroactive price adjustment
35                       p_pa_quantity IN NUMBER,
36                       p_inv_source  IN VARCHAR2,
37                       p_line_type_lookup_code IN VARCHAR2 ,
38                       p_matching_basis in VARCHAR2 default null, -- Bug 3642604
39                       p_nrtax_amt in number default null, -- Bug 3642604
40 				  P_CASH_BASIS_ACCTG in varchar2 default 'N',
41                       p_accrue_on_receipt_flag  IN varchar2 default NULL /* Bug 5014034 */
42                       ) RETURN NUMBER
43 IS
44     l_rcpt_qty number;
45     l_inv_num  number;
46     l_tot_inv_qty  number;
47 	l_inv_num2  number;		 -- Bug 13602288:self assessed tax enhancement
48     l_tot_inv_qty2  number;	 -- Bug 13602288:self assessed tax enhancement
49 
50     --Pa.M
51     L_RateBasedPO  Varchar2(1);
52     L_CWKTCXface   Varchar2(1);
53     L_EiCost       Number;
54     l_PoLineCosts       Number;
55     l_RcptNrTaxCosts    Number;
56     l_PoLineDistCnt     Number;
57     l_PoLineDistCosts   Number;
58     l_calc_ap_tax       Number ;
59     l_qty_billed        NUMBER ;
60 	l_qty_billed2        NUMBER ; -- Bug 13602288:self assessed tax enhancement
61 
62     l_FoundFlag    Varchar2(1) := 'N';
63     l_Index        Number;
64 
65 BEGIN
66 
67  -- R12 change for cash basis accounting.
68 
69     --dbms_output.put_line('qty_ordered = ' || p_qty_ordered);
70     --dbms_output.put_line('qty_cancel = ' || p_qty_cancel);
71     --dbms_output.put_line('qty_billed = ' || p_qty_billed);
72 
73     --  Bug 3556021 : When fired for AP Invoice this function will return
74     --  zero for TAX and PO price adjustment lines.
75     l_qty_billed  := p_qty_billed ;
76 
77     IF ( p_module = 'AP' AND (NVL(p_inv_source,'X') ='PPA' OR p_line_type_lookup_code = 'TAX')) THEN
78        return 0;
79     END IF;
80 
81     IF p_accrue_on_receipt_flag = 'Y' and l_qty_billed <> 0 THEN
82 
83        -- Bug    : 5014034
84        -- Isssue : R12 functionality would interface receipts for accrue on receipt PO and
85        --          variance would interface from supplier invoice which was matched to a
86        --          accrue on receipt PO.
87        --
88        --          Supplier cost interface process marks the invoice distribution with pa_addition_flag value 'G'
89        --          to indicate receipt would interface for such distributions.
90        --          PSI do not shows invoice distributions that has pa_addition_flag value 'G'
91        -- Resolution
92        --          Fix under this bug is making sure that PO commitments are not reduced in PSI corresponding to
93        --          qty billed amount updated as part of PO match in Supplier invoice.
94        --          Quantity billed is not considered for accrue on receipt PO because invoice distributions are not
95        --          elligible for interface.
96        --          We are only considering qty billed for historical transactions that has pa addition flag value 'Y'.
97        --
98 
99        select sum(apd.quantity_invoiced)
100          into l_qty_billed
101          from po_distributions_all pod,
102               ap_invoice_distributions_all apd
103         where pod.po_distribution_id              = p_po_dist
104           and pod.po_distribution_id              = apd.po_distribution_id
105           and NVL(pod.accrue_on_receipt_flag,'N') = 'Y'
106           and apd.pa_addition_flag                = 'Y'
107           and apd.line_type_lookup_code           in ( 'ACCRUAL', 'ITEM', 'PREPAY', 'NONREC_TAX' )
108           and nvl(apd.quantity_invoiced,0)        <> 0 ;
109 
110        -- Bug 13602288: Added below select query as a part of self assessed tax enhancement
111        select sum(sat.quantity_invoiced)
112          into l_qty_billed2
113          from po_distributions_all pod,
114               ap_self_assessed_tax_dist_all sat
115         where pod.po_distribution_id              = p_po_dist
116           and pod.po_distribution_id              = sat.po_distribution_id
117           and NVL(pod.accrue_on_receipt_flag,'N') = 'Y'
118           and sat.pa_addition_flag                = 'Y'
119           and sat.line_type_lookup_code           in ( 'NONREC_TAX' )
120           and nvl(sat.quantity_invoiced,0)        <> 0 ;
121 
122        l_qty_billed := NVL(l_qty_billed,0) + NVL(l_qty_billed2,0) ; -- Bug 13602288:self assessed tax enhancement
123 
124     END IF ;
125 
126     --PA.M
127     L_RateBasedPO :=  Pa_Pjc_Cwk_Utils.Is_Rate_Based_Line(p_po_line_id, null);
128     L_CWKTCXface :=  Pa_Pjc_Cwk_Utils.Is_Cwk_TC_Xface_Allowed(P_Project_Id);
129 
130     If L_RateBasedPO = 'Y' and L_CWKTCXface = 'Y' Then ---{
131 
132        l_FoundFlag := 'N';
133 
134        IF G_CommCostTab.count > 0 THEN
135 
136           FOR j in G_CommCostTab.first..G_CommCostTab.LAST LOOP
137 
138               IF G_CommCostTab(j).project_id = p_project_id and
139                  G_CommCostTab(j).task_id = p_task_id and
140                  G_CommCostTab(j).po_line_id = p_po_line_id THEN
141 
142                  l_FoundFlag := 'Y';
143 
144                  l_PoLineCosts := nvl(G_CommCostTab(j).commcosts,0);
145 
146              END IF;
147 
148           END LOOP;
149 
150        END IF;
151 
152   /* If cash basis accounting is implemented then receipts are not interfaced to PA */
153      IF P_CASH_BASIS_ACCTG = 'N' THEN --R12 change ------{
157         where a.po_distribution_id = p_po_dist
154        Select nvl(Sum(nvl(ENTERED_NR_TAX,0)),0)
155          Into l_RcptNrTaxCosts
156          from rcv_transactions a,   rcv_receiving_sub_ledger c
158          and ((a.destination_type_code = 'EXPENSE' ) or
159              (a.destination_type_code = 'RECEIVING' and
160               a.transaction_type in ('RETURN TO RECEIVING' , 'RETURN TO VENDOR')))
161          and c.pa_addition_flag = 'Y'
162          and c.rcv_transaction_id = a.transaction_id
163          and c.code_combination_id = p_ccid
164          and c.actual_flag = 'A';
165       END IF;
166 
167        -- If NRTAX has been interfaced as receipts then we will not deduct the AP nrtax else it will be deducted twice
168        -- Calculate the AP tax only if Receipt tax is zero
169        If l_RcptNrTaxCosts = 0 Then
170           l_calc_ap_tax := 1;
171        Else
172           l_calc_ap_tax := 0;
173        End If;
174 
175        If l_FoundFlag = 'N' Then
176 
177           --Commitment Costs = ((Sum of PO Dist Costs for Proj/Task and Po Line) -
178           --                      (Sum of distributed EI Costs) -
179           --                      (Sum of NRTax interfaced to PA as receipts or supplier costs))
180 
181           --Get sum of all EI Costs for the Project, Task and Po Line Id
182  /*         select sum(nvl(denom_raw_cost,0))
183             into l_EiCost
184             from pa_expenditure_items_all ei
185            where ei.project_id = p_project_id
186              and ei.task_id = p_task_id
187              and ei.po_line_id = p_po_line_id
188              and cost_distributed_flag = 'Y';
189 */
190 
191             -- Bug 4093917 : Modified the EI query to retrieve cost from CDL so incase the EI is marked for recosting, po cmt is not again considered
192             -- Bug 6979249: since we are summing all EI Costs based on project,Task and Po Line Id hence PO Projects PSI Commitment are not getting relieved .
193 	    -- so commented the project and task conditions  to releive Po project PSI commitment.
194             Select sum(nvl(cdl.denom_raw_cost,0))
195             into   l_EiCost
196             from   pa_cost_distribution_lines_all cdl
197                  , pa_expenditure_items_all ei
198             where  cdl.expenditure_item_id = ei.expenditure_item_id
199            /* and    ei.project_id = p_project_id
200             and    ei.task_id = p_task_id commented for bug:6979249*/
201             and    ei.po_line_id = p_po_line_id;
202 
203 
204           -- Bug 3529107 : Modified the below code such that PSI shows rate based PO's amount
205           -- without subtracting the billed amount which is not eligible for interface to PA.
206           -- i.e.Amount on PO = (Amount ordered)-(Amount canceled) - (Interfaced distributed
207           -- Expenditure Costs) - (NRTAX interfaced to PA as supplier cost or receipts)
208 
209           Select count(*), Sum(nvl(Amount_Ordered,0) + nvl(NonRecoverable_Tax,0) - nvl(Amount_Cancelled,0) -
210                                ((nvl(NonRecoverable_Tax,0) * nvl(amount_billed,0) / nvl(amount_ordered,1)) * l_calc_ap_tax)
211                               )
212             Into l_PoLineDistCnt, l_PoLineDistCosts
213             From Po_Distributions_All Pod
214            Where Pod.Project_Id = P_Project_Id
215              And Pod.distribution_type <> 'PREPAYMENT'
216              And Pod.Task_Id = P_Task_Id
217              And Pod.Po_Line_Id = P_Po_Line_Id;
218 
219           l_PoLineCosts := nvl(((nvl(l_PoLineDistCosts,0)/nvl(l_PoLineDistCnt,1)) - (nvl(l_EiCost,0)/nvl(l_PoLineDistCnt,1))),0);
220 
221           l_index := G_CommCostTab.Count + 1;
222 
223           G_CommCostTab(l_index).project_id := p_project_id;
224           G_CommCostTab(l_index).task_id := p_task_id;
225           G_CommCostTab(l_index).po_line_id := p_po_line_id;
226           G_CommCostTab(l_index).commcosts := l_PoLineCosts;
227 
228        End If;
229 
230 
231        -- Deduct the Receipt tax only if tax has been interfaced as receipt
232        If l_calc_ap_tax = 0 Then
233          L_Rcpt_Qty := Greatest(0, (l_PoLineCosts - nvl(l_RcptNrTaxCosts,0) ));
234        Else
235          L_Rcpt_Qty := Greatest(0, l_PoLineCosts);
236        End if;
237 
238     Else
239 
240 
241   /* If cash basis accounting is implemented then receipts are not interfaced to PA */
242      IF P_CASH_BASIS_ACCTG = 'N' THEN --R12 change ------{
243 
244 /*Added for bug#6408874 - START */
245 
246         IF ( (nvl(g_po_distr_id,-999) = nvl(p_po_dist,-999)) AND
247               (nvl(g_qty_ordered,-999) = nvl(p_qty_ordered,-999)) AND
248               (nvl(g_qty_cancel,-999) = nvl(p_qty_cancel,-999)) AND
249               (nvl(g_qty_billed,-999) = nvl(l_qty_billed,-999)) AND -- Changed to l_quantity_billed
250               (nvl(g_module,'XSDD') = nvl(p_module,'XSDD')) AND
251               (nvl(g_pa_quantity,-999) = nvl(p_pa_quantity,-999)) AND
252               (nvl(g_inv_source,'XSDD') = nvl(p_inv_source,'XSDD')) AND
253               (nvl(g_line_type_lookup_code,'XSDD') = nvl(p_line_type_lookup_code,'XSDD'))
254             ) THEN
255          return g_rcpt_qty;
256          END IF;
257 
258 /*Added for bug#6408874 - END */
259 
260    IF nvl(p_matching_basis,'QUANTITY') = 'AMOUNT' THEN /* modified for bug bug 3496492 */
261 
262 /* This is an amount based PO and so quantity will be the same as the amount */
263 
264 /* Added index hint as part of bug 6408874 */
265      select /*+ Index(c RCV_RECEIVING_SUB_LEDGER_N1) */sum(decode(a.destination_type_code,
266                               'EXPENSE',
267                               decode(transaction_type,
268                                      'RETURN TO RECEIVING',
269                                       -1 * (decode(c.pa_addition_flag,
270                                                    'Y',
271                                                    (nvl(c.entered_dr,0)-nvl(c.entered_cr,0)),
272                                                    'I',
273                                                    (nvl(c.entered_dr,0)-nvl(c.entered_cr,0)-nvl(c.entered_nr_tax,0)))),
274                                            (decode(c.pa_addition_flag,
275                                                    'Y',
276                                                    (nvl(c.entered_dr,0)-nvl(c.entered_cr,0)),
277                                                    'I',
278                                                    (nvl(c.entered_dr,0)-nvl(c.entered_cr,0)-nvl(c.entered_nr_tax,0))))),
279                                'RECEIVING',
280                                -1 * (decode(c.pa_addition_flag,
281                                             'Y',
282                                             (nvl(c.entered_dr,0)-nvl(c.entered_cr,0)),
283                                             'I',
284                                             (nvl(c.entered_dr,0)-nvl(c.entered_cr,0)-nvl(c.entered_nr_tax,0))))))
285       into l_rcpt_qty
286       from rcv_transactions a,
287            rcv_receiving_sub_ledger c
288       where a.po_distribution_id = p_po_dist
289       and ((a.destination_type_code = 'EXPENSE') or
290         (a.destination_type_code = 'RECEIVING' and
291          a.transaction_type in ('RETURN TO RECEIVING' , 'RETURN TO VENDOR')))
292       and c.pa_addition_flag in ('Y', 'I')
293       and c.rcv_transaction_id = a.transaction_id
294       and c.actual_flag = 'A';
295 
296     ELSE
297 
298        /*bug 5946201 - We need a specific SELECT for eIB items for reason mentioned in the bug*/
299       IF (Is_eIB_item(p_po_dist) = 'Y' AND g_accrue_on_receipt_flag = 'N') THEN
300 
301  	         select sum(decode(destination_type_code, 'EXPENSE', decode(transaction_type,'RETURN TO RECEIVING',-1 * quantity, quantity),'RECEIVING',-1 * quantity))
302  	         into l_rcpt_qty
303  	         from rcv_transactions a
304  	         where a.po_distribution_id = p_po_dist
305  	         and ((a.destination_type_code = 'EXPENSE' ) or
306  	                 (a.destination_type_code = 'RECEIVING' and a.transaction_type in ('RETURN TO RECEIVING' , 'RETURN TO VENDOR')))
307  	         and  a.pa_addition_flag in ('Y','I') ;
308 
309       ELSE /* for 1.all eIB items with accrue at receipt checked and 2.All non-eIB items existing  SELECT is fine  */
310 /* Added index hint as part of bug 6408874 */
311 
312 		select sum(decode(destination_type_code,
313                               'EXPENSE',
314                               decode(transaction_type,
315                                           'RETURN TO RECEIVING',
316                                           -1 * quantity,
317                                           quantity),
318                                'RECEIVING',
319                                -1 * quantity))
320 		into l_rcpt_qty
321 		from rcv_transactions a
322 		where a.po_distribution_id = p_po_dist
323 		and ((a.destination_type_code = 'EXPENSE' ) or
324 		(a.destination_type_code = 'RECEIVING' and
325 		a.transaction_type in ('RETURN TO RECEIVING' , 'RETURN TO VENDOR')))
326     and EXISTS ( SELECT /*+ Index(rcv_sub RCV_RECEIVING_SUB_LEDGER_N1) */ rcv_sub.rcv_transaction_id
327 		FROM rcv_receiving_sub_ledger rcv_sub
328 		WHERE rcv_sub.rcv_transaction_id = a.transaction_id
329 		AND rcv_sub.pa_addition_flag in ('Y', 'I'));
330       END IF; /* IF is_eib_item...*/
331     END IF;
332    END IF; --Cash basis accounting.  -----}
333     --dbms_output.put_line('rcpt after select = ' || nvl(l_rcpt_qty,0));
334 
335     --                instead of average .And during calculation of logic donot consider
336     --                TAX,PO PRICE ADJUSTed lines.
337 
338     if (nvl(l_rcpt_qty,0) = 0) then
339        --dbms_output.put_line('rcpt qty = 0');
340        if (p_module = 'PO') then
341           if nvl(p_matching_basis,'QUANTITY') = 'AMOUNT' then -- Bug 3642604
342             l_rcpt_qty := p_qty_ordered + p_nrtax_amt - p_qty_cancel- l_qty_billed - (p_nrtax_amt * l_qty_billed/nvl(p_qty_ordered,1));
343           else
344             l_rcpt_qty := p_qty_ordered-p_qty_cancel-l_qty_billed;
345           end if;
346           --dbms_output.put_line('rcpt qty 0 and PO = ' || nvl(l_rcpt_qty,0));
347        elsif (p_module = 'AP') then
348           l_rcpt_qty := p_pa_quantity ; --l_tot_inv_qty/l_inv_num; -- Bug 3556021
349           --dbms_output.put_line('rcpt qty 0 and AP = ' || nvl(l_rcpt_qty,0));
350        end if;
351        g_rcpt_qty := l_rcpt_qty; -- Added for Bug#6408874
352      /*Added for bug#13793317 - START */
353        g_po_distr_id := p_po_dist;
354        g_qty_ordered := p_qty_ordered;
355        g_qty_cancel  := p_qty_cancel;
356        g_qty_billed  := l_qty_billed; -- Changed to l_quantity_billed
357        g_module      := p_module;
358        g_pa_quantity := p_pa_quantity;
359        g_inv_source  := p_inv_source;
360        g_line_type_lookup_code := p_line_type_lookup_code;
361     /*Added for bug#13793317 - END */
362 
363        return l_rcpt_qty;
364     end if;
365 
366     if (p_module = 'PO') then
367        --dbms_output.put_line('calling = PO ');
368        if nvl(p_matching_basis,'QUANTITY') = 'AMOUNT' then -- Bug 3642604
369          l_rcpt_qty := p_qty_ordered + p_nrtax_amt -p_qty_cancel-greatest(((l_qty_billed + (p_nrtax_amt * l_qty_billed/nvl(p_qty_ordered,1))) -l_rcpt_qty),0)-l_rcpt_qty ;
370        else
371          l_rcpt_qty := p_qty_ordered -p_qty_cancel-greatest((l_qty_billed-l_rcpt_qty),0)-l_rcpt_qty ;
372        end if;
373        --dbms_output.put_line('rcpt in PO = '||l_rcpt_qty);
374     elsif (p_module = 'AP') then
375        --dbms_output.put_line('calling = AP ');
376 
377   -- R12 change
381       -- amount and quantity
378      IF P_CASH_BASIS_ACCTG = 'Y' THEN --R12 change ------{
379 
380       -- For each PO distribution, take the total payment amount, and prorate it invoice distribution
382 
383        select count(*),
384              SUM(dist.pa_quantity*(SUM(nvl(paydist.paid_base_amount,paydist.amount))/(nvl(dist.base_amount,dist.amount))))
385        into  l_inv_num, l_tot_inv_qty
386        from  ap_invoice_distributions_all dist,
387              ap_payment_hist_dists paydist,
388              ap_invoices_all inv
389        where dist.po_distribution_id = p_po_dist
390        and   dist.charge_applicable_to_dist_id is null  --R12 change
391        and   dist.related_id is null -- R12 change
392        and   dist. line_type_lookup_code <> 'REC_TAX'
393        and   paydist.pa_addition_flag ='N'
394        and   inv.invoice_id = dist.invoice_id
395        and   dist.invoice_distribution_id = paydist.invoice_distribution_id
396        and   NVL(inv.source,'X') <> 'PPA'
397        --    4905546
398        --    ap_payment_hist_dists has discounts and cash records. we need to include quantity
399        --    only for the payment otherwise quantity would double because of discount.
400        --    adding the criteria to filter discounts for payment.
401        and   paydist.pay_dist_lookup_code = 'CASH'
402        group by dist.invoice_distribution_id,NVL(dist.base_amount,dist.amount), dist.pa_quantity;
403 
404 -- Bug 13602288: Added below select query as a part of self assessed tax enhancement
405        select count(*),
406              SUM(sat.pa_quantity*(SUM(nvl(paydist.paid_base_amount,paydist.amount))/(nvl(sat.base_amount,sat.amount))))
407        into  l_inv_num2, l_tot_inv_qty2
408        from  ap_self_assessed_tax_dist_all sat,
409              ap_payment_hist_dists paydist,
410              ap_invoices_all inv
411        where sat.po_distribution_id = p_po_dist
412        and   sat.charge_applicable_to_dist_id is null
413        and   sat.related_id is null
414        and   sat. line_type_lookup_code <> 'REC_TAX'
415        and   paydist.pa_addition_flag ='N'
416        and   inv.invoice_id = sat.invoice_id
417        and   sat.invoice_distribution_id = paydist.invoice_distribution_id
418        and   NVL(inv.source,'X') <> 'PPA'
419        and   paydist.pay_dist_lookup_code = 'CASH'
420        group by sat.invoice_distribution_id,NVL(sat.base_amount,sat.amount), sat.pa_quantity;
421 
422 	l_inv_num:= l_inv_num + l_inv_num2;		-- Bug 13602288:self assessed tax enhancement
423         l_tot_inv_qty:= l_tot_inv_qty + l_tot_inv_qty2; -- Bug 13602288:self assessed tax enhancement
424 
425        l_rcpt_qty := greatest(0,greatest((l_tot_inv_qty),0)/l_inv_num);
426 
427      ELSE
428        select count(*), sum(dist.pa_quantity)
429        into  l_inv_num, l_tot_inv_qty
430        from  ap_invoice_distributions_all dist,
431              ap_invoices_all inv
432        where dist.po_distribution_id = p_po_dist
433        -- and   dist.line_type_lookup_code = 'ITEM' --R12 change
434        and   dist. line_type_lookup_code <> 'REC_TAX'
435        --and   nvl(reversal_flag,'N') <> 'Y' /* Bug 5673779 */ /* Commented for Bug 13002754 -- Bug 13251424 */
436        and   dist.charge_applicable_to_dist_id is null --R12 change
437        and   dist.related_id is null --R12 change
438        and   dist.pa_addition_flag not in ('Z','T','E','Y')  /** Added for bug 3167288 **/
439        and   inv.invoice_id = dist.invoice_id                -- Bug 3556021
440        and   NVL(inv.source,'X') <> 'PPA';                   -- Bug 3556021
441 
442        --dbms_output.put_line('no. of invoices = ' || nvl(l_inv_num,0));
443        --dbms_output.put_line('total inv amount = ' || nvl(l_tot_inv_qty,0));
444 
445 -- Bug 13602288: Added below select query as a part of self assessed tax enhancement
446 
447        select count(*), sum(sat.pa_quantity)
448        into  l_inv_num2, l_tot_inv_qty2
449        from  ap_self_assessed_tax_dist_all sat,
450              ap_invoices_all inv
451        where sat.po_distribution_id = p_po_dist
452        and   sat. line_type_lookup_code <> 'REC_TAX'
453        and   nvl(reversal_flag,'N') <> 'Y'
454        and   sat.charge_applicable_to_dist_id is null
455        and   sat.related_id is null
456        and   sat.pa_addition_flag not in ('Z','T','E','Y')
457        and   inv.invoice_id = sat.invoice_id
458        and   NVL(inv.source,'X') <> 'PPA';
459 
460 	l_inv_num:= l_inv_num + l_inv_num2;		-- Bug 13602288:self assessed tax enhancement
461         l_tot_inv_qty:= l_tot_inv_qty + l_tot_inv_qty2; -- Bug 13602288:self assessed tax enhancement
462 
463        l_rcpt_qty := greatest(0,greatest((l_tot_inv_qty-l_rcpt_qty),0)/l_inv_num);
464        --dbms_output.put_line('rcpt in AP= '||l_rcpt_qty);
465      END IF; -----------------}
466     end if;
467 
468    End If;  ---}
469 
470    g_rcpt_qty := l_rcpt_qty; -- Added for Bug#6408874
471 /*Added for bug#13793317 - START */
472    g_po_distr_id := p_po_dist;
473    g_qty_ordered := p_qty_ordered;
474    g_qty_cancel  := p_qty_cancel;
475    g_qty_billed  := l_qty_billed; -- Changed to l_quantity_billed
476    g_module      := p_module;
477    g_pa_quantity := p_pa_quantity;
478    g_inv_source  := p_inv_source;
479    g_line_type_lookup_code := p_line_type_lookup_code;
480 /*Added for bug#13793317 - END */
481 
482    return l_rcpt_qty;
483 
484 EXCEPTION
485    when no_data_found then
486 --        null; Bug 3864527
487         return 0;
488 END get_rcpt_qty;
489 
490 /* Function : get_inv_cmt
491    Return   : This function returns the invoice amount not yet interfaced to PA
492               taking into consideration the receipt amount interfaced to PA.
493    IN parameters: PO Distribution Id,
494                   Denom Amt Flag   : To distinguish transaction and functional amount
495                   PA Addition Flag : Invoice Distribution's pa_addition_flag
496                   Variance Amount  : Total of invoice_proce_variance and exchange_rate_variance
497                   Calling module   : PO or AP, but used mainly for AP currently.
498    Logic:
499          If called from the AP view, first the receipt amount interfaced to PA is selected.
500          Then the invoice amount omiting the variances is selected in addition to the number
501          of invoice created for a given po distribution.
502          If the pa_addition_flag is 'F', meaning the variance amount has been interfaced to PA
503          then the variance amount is not considered as a commitment, else it is considered for
504          AP commitment.
505          The AP commitment is calculated as the invoice amount excluding the variance, receipt
506          amount. And then we add the variance if it has not yet been transferred to PA.
507          Since its hard to figure out which receipt matches to which invoice, we always divide
508          the total invoice amount exculding the receipt amount by the number of invoices
509          created for a po distribution.
510 */
511 
512 FUNCTION get_inv_cmt(p_po_dist in number,
513                      p_denom_amt_flag in varchar2,
514                      p_pa_add_flag in varchar2,
515                      p_var_amt in number,
516                      p_ccid in number,
517                      p_module in varchar2,
518                      p_invoice_id       in number DEFAULT NULL ,        /* Added for Bug 3394153 */
519                      p_dist_line_num    in number DEFAULT NULL,         /* Added for Bug 3394153 */
520                      p_inv_dist_id      in number DEFAULT NULL,         /* Added for Bug 3394153 */
521 				 P_CASH_BASIS_ACCTG varchar2 default 'N'
522 				 ) RETURN NUMBER
523 IS
524     l_rcpt_amt number;
525     l_inv_num  number;
526     l_inv_amt  number;
527     l_var_amt  number;
528 	l_inv_num2  number;		-- Bug 13602288:self assessed tax enhancement
529     l_inv_amt2  number;		-- Bug 13602288:self assessed tax enhancement
530 
531 BEGIN
532 
533 IF P_CASH_BASIS_ACCTG = 'N' THEN  --R12 change --------{
534     --pricing changes start
535     IF (p_denom_amt_flag <> 'Y') THEN
536     select sum(decode(c.pa_addition_flag, 'Y', (nvl(accounted_dr,0)-nvl(accounted_cr,0)),
537                                           'I', ((nvl(accounted_dr,0)-nvl(accounted_cr,0))-(nvl(accounted_nr_tax,0))
538                                                 )))
539     into l_rcpt_amt
540     from rcv_transactions a,   rcv_receiving_sub_ledger c
541     where a.po_distribution_id = p_po_dist
542     and ((a.destination_type_code = 'EXPENSE' ) or
543         (a.destination_type_code = 'RECEIVING' and
544          a.transaction_type in ('RETURN TO RECEIVING' , 'RETURN TO VENDOR')))
545     and c.pa_addition_flag in ('Y', 'I')
546     and c.rcv_transaction_id = a.transaction_id
547     and c.code_combination_id = p_ccid
548     and c.actual_flag = 'A';
549 
550     ELSE
551     select sum(decode(c.pa_addition_flag, 'Y', (nvl(entered_dr,0)-nvl(entered_cr,0)),
552                                           'I', ((nvl(entered_dr,0)-nvl(entered_cr,0))-(nvl(entered_nr_tax,0))
553                                                 )))
554     into l_rcpt_amt
555     from rcv_transactions a,   rcv_receiving_sub_ledger c
556     where a.po_distribution_id = p_po_dist
557     and ((a.destination_type_code = 'EXPENSE' ) or
558         (a.destination_type_code = 'RECEIVING' and
559          a.transaction_type in ('RETURN TO RECEIVING' , 'RETURN TO VENDOR')))
560     and c.pa_addition_flag in ('Y', 'I')
561     and c.rcv_transaction_id = a.transaction_id
562     and c.code_combination_id = p_ccid
563     and c.actual_flag = 'A';
564     END IF;
565  END IF; --R12 change ----------------------------------}
566     --pricing changes end
567     --dbms_output.put_line('rcpt after select = ' || nvl(l_rcpt_amt,0));
568 
569     /* Bug 3394153 : If there are no receipts(matched to PO) interfaced to Projects then
570        this function returns the actual commitment amount for each invoice.
571        If there are receipts interfaced then since the invoices can never be transferred
572        to Projects we would continue with the current functionality of prorating the total
573        invoice amount amongst all the invoices equally and returning the average commitment. */
574 
575     /* Bug 3761335 : removed the exchange_rate_varaince from the select clause if
576        p_denom_amt_flag is 'Y' , exchange_rate_varaince should not be considered in case of
577        transaction currency amount , it should be considered only in case of
578        functional currency amount */
579 
580     if (p_module = 'AP') then
581       if(l_rcpt_amt is NOT NULL) Then   /* Bug 3394153 :Added If Condition. */
582                select count(*),
583                       sum(decode(p_denom_amt_flag,
584                           'Y', amount,
585                           'N', nvl(base_amount,amount)))
586                into l_inv_num, l_inv_amt
587                from ap_invoice_distributions_all
588                where po_distribution_id = p_po_dist
589                --and line_type_lookup_code = 'ITEM'
590                and line_type_lookup_code <> 'REC_TAX' -- R12 change
591                --and nvl(reversal_flag,'N') <> 'Y' /* Bug 5673779 */ /* Commented for Bug 13002754 -- Bug 13251424 */
592                and pa_addition_flag not in ('Z','T','E','Y') /** Added for bug 3167288 **/ /*Bug 9776971*/
593 			   ;
594 -- Bug 13602288: Added below select query as a part of self assessed tax enhancement
595 	       select count(*),
596                       sum(decode(p_denom_amt_flag,
597                           'Y', amount,
598                           'N', nvl(base_amount,amount)))
599                into l_inv_num2, l_inv_amt2
600                from ap_self_assessed_tax_dist_all
604                and pa_addition_flag not in ('Z','T','E','Y');
601                where po_distribution_id = p_po_dist
602                and line_type_lookup_code <> 'REC_TAX'
603                and nvl(reversal_flag,'N') <> 'Y'
605 
606 	   l_inv_num:= l_inv_num + l_inv_num2;	-- Bug 13602288:self assessed tax enhancement
607 	   l_inv_amt:= l_inv_amt + l_inv_amt2;	-- Bug 13602288:self assessed tax enhancement
608 
609        Else /* Bug 3394153: Added Else Block. */
610          -- R12 change
611                select sum(decode(p_denom_amt_flag, /* Bug 4015448. Added Dummy Sum */
612                           'Y', amount,
613                           'N', nvl(base_amount,amount)))
614                into l_inv_amt
615                from ap_invoice_distributions_all
616                where po_distribution_id = p_po_dist
617                  and invoice_id = p_invoice_id
618                  -- and distribution_line_number = p_dist_line_num --R12 change
619                  and invoice_distribution_id = p_inv_dist_id -- R12 change
620                  and line_type_lookup_code <> 'REC_TAX'  --R12 change
621                  --and nvl(reversal_flag,'N') <> 'Y' /* Bug 5673779 */ /* Commented for Bug 13002754 -- Bug 13251424 */
622                  and pa_addition_flag not in ('Z','T','E','Y' ) ; 	/*Bug 9776971*/
623 
624 -- Bug 13602288: Added below select query as a part of self assessed tax enhancement
625 
626                select sum(decode(p_denom_amt_flag,
627                           'Y', amount,
628                           'N', nvl(base_amount,amount)))
629                into l_inv_amt2
630                from ap_self_assessed_tax_dist_all
631                where po_distribution_id = p_po_dist
632                  and invoice_id = p_invoice_id
633                  and invoice_distribution_id = p_inv_dist_id
634                  and line_type_lookup_code <> 'REC_TAX'
635                  and nvl(reversal_flag,'N') <> 'Y'
636                  and pa_addition_flag not in ('Z','T','E','Y' ) ;
637 
638                 l_var_amt := nvl(p_var_amt,0);
639 
640                 l_inv_amt := l_inv_amt + l_inv_amt2 + l_var_amt;	-- Bug 13602288:self assessed tax enhancement
641 
642                 return l_inv_amt;
643 
644       End If;   /* Bug 3394153 : End Of Changes */
645     End If;
646        --dbms_output.put_line('no. of invoices = ' || nvl(l_inv_num,0));
647        --dbms_output.put_line('total inv amount = ' || nvl(l_inv_amt,0));
648 
649     l_var_amt := nvl(p_var_amt,0);
650 
651 
652     if (p_module = 'AP') then
653        l_rcpt_amt := greatest(0,greatest((l_inv_amt-nvl(l_rcpt_amt,0)),0)/nvl(l_inv_num,1)) + l_var_amt;
654        --dbms_output.put_line('rcpt in AP= '||l_rcpt_amt);
655     end if;
656 
657     return l_rcpt_amt;
658 
659 EXCEPTION
660    when no_data_found then
661 --	  Null;  Bug 3864527
662         return 0;
663 END get_inv_cmt;
664 
665 
666 --bug:4610727 determine outstanding qty on ap distribution.
667 -- following function is used by grants views.
668 --
669    function get_apdist_qty( p_inv_dist_id    in NUMBER,
670                             p_invoice_id     in NUMBER,
671 			    p_cost           in NUMBER,
672 			    p_quantity       in NUMBER,
673 			    p_calling_module in varchar2,
674 			    p_denom_amt_flag in varchar2,
675 			    P_CASH_BASIS_ACCTG in varchar2 default 'N'
676 			    ) return number is
677      l_os_amount number ;
678      l_inv_amt   number ;
679      l_inv_qty   number ;
680      l_pay_amt   number ;
681      l_disc_amt  number ;
682      l_prepay_amt number ;
683      l_discount_start_date VARCHAR2(15);
684      l_system_discount    DATE ;
685    begin
686 
687         IF p_calling_module <> 'GMS' then
688 	   return p_quantity ;
689         END IF ;
690 
691 	l_inv_amt   := p_cost ;
692 
693 	IF P_CASH_BASIS_ACCTG = 'N' and p_calling_module = 'GMS' then
694 	   return p_quantity ;
695 	end if ;
696 
697        IF NVL(l_inv_amt,0) <> 0 THEN
698                --l_discount_start_date := nvl(fnd_profile.value_specific('PA_DISC_PULL_START_DATE'),'2051/01/01') ; /* Bug 4474213 */
699 	       --l_system_discount     := fnd_date.canonical_to_date(l_discount_start_date);
700 
701                --    4905546
702                --    ap_payment_hist_dists has discounts and cash records. we need to include quantity
703                --    only for the payment otherwise quantity would double because of discount.
704                --    adding the criteria to filter discounts for payment.
705 
706 
707                --
708                -- Bug : 4962731
709                --     : R12.PJ:XB1:QA:BC:INCORRECT AMOUNTS INTERFACED TO PROJECTS IN CASH BASED ACC
710                --
711 	       --IF l_system_discount > TRUNC(SYSDATE) THEN
712 	          select sum( decode(p_denom_amt_flag, /* Bug 4015448. Added Dummy Sum */
713 			             'Y', paydist.amount,
714 			             'N', nvl(paydist.paid_base_amount,paydist.amount)))
715 	            into  l_pay_amt
716 	            from  ap_payment_hist_dists paydist
717 	           where paydist.invoice_distribution_id = p_inv_dist_id
718 		     and NVL(paydist.pa_addition_flag,'N')  <> 'N'
719                      and paydist.pay_dist_lookup_code    = 'CASH';
720 
721 		  -- discount method is PRORATE and not interfaced to Projects. Hence the pa addition flag is never
722 		  -- switched to Y in this case. We need to consider discounts for the payment line that has interfaced to
723 		  -- projects.
724 
725 		  --
726 		  -- Bug : 4962731
727 		  --     : R12.PJ:XB1:QA:BC:INCORRECT AMOUNTS INTERFACED TO PROJECTS IN CASH BASED ACC
728 		  --
732 	             into  l_disc_amt
729 	           select sum( decode(p_denom_amt_flag, /* Bug 4015448. Added Dummy Sum */
730 			               'Y', paydist1.amount,
731 			               'N', nvl(paydist1.paid_base_amount,paydist1.amount)))
733 	             from  ap_payment_hist_dists paydist1,
734 		          ap_payment_hist_dists paydist2
735 	            where paydist1.invoice_distribution_id = p_inv_dist_id
736 		      and paydist2.invoice_distribution_id = p_inv_dist_id
737 		      and paydist2.invoice_distribution_id = paydist1.invoice_distribution_id
738 		      and paydist2.payment_history_id      = paydist1.payment_history_id
739 		      and paydist2.invoice_payment_id      = paydist1.invoice_payment_id
740 		      and paydist2.pay_dist_lookup_code    = 'CASH'
741 		      and paydist1.pay_dist_lookup_code   IN (  'DISCOUNT' )
742 		       and NVL(paydist2.pa_addition_flag,'N')  <> 'N' ;
743 		  --
744 		  -- Bug : 4962731
745 		  --     : R12.PJ:XB1:QA:BC:INCORRECT AMOUNTS INTERFACED TO PROJECTS IN CASH BASED ACC
746 		  --
747 
748                     l_pay_amt := NVL(l_pay_amt,0) + NVL(l_disc_amt,0) ;
749 
750 	       --END IF ;
751 
752 	       select sum( decode(p_denom_amt_flag, /* Bug 4015448. Added Dummy Sum */
753 		  'Y', ppaydist.amount,
754 		  'N', nvl(ppaydist.base_amount,ppaydist.amount)))
755 	     into  l_prepay_amt
756 	     from  ap_prepay_app_dists ppaydist
757 	    where ppaydist.invoice_distribution_id = p_inv_dist_id
758 	      and NVL(ppaydist.pa_addition_flag,'N')  <> 'N' ;
759 
760 	   l_pay_amt := nvl(l_pay_amt,0) + ( nvl(l_prepay_amt,0) * -1 )  ;
761 
762        END IF ;
763 
764        l_os_amount := NVL(l_inv_amt,0) - NVL(l_pay_amt,0) ;
765        l_inv_qty   := (nvl(l_os_amount,0)/nvl(p_cost,1) ) * nvl(p_quantity,0) ;
766 
767        return l_inv_qty  ;
768 
769 end get_apdist_qty;
770 
771 
772 --bug:4610727 determine outstanding amount on ap distribution.
773 function get_apdist_amt( p_inv_dist_id    in NUMBER,
774                          p_invoice_id     in NUMBER,
775                          p_cost           in NUMBER,
776 		         p_denom_amt_flag in varchar2,
777 			 p_calling_module in varchar2,
778 			 P_CASH_BASIS_ACCTG in varchar2 default 'N'
779 			 ) return number is
780 
781      l_os_amount  number ;
782      l_inv_amt    number ;
783      l_pay_amt    number ;
784      l_disc_amt   number ;
785      l_prepay_amt number ;
786 	 l_inv_amt2    number ;  -- Bug 13602288:self assessed tax enhancement
787 
788      l_discount_start_date VARCHAR2(15);
789      l_system_discount    DATE ;
790 
791    begin
792 
793      l_inv_amt   := p_cost ;
794 
795 	IF P_CASH_BASIS_ACCTG = 'N' and p_calling_module = 'GMS' then
796 	   return l_inv_amt ;
797 	end if ;
798 
799 	IF  p_calling_module = 'PA' THEN
800 
801                select decode(p_denom_amt_flag, /* Bug 4015448. Added Dummy Sum */
802                           'Y', dist.amount,
803                           'N', nvl(dist.base_amount,dist.amount))
804                into  l_inv_amt
805                from  ap_invoice_distributions_all dist
806                where invoice_id = p_invoice_id
807                and   dist.invoice_distribution_id = p_inv_dist_id ;
808 
809 -- Bug 13602288: Added below select query as a part of self assessed tax enhancement
810 
811                select decode(p_denom_amt_flag,
812                           'Y', sat.amount,
813                           'N', nvl(sat.base_amount,sat.amount))
814                into  l_inv_amt2
815                from  ap_self_assessed_tax_dist_all sat
816                where sat.invoice_id = p_invoice_id
817                and   sat.invoice_distribution_id = p_inv_dist_id ;
818 
819 	   l_inv_amt:= l_inv_amt + l_inv_amt2;	-- Bug 13602288:self assessed tax enhancement
820 
821 	END IF ;
822 
823 
824 	IF NVL(l_inv_amt,0) <> 0 THEN
825                --l_discount_start_date := nvl(fnd_profile.value_specific('PA_DISC_PULL_START_DATE'),'2051/01/01') ; /* Bug 4474213 */
826 	       --l_system_discount     := fnd_date.canonical_to_date(l_discount_start_date);
827 
828                --    4905546
829                --    ap_payment_hist_dists has discounts and cash records. we need to include quantity
830                --    only for the payment otherwise quantity would double because of discount.
831                --    adding the criteria to filter discounts for payment.
832 	       --
833 	       -- Bug : 4962731
834 	       --     : R12.PJ:XB1:QA:BC:INCORRECT AMOUNTS INTERFACED TO PROJECTS IN CASH BASED ACC
835 	       --
836 	       --IF l_system_discount > TRUNC(SYSDATE) THEN
837 	          select sum( decode(p_denom_amt_flag, /* Bug 4015448. Added Dummy Sum */
838 			             'Y', paydist.amount,
839 			             'N', nvl(paydist.paid_base_amount,paydist.amount)))
840 	            into  l_pay_amt
841 	            from  ap_payment_hist_dists paydist
842 	           where paydist.invoice_distribution_id = p_inv_dist_id
843                      and paydist.pay_dist_lookup_code    = 'CASH'
844 		     and NVL(paydist.pa_addition_flag,'N')  <> 'N' ;
845 
846 	       --ELSE
847 
848 		  -- discount method is PRORATE and not interfaced to Projects. Hence the pa addition flag is never
849 		  -- switched to Y in this case. We need to consider discounts for the payment line that has interfaced to
850 		  -- projects.
851 		  --
852 		  -- Bug : 4962731
853 		  --     : R12.PJ:XB1:QA:BC:INCORRECT AMOUNTS INTERFACED TO PROJECTS IN CASH BASED ACC
854 		  --
855 
856 	           select sum( decode(p_denom_amt_flag, /* Bug 4015448. Added Dummy Sum */
857 			               'Y', paydist1.amount,
861 		          ap_payment_hist_dists paydist2
858 			               'N', nvl(paydist1.paid_base_amount,paydist1.amount)))
859 	             into  l_disc_amt
860 	             from  ap_payment_hist_dists paydist1,
862 	            where paydist1.invoice_distribution_id = p_inv_dist_id
863 		      and paydist2.invoice_distribution_id = p_inv_dist_id
864 		      and paydist2.invoice_distribution_id = paydist1.invoice_distribution_id
865 		      and paydist2.payment_history_id      = paydist1.payment_history_id
866 		      and paydist2.invoice_payment_id      = paydist1.invoice_payment_id
867 		      and paydist2.pay_dist_lookup_code    = 'CASH'
868 		      and paydist1.pay_dist_lookup_code   IN ( 'DISCOUNT' )
869 		       and NVL(paydist2.pa_addition_flag,'N')  <> 'N' ;
870 
871 	       --
872 	       -- Bug : 4962731
873 	       --     : R12.PJ:XB1:QA:BC:INCORRECT AMOUNTS INTERFACED TO PROJECTS IN CASH BASED ACC
874 	       l_pay_amt := NVL(l_pay_amt,0) + NVL(l_disc_amt,0) ;
875 
876           --END IF ;
877 
878 	   select sum( decode(p_denom_amt_flag, /* Bug 4015448. Added Dummy Sum */
879 		  'Y', ppaydist.amount,
880 		  'N', nvl(ppaydist.base_amount,ppaydist.amount)))
881 	     into  l_prepay_amt
882 	     from  ap_prepay_app_dists ppaydist
883 	    where ppaydist.invoice_distribution_id = p_inv_dist_id
884 	      and NVL(ppaydist.pa_addition_flag,'N')  <> 'N' ;
885 
886 	   l_pay_amt := nvl(l_pay_amt,0) + ( nvl(l_prepay_amt,0) * -1 )  ;
887 
888 	END IF ;
889 
890 	l_os_amount := NVL(l_inv_amt,0) - NVL(l_pay_amt,0) ;
891 
892 	return l_os_amount ;
893 end get_apdist_amt;
894 
895 
896 /* Bug:4914006  R12.PJ:XB3:QA:APL:PREPAYMENT COMMITMENT AMOUNT NOT REDUCED AFTER   */
897 function get_inv_cmt(p_po_dist in number,
898                      p_denom_amt_flag in varchar2,
899                      p_pa_add_flag in varchar2,
900                      p_var_amt in number,
901                      p_ccid   in number,
902                      p_module in varchar2,
903                      p_invoice_id       in number DEFAULT NULL ,        /* Added for Bug 3394153 */
904                      p_dist_line_num    in number DEFAULT NULL,         /* Added for Bug 3394153 */
905                      p_inv_dist_id      in number DEFAULT NULL,
906                      p_accrue_on_rcpt_flag in varchar2,
907                      p_po_line_id in number,
908                      p_forqty     in varchar2,
909                      p_cost       in number,
910                      p_project_id in number,
911                      p_dist_type  in varchar2,
912                      p_pa_quantity in number,  -- Bug 3556021
913                      p_inv_source  in varchar2,
914 		     P_CASH_BASIS_ACCTG in varchar2 default 'N',
915 		     p_inv_type    in varchar2,
916 		     p_hist_flag   in varchar2,
917 		     p_prepay_amt_remaining in number
918 		     ) return number -- Bug 3556021
919 Is
920 
921    L_RateBasedPO    Varchar2(1);
922    L_CWKTCXface     Varchar2(1);
923 
924    L_Ret_Amt        Number;
925    L_Ret_val        Number;
926    l_Var_Amt        Number;
927    l_dummy          NUMBER; -- Bug 3529107
928    l_exchange_rate  NUMBER ;
929 
930    l_po_line_type   Varchar2(30) := 'QUANTITY';
931 
932    -- Bug 3529107 :
933    -- This cursor is added to further validate the Ap invoice before filtering out
934    -- from PSI commitments window.These vaildations are done in addition to what are done
935    -- at pa_proj_ap_inv_distributions view level so that the logic is in sync with
936    -- update statment in paapimp_pkg.mark_inv_var_paflag procedure which updates
937    -- these records to 'G' status during "PRC : Interface supplier cost" process.
938 
939    CURSOR C_Valid_Invoice IS
940    SELECT 1
941      FROM ap_invoices_all
942     WHERE invoice_id = p_invoice_id
943       AND invoice_type_lookup_code <> 'EXPENSE REPORT'
944       AND nvl(source, 'xx' ) NOT IN ('PA_COST_ADJUSTMENTS');
945 
946    --
947    -- Bug : 5522820
948    --       R12.PJ:XB9:QA:APL: PREPAYMENT IN FOREIGN CURRENCY - FUNC COST INCORRECT IN PSI
949    --
950    CURSOR C_currency_attributes IS
951    SELECT exchange_rate
952      FROM ap_invoices_all
953     WHERE invoice_id = p_invoice_id ;
954 
955    l_av number;
956    l_base_av number;
957    l_in_var_amt number;
958 
959 Begin
960 
961     L_RateBasedPO :=  Pa_Pjc_Cwk_Utils.Is_Rate_Based_Line(p_po_line_id, null);
962     L_CWKTCXface :=  Pa_Pjc_Cwk_Utils.Is_Cwk_TC_Xface_Allowed(P_Project_Id);
963 
964     -- R12 change for cash basis accounting.
965      If p_po_dist is not null and p_forqty = 'Y' then
966 
967       select nvl(pll.matching_basis, 'QUANTITY') /* modified for bug bug 3496492 */
968         into l_po_line_type
969         from po_lines_all po_line,
970              po_distributions_all po_dist,
971              po_line_locations_all pll
972        where Po_dist.distribution_type <> 'PREPAYMENT'
973          and pll.po_line_id = po_line.po_line_id
974          and po_line.po_line_id = po_dist.po_line_id
975          and po_dist.po_distribution_id = p_po_dist;
976 
977     End if;
978     --{
979     --4610727 - PJ.R12:DI1:APLINES: PSI OUTSTANDING AMOUNT FOR AP IN CASH BASED ACCOUNTING
980     IF NVL(P_CASH_BASIS_ACCTG, 'N') = 'Y' then
981 
982        --{{
986 	  -- Rate based PO project impl option allows to interface time card into projects.
983        IF L_RateBasedPO = 'Y' and L_CWKTCXface = 'Y' Then
984           --{{{
985 
987 	  -- item line is not reported as commitment because timecard will be processed in projects
988 	  -- For tax and variance lines we need to return outstanding amount i.e.
989 	  -- Invoice distribution amount - payament interfaced amount.
990           IF p_dist_type not in ( 'ACCRUAL', 'ITEM')  THEN
991 
992 
993              IF p_dist_type = 'PREPAY' then
994 	        l_ret_amt := p_cost ;
995 	     ELSE
996 	        -- R12 will have a separate line for the tax and variance and we need to determine
997 		    -- the outstanding amount based on Invoice distribution amount and payament
998 		    -- amount that has interface to projects..
999 
1000 		    -- BUG 4914006
1001 		    -- Prepayment discount is not applicable and also payment never gets
1002 		    -- interfaced to projects. So we should be looking at the amount remaining
1003 		    -- on prepayments.
1004             IF p_inv_type = 'PREPAYMENT'   and
1005 	       NVL(p_hist_flag,'N') <> 'Y' and
1006                p_forqty  <> 'Y' then
1007 
1008                l_ret_amt :=  p_prepay_amt_remaining ;
1009 
1010 	       --
1011 	       -- Bug : 5522820
1012 	       --       R12.PJ:XB9:QA:APL: PREPAYMENT IN FOREIGN CURRENCY - FUNC COST INCORRECT IN PSI
1013 	       --
1014 	       IF p_denom_amt_flag = 'N' THEN
1015 	           open C_currency_attributes ;
1016 		   fetch C_currency_attributes into l_exchange_rate ;
1017 		   close C_currency_attributes ;
1018 		   l_exchange_rate := NVL(l_exchange_rate,1) ;
1019 		   l_ret_amt := l_exchange_rate * p_prepay_amt_remaining ;
1020 		   l_ret_amt := pa_currency.round_currency_amt( l_ret_amt ) ;
1021 
1022 	       END IF ;
1023 
1024 	       -- Prepayment has not been paid yet.
1025 	       -- Bug: 5393523 Unpaid prepayments do not show in PSI.
1026 	       IF p_prepay_amt_remaining is NULL then
1027 	          l_ret_amt := get_apdist_amt( p_inv_dist_id,
1028 		                               p_invoice_id,
1029 					       NULL,
1030 					       p_denom_amt_flag,
1031 					       'PA',
1032 					       P_CASH_BASIS_ACCTG );
1033 	       END IF ;
1034             ELSE
1035 	   	      --
1036 	          l_ret_amt := get_apdist_amt( p_inv_dist_id, p_invoice_id, NULL, p_denom_amt_flag, 'PA',P_CASH_BASIS_ACCTG );
1037             END IF ;
1038 
1039 	     END IF ;
1040 
1041 	  ELSE
1042 	  -- Rate based po with timecard interfaced in projects corresponding to the
1043 	  -- item line and no outstanding amount as commitment.
1044 
1045 	     l_ret_amt := nvl(p_var_amt,0) ;
1046 
1047 	  END IF ;
1048 	  --}}}
1049        ELSE
1050        --{{ continue
1051        --
1052        -- Cash based accounting for standard ap invoices and non rate based pos or when interface
1053        -- invoice option is set in project impl option.
1054 
1055        -- Apply prepay amount will be reported as it is because there is no payament for
1056        -- prepayment application and this is reported as invoice cost.
1057        --
1058              IF p_dist_type = 'PREPAY' then
1059 	        l_ret_amt := p_cost ;
1060 	     ELSE
1061 	        -- We need to determine the outstanding invoice amount based on Invoice distribution
1062 		-- amount and payament amount that has interface to projects..
1063 		--
1064                 IF p_inv_type = 'PREPAYMENT' and NVL(p_hist_flag,'N') <> 'Y' and
1065                    p_forqty  <> 'Y' then
1066                    l_ret_amt :=  p_prepay_amt_remaining ;
1067 
1068 	           --
1069 	           -- Bug : 5522820
1070 	           --       R12.PJ:XB9:QA:APL: PREPAYMENT IN FOREIGN CURRENCY - FUNC COST INCORRECT IN PSI
1071 	           --
1072 	           IF p_denom_amt_flag = 'N' THEN
1073 	              open C_currency_attributes ;
1074 		      fetch C_currency_attributes into l_exchange_rate ;
1075 		      close C_currency_attributes ;
1076 		      l_exchange_rate := NVL(l_exchange_rate,1) ;
1077 		      l_ret_amt := l_exchange_rate * p_prepay_amt_remaining ;
1078 		      l_ret_amt := pa_currency.round_currency_amt( l_ret_amt ) ;
1079 
1080 	         END IF ;
1081 
1082 
1083 	           -- Prepayment has not been paid yet.
1084 	           -- Bug: 5393523 Unpaid prepayments do not show in PSI.
1085 		   IF p_prepay_amt_remaining is NULL THEN
1086 	              l_ret_amt := get_apdist_amt( p_inv_dist_id,
1087 		                                   p_invoice_id,
1088 						   NULL,
1089 						   p_denom_amt_flag,
1090 						   'PA',
1091 						   P_CASH_BASIS_ACCTG );
1092 		   END IF ;
1093 		ELSE
1094 	           l_ret_amt := get_apdist_amt( p_inv_dist_id, p_invoice_id, NULL, p_denom_amt_flag, 'PA', P_CASH_BASIS_ACCTG );
1095                 END IF ;
1096 
1097 	     END IF ;
1098        END IF ;
1099        --}} end of cash based processing
1100        IF p_forqty = 'Y' then
1101           IF l_po_line_type <> 'AMOUNT' then
1102 	     l_ret_amt :=  round((l_ret_amt/ p_cost) * nvl(p_pa_quantity,0), 2) ;
1103           end if ;
1104        end if ;
1105        return l_ret_amt ;
1106     END IF ;
1107     --4610727 - PJ.R12:DI1:APLINES: PSI OUTSTANDING AMOUNT FOR AP IN CASH BASED ACCOUNTING
1108     -- end of fix.
1109 
1110 
1111     l_in_var_amt := p_var_amt;
1112 
1113     If L_RateBasedPO = 'Y' and L_CWKTCXface = 'Y' Then ---{
1114 
1115        -- For Rate based or Amount based Po's quantity is same as amount
1116 
1117        -- Bug 3529107 : Added the below IF condition such that AP distributions (Non NRT Lines
1118        -- and NON variance lines) matched to a Rate based PO will not be shown as commitments
1119        -- in PSI as these lines will never be interfaced to PA .
1120        IF p_dist_type <> 'TAX' then
1121 
1122           OPEN  C_Valid_Invoice;
1123           FETCH C_Valid_Invoice INTO l_dummy;
1124           IF C_Valid_Invoice%FOUND THEN
1125              CLOSE C_Valid_Invoice;
1126 
1127              --For the standard invoice distributions (i.e. non tax distributons), appropriate
1128              --variance amounts must be returned depending on whether the variances are
1129              --interfaced to PA or not.
1130              IF p_dist_type in ( 'ACCRUAL',  'ITEM')  THEN
1131                 l_Ret_Amt := nvl(p_var_amt,0) ;
1132              ELSE
1133 	        l_Ret_Amt := p_cost ;
1134 	     END IF ;
1135              RETURN l_Ret_Amt;
1136           END IF;
1137           CLOSE C_Valid_Invoice;
1138       END IF ;
1139 
1140        --For Tax distributions
1141        IF p_accrue_on_rcpt_flag = 'Y' Then  -- {
1142 
1143              --Call get_inv_cmt
1144                  L_Ret_Amt := PA_CMT_UTILS.get_inv_cmt(p_po_dist,
1145                                                        p_denom_amt_flag,
1146                                                        p_pa_add_flag,
1147                                                        l_in_var_amt,
1148                                                        p_ccid,
1149                                                        'AP',
1150                                                        p_invoice_id,
1151                                                        -- bug : 4671855
1152                                                        p_dist_line_num ,
1153                                                        p_inv_dist_id,
1154 							   		                   P_CASH_BASIS_ACCTG);
1155        Else
1156 
1157           l_var_amt := nvl(l_in_var_amt,0);
1158 
1159           if (p_module = 'AP') then
1160              IF p_inv_type = 'PREPAYMENT' AND NVL(p_hist_flag,'N') <> 'Y' and
1161                  p_forqty  <> 'Y' then
1162                  l_ret_amt :=  p_prepay_amt_remaining ;
1163 	           --
1164 	           -- Bug : 5522820
1165 	           --       R12.PJ:XB9:QA:APL: PREPAYMENT IN FOREIGN CURRENCY - FUNC COST INCORRECT IN PSI
1166 	           --
1167 	         IF p_denom_amt_flag = 'N' THEN
1168 	           open C_currency_attributes ;
1169 		   fetch C_currency_attributes into l_exchange_rate ;
1170 		   close C_currency_attributes ;
1171 		   l_exchange_rate := NVL(l_exchange_rate,1) ;
1172 		   l_ret_amt := l_exchange_rate * p_prepay_amt_remaining ;
1173 		   l_ret_amt := pa_currency.round_currency_amt( l_ret_amt ) ;
1174 
1175 	         END IF ;
1176 
1177 
1178 	         -- Prepayment has not been paid yet.
1179 	         -- Bug: 5393523 Unpaid prepayments do not show in PSI.
1180 		 IF p_prepay_amt_remaining is NULL then
1181                     l_Ret_Amt := (P_Cost - l_var_amt);
1182 		 END IF ;
1183              ELSE
1184                  l_Ret_Amt := (P_Cost - l_var_amt);
1185              END IF ;
1186 
1187           end if;
1188 
1189        End If;                    -- }
1190 
1191     Else
1192 
1193        If p_accrue_on_rcpt_flag = 'Y' Then   -- {
1194 
1195           If p_forqty = 'Y' and l_po_line_type <> 'AMOUNT' Then
1196 
1197              --Call get_rcpt_qty
1198 
1199                  L_Ret_Amt := PA_CMT_UTILS.get_rcpt_qty(p_po_dist,0,0,0,'AP',p_po_line_id,p_project_id,null,p_ccid,
1200                                                     p_pa_quantity,p_inv_source,p_dist_type,l_po_line_type,null, -- Bug 3556021
1201 										  P_CASH_BASIS_ACCTG, p_accrue_on_rcpt_flag);
1202 
1203           Else
1204 
1205              --Call get_inv_cmt
1206              L_Ret_Amt := PA_CMT_UTILS.get_inv_cmt(p_po_dist,
1207                                                 p_denom_amt_flag,
1208                                                 p_pa_add_flag,
1209                                                 l_in_var_amt,
1210                                                 p_ccid,
1211                                                 'AP',
1212                                                 p_invoice_id,
1213                                                 -- bug : 4671855
1214                                                 p_dist_line_num ,
1215                                                 p_inv_dist_id,
1216 									   P_CASH_BASIS_ACCTG);
1217           End If;
1218 
1219       Else
1220 
1221            L_Ret_val := p_cost ;
1222            IF p_inv_type = 'PREPAYMENT' AND NVL(p_hist_flag,'N') <> 'Y' and
1223                  p_forqty  <> 'Y' then
1224                  l_ret_val :=  p_prepay_amt_remaining ;
1225 
1226 	           --
1227 	           -- Bug : 5522820
1228 	           --       R12.PJ:XB9:QA:APL: PREPAYMENT IN FOREIGN CURRENCY - FUNC COST INCORRECT IN PSI
1229 	           --
1230 	         IF p_denom_amt_flag = 'N' THEN
1231 	           open C_currency_attributes ;
1232 		   fetch C_currency_attributes into l_exchange_rate ;
1233 		   close C_currency_attributes ;
1234 		   l_exchange_rate := NVL(l_exchange_rate,1) ;
1235 		   l_ret_val := l_exchange_rate * p_prepay_amt_remaining ;
1236 		   l_ret_val := pa_currency.round_currency_amt( l_ret_val ) ;
1237 
1238 	         END IF ;
1239 
1240 	         -- Prepayment has not been paid yet.
1241 	         -- Bug: 5393523 Unpaid prepayments do not show in PSI.
1242 		 IF p_prepay_amt_remaining is NULL then
1243 		    L_Ret_val := p_cost ;
1244 		 END IF ;
1245             END IF ;
1246 
1247           Select decode(p_forqty,'Y', decode(l_po_line_type,'AMOUNT',l_ret_val,p_pa_quantity),l_ret_val)
1248           into   l_ret_val
1249           from dual;
1250 
1251           --Select decode(p_forqty,'Y', decode(l_po_line_type,'AMOUNT',p_cost,p_pa_quantity),p_cost)
1252           --into   l_ret_val
1253           --from dual;
1254 
1255           l_Ret_Amt := l_ret_val;
1256 
1257       End If;                        -- }
1258 
1259    End If;  ---}
1260 
1261    Return l_Ret_Amt;
1262 
1263 Exception
1264 
1265    When No_Data_Found Then
1266 --        Null;  Bug 3864527
1267         return 0;
1268 
1269    When Others Then
1270 --	  Null; Bug 3864527
1271 	return 0;
1272 
1273 End get_inv_cmt;
1274 
1275 --R12 changes for AP LINES uptake
1276 function get_inv_var(p_inv_dist in number,
1277                      p_denom_amt_flag in varchar2,
1278                      p_amt_var in number,
1279                      p_qty_var in number
1280                     ) return number
1281 IS
1282    l_Var_Amt        Number;
1283 BEGIN
1284      -- 4610727 - PJ.R12:DI1:APLINES: PSI OUTSTANDING AMOUNT FOR AP IN CASH BASED ACCOUNTING
1285      -- R12 we will have variance on a separate distribution and hence we do not need to determine the
1286      -- variance amount.
1287      -- only in case of amount based po we may have amount variance on the same distribution
1288      -- as item and hence we can return the amount variance value back here.
1289      return  nvl(p_amt_var,0) ;
1290 
1291 END get_inv_var;
1292 
1293 /*Introduced for bug 5946201*/
1294 FUNCTION Is_eIB_item     ( p_po_dist_id      IN   NUMBER
1295                           ) RETURN VARCHAR2 IS
1296  l_flag  varchar2(1) := 'N';
1297 BEGIN
1298  select distinct msi.comms_nl_trackable_flag,nvl(pod.accrue_on_receipt_flag,'N')
1299  into l_flag,g_accrue_on_receipt_flag
1300  from
1301  mtl_system_items msi ,
1302  po_distributions_all pod,
1303  po_lines_all pol
1304  where
1305  msi.inventory_item_id=pol.item_id
1306  and pol.po_line_id=pod.po_line_id
1307  and pod.po_distribution_id = p_po_dist_id;
1308 
1309 
1310  Return l_flag;
1311 
1312 EXCEPTION
1313   WHEN OTHERS THEN
1314 
1315    RETURN 'N' ;
1316 
1317 END Is_eIB_item;
1318 
1319 
1320 END PA_CMT_UTILS;