DBA Data[Home] [Help]

PACKAGE BODY: APPS.PA_CMT_UTILS

Source


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