DBA Data[Home] [Help]

PACKAGE BODY: APPS.PA_DEDUCTIONS

Source


1 PACKAGE BODY PA_DEDUCTIONS AS
2 -- /* $Header: PADEDTXB.pls 120.0.12020000.2 2012/07/19 09:33:01 admarath ship $
3 
4   TYPE g_dctn_hdr_amt IS RECORD (
5              p_dctn_hdr_id  NUMBER,
6              p_total_amount NUMBER);
7 
8   TYPE g_dctn_hdrtbl_amt IS TABLE OF g_dctn_hdr_amt INDEX BY BINARY_INTEGER;
9 
10   g_api_name      VARCHAR2(30);
11   P_DEBUG_MODE varchar2(1) := NVL(FND_PROFILE.value('PA_DEBUG_MODE'), 'N');
12 
13   -- This procedure is for logging debug messages so as to debug the code
14   -- in case of any unknown issues that occur during the entire cycle of
15   -- a deduction request.
16 
17   Procedure log_message (p_log_msg IN VARCHAR2,p_proc_name VARCHAR2)  ;
18 
19 
20   -- This procedure is to backout the interface table data in case of
21   -- any issues during the payables import process.
22 
23   Procedure Delete_Failed_Rec(p_dctn_req_id NUMBER);
24 
25 
26   -- This function verifies if the debit memo number has been provided by user
27   -- and if not, it calls client extension to generate the debit memo number.
28   -- If the client extension does not return any value, this function generates
29   -- and returns a unique sequence number which does not exists in the system.
30 
31   Function Validate_DM( p_dctn_hdr       IN OUT NOCOPY g_dctn_hdrtbl
32                        ,p_msg_count      OUT NOCOPY NUMBER
33                        ,p_msg_data       OUT NOCOPY VARCHAR2
34                        ,p_return_status  OUT NOCOPY VARCHAR2) Return Boolean;
35 
36 
37   -- This procedure is to accept the error codes and token values so as to push
38   -- any error to stack. This is being called from various procedures to store
39   -- error messages in error stack.
40 
41   Procedure AddError_To_Stack( p_error_code VARCHAR2
42                               ,p_hdr_or_txn VARCHAR2 := 'H' -- H->Header, D->Detail
43                               ,p_token1_val VARCHAR2 :=''
44                               ,p_token2_val VARCHAR2 :=''
45                               ,p_token3_val VARCHAR2 :=''
46                               ,p_token4_val VARCHAR2 :='');
47 
48   -- This procedure is to create entry into ap_invoices_interface table.
49   Procedure Create_Invoice_Header (
50         p_deduction_req_id       IN  NUMBER
51        ,p_invoice_id             IN  NUMBER
52        ,p_invoice_num            IN  VARCHAR2
53        ,p_invoice_date           IN  DATE
54        ,p_vendor_id              IN  NUMBER
55        ,p_vendor_site_id         IN  NUMBER
56        ,p_invoice_amount         IN  NUMBER
57        ,p_invoice_currency_code  IN  VARCHAR2
58        ,p_exchange_rate          IN  NUMBER
59        ,p_exchange_rate_type     IN  VARCHAR2
60        ,p_exchange_date          IN  DATE
61        ,p_description            IN  VARCHAR2
62        ,p_tax_flag               IN  VARCHAR2
63        ,p_org_id                 IN  NUMBER );
64 
65   -- This procedure is to create entries into ap_invoice_lines_interface
66   Procedure Create_Invoice_Line (
67         p_invoice_id            IN  NUMBER
68        ,p_amount                IN  NUMBER
69        ,p_accounting_date       IN  DATE
70        ,p_project_id            IN  NUMBER
71        ,p_task_id               IN  NUMBER
72        ,p_expenditure_item_date IN  DATE
73        ,p_expenditure_type      IN  VARCHAR2
74        ,p_expenditure_org       IN  NUMBER
75        ,p_project_acct_context  IN  VARCHAR2
76        ,p_description           IN  VARCHAR2
77        ,p_qty_invoiced          IN  NUMBER
78        ,p_org_id                IN  NUMBER );
79 
80   -- This procedure is to initiate the import process for the specific
81   -- debit memo on successful creation of data in ap interface tables.
82  /* Bug 8740525 sosharma commented and moved to specification
83  Procedure Import_DebitMemo(p_dctn_req_id NUMBER
84                             ,p_msg_count OUT NOCOPY NUMBER
85                             ,p_msg_data  OUT NOCOPY VARCHAR2
86                             ,p_return_status OUT NOCOPY VARCHAR2
87                             );*/
88 
89   -- This procedure is to update the deduction request document status
90   -- in the whole cycle of creation of a deduction request to the creation
91   -- debit memo for that deduction request in payables.
92   Procedure Update_Deduction_Status(p_dctn_hdr_id IN PA_DEDUCTIONS_ALL.deduction_req_id%TYPE,
93                                     p_status      IN VARCHAR2);
94 
95   /*---------------------------------------------------------------------------------------------------------
96     -- This procedure populates PA_DEDUCTIONS_ALL table after validating the data.
97     -- Input parameters
98     -- Parameters                Type           Required  Description
99     --  p_dctn_hdr               TABLE          YES       It stores the deduction header information
100     -- Out parameters
101     -- Parameters                Type           Required  Description
102     --  p_return_status          VARCHAR2       YES       The return status of the APIs.
103     --                                                    Valid values are:
104     --                                                    S (API completed successfully),
105     --                                                    E (business rule violation error) and
106     --                                                    U(Unexpected error, such as an Oracle error.
107     --  p_msg_count              NUMBER         YES       Holds the number of messages in the global message
108                                                           table. Calling programs should use this as the
109                                                           basis to fetch all the stored messages.
110     --  p_msg_data               VARCHAR2       YES       Holds the message code, if the API returned only
111                                                           one error/warning message Otherwise the column is
112                                                           left blank.
113     --  p_calling_mode           VARCHAR2       YES       Holds whether the call is being made from public
114                                                           API or from the create deductions page. This is to
115                                                           enforce additional validations in case if this is
116                                                           called from Public API.
117   ----------------------------------------------------------------------------------------------------------*/
118   Procedure Create_Deduction_Hdr(p_dctn_hdr      IN OUT NOCOPY g_dctn_hdrtbl,
119                                  p_msg_count     OUT NOCOPY  NUMBER,
120                                  p_msg_data      OUT NOCOPY  VARCHAR2,
121                                  p_return_status OUT NOCOPY  VARCHAR2,
122                                  p_calling_mode  IN          VARCHAR2) Is
123 
124   INVALID_DATA EXCEPTION;
125   PRAGMA EXCEPTION_INIT(INVALID_DATA,-20001);
126 
127   l_dctn_hdr   g_dctn_hdrtbl;
128 
129   CURSOR C1(ded_id IN NUMBER) is
130   select 'Y' from dual where not exists(select 1 from pa_deductions_all
131   where deduction_req_id=ded_id);
132 
133   notexist VARCHAR2(1);
134 
135   Begin
136 
137      g_api_name := 'Create_Deduction_Hdr';
138 
139      IF P_DEBUG_MODE = 'Y' THEN
140       log_message ('In Create deduction header procedure', g_api_name);
141      END IF;
142 
143      p_return_status :='S';
144      l_dctn_hdr.delete;
145      FND_MSG_PUB.initialize;
146 
147      For i In 1..p_dctn_hdr.COUNT Loop
148        l_dctn_hdr(i) := p_dctn_hdr(i);
149 
150        IF P_DEBUG_MODE = 'Y' THEN
151          log_message ('Before calling validate header proc: '||l_dctn_hdr(i).deduction_req_id,
152                       g_api_name);
153        END IF;
154 
155 OPEN C1(p_dctn_hdr(i).deduction_req_id);
156 FETCH C1 INTO notexist;
157 CLOSE C1;
158 
159 IF notexist = 'Y' THEN
160        If Validate_Deduction_Hdr(l_Dctn_Hdr,P_msg_count, p_msg_data,p_return_status) Then
161          p_dctn_hdr(i) := l_Dctn_Hdr(i);
162 
163          IF P_DEBUG_MODE = 'Y' THEN
164            log_message ('Before inserting into header', g_api_name);
165          END IF;
166 
167          INSERT INTO PA_DEDUCTIONS_ALL(
168                         deduction_req_id
169                        ,project_id
170                        ,vendor_id
171                        ,vendor_site_id
172                        ,change_doc_num
173                        ,change_doc_type
174                        ,ci_id
175                        ,po_number
176                        ,po_header_id
177                        ,deduction_req_num
178                        ,debit_memo_num
179                        ,currency_code
180                        ,conversion_ratetype
181                        ,conversion_ratedate
182                        ,conversion_rate
183                        ,total_amount
184                        ,total_pfc_amount
185                        ,deduction_req_date
186                        ,debit_memo_date
187                        ,description
188                        ,status
189                        ,document_type
190                        ,org_id
191                        ,creation_date
192                        ,created_by        )
193                    SELECT
194                        p_dctn_hdr(i).deduction_req_id
195                       ,p_dctn_hdr(i).project_id
196                       ,p_dctn_hdr(i).vendor_id
197                       ,p_dctn_hdr(i).vendor_site_id
198                       ,p_dctn_hdr(i).change_doc_num
199                       ,p_dctn_hdr(i).change_doc_type
200                       ,p_dctn_hdr(i).ci_id
201                       ,p_dctn_hdr(i).po_number
202                       ,p_dctn_hdr(i).po_header_id
203                       ,p_dctn_hdr(i).deduction_req_num
204                       ,p_dctn_hdr(i).debit_memo_num
205                       ,p_dctn_hdr(i).currency_code
206                       ,p_dctn_hdr(i).conversion_ratetype
207                       ,p_dctn_hdr(i).conversion_ratedate
208                       ,p_dctn_hdr(i).conversion_rate
209                       ,0
210                       ,0
211                       ,p_dctn_hdr(i).deduction_req_date
212                       ,p_dctn_hdr(i).debit_memo_date
213                       ,p_dctn_hdr(i).description
214                       ,p_dctn_hdr(i).status
215                       ,DECODE(p_dctn_hdr(i).ci_id, NULL,'M','C')
216                       ,p_dctn_hdr(i).org_id
217                       ,SYSDATE
218                       ,g_user_id FROM DUAL;
219            p_return_status :='S';
220        End If;
221      END IF;
222      End Loop;
223   EXCEPTION
224     WHEN OTHERS THEN
225          p_msg_count:=1;
226          p_msg_data:=SQLERRM;
227          p_return_status := 'U';
228   End;
229 
230   /*---------------------------------------------------------------------------------------------------------
231     -- This procedure populates PA_DEDUCTION_TRANSACTIONS_ALL table after validating the data.
232     -- Input parameters
233     -- Parameters                Type           Required  Description
234     --  p_dctn_dtl               TABLE          YES       It stores the deduction transactions information
235     -- Out parameters
236     -- Parameters                Type           Required  Description
237     --  p_return_status          VARCHAR2       YES       The return status of the APIs.
238     --                                                    Valid values are:
239     --                                                    S (API completed successfully),
240     --                                                    E (business rule violation error) and
241     --                                                    U(Unexpected error, such as an Oracle error.
242     --  p_msg_count              NUMBER         YES       Holds the number of messages in the global message
243                                                           table. Calling programs should use this as the
244                                                           basis to fetch all the stored messages.
245     --  p_msg_data               VARCHAR2       YES       Holds the message code, if the API returned only
246                                                           one error/warning message Otherwise the column is
247                                                           left blank.
248     --  p_calling_mode           VARCHAR2       YES       Holds whether the call is being made from public
249                                                           API or from the create deductions page. This is to
250                                                           enforce additional validations in case if this is
251                                                           called from Public API.
252   ----------------------------------------------------------------------------------------------------------*/
253   Procedure Create_Deduction_Txn(p_dctn_dtl      IN OUT NOCOPY g_dctn_txntbl,
254                                  p_msg_count     OUT NOCOPY	NUMBER,
255                                  p_msg_data	     OUT NOCOPY VARCHAR2,
256                                  p_return_status OUT NOCOPY VARCHAR2,
257                                  p_calling_mode  IN         VARCHAR2) Is
258     INVALID_DATA EXCEPTION ;
259     PRAGMA EXCEPTION_INIT(INVALID_DATA,-20001);
260 
261     l_dctn_hdrtbl g_dctn_hdrtbl_amt;
262     l_dctn_hdrcnt NUMBER :=0;
263     l_dctn_hdrfnd VARCHAR2(1) :='N';
264     l_dctn_hdrid  NUMBER;
265     l_rec_no      NUMBER;
266     l_dctn_tbl_hdrid  g_dctn_hdrid; --Bug# 8877035
267 
268   Begin
269 
270    g_api_name := 'Create_Deduction_Txn';
271 
272    IF P_DEBUG_MODE = 'Y' THEN
273       log_message ('In Create deduction transaction ', g_api_name);
274    END IF;
275 
276    p_return_status :='S';
277    FND_MSG_PUB.initialize;
278 
279    IF P_DEBUG_MODE = 'Y' THEN
280      log_message ('Before calling validate detail transaction', g_api_name);
281    END IF;
282 
283    IF p_dctn_dtl.COUNT >0 THEN
284     If Validate_Deduction_Txn(P_Dctn_Dtl,P_msg_count, p_msg_data,p_return_status) Then
285      IF p_msg_data IS NULL THEN
286         For i In p_dctn_dtl.FIRST..p_dctn_dtl.LAST Loop
287 
288          IF l_dctn_hdrcnt = 0 THEN
289             l_dctn_hdrcnt := l_dctn_hdrcnt +1;
290             l_dctn_hdrid  := p_dctn_dtl(i).deduction_req_id;
291             l_dctn_hdrtbl(l_dctn_hdrcnt).p_dctn_hdr_id := p_dctn_dtl(i).deduction_req_id;
292             l_dctn_tbl_hdrid(l_dctn_hdrcnt) := p_dctn_dtl(i).deduction_req_id; --Bug# 8877035
293             l_dctn_hdrtbl(l_dctn_hdrcnt).p_total_amount :=0;
294          ELSE
295            IF nvl(l_dctn_hdrid,-99) <> p_dctn_dtl(i).deduction_req_id THEN
296               l_dctn_hdrid  := p_dctn_dtl(i).deduction_req_id;
297               l_dctn_hdrfnd := 'N';
298               l_rec_no := 0;
299                FOR J in 1..l_dctn_hdrtbl.COUNT LOOP
300                IF l_dctn_hdrtbl(J).p_dctn_hdr_id = p_dctn_dtl(i).deduction_req_id THEN
301                  l_dctn_hdrfnd := 'Y';
302                  l_rec_no := J;
303                  EXIT;
304                END IF; END LOOP;
305                IF l_dctn_hdrfnd = 'N' THEN
306                   l_dctn_hdrcnt := l_dctn_hdrcnt +1;
307                   l_dctn_hdrtbl(l_dctn_hdrcnt).p_dctn_hdr_id := p_dctn_dtl(i).deduction_req_id;
308                   l_dctn_tbl_hdrid(l_dctn_hdrcnt) := p_dctn_dtl(i).deduction_req_id; --Bug# 8877035
309                   l_dctn_hdrtbl(l_dctn_hdrcnt).p_total_amount :=0;
310                END IF;
311            END IF;
312          END IF;
313 
314          IF P_DEBUG_MODE = 'Y' THEN
315             log_message ('Before inserting into deduction transaction ', g_api_name);
316          END IF;
317 
318          INSERT INTO PA_DEDUCTION_TRANSACTIONS_ALL (
319                       deduction_req_id
320                      ,deduction_req_tran_id
321                      ,project_id
322                      ,task_id
323                      ,expenditure_type
324                      ,expenditure_org_id
325                      ,quantity
326                      ,override_quantity
327                      ,expenditure_item_id
328                      ,projfunc_currency_code
329                      ,orig_projfunc_amount
330                      ,override_projfunc_amount
331                      ,conversion_ratetype
332                      ,conversion_ratedate
333                      ,conversion_rate
334                      ,amount
335                      ,expenditure_item_date
336                      ,gl_date
337                      ,creation_date
338                      ,created_by
339                      ,description
340                      )
341                   SELECT
342                       p_dctn_dtl(i).deduction_req_id
343                      ,PA_DEDUCTION_TXNS_S.nextval
344                      ,p_dctn_dtl(i).project_id
345                      ,p_dctn_dtl(i).task_id
346                      ,p_dctn_dtl(i).expenditure_type
347                      ,p_dctn_dtl(i).expenditure_org_id
348                      ,p_dctn_dtl(i).quantity
349                      ,nvl(p_dctn_dtl(i).override_quantity,p_dctn_dtl(i).quantity)
350                      ,p_dctn_dtl(i).expenditure_item_id
351                      ,p_dctn_dtl(i).projfunc_currency_code
352                      ,p_dctn_dtl(i).orig_projfunc_amount
353                      ,nvl(p_dctn_dtl(i).override_projfunc_amount,p_dctn_dtl(i).orig_projfunc_amount)
354                      ,p_dctn_dtl(i).conversion_ratetype
355                      ,p_dctn_dtl(i).conversion_ratedate
356                      ,p_dctn_dtl(i).conversion_rate
357                      ,p_dctn_dtl(i).amount
358                      ,p_dctn_dtl(i).expenditure_item_date
359                      ,p_dctn_dtl(i).expenditure_item_date
360                      ,SYSDATE
361                      ,g_user_id
362                      ,p_dctn_dtl(i).description FROM DUAL WHERE p_dctn_dtl(i).status IS NULL;
363 
364         End Loop;
365 
366        IF P_DEBUG_MODE = 'Y' THEN
367          log_message ('Before updating the total amount on header ', g_api_name);
368        END IF;
369 
370         /* Bug#8877035, used pl/sql table of column type instead of record type
371            to aviod the restrictions in 10g, 9i databases */
372 
373         FORALL I in 1..l_dctn_tbl_hdrid.COUNT --l_dctn_hdrtbl.COUNT
374         UPDATE PA_DEDUCTIONS_ALL SET total_amount = nvl((
375                                  SELECT SUM(amount) FROM
376                                  PA_DEDUCTION_TRANSACTIONS_ALL
377                                  WHERE deduction_req_id = l_dctn_tbl_hdrid(i) --l_dctn_hdrtbl(i).p_dctn_hdr_id
378                                   ),0) ,
379                                      total_pfc_amount = nvl((
380                                         SELECT
381                                       SUM(nvl(override_projfunc_amount,orig_projfunc_amount)) FROM
382                                      PA_DEDUCTION_TRANSACTIONS_ALL
383                                      WHERE deduction_req_id = l_dctn_tbl_hdrid(i)
384                                   ),0)
385         WHERE deduction_req_id = l_dctn_tbl_hdrid(i);--l_dctn_hdrtbl(i).p_dctn_hdr_id;
386 
387         p_return_status :='S';
388      END IF;
389     End If;
390    END IF;
391   EXCEPTION
392     WHEN OTHERS THEN
393          IF P_DEBUG_MODE = 'Y' THEN
394            log_message ('In Others Exception: '||SQLERRM, g_api_name);
395          END IF;
396 
397          p_msg_count:=1;
398          p_msg_data:=SQLERRM;
399          p_return_status := 'U';
400   End;
401 
402   /*---------------------------------------------------------------------------------------------------------
403     -- This procedure is to update existing data in PA_DEDUCTIONS_ALL table after validating the data.
404     -- Input parameters
405     -- Parameters                Type           Required  Description
406     --  p_dctn_hdr               TABLE          YES       It stores the deduction header information
407     -- Out parameters
408     -- Parameters                Type           Required  Description
409     --  p_return_status          VARCHAR2       YES       The return status of the APIs.
410     --                                                    Valid values are:
411     --                                                    S (API completed successfully),
412     --                                                    E (business rule violation error) and
413     --                                                    U(Unexpected error, such as an Oracle error.
414     --  p_msg_count              NUMBER         YES       Holds the number of messages in the global message
415                                                           table. Calling programs should use this as the
416                                                           basis to fetch all the stored messages.
417     --  p_msg_data               VARCHAR2       YES       Holds the message code, if the API returned only
418                                                           one error/warning message Otherwise the column is
419                                                           left blank.
420     --  p_calling_mode           VARCHAR2       YES       Holds whether the call is being made from public
421                                                           API or from the create deductions page. This is to
422                                                           enforce additional validations in case if this is
423                                                           called from Public API.
424   ----------------------------------------------------------------------------------------------------------*/
425   Procedure Update_Deduction_Hdr( p_dctn_hdr      IN OUT NOCOPY g_dctn_hdrtbl
426                                  ,p_msg_count     OUT NOCOPY  NUMBER
427                                  ,p_msg_data      OUT NOCOPY  VARCHAR2
428                                  ,p_return_status OUT NOCOPY  VARCHAR2
429                                  ,p_calling_mode  IN          VARCHAR2) Is
430     l_dctn_hdr   g_dctn_hdrtbl;
431   Begin
432 
433     g_api_name := 'Update_Deduction_Hdr';
434     p_return_status :='S';
435     FND_MSG_PUB.initialize;
436 
437     IF P_DEBUG_MODE = 'Y' THEN
438        log_message ('In Update deduction header procedure',g_api_name);
439     END IF;
440 
441     IF p_dctn_hdr.COUNT >0 THEN
442      FOR I IN p_dctn_hdr.FIRST..p_dctn_hdr.LAST LOOP
443        l_dctn_hdr(i) := p_dctn_hdr(i);
444 
445        IF P_DEBUG_MODE = 'Y' THEN
446          log_message ('Before calling validate header proc: '||l_dctn_hdr(i).deduction_req_id,
447                       g_api_name);
448        END IF;
449 
450        If Validate_Deduction_Hdr(l_Dctn_Hdr,P_msg_count, p_msg_data,p_return_status) Then
451           UPDATE pa_deductions_all
452           SET     debit_memo_num        =  p_dctn_hdr(I).debit_memo_num
453                  ,debit_memo_date       =  p_dctn_hdr(I).debit_memo_date
454                  ,conversion_ratetype   =  p_dctn_hdr(I).conversion_ratetype
455                  ,conversion_ratedate   =  p_dctn_hdr(I).conversion_ratedate
456                  ,conversion_rate       =  p_dctn_hdr(I).conversion_rate
457                  ,total_amount          =  nvl(p_dctn_hdr(I).total_amount,nvl(total_amount,0))
458                  ,description           =  p_dctn_hdr(I).description
459                  ,status                =  'WORKING'
460                  ,last_updated_by       =  g_user_id
461                  ,last_updation_date    =  SYSDATE
462           WHERE  deduction_req_id = p_dctn_hdr(I).deduction_req_id;
463        End If;
464      END LOOP;
465     END IF;
466   EXCEPTION
467     WHEN OTHERS THEN
468        IF P_DEBUG_MODE = 'Y' THEN
469          log_message ('In Others Exception :'||SQLERRM, g_api_name);
470        END IF;
471 
472         p_msg_count:=1;
473         p_msg_data:=SQLERRM;
474         p_return_status := 'U';
475   End;
476 
477   /*---------------------------------------------------------------------------------------------------------
478     -- This procedure is to update existing data in PA_DEDUCTION_TRANSACTIONS_ALL table after
479     -- validating the data.
480     -- Input parameters
481     -- Parameters                Type           Required  Description
482     --  p_dctn_dtl               TABLE          YES       It stores the deduction transactions information
483     -- Out parameters
484     -- Parameters                Type           Required  Description
485     --  p_return_status          VARCHAR2       YES       The return status of the APIs.
486     --                                                    Valid values are:
487     --                                                    S (API completed successfully),
488     --                                                    E (business rule violation error) and
489     --                                                    U(Unexpected error, such as an Oracle error.
490     --  p_msg_count              NUMBER         YES       Holds the number of messages in the global message
491                                                           table. Calling programs should use this as the
492                                                           basis to fetch all the stored messages.
493     --  p_msg_data               VARCHAR2       YES       Holds the message code, if the API returned only
494                                                           one error/warning message Otherwise the column is
495                                                           left blank.
496     --  p_calling_mode           VARCHAR2       YES       Holds whether the call is being made from public
497                                                           API or from the create deductions page. This is to
498                                                           enforce additional validations in case if this is
499                                                           called from Public API.
500   ----------------------------------------------------------------------------------------------------------*/
501   Procedure Update_Deduction_Txn( p_dctn_dtl IN OUT NOCOPY g_dctn_txntbl
502                                  ,p_msg_count OUT NOCOPY	NUMBER
503                                  ,p_msg_data	 OUT NOCOPY	VARCHAR2
504                                  ,p_return_status OUT NOCOPY VARCHAR2
505                                  ,p_calling_mode IN VARCHAR2) Is
506    l_dctn_hdrtbl g_dctn_hdrtbl_amt;
507    l_dctn_hdrcnt NUMBER :=0;
508    l_dctn_hdrfnd VARCHAR2(1) :='N';
509    l_dctn_hdrid  NUMBER;
510    l_dctn_tbl_hdrid  g_dctn_hdrid; -- Bug# 8877035
511   Begin
512     g_api_name := 'Update_Deduction_Txn';
513     IF P_DEBUG_MODE = 'Y' THEN
514        log_message ('In Update deduction transaction procedure',g_api_name);
515     END IF;
516 
517     p_return_status :='S';
518     FND_MSG_PUB.initialize;
519 
520     IF p_dctn_dtl.COUNT > 0 THEN
521      IF P_DEBUG_MODE = 'Y' THEN
522        log_message ('Before calling validate deduction transaction procedure',g_api_name);
523      END IF;
524 
525      If Validate_Deduction_Txn(P_Dctn_Dtl,P_msg_count, p_msg_data,p_return_status) Then
526        FOR I IN p_dctn_dtl.FIRST..p_dctn_dtl.LAST LOOP
527         IF P_DEBUG_MODE = 'Y' THEN
528          log_message ('Storing distinct deduction header values in a plsql table',g_api_name);
529         END IF;
530 
531        IF l_dctn_hdrcnt = 0 THEN
532           l_dctn_hdrcnt := l_dctn_hdrcnt +1;
533           l_dctn_hdrid  := p_dctn_dtl(i).deduction_req_id;
534           l_dctn_hdrtbl(l_dctn_hdrcnt).p_dctn_hdr_id := p_dctn_dtl(i).deduction_req_id;
535           l_dctn_tbl_hdrid(l_dctn_hdrcnt) := p_dctn_dtl(i).deduction_req_id;-- Bug# 8877035
536           l_dctn_hdrtbl(l_dctn_hdrcnt).p_total_amount :=0;
537        ELSE
538          IF nvl(l_dctn_hdrid,-99) <> p_dctn_dtl(i).deduction_req_id THEN
539             l_dctn_hdrid  := p_dctn_dtl(i).deduction_req_id;
540             l_dctn_hdrfnd := 'N';
541              FOR J in 1..l_dctn_hdrtbl.COUNT LOOP
542              IF l_dctn_hdrtbl(J).p_dctn_hdr_id = p_dctn_dtl(i).deduction_req_id THEN
543                l_dctn_hdrfnd := 'Y';
544                EXIT;
545              END IF; END LOOP;
546              IF l_dctn_hdrfnd = 'N' THEN
547                 l_dctn_hdrcnt := l_dctn_hdrcnt +1;
548                 l_dctn_tbl_hdrid(l_dctn_hdrcnt) := p_dctn_dtl(i).deduction_req_id; -- Bug# 8877035
549                 l_dctn_hdrtbl(l_dctn_hdrcnt).p_dctn_hdr_id := p_dctn_dtl(i).deduction_req_id;
550                 l_dctn_hdrtbl(l_dctn_hdrcnt).p_total_amount :=0;
551              END IF;
552          END IF;
553        END IF;
554        IF P_DEBUG_MODE = 'Y' THEN
555          log_message ('Before updating the deduction transaction table',g_api_name);
556        END IF;
557 
558        UPDATE pa_deduction_transactions_all
559        SET      task_id                  =  p_dctn_dtl(i).task_id
560                ,expenditure_type         =  p_dctn_dtl(i).expenditure_type
561                ,expenditure_org_id       =  p_dctn_dtl(i).expenditure_org_id
562                ,quantity                 =  p_dctn_dtl(i).quantity
563                ,override_quantity        =  nvl(p_dctn_dtl(i).override_quantity,p_dctn_dtl(i).quantity)
564                ,projfunc_currency_code   =  p_dctn_dtl(i).projfunc_currency_code
565                ,orig_projfunc_amount     =  p_dctn_dtl(i).orig_projfunc_amount
566                ,override_projfunc_amount =  nvl(p_dctn_dtl(i).override_projfunc_amount,
567                                                 p_dctn_dtl(i).orig_projfunc_amount)
568                ,conversion_ratetype      =  p_dctn_dtl(i).conversion_ratetype
569                ,conversion_ratedate      =  p_dctn_dtl(i).conversion_ratedate
570                ,conversion_rate          =  p_dctn_dtl(i).conversion_rate
571                ,expenditure_item_date    =  p_dctn_dtl(i).expenditure_item_date
572                ,amount                   =  p_dctn_dtl(i).amount
573                ,description              =  p_dctn_dtl(i).description
574                ,last_updated_by          =  g_user_id
575                ,last_updation_date       =  SYSDATE
576        WHERE  deduction_req_tran_id = p_dctn_dtl(I).deduction_req_tran_id; END LOOP;
577        IF P_DEBUG_MODE = 'Y' THEN
578         log_message ('Updating total amount in the header table',g_api_name);
579        END IF;
580 
581         /* Bug#8877035, used pl/sql table of column type instead of record type
582            to aviod the restrictions in 10g, 9i databases */
583 
584         FORALL I in 1..l_dctn_tbl_hdrid.COUNT
585         UPDATE PA_DEDUCTIONS_ALL SET total_amount = nvl((
586                                  SELECT SUM(amount) FROM
587                                  PA_DEDUCTION_TRANSACTIONS_ALL
588                                  WHERE deduction_req_id = l_dctn_tbl_hdrid(i) --l_dctn_hdrtbl(i).p_dctn_hdr_id
589                                   ),0),
590                                          total_pfc_amount = nvl((
591                                      SELECT SUM(nvl(override_projfunc_amount,orig_projfunc_amount)) FROM
592                                      PA_DEDUCTION_TRANSACTIONS_ALL
593                                      WHERE deduction_req_id = l_dctn_tbl_hdrid(i)
594                                      ),0)
595         WHERE deduction_req_id = l_dctn_tbl_hdrid(i);--l_dctn_hdrtbl(i).p_dctn_hdr_id;
596 
597      End If;
598     END IF;
599   EXCEPTION
600     WHEN OTHERS THEN
601          p_msg_count:=1;
602          p_msg_data:=SQLERRM;
603          p_return_status := 'U';
604   End;
605 
606   /*---------------------------------------------------------------------------------------------------------
607     -- This procedure is to delete existing data in PA_DEDUCTIONS_ALL table after validating the data.
608     -- Input parameters
609     -- Parameters                Type           Required  Description
610     --  p_dctn_hdrid             TABLE          YES       It stores the array of deducion requests
611     -- Out parameters
612     -- Parameters                Type           Required  Description
613     --  p_return_status          VARCHAR2       YES       The return status of the APIs.
614     --                                                    Valid values are:
615     --                                                    S (API completed successfully),
616     --                                                    E (business rule violation error) and
617     --                                                    U(Unexpected error, such as an Oracle error.
618     --  p_msg_count              NUMBER         YES       Holds the number of messages in the global message
619                                                           table. Calling programs should use this as the
620                                                           basis to fetch all the stored messages.
621     --  p_msg_data               VARCHAR2       YES       Holds the message code, if the API returned only
622                                                           one error/warning message Otherwise the column is
623                                                           left blank.
624   ----------------------------------------------------------------------------------------------------------*/
625   Procedure Delete_Deduction_Hdr( p_dctn_hdrid g_dctn_hdrid
626                                  ,p_msg_count OUT NOCOPY NUMBER
627                                  ,p_msg_data  OUT NOCOPY VARCHAR2
628                                  ,p_return_status OUT NOCOPY VARCHAR2
629                                 ) Is
630   Begin
631     g_api_name := 'Delete_Deduction_Hdr';
632     FND_MSG_PUB.initialize;
633     p_return_status :='S';
634 
635     IF P_DEBUG_MODE = 'Y' THEN
636        log_message ('In Delete deduction header procedure',g_api_name);
637     END IF;
638 
639     IF P_DEBUG_MODE = 'Y' THEN
640        log_message ('Before deleting the header information',g_api_name);
641     END IF;
642 
643     FORALL I IN 1..p_dctn_hdrid.COUNT
644     DELETE PA_DEDUCTIONS_ALL WHERE deduction_req_id = p_dctn_hdrid(I) AND status NOT IN('PROCESSED','SUBMITTED');
645 
646      IF P_DEBUG_MODE = 'Y' THEN
647        log_message ('Before deleting the transaction information',g_api_name);
648      END IF;
649 
650     FORALL I IN 1..p_dctn_hdrid.COUNT
651     DELETE PA_DEDUCTION_TRANSACTIONS_ALL WHERE deduction_req_id = p_dctn_hdrid(I) AND NOT EXISTS(
652            SELECT 1 FROM PA_DEDUCTIONS_ALL WHERE deduction_req_id = p_dctn_hdrid(I) );
653     --Commit;
654   EXCEPTION
655     WHEN OTHERS THEN
656        IF P_DEBUG_MODE = 'Y' THEN
657          log_message ('In Others Exception: '||SQLERRM,g_api_name);
658        END IF;
659        p_msg_count:=1;
660        p_msg_data:=SQLERRM;
661        p_return_status := 'U';
662   End;
663 
664   /*---------------------------------------------------------------------------------------------------------
665     -- This procedure is to delete existing data in PA_DEDUCTION_TRANSACTIONS_ALL table
666     -- after validating the data.
667     -- Input parameters
668     -- Parameters                Type           Required  Description
669     --  p_dctn_txnid             TABLE          YES       It stores the array of deducion request transactions
670     -- Out parameters
671     -- Parameters                Type           Required  Description
672     --  p_return_status          VARCHAR2       YES       The return status of the APIs.
673     --                                                    Valid values are:
674     --                                                    S (API completed successfully),
675     --                                                    E (business rule violation error) and
676     --                                                    U(Unexpected error, such as an Oracle error.
677     --  p_msg_count              NUMBER         YES       Holds the number of messages in the global message
678                                                           table. Calling programs should use this as the
679                                                           basis to fetch all the stored messages.
680     --  p_msg_data               VARCHAR2       YES       Holds the message code, if the API returned only
681                                                           one error/warning message Otherwise the column is
682                                                           left blank.
683   ----------------------------------------------------------------------------------------------------------*/
684   Procedure Delete_Deduction_Txn( p_dctn_txnid g_dctn_txnid
685                                  ,p_msg_count OUT NOCOPY NUMBER
686                                  ,p_msg_data  OUT NOCOPY VARCHAR2
687                                  ,p_return_status OUT NOCOPY VARCHAR2
688                                 ) Is
689   Begin
690     g_api_name := 'Delete_Deduction_Txn';
691     p_return_status :='S';
692     FND_MSG_PUB.initialize;
693 
694     IF P_DEBUG_MODE = 'Y' THEN
695        log_message ('In Delete deduction transaction procedure',g_api_name);
696        log_message ('Deducting the respective transaction amount from header',g_api_name);
697     END IF;
698 
699     FORALL I IN 1..p_dctn_txnid.COUNT
700     UPDATE PA_DEDUCTIONS_ALL dctn_hdr SET total_amount = total_amount-nvl(
701             (SELECT amount FROM PA_DEDUCTION_TRANSACTIONS_ALL dctn_txn
702              WHERE deduction_req_tran_id = p_dctn_txnid(I)
703              AND deduction_req_id = dctn_hdr.deduction_req_id
704              AND EXISTS (
705              SELECT 1 FROM PA_DEDUCTIONS_ALL WHERE deduction_req_id = dctn_txn.deduction_req_id
706              AND status NOT IN('PROCESSED','SUBMITTED','APPROVED'))),0);
707     IF P_DEBUG_MODE = 'Y' THEN
708         log_message ('Deleting the data from transaction table',g_api_name);
709     END IF;
710 
711     FORALL I IN 1..p_dctn_txnid.COUNT
712     DELETE PA_DEDUCTION_TRANSACTIONS_ALL dctn_txn WHERE deduction_req_tran_id = p_dctn_txnid(I)
713     AND EXISTS (
714            SELECT 1 FROM PA_DEDUCTIONS_ALL WHERE deduction_req_id = dctn_txn.deduction_req_id
715            AND status NOT IN('PROCESSED','SUBMITTED','APPROVED'));
716     --Commit;
717   EXCEPTION
718     WHEN OTHERS THEN
719          IF P_DEBUG_MODE = 'Y' THEN
720            log_message ('In Others Exceptioin :'||SQLERRM,g_api_name);
721          END IF;
722          p_msg_count:=1;
723          p_msg_data:=SQLERRM;
724          p_return_status := 'U';
725   End;
726 
727   /*---------------------------------------------------------------------------------------------------------
728     -- This function is to validate Deduction header information and return the result to the called proc.
729     -- Input parameters
730     -- Parameters                Type           Required  Description
731     --  p_dctn_hdr               TABLE          YES       It stores the deduction header information
732     -- Out parameters
733     -- Parameters                Type           Required  Description
734     --  p_return_status          VARCHAR2       YES       The return status of the APIs.
735     --                                                    Valid values are:
736     --                                                    S (API completed successfully),
737     --                                                    E (business rule violation error) and
738     --                                                    U(Unexpected error, such as an Oracle error.
739     --  p_msg_count              NUMBER         YES       Holds the number of messages in the global message
740                                                           table. Calling programs should use this as the
741                                                           basis to fetch all the stored messages.
742     --  p_msg_data               VARCHAR2       YES       Holds the message code, if the API returned only
743                                                           one error/warning message Otherwise the column is
744                                                           left blank.
745     --  p_calling_mode           VARCHAR2       YES       Holds whether the call is being made from public
746                                                           API or from the create deductions page. This is to
747                                                           enforce additional validations in case if this is
748                                                           called from Public API.
749   ----------------------------------------------------------------------------------------------------------*/
750   Function  Validate_Deduction_Hdr( p_dctn_hdr IN OUT NOCOPY g_dctn_hdrtbl
751                                    ,p_msg_count OUT NOCOPY NUMBER
752                                    ,p_msg_data  OUT NOCOPY VARCHAR2
753                                    ,p_return_status OUT NOCOPY VARCHAR2
754                                    ,p_calling_mode IN VARCHAR2 :=''
755                                   ) Return Boolean Is
756 
757     CURSOR C1(p_dctn_req_num PA_DEDUCTIONS_ALL.deduction_req_num%TYPE,
758               p_dctn_req_id  PA_DEDUCTIONS_ALL.deduction_req_id%TYPE)  is
759       SELECT 'N'
760       FROM   PA_DEDUCTIONS_ALL
761       WHERE  deduction_req_num = p_dctn_req_num
762       AND    deduction_req_id <> p_dctn_req_id;
763 
764     CURSOR C2(p_debit_memo_num PA_DEDUCTIONS_ALL.debit_memo_num%TYPE,
765               p_org_id         PA_DEDUCTIONS_ALL.org_id%TYPE,
766               p_vendor_id      PA_DEDUCTIONS_ALL.vendor_id%TYPE,
767               p_dctn_req_id    PA_DEDUCTIONS_ALL.deduction_req_id%TYPE)  is
768       SELECT 'N'
769       FROM   PA_DEDUCTIONS_ALL
770       WHERE  debit_memo_num = p_debit_memo_num
771       AND    org_id = p_org_id
772       AND    vendor_id = p_vendor_id
773       AND    deduction_req_id <> nvl(p_dctn_req_id,-99);
774 
775     CURSOR C3(p_debit_memo_num PA_DEDUCTIONS_ALL.debit_memo_num%TYPE,
776               p_vendor_id      PA_DEDUCTIONS_ALL.vendor_id%TYPE,
777               p_org_id PA_DEDUCTIONS_ALL.org_id%TYPE)  is
778       SELECT 'N'
779       FROM   DUAL WHERE EXISTS (
780                      SELECT 1
781                      FROM   AP_INVOICES_ALL
782                      WHERE  invoice_num = p_debit_memo_num
783                      AND    vendor_id = p_vendor_id
784                      AND    org_id = p_org_id
785                      UNION ALL
786                      SELECT 1
787                      FROM   AP_INVOICES_INTERFACE
788                      WHERE  invoice_num = p_debit_memo_num
789                      AND    vendor_id = p_vendor_id
790                      AND    org_id = p_org_id
791                      AND    nvl(status, 'REJECTED') <> 'REJECTED');
792 
793     CURSOR C4(p_po_header_id NUMBER) IS
794        SELECT PO_INQ_SV.get_po_total (type_lookup_code,
795                                       po_header_id,
796                                       '') FROM PO_HEADERS_ALL WHERE po_header_id = p_po_header_id;
797 
798     is_dctn_req_unique   VARCHAR2(1) := 'Y';
799     is_debit_memo_unique VARCHAR2(1) := 'Y';
800 
801     l_po_total_amt       NUMBER;
802 
803   Begin
804     g_api_name := 'Validate_Deduction_Hdr';
805     p_return_status := 'S';
806 
807     IF P_DEBUG_MODE = 'Y' THEN
808        log_message ('In validate header procedure',g_api_name);
809     END IF;
810 
811     IF p_dctn_hdr.count > 0 THEN
812        FOR I in p_dctn_hdr.FIRST..p_dctn_hdr.LAST LOOP
813          BEGIN
814            IF P_DEBUG_MODE = 'Y' THEN
815              log_message ('Debit Memo Number '||p_dctn_hdr(i).debit_memo_num||
816                           ' Org '||p_dctn_hdr(i).org_id||
817                           ' Debit Memo Request '||p_dctn_hdr(i).deduction_req_num||
818                           ' Vendor Id '||p_dctn_hdr(i).vendor_id||
819                           ' Deduction req id '||p_dctn_hdr(i).deduction_req_id, g_api_name);
820 
821              log_message ('Validating Uniqueness of deduction request number' ,g_api_name);
822            END IF;
823 
824             OPEN C1(p_dctn_hdr(i).deduction_req_num, p_dctn_hdr(i).deduction_req_id);
825             FETCH C1 INTO is_dctn_req_unique;
826             CLOSE C1;
827               IF is_dctn_req_unique = 'N' THEN
828                  p_return_status := 'E';
829                  p_msg_data := 'PA_DED_REQ_NUM_UNIQ';
830                  is_dctn_req_unique :='Y';
831                  p_dctn_hdr(i).status := 'PA_DREQ_UNIQ';
832                  AddError_To_Stack( p_error_code => 'PA_DED_REQ_NUM_UNIQ'
833                                    ,p_hdr_or_txn => 'H');
834 
835               END IF;
836 
837             IF P_DEBUG_MODE = 'Y' THEN
838              log_message ('Validating Uniqueness of debit memo number' ,g_api_name);
839             END IF;
840 
841             OPEN C2(p_dctn_hdr(i).debit_memo_num, p_dctn_hdr(i).org_id,
842                     p_dctn_hdr(i).vendor_id, p_dctn_hdr(i).deduction_req_id);
843             FETCH C2 INTO is_debit_memo_unique;
844             CLOSE C2;
845               IF is_debit_memo_unique = 'N' THEN
846                  is_debit_memo_unique := 'Y';
847                  IF p_dctn_hdr(i).status IS NULL THEN
848                     p_return_status := 'E';
849                     p_msg_data := 'PA_DEB_MEM_NUM_UNIQ';
850                     p_dctn_hdr(i).status := 'PA_DMNUM_UNIQ';
851                  END IF;
852                  AddError_To_Stack( p_error_code => 'PA_DEB_MEM_NUM_UNIQ'
853                                    ,p_hdr_or_txn => 'H');
854               END IF;
855             IF p_dctn_hdr(i).status <> 'PA_DEB_MEM_NUM_UNIQ' THEN
856               OPEN C3(p_dctn_hdr(i).debit_memo_num,p_dctn_hdr(i).vendor_id, p_dctn_hdr(i).org_id);
857               FETCH C3 INTO is_debit_memo_unique;
858               CLOSE C3;
859               IF is_debit_memo_unique = 'N' THEN
860                  is_debit_memo_unique := 'Y';
861                  IF p_dctn_hdr(i).status IS NULL THEN
862                    p_return_status := 'E';
863                    p_msg_data := 'PA_DEB_MEM_NUM_UNIQ';
864                    p_dctn_hdr(i).status := 'PA_DMNUM_UNIQ';
865                  END IF;
866                  AddError_To_Stack( p_error_code => 'PA_DEB_MEM_NUM_UNIQ'
867                                    ,p_hdr_or_txn => 'H');
868               END IF;
869             END IF;
870 
871             /*
872             IF P_DEBUG_MODE = 'Y' THEN
873                log_message ('Validating PO Amount against deduction request' ,g_api_name);
874             END IF;
875 
876             IF p_dctn_hdr(i).po_header_id IS NOT NULL THEN
877                 OPEN C4(p_dctn_hdr(i).po_header_id);
878                 FETCH C4 INTO l_po_total_amt;
879                 CLOSE C4;
880 
881                 IF nvl(p_dctn_hdr(i).total_amount,0) > nvl(l_po_total_amt,0) THEN
882                    IF p_dctn_hdr(i).status IS NULL THEN
883                       p_return_status := 'E';
884                       p_msg_data := 'PA_DCTN_AMT_EXCEEDS_POAMT';
885                       p_dctn_hdr(i).status := 'PA_DAMT_MORE';
886                    END IF;
887                    AddError_To_Stack( p_error_code => 'PA_DCTN_AMT_EXCEEDS_POAMT'
888                                      ,p_hdr_or_txn => 'H');
889                 END IF;
890             END IF;*/
891 
892          EXCEPTION
893           WHEN OTHERS THEN
894              IF P_DEBUG_MODE = 'Y' THEN
895                log_message ('In Others Exception: '||SQLERRM ,g_api_name);
896              END IF;
897                p_return_status:= 'E';
898                p_msg_data :=SQLCODE;
899                p_msg_count:=1;
900          END;
901          IF p_dctn_hdr(i).status IS NULL THEN
902             p_dctn_hdr(i).status := 'WORKING';
903          END IF;
904 	   END LOOP;
905     END IF;
906     IF p_msg_data IS NOT NULL THEN
907       IF P_DEBUG_MODE = 'Y' THEN
908        log_message ('Validation failed :'||p_msg_data ,g_api_name);
909       END IF;
910        RETURN FALSE;
911     END IF;
912 	RETURN TRUE;
913   End;
914 
915   /*---------------------------------------------------------------------------------------------------------
916     -- This procedure is to validate Deduction header information and return the result to the called proc.
917     -- Input parameters
918     -- Parameters                Type           Required  Description
919     --  p_dctn_dtl               TABLE          YES       It stores deduction request transactions information
920     -- Out parameters
921     -- Parameters                Type           Required  Description
922     --  p_return_status          VARCHAR2       YES       The return status of the APIs.
923     --                                                    Valid values are:
924     --                                                    S (API completed successfully),
925     --                                                    E (business rule violation error) and
926     --                                                    U(Unexpected error, such as an Oracle error.
927     --  p_msg_count              NUMBER         YES       Holds the number of messages in the global message
928                                                           table. Calling programs should use this as the
929                                                           basis to fetch all the stored messages.
930     --  p_msg_data               VARCHAR2       YES       Holds the message code, if the API returned only
931                                                           one error/warning message Otherwise the column is
932                                                           left blank.
933     --  p_calling_mode           VARCHAR2       YES       Holds whether the call is being made from public
934                                                           API or from the create deductions page. This is to
935                                                           enforce additional validations in case if this is
936                                                           called from Public API.
937   ----------------------------------------------------------------------------------------------------------*/
938   Function  Validate_Deduction_Txn( p_dctn_dtl IN OUT NOCOPY g_dctn_txntbl
939                                    ,p_msg_count OUT NOCOPY NUMBER
940                                    ,p_msg_data  OUT NOCOPY VARCHAR2
941                                    ,p_return_status OUT NOCOPY VARCHAR2
942                                    ,p_calling_mode IN VARCHAR2 :=''
943                                   ) Return Boolean Is
944 
945     CURSOR C1(p_dctn_req_id NUMBER) IS
946         SELECT project_id,
947                vendor_id,
948                po_number,
949                deduction_req_date,
950                org_id
951         FROM   PA_DEDUCTIONS_ALL
952         WHERE  deduction_req_id = p_dctn_req_id;
953 
954     CURSOR C2(c_exp_item_id  NUMBER, p_dctn_txn_id NUMBER) IS
955       SELECT 'Y'
956       FROM   PA_DEDUCTION_TRANSACTIONS_ALL
957       WHERE  expenditure_item_id = c_exp_item_id
958       AND    deduction_req_tran_id <> p_dctn_txn_id;
959 
960     CURSOR C3(p_po_header_id NUMBER) IS
961        SELECT PO_INQ_SV.get_po_total (type_lookup_code,
962                                       po_header_id,
963                                       '') FROM PO_HEADERS_ALL WHERE po_header_id = p_po_header_id;
964 
965     l_dctn_req_id PA_DEDUCTIONS_ALL.deduction_req_id%TYPE;
966     l_exp_item_exists VARCHAR2(1) := 'N';
967     tbl_dctn_hdr C1%ROWTYPE;
968 
969      CURSOR C4(p_etype VARCHAR2) IS
970          SELECT
971                  system_linkage_function
972                 ,start_date_active
973                 ,end_date_active
974           FROM  pa_expend_typ_sys_links
975           WHERE system_linkage_function = 'VI'
976           AND   expenditure_type        = p_etype ;
977 
978     l_exp_type_info C4%ROWTYPE;
979 
980     l_msg_application        Varchar2(80);
981     l_msg_type               Varchar2(80);
982     l_msg_token1             Varchar2(80);
983     l_msg_token2             Varchar2(80);
984     l_msg_token3             Varchar2(80);
985     l_msg_count              NUMBER;
986     l_msg_data               Varchar2(4000);
987 
988     l_recno                  NUMBER :=1;
989     l_billable_flag          VARCHAR2(1);
990   Begin
991 
992     g_api_name := 'Validate_Deduction_Txn';
993     p_return_status := 'S';
994     IF P_DEBUG_MODE = 'Y' THEN
995        log_message ('In Validate Deduction Transaction procedure' ,g_api_name);
996     END IF;
997 
998      IF p_dctn_dtl.COUNT > 0 THEN
999         FOR I in p_dctn_dtl.FIRST..p_dctn_dtl.LAST LOOP
1000           IF P_DEBUG_MODE = 'Y' THEN
1001              log_message ('Deduction_Req_ID '||p_dctn_dtl(i).deduction_req_id||
1002                           ' Project_ID '||p_dctn_dtl(i).project_id||
1003                           ' Task_Id '||p_dctn_dtl(i).task_id||
1004                           ' Expenditure_Item_Date '||p_dctn_dtl(i).expenditure_item_date||
1005                           ' Expenditure Type '||p_dctn_dtl(i).expenditure_type, g_api_name);
1006           END IF;
1007           IF  nvl(l_dctn_req_id,-99) <> p_dctn_dtl(i).deduction_req_id THEN
1008             IF P_DEBUG_MODE = 'Y' THEN
1009              log_message ('Validating whether the deduction header exists or not', g_api_name);
1010             END IF;
1011 
1012               OPEN C1(p_dctn_dtl(i).deduction_req_id);
1013               FETCH C1 INTO tbl_dctn_hdr;
1014               IF C1%NOTFOUND THEN
1015                  CLOSE C1;
1016                  p_msg_data := 'PA_DCTN_HDR_NOT_EXISTS';
1017                  p_return_status := 'E';
1018                  p_dctn_dtl(I).status := 'HDR_NOT_SAVED';
1019                  AddError_To_Stack( p_error_code => p_msg_data
1020                                    ,p_hdr_or_txn => 'H'
1021                                    ,p_token2_val => p_dctn_dtl(i).deduction_req_id);
1022                  RETURN FALSE;
1023               END IF;
1024               CLOSE C1;
1025               l_dctn_req_id := p_dctn_dtl(i).deduction_req_id;
1026               p_dctn_dtl(I).project_id := tbl_dctn_hdr.project_id; /* Temporary Code*/
1027               l_recno :=1;
1028           END IF;
1029 
1030 
1031           IF p_dctn_dtl(I).expenditure_item_id IS NOT NULL THEN
1032            IF P_DEBUG_MODE = 'Y' THEN
1033             log_message ('Validating if EI is already used for any other deduciton request',
1034                           g_api_name);
1035            END IF;
1036 
1037              OPEN C2(p_dctn_dtl(I).expenditure_item_id, p_dctn_dtl(I).deduction_req_tran_id);
1038              FETCH C2 INTO l_exp_item_exists;
1039              CLOSE C2;
1040 
1041              IF l_exp_item_exists = 'Y' THEN
1042                  p_msg_data := 'PA_DCTN_EID_EXISTS';
1043                  p_return_status := 'E';
1044                  p_dctn_dtl(I).status := 'EID_EXISTS';
1045                  AddError_To_Stack( p_error_code => p_msg_data
1046                                ,p_hdr_or_txn => 'T'
1047                                ,p_token1_val => l_recno);
1048              END IF;
1049 
1050              IF P_DEBUG_MODE = 'Y' THEN
1051                log_message ('Validating expenditure type', g_api_name);
1052              END IF;
1053 
1054              OPEN C4(p_dctn_dtl(I).expenditure_type);
1055              FETCH C4 INTO l_exp_type_info;
1056              IF C4%NOTFOUND THEN
1057                 IF  p_msg_data IS NULL THEN
1058                  p_msg_data := 'PA_DED_EXP_INV_TYPE';
1059                  p_return_status := 'E';
1060                  p_dctn_dtl(I).status := 'EXP_TYPE_INV';
1061                 END IF;
1062                 AddError_To_Stack( p_error_code => 'PA_DED_EXP_INV_TYPE'
1063                                ,p_hdr_or_txn => 'T'
1064                                ,p_token1_val => l_recno
1065 			       ,p_token2_val => p_dctn_dtl(I).expenditure_item_id);
1066              ELSIF p_dctn_dtl(I).expenditure_item_date NOT BETWEEN l_exp_type_info.start_date_active
1067                    AND NVL(l_exp_type_info.end_date_active, p_dctn_dtl(I).expenditure_item_date) THEN
1068                 IF  p_msg_data IS NULL THEN
1069                  p_msg_data := 'ETYPE_SLINK_INACTIVE';
1070                  p_return_status := 'E';
1071                  p_dctn_dtl(I).status := 'EXP_TYPE_INV';
1072                 END IF;
1073                 AddError_To_Stack( p_error_code => 'ETYPE_SLINK_INACTIVE'
1074                                   ,p_hdr_or_txn => 'T'
1075                                   ,p_token1_val => l_recno);
1076              END IF;
1077              CLOSE C4;
1078           END IF;
1079 
1080           IF P_DEBUG_MODE = 'Y' THEN
1081             log_message ('Validating project functional currency amount', g_api_name);
1082           END IF;
1083 
1084           IF nvl(p_dctn_dtl(I).override_projfunc_amount,
1085                  p_dctn_dtl(I).orig_projfunc_amount) IS NULL THEN
1086              IF  p_msg_data IS NULL THEN
1087                  p_msg_data := 'PA_DCTN_PFC_AMT_NULL';
1088                  p_return_status := 'E';
1089                  p_dctn_dtl(I).status := 'PFC_AMT_NULL';
1090              END IF;
1091              AddError_To_Stack( p_error_code => 'PA_DCTN_PFC_AMT_NULL'
1092                                ,p_hdr_or_txn => 'T'
1093                                ,p_token1_val => l_recno);
1094           END IF;
1095 
1096           IF P_DEBUG_MODE = 'Y' THEN
1097              log_message ('Validating transaction currency amount', g_api_name);
1098           END IF;
1099 
1100           IF p_dctn_dtl(I).amount IS NULL THEN
1101              IF  p_msg_data IS NULL THEN
1102                  p_msg_data := 'PA_DCTN_DMEMO_AMT_NULL';
1103                  p_return_status := 'E';
1104                  p_dctn_dtl(I).status := 'PFC_DAMT_NULL';
1105              END IF;
1106              AddError_To_Stack( p_error_code => 'PA_DCTN_DMEMO_AMT_NULL'
1107                                ,p_hdr_or_txn => 'T'
1108                                ,p_token1_val => l_recno);
1109           END IF;
1110 
1111           IF P_DEBUG_MODE = 'Y' THEN
1112             log_message ('Before calling PATC validate_transaction procedure', g_api_name);
1113           END IF;
1114 
1115           PA_TRANSACTIONS_PUB.VALIDATE_TRANSACTION(
1116               x_project_id          => tbl_dctn_hdr.project_id,
1117               x_task_id             => p_dctn_dtl(i).task_id,
1118               x_ei_date             => p_dctn_dtl(i).expenditure_item_date,
1119               x_expenditure_type    => p_dctn_dtl(i).expenditure_type,
1120               x_non_labor_resource  => null,
1121               x_person_id           => null,
1122               x_billable_flag       => l_billable_flag,
1123               x_quantity            => p_dctn_dtl(i).override_quantity,
1124               x_transfer_ei         => null,
1125               x_incurred_by_org_id  => p_dctn_dtl(i).expenditure_org_id,
1126               x_nl_resource_org_id  => null,
1127               x_transaction_source  => '',
1128               x_calling_module      => 'APXIIMPT',
1129               x_vendor_id           => tbl_dctn_hdr.vendor_id,
1130               x_entered_by_user_id  => g_user_id,
1131               x_denom_currency_code => null,
1132               x_acct_currency_code  => null,
1133               x_denom_raw_cost      =>  null,
1134               x_acct_raw_cost       => null,
1135               x_acct_rate_type      => null,
1136               x_acct_rate_date      => null,
1137               x_acct_exchange_rate  => null,
1138               x_msg_application     => l_msg_application,
1139               x_msg_type            => l_msg_type,
1140               x_msg_token1          => l_msg_token1,
1141               x_msg_token2          => l_msg_token2,
1142               x_msg_token3          => l_msg_token3,
1143               x_msg_count           => l_msg_count,
1144               x_msg_data            => l_msg_data,
1145               p_sys_link_function   => '');
1146 
1147           IF P_DEBUG_MODE = 'Y' THEN
1148             log_message ('After calling PATC validate_transaction procedure :'||l_msg_data, g_api_name);
1149           END IF;
1150 
1151           IF l_msg_data IS NOT NULL THEN
1152              IF p_msg_data IS NULL THEN
1153                  p_msg_data := l_msg_data;
1154                  p_return_status := 'E';
1155                  p_dctn_dtl(I).status := substr(l_msg_data,1,15);
1156              END IF;
1157                  AddError_To_Stack( p_error_code => l_msg_data
1158                                ,p_hdr_or_txn => 'T'
1159                                ,p_token1_val => l_recno);
1160           END IF;
1161 
1162           l_recno := l_recno + 1;
1163         END LOOP;
1164      END IF;
1165      RETURN TRUE;
1166   End;
1167 
1168   /*---------------------------------------------------------------------------------------------------------
1169     -- This procedure is to submit the deducion request for approval thereby for the creation of Debit memo.
1170     -- This is being called on pressing the submit button on Create deductions page.
1171     -- Input parameters
1172     -- Parameters                Type           Required  Description
1173     --  p_dctn_req_id            NUMBER         YES       Deduction request id for which debit memo needs
1174                                                           to be raised
1175     -- Out parameters
1176     -- Parameters                Type           Required  Description
1177     --  p_return_status          VARCHAR2       YES       The return status of the APIs.
1178     --                                                    Valid values are:
1179     --                                                    S (API completed successfully),
1180     --                                                    E (business rule violation error) and
1181     --                                                    U(Unexpected error, such as an Oracle error.
1182     --  p_msg_count              NUMBER         YES       Holds the number of messages in the global message
1183                                                           table. Calling programs should use this as the
1184                                                           basis to fetch all the stored messages.
1185     --  p_msg_data               VARCHAR2       YES       Holds the message code, if the API returned only
1186                                                           one error/warning message Otherwise the column is
1187                                                           left blank.
1188   ----------------------------------------------------------------------------------------------------------*/
1189   Procedure Submit_For_DebitMemo ( p_dctn_req_id IN PA_DEDUCTIONS_ALL.deduction_req_id%TYPE
1190                                   ,p_msg_count OUT NOCOPY NUMBER
1191                                   ,p_msg_data  OUT NOCOPY VARCHAR2
1192                                   ,p_return_status OUT NOCOPY VARCHAR2
1193                                  ) IS
1194 
1195     x_err_stack                VARCHAR2(2000);
1196     x_err_stage                VARCHAR2(2000);
1197     x_err_code                 NUMBER;
1198 
1199     CURSOR C1 IS
1200        SELECT * FROM PA_DEDUCTION_TRANSACTIONS_ALL
1201        WHERE  deduction_req_id = p_dctn_req_id;
1202 
1203     l_dctn_req_cnt   NUMBER;
1204     p_next_number    PA_DEDUCTIONS_ALL.debit_memo_num%TYPE;
1205 
1206     l_dctn_hdrtbl              g_dctn_hdrtbl;
1207     l_dctn_txntbl              g_dctn_txntbl;
1208     cnt                        NUMBER :=0;
1209 
1210   BEGIN
1211         g_api_name := 'Submit_For_DebitMemo_1';
1212         IF P_DEBUG_MODE = 'Y' THEN
1213           log_message ('Submit_For_DebitMemo started for deduction request:' ||p_dctn_req_id,
1214                       g_api_name);
1215         END IF;
1216 
1217         p_return_status := 'S';
1218         FND_MSG_PUB.initialize;
1219 
1220         IF P_DEBUG_MODE = 'Y' THEN
1221           log_message ('Verifying if the deduction header exists in database', g_api_name);
1222         END IF;
1223 
1224         OPEN cur_dctn_hdr_info(p_dctn_req_id);
1225         FETCH cur_dctn_hdr_info INTO cur_dctn_hdr;
1226         IF cur_dctn_hdr_info%NOTFOUND THEN
1227            p_return_status := 'E';
1228            p_msg_data := 'PA_DCTN_HDR_NOT_EXISTS';
1229            p_msg_count :=1;
1230            CLOSE cur_dctn_hdr_info;
1231 
1232            AddError_To_Stack( p_error_code => p_msg_data
1233                              ,p_hdr_or_txn => 'H'
1234                              ,p_token2_val => p_dctn_req_id);
1235            RETURN;
1236         END IF;
1237         CLOSE cur_dctn_hdr_info;
1238 
1239         IF P_DEBUG_MODE = 'Y' THEN
1240           log_message ('Verifying debit memo date is given or not', g_api_name);
1241         END IF;
1242 
1243         IF cur_dctn_hdr.debit_memo_date IS NULL THEN
1244            p_return_status := 'E';
1245            p_msg_data := 'PA_DCTN_DMEMO_DATE_NULL';
1246            p_msg_count :=1;
1247 
1248            AddError_To_Stack( p_error_code => p_msg_data
1249                              ,p_hdr_or_txn => 'H');
1250            RETURN;
1251         END IF;
1252 
1253         IF P_DEBUG_MODE = 'Y' THEN
1254           log_message ('Verifying if debit memo amount is negative', g_api_name);
1255         END IF;
1256 
1257         IF nvl(cur_dctn_hdr.total_amount,0) < 0 THEN
1258              IF p_msg_data IS NULL THEN
1259                  p_msg_data := 'PA_DEB_MEM_AMT_NEG';
1260                  p_return_status := 'E';
1261              END IF;
1262              AddError_To_Stack( p_error_code => 'PA_DEB_MEM_AMT_NEG'
1263                                ,p_hdr_or_txn => 'H');
1264              RETURN;
1265         END IF;
1266 
1267         IF P_DEBUG_MODE = 'Y' THEN
1268            log_message ('Initializing the pl/sql table for validating header', g_api_name);
1269         END IF;
1270 
1271         l_dctn_hdrtbl(1).deduction_req_id    :=  cur_dctn_hdr.deduction_req_id     ;
1272         l_dctn_hdrtbl(1).project_id          :=  cur_dctn_hdr.project_id           ;
1273         l_dctn_hdrtbl(1).vendor_id           :=  cur_dctn_hdr.vendor_id            ;
1274         l_dctn_hdrtbl(1).vendor_site_id      :=  cur_dctn_hdr.vendor_site_id       ;
1275         l_dctn_hdrtbl(1).change_doc_num      :=  cur_dctn_hdr.change_doc_num       ;
1276         l_dctn_hdrtbl(1).change_doc_type     :=  cur_dctn_hdr.change_doc_type      ;
1277         l_dctn_hdrtbl(1).ci_id               :=  cur_dctn_hdr.ci_id                ;
1278         l_dctn_hdrtbl(1).po_number           :=  cur_dctn_hdr.po_number            ;
1279         l_dctn_hdrtbl(1).po_header_id        :=  cur_dctn_hdr.po_header_id         ;
1280         l_dctn_hdrtbl(1).deduction_req_num   :=  cur_dctn_hdr.deduction_req_num    ;
1281         l_dctn_hdrtbl(1).debit_memo_num      :=  cur_dctn_hdr.debit_memo_num       ;
1282         l_dctn_hdrtbl(1).currency_code       :=  cur_dctn_hdr.currency_code        ;
1283         l_dctn_hdrtbl(1).conversion_ratetype :=  cur_dctn_hdr.conversion_ratetype  ;
1284         l_dctn_hdrtbl(1).conversion_ratedate :=  cur_dctn_hdr.conversion_ratedate  ;
1285         l_dctn_hdrtbl(1).conversion_rate     :=  cur_dctn_hdr.conversion_rate      ;
1286         l_dctn_hdrtbl(1).total_amount        :=  cur_dctn_hdr.total_amount         ;
1287         l_dctn_hdrtbl(1).deduction_req_date  :=  cur_dctn_hdr.deduction_req_date   ;
1288         l_dctn_hdrtbl(1).debit_memo_date     :=  cur_dctn_hdr.debit_memo_date      ;
1289         l_dctn_hdrtbl(1).description         :=  cur_dctn_hdr.description          ;
1290         l_dctn_hdrtbl(1).status              :=  cur_dctn_hdr.status               ;
1291         l_dctn_hdrtbl(1).org_id              :=  cur_dctn_hdr.org_id               ;
1292 
1293         p_msg_count:= '';
1294         p_msg_data := '';
1295         p_return_status :='';
1296 
1297         /* Bug# 9401673 Commented the below condition and added condition on deduction status. */
1298 	/* Condition on deduction status is required to call the client extension only for the
1299 	   first time when we submit the deduction for approval.
1300 
1301 	   The client extension should not be called again when we resubmit the deduction for approval
1302 	   in case if the deduction was rejected/failed during the last submission. This is to avoid
1303 	   rederiving the debit memo number by the client extension.
1304 	*/
1305 
1306 	--IF cur_dctn_hdr.debit_memo_num IS NULL THEN
1307 	IF cur_dctn_hdr.status = 'WORKING' THEN
1308           IF P_DEBUG_MODE = 'Y' THEN
1309             log_message ('Generating debit memo number', g_api_name);
1310           END IF;
1311 
1312           IF NOT Validate_DM(l_dctn_hdrtbl
1313                          ,p_msg_count
1314                          ,p_msg_data
1315                          ,p_return_status
1316                          ) THEN
1317 
1318             IF P_DEBUG_MODE = 'Y' THEN
1319               log_message ('Debit memo generation failed', g_api_name);
1320             END IF;
1321             RETURN;
1322           ELSE
1323            IF P_DEBUG_MODE = 'Y' THEN
1324              log_message ('Updating the debit memo number on Deduction request header', g_api_name);
1325            END IF;
1326 
1327             UPDATE PA_DEDUCTIONS_ALL pda
1328             SET    debit_memo_num = l_dctn_hdrtbl(1).debit_memo_num
1329             WHERE  deduction_req_id = p_dctn_req_id;
1330 
1331             COMMIT;
1332           END IF;
1333 	END IF;
1334         --END IF;
1335 
1336         cnt :=1;
1337 
1338         If Validate_Deduction_Hdr(l_dctn_hdrtbl,P_msg_count, p_msg_data,p_return_status) Then
1339            IF P_DEBUG_MODE = 'Y' THEN
1340              log_message ('Initializing pl/sql table for detail tranasctions for validing them',
1341                            g_api_name);
1342            END IF;
1343 
1344           FOR cur_dctn_txn IN C1 LOOP
1345            l_dctn_txntbl(cnt).deduction_req_id          := cur_dctn_txn.deduction_req_id        ;
1346            l_dctn_txntbl(cnt).deduction_req_tran_id     := cur_dctn_txn.deduction_req_tran_id   ;
1347            l_dctn_txntbl(cnt).project_id                := cur_dctn_txn.project_id              ;
1348            l_dctn_txntbl(cnt).task_id                   := cur_dctn_txn.task_id                 ;
1349            l_dctn_txntbl(cnt).expenditure_type          := cur_dctn_txn.expenditure_type        ;
1350            l_dctn_txntbl(cnt).expenditure_item_date     := cur_dctn_txn.expenditure_item_date   ;
1351            l_dctn_txntbl(cnt).gl_date                   := cur_dctn_txn.gl_date                 ;
1352            l_dctn_txntbl(cnt).expenditure_org_id        := cur_dctn_txn.expenditure_org_id      ;
1353            l_dctn_txntbl(cnt).quantity                  := cur_dctn_txn.quantity                ;
1354            l_dctn_txntbl(cnt).override_quantity         := cur_dctn_txn.override_quantity       ;
1355            l_dctn_txntbl(cnt).expenditure_item_id       := cur_dctn_txn.expenditure_item_id     ;
1356            l_dctn_txntbl(cnt).projfunc_currency_code    := cur_dctn_txn.projfunc_currency_code  ;
1357            l_dctn_txntbl(cnt).orig_projfunc_amount      := cur_dctn_txn.orig_projfunc_amount    ;
1358            l_dctn_txntbl(cnt).override_projfunc_amount  := cur_dctn_txn.override_projfunc_amount;
1359            l_dctn_txntbl(cnt).conversion_ratetype       := cur_dctn_txn.conversion_ratetype     ;
1360            l_dctn_txntbl(cnt).conversion_ratedate       := cur_dctn_txn.conversion_ratedate     ;
1361            l_dctn_txntbl(cnt).conversion_rate           := cur_dctn_txn.conversion_rate         ;
1362            l_dctn_txntbl(cnt).amount                    := cur_dctn_txn.amount                  ;
1363            l_dctn_txntbl(cnt).description               := cur_dctn_txn.description             ;
1364            cnt := cnt+1;
1365           END LOOP;
1366 
1367           IF cnt = 1 THEN
1368              IF P_DEBUG_MODE = 'Y' THEN
1369                log_message ('There are no detail transactions and hence cannot be submitted',
1370                              g_api_name);
1371              END IF;
1372 
1373                p_return_status := 'E';
1374                p_msg_data := 'PA_DED_REQ_ITEM_LESS';
1375                p_msg_count :=1;
1376                AddError_To_Stack( p_error_code => p_msg_data
1377                                  ,p_hdr_or_txn => 'H');
1378                RETURN;
1379           ELSE
1380             If Validate_Deduction_Txn(l_dctn_txntbl,P_msg_count, p_msg_data,p_return_status) Then
1381 
1382               IF P_DEBUG_MODE = 'Y' THEN
1383                log_message ('Validation on detail transactions is successful', g_api_name);
1384               END IF;
1385 
1386            	   Update_Deduction_Status(p_dctn_req_id,
1387                                           'SUBMITTED');
1388 		       COMMIT;
1389 
1390                IF P_DEBUG_MODE = 'Y' THEN
1391                  log_message ('Before calling workflow for deduction approval', g_api_name);
1392                END IF;
1393 
1394                PA_DCTN_APRV_NOTIFICATION.START_DCTN_APRV_WF (p_dctn_req_id
1395                                                             ,x_err_stack
1396                                                             ,x_err_stage
1397                                                             ,x_err_code );
1398 
1399                IF P_DEBUG_MODE = 'Y' THEN
1400                  IF x_err_code <>0 THEN
1401                    log_message ('Workflow is failed', g_api_name);
1402                  ELSE
1403                    log_message ('Workflow is successful', g_api_name);
1404                  END IF;
1405                END IF;
1406 
1407                COMMIT;
1408             End If;
1409 	      END IF;
1410         Else
1411           IF P_DEBUG_MODE = 'Y' THEN
1412             log_message ('Header validation failed', g_api_name);
1413           END IF;
1414 
1415            UPDATE PA_DEDUCTIONS_ALL pda
1416            SET    status = DECODE(p_return_status,'E','REJECTED',status)
1417            WHERE  deduction_req_id = p_dctn_req_id;
1418 
1419            COMMIT;
1420 	    End If;
1421 
1422   EXCEPTION
1423       WHEN OTHERS THEN
1424         IF P_DEBUG_MODE = 'Y' THEN
1425           log_message ('In Others exception : '||SQLERRM, g_api_name);
1426         END IF;
1427 
1428         Delete_Failed_Rec(p_dctn_req_id);
1429         p_msg_data:=SQLERRM;
1430         p_return_status := 'U';
1431         p_msg_count :=1;
1432         AddError_To_Stack( p_error_code => p_msg_data
1433                           ,p_hdr_or_txn => 'H');
1434   END;
1435 
1436   /*---------------------------------------------------------------------------------------------------------
1437     -- This procedure is to raise a debit memo in payables. This is being called from deduction request
1438     -- approval workflow on deduction request's approval.
1439     -- Input parameters
1440     -- Parameters                Type           Required  Description
1441     --  p_dctn_req_id            NUMBER         YES       Deduction request id for which debit memo needs
1442                                                           to be raised
1443     -- Out parameters
1444     -- Parameters                Type           Required  Description
1445     --  p_return_status          VARCHAR2       YES       The return status of the APIs.
1446     --                                                    Valid values are:
1447     --                                                    S (API completed successfully),
1448     --                                                    E (business rule violation error) and
1449     --                                                    U(Unexpected error, such as an Oracle error.
1450     --  p_msg_count              NUMBER         YES       Holds the number of messages in the global message
1451                                                           table. Calling programs should use this as the
1452                                                           basis to fetch all the stored messages.
1453     --  p_msg_data               VARCHAR2       YES       Holds the message code, if the API returned only
1454                                                           one error/warning message Otherwise the column is
1455                                                           left blank.
1456   ----------------------------------------------------------------------------------------------------------*/
1457   Procedure Submit_For_DebitMemo ( p_dctn_hdr_rec IN cur_dctn_hdr_info%ROWTYPE
1458                                   ,p_msg_count OUT NOCOPY NUMBER
1459                                   ,p_msg_data  OUT NOCOPY VARCHAR2
1460                                   ,p_return_status OUT NOCOPY VARCHAR2
1461                                  ) IS
1462 
1463     CURSOR C2(p_dctn_req_id PA_DEDUCTIONS_ALL.deduction_req_id%TYPE) IS
1464        SELECT *
1465        FROM PA_DEDUCTION_TRANSACTIONS_ALL WHERE deduction_req_id = p_dctn_req_id;
1466 
1467     l_int_invoice_id           NUMBER;
1468     l_int_invoice_line_id      NUMBER;
1469 
1470     l_description              VARCHAR2(240);
1471     l_exchange_rate            NUMBER;
1472     l_exchange_rate_type       VARCHAR2(30);
1473     l_exchange_date            DATE;
1474 
1475     l_dctn_hdrtbl              g_dctn_hdrtbl;
1476     l_dctn_txntbl              g_dctn_txntbl;
1477     cnt                        NUMBER :=0;
1478 
1479     l_is_deduction_valid       VARCHAR2(1):= 'Y';
1480     l_tax_flag                 VARCHAR2(1):= 'N';
1481     reqid                      NUMBER;
1482     cur_dctn_txn               C2%ROWTYPE;
1483   Begin
1484         g_api_name := 'Submit_For_DebitMemo_2';
1485 
1486         IF P_DEBUG_MODE = 'Y' THEN
1487           log_message ('Submit procedure for interfacing and importing the debit memo', g_api_name);
1488         END IF;
1489 
1490         p_return_status := 'S';
1491         FND_MSG_PUB.initialize;
1492 
1493         IF P_DEBUG_MODE = 'Y' THEN
1494           log_message ('Updating deduction request status to Approved :'||l_int_invoice_id, g_api_name);
1495         END IF;
1496 
1497         Update_Deduction_Status(p_dctn_hdr_rec.deduction_req_id,
1498                                 'APPROVED');
1499 
1500         SELECT AP_INVOICES_INTERFACE_S.nextval
1501         INTO   l_int_invoice_id
1502      	FROM   SYS.DUAL;
1503 
1504         IF P_DEBUG_MODE = 'Y' THEN
1505           log_message ('Invoice_Id in interface table :'||l_int_invoice_id, g_api_name);
1506         END IF;
1507 
1508         IF p_dctn_hdr_rec.po_number IS NOT NULL THEN
1509            l_description := SUBSTR(p_dctn_hdr_rec.description,1,210)||p_dctn_hdr_rec.po_number;
1510         ELSE
1511            l_description := SUBSTR(p_dctn_hdr_rec.description,1,240);
1512         END IF;
1513 
1514 
1515         IF p_dctn_hdr_rec.document_type = 'M' THEN
1516            l_tax_flag := 'Y';
1517         ELSE
1518            l_tax_flag := 'N';
1519         END IF;
1520 
1521         IF P_DEBUG_MODE = 'Y' THEN
1522           log_message ('Tax Calculation Flag :'||l_tax_flag, g_api_name);
1523         END IF;
1524 
1525         l_dctn_hdrtbl(1).deduction_req_id    :=  p_dctn_hdr_rec.deduction_req_id     ;
1526         l_dctn_hdrtbl(1).project_id          :=  p_dctn_hdr_rec.project_id           ;
1527         l_dctn_hdrtbl(1).vendor_id           :=  p_dctn_hdr_rec.vendor_id            ;
1528         l_dctn_hdrtbl(1).vendor_site_id      :=  p_dctn_hdr_rec.vendor_site_id       ;
1529         l_dctn_hdrtbl(1).change_doc_num      :=  p_dctn_hdr_rec.change_doc_num       ;
1530         l_dctn_hdrtbl(1).change_doc_type     :=  p_dctn_hdr_rec.change_doc_type      ;
1531         l_dctn_hdrtbl(1).ci_id               :=  p_dctn_hdr_rec.ci_id                ;
1532         l_dctn_hdrtbl(1).po_number           :=  p_dctn_hdr_rec.po_number            ;
1533         l_dctn_hdrtbl(1).po_header_id        :=  p_dctn_hdr_rec.po_header_id         ;
1534         l_dctn_hdrtbl(1).deduction_req_num   :=  p_dctn_hdr_rec.deduction_req_num    ;
1535         l_dctn_hdrtbl(1).debit_memo_num      :=  p_dctn_hdr_rec.debit_memo_num       ;
1536         l_dctn_hdrtbl(1).currency_code       :=  p_dctn_hdr_rec.currency_code        ;
1537         l_dctn_hdrtbl(1).conversion_ratetype :=  p_dctn_hdr_rec.conversion_ratetype  ;
1538         l_dctn_hdrtbl(1).conversion_ratedate :=  p_dctn_hdr_rec.conversion_ratedate  ;
1539         l_dctn_hdrtbl(1).conversion_rate     :=  p_dctn_hdr_rec.conversion_rate      ;
1540         l_dctn_hdrtbl(1).total_amount        :=  p_dctn_hdr_rec.total_amount         ;
1541         l_dctn_hdrtbl(1).deduction_req_date  :=  p_dctn_hdr_rec.deduction_req_date   ;
1542         l_dctn_hdrtbl(1).debit_memo_date     :=  p_dctn_hdr_rec.debit_memo_date      ;
1543         l_dctn_hdrtbl(1).description         :=  p_dctn_hdr_rec.description          ;
1544         l_dctn_hdrtbl(1).status              :=  p_dctn_hdr_rec.status               ;
1545         l_dctn_hdrtbl(1).org_id              :=  p_dctn_hdr_rec.org_id               ;
1546 
1547         cnt :=1;
1548 
1549         FOR cur_dctn_txn IN C2(p_dctn_hdr_rec.deduction_req_id) LOOP
1550            l_dctn_txntbl(cnt).deduction_req_id          := cur_dctn_txn.deduction_req_id        ;
1551            l_dctn_txntbl(cnt).deduction_req_tran_id     := cur_dctn_txn.deduction_req_tran_id   ;
1552            l_dctn_txntbl(cnt).project_id                := cur_dctn_txn.project_id              ;
1553            l_dctn_txntbl(cnt).task_id                   := cur_dctn_txn.task_id                 ;
1554            l_dctn_txntbl(cnt).expenditure_type          := cur_dctn_txn.expenditure_type        ;
1555            l_dctn_txntbl(cnt).expenditure_item_date     := cur_dctn_txn.expenditure_item_date   ;
1556            l_dctn_txntbl(cnt).gl_date                   := cur_dctn_txn.gl_date                 ;
1557            l_dctn_txntbl(cnt).expenditure_org_id        := cur_dctn_txn.expenditure_org_id      ;
1558            l_dctn_txntbl(cnt).quantity                  := cur_dctn_txn.quantity                ;
1559            l_dctn_txntbl(cnt).override_quantity         := cur_dctn_txn.override_quantity       ;
1560            l_dctn_txntbl(cnt).expenditure_item_id       := cur_dctn_txn.expenditure_item_id     ;
1561            l_dctn_txntbl(cnt).projfunc_currency_code    := cur_dctn_txn.projfunc_currency_code  ;
1562            l_dctn_txntbl(cnt).orig_projfunc_amount      := cur_dctn_txn.orig_projfunc_amount    ;
1563            l_dctn_txntbl(cnt).override_projfunc_amount  := cur_dctn_txn.override_projfunc_amount;
1564            l_dctn_txntbl(cnt).conversion_ratetype       := cur_dctn_txn.conversion_ratetype     ;
1565            l_dctn_txntbl(cnt).conversion_ratedate       := cur_dctn_txn.conversion_ratedate     ;
1566            l_dctn_txntbl(cnt).conversion_rate           := cur_dctn_txn.conversion_rate         ;
1567            l_dctn_txntbl(cnt).amount                    := cur_dctn_txn.amount                  ;
1568            l_dctn_txntbl(cnt).description               := cur_dctn_txn.description             ;
1569            cnt := cnt+1;
1570         END LOOP;
1571 
1572         IF P_DEBUG_MODE = 'Y' THEN
1573            log_message ('Before creating the invoice header',g_api_name);
1574         END IF;
1575 
1576 	    Create_Invoice_Header (
1577 	       p_dctn_hdr_rec.deduction_req_id
1578 	      ,l_int_invoice_id
1579 	      ,p_dctn_hdr_rec.debit_memo_num
1580 	      ,p_dctn_hdr_rec.debit_memo_date
1581 	      ,p_dctn_hdr_rec.vendor_id
1582 	      ,p_dctn_hdr_rec.vendor_site_id
1583 	      ,p_dctn_hdr_rec.total_amount
1584 	      ,p_dctn_hdr_rec.currency_code
1585 	      ,l_exchange_rate
1586 	      ,l_exchange_rate_type
1587 	      ,l_exchange_date
1588 	      ,l_description
1589 	      ,l_tax_flag
1590 	      ,p_dctn_hdr_rec.org_id );
1591 
1592         IF P_DEBUG_MODE = 'Y' THEN
1593            log_message ('Before creating the invoice lines',g_api_name);
1594         END IF;
1595 
1596 	    FOR I IN 1..l_dctn_txntbl.COUNT LOOP
1597 	        Create_Invoice_Line (
1598 	            l_int_invoice_id
1599 	            ,PA_CURRENCY.round_trans_currency_amt(l_dctn_txntbl(i).amount,
1600                                                       p_dctn_hdr_rec.currency_code)
1601 	            ,nvl(l_dctn_txntbl(i).gl_date, l_dctn_txntbl(i).expenditure_item_date)
1602 	            ,l_dctn_txntbl(i).project_id
1603 	            ,l_dctn_txntbl(i).task_id
1604 	            ,l_dctn_txntbl(i).expenditure_item_date
1605 	            ,l_dctn_txntbl(i).expenditure_type
1606 	            ,l_dctn_txntbl(i).expenditure_org_id
1607 	            ,'Yes'
1608 	            ,l_dctn_txntbl(i).description
1609 	            ,l_dctn_txntbl(i).override_quantity
1610 	            ,p_dctn_hdr_rec.org_id );
1611 	    END LOOP;
1612 
1613         IF P_DEBUG_MODE = 'Y' THEN
1614            log_message ('Before calling Payables Open Import',g_api_name);
1615         END IF;
1616         /* Bug 8740525 sosharma commented and added code for concurrent request */
1617         /*Import_DebitMemo(p_dctn_hdr_rec.deduction_req_id
1618                         ,p_msg_count
1619                         ,p_msg_data
1620                         ,p_return_status
1621                         );*/
1622 
1623      reqid:=fnd_request.submit_request('PA','PA_DEBITMEMO_IMPORT','',null,FALSE,p_dctn_hdr_rec.deduction_req_id);
1624 
1625         IF P_DEBUG_MODE = 'Y' THEN
1626           IF p_return_status = 'S' THEN
1627             log_message ('Payables open interface concurrent request raised', reqid);
1628           END IF;
1629         END IF;
1630 
1631   EXCEPTION
1632     WHEN OTHERS THEN
1633        IF P_DEBUG_MODE = 'Y' THEN
1634          log_message ('Unexpected error in the procedure: '||g_api_name, g_api_name);
1635          log_message ('Error :'||SQLERRM, g_api_name);
1636        END IF;
1637 
1638          Update_Deduction_Status(p_dctn_hdr_rec.deduction_req_id,
1639                                  'FAILED');
1640       /*   p_msg_data:=SQLERRM;
1641          p_return_status := 'U';
1642          p_msg_count :=1;
1643          AddError_To_Stack( p_error_code => p_msg_data
1644                            ,p_hdr_or_txn => 'H');*/
1645   End;
1646 
1647   Procedure Create_Invoice_Header (
1648         p_deduction_req_id       IN  NUMBER
1649        ,p_invoice_id             IN  NUMBER
1650        ,p_invoice_num            IN  VARCHAR2
1651        ,p_invoice_date           IN  DATE
1652        ,p_vendor_id              IN  NUMBER
1653        ,p_vendor_site_id         IN  NUMBER
1654        ,p_invoice_amount         IN  NUMBER
1655        ,p_invoice_currency_code  IN  VARCHAR2
1656        ,p_exchange_rate          IN  NUMBER
1657        ,p_exchange_rate_type     IN  VARCHAR2
1658        ,p_exchange_date          IN  DATE
1659        ,p_description            IN  VARCHAR2
1660        ,p_tax_flag               IN  VARCHAR2
1661        ,p_org_id                 IN  NUMBER ) IS
1662 
1663     l_rowid   ROWID;
1664     l_groupid AP_INVOICES_INTERFACE.group_id%TYPE;
1665   Begin
1666           g_api_name := 'Create_Invoice_Header';
1667 
1668           IF P_DEBUG_MODE = 'Y' THEN
1669             log_message ('In Creating header information in interface table',g_api_name);
1670           END IF;
1671 
1672           l_groupid := 'DM'||TO_CHAR(SYSDATE,'YYYYMMDD')||p_invoice_num;
1673 
1674           IF P_DEBUG_MODE = 'Y' THEN
1675             log_message ('Before inserting invoice header : '||l_groupId, g_api_name);
1676           END IF;
1677 
1678           INSERT INTO AP_INVOICES_INTERFACE (
1679                             invoice_id
1680                            ,invoice_num
1681                            ,invoice_type_lookup_code
1682                            ,invoice_date
1683                            ,vendor_id
1684                            ,vendor_site_id
1685                            ,invoice_amount
1686                            ,invoice_currency_code
1687                            ,description
1688                            ,voucher_num
1689                            ,application_id
1690                            ,product_table
1691                            ,reference_key1
1692                            ,calc_tax_during_import_flag
1693                            ,group_id
1694                            ,source
1695                            ,creation_date
1696                            ,created_by
1697                            ,org_id )
1698                   VALUES   (
1699                             p_invoice_id
1700                            ,p_invoice_num
1701                            ,'DEBIT'
1702                            ,p_invoice_date
1703                            ,p_vendor_id
1704                            ,p_vendor_site_id
1705                            ,-p_invoice_amount
1706                            ,p_invoice_currency_code
1707                            ,p_description
1708                            ,p_invoice_num
1709                            ,275
1710                            ,'PA_DEDUCTIONS_ALL'
1711                            ,p_deduction_req_id
1712                            ,p_tax_flag
1713                            ,l_groupid
1714                            ,'Oracle Project Accounting'
1715                            ,SYSDATE
1716                            ,g_user_id
1717                            ,p_org_id );
1718 
1719         IF P_DEBUG_MODE = 'Y' THEN
1720           log_message ('After inserting into invoice interface table',g_api_name);
1721         END IF;
1722   End;
1723 
1724   Procedure Create_Invoice_Line (
1725           p_invoice_id            IN  NUMBER
1726          ,p_amount                IN  NUMBER
1727          ,p_accounting_date       IN  DATE
1728          ,p_project_id            IN  NUMBER
1729          ,p_task_id               IN  NUMBER
1730          ,p_expenditure_item_date IN  DATE
1731          ,p_expenditure_type      IN  VARCHAR2
1732          ,p_expenditure_org       IN  NUMBER
1733          ,p_project_acct_context  IN  VARCHAR2
1734          ,p_description           IN  VARCHAR2
1735          ,p_qty_invoiced          IN  NUMBER
1736          ,p_org_id                IN  NUMBER ) IS
1737 
1738   l_invoice_line_id   NUMBER;
1739   l_rowid             ROWID;
1740   Begin
1741        g_api_name := 'Create_Invoice_Line';
1742        log_message ('Before inserting lines into interface lines table', g_api_name);
1743 
1744        SELECT ap_invoice_lines_interface_s.nextval
1745        INTO   l_invoice_line_id
1746        FROM   sys.dual;
1747 
1748        IF P_DEBUG_MODE = 'Y' THEN
1749          log_message ('Invoice Line Id : '||l_invoice_line_id, g_api_name);
1750        END IF;
1751 
1752        INSERT INTO AP_INVOICE_LINES_INTERFACE (
1753                      invoice_id
1754                     ,invoice_line_id
1755                     ,line_type_lookup_code
1756                     ,amount
1757                     ,quantity_invoiced
1758                     ,org_id
1759                     ,project_id
1760                     ,task_id
1761                     ,expenditure_type
1762                     ,expenditure_organization_id
1763                     ,expenditure_item_date
1764                     ,project_accounting_context
1765                     ,accounting_date
1766                     ,description
1767                     ,pa_addition_flag
1768                     ,creation_date
1769                     ,created_by
1770                     )
1771     		 VALUES (
1772                     p_invoice_id
1773                    ,l_invoice_line_id
1774                    ,'ITEM'
1775                    ,-p_amount
1776                    ,p_qty_invoiced
1777                    ,p_org_id
1778                    ,p_project_id
1779                    ,p_task_id
1780                    ,p_expenditure_type
1781                    ,p_expenditure_org
1782                    ,p_expenditure_item_date
1783                    ,p_project_acct_context
1784                    ,p_accounting_date
1785                    ,p_description
1786                    ,'N'
1787                    ,SYSDATE
1788                    ,g_user_id) ;
1789 
1790        IF P_DEBUG_MODE = 'Y' THEN
1791           log_message ('After inserting into interface :'||SQL%ROWCOUNT|| ' records inserted',
1792                        g_api_name);
1793        END IF;
1794   End;
1795 
1796   Procedure Update_Deduction_Status(p_dctn_hdr_id IN PA_DEDUCTIONS_ALL.deduction_req_id%TYPE,
1797                                     p_status      IN VARCHAR2) IS
1798   -- PRAGMA AUTONOMOUS_TRANSACTION;
1799   Begin
1800         UPDATE PA_DEDUCTIONS_ALL SET status = p_status WHERE deduction_req_id = p_dctn_hdr_id;
1801       --  COMMIT;
1802   End;
1803 /* Bug 8740525 sosharma commented and added code for concurrent request */
1804   Procedure Import_DebitMemo(errbuf OUT NOCOPY varchar2,
1805                              ret_code OUT NOCOPY varchar2,
1806                              p_dctn_req_id IN NUMBER
1807                         --  ,p_msg_count OUT NOCOPY NUMBER
1808                         --    ,p_msg_data  OUT NOCOPY VARCHAR2
1809                         --    ,p_return_status OUT NOCOPY VARCHAR2
1810                             ) IS
1811 	   	p_batch_name              VARCHAR2(100);
1812 	p_gl_date                 DATE;
1813 	p_hold_code               VARCHAR2(100);
1814 	p_hold_reason             VARCHAR2(1000);
1815 	p_commit_cycles           NUMBER;
1816 	p_source                  VARCHAR2(100);
1817 	p_group_id                VARCHAR2(100);
1818 	p_conc_request_id         NUMBER;
1819 	p_debug_switch            VARCHAR2(1) :='N';
1820 	p_org_id                  NUMBER;
1821 	p_batch_error_flag        VARCHAR2(1);
1822 	p_invoices_fetched        NUMBER;
1823 	p_invoices_created        NUMBER;
1824         p_total_invoice_amount    NUMBER;
1825         p_print_batch             VARCHAR2(1);
1826 	p_calling_sequence        VARCHAR2(100);
1827 
1828     CURSOR C1 IS
1829        SELECT * FROM AP_INVOICES_INTERFACE
1830        WHERE product_table = 'PA_DEDUCTIONS_ALL'
1831        AND reference_key1 = p_dctn_req_id;
1832 
1833     CURSOR C2 IS
1834        SELECT * FROM PA_DEDUCTIONS_ALL
1835        WHERE deduction_req_id = p_dctn_req_id;
1836 
1837 
1838        CURSOR C3 IS
1839          select pded.deduction_req_num,pded.debit_memo_num,pded.deduction_req_date,
1840 	pded.debit_memo_date,pded.currency_code,pa.segment1,pa.name
1841 	,v.vendor_name
1842 	,vs.vendor_site_code
1843 	,hr.name hr_name
1844 	from pa_deductions_all pded,pa_projects_all pa
1845 	,po_vendors v, po_vendor_sites_all vs,hr_organization_units hr
1846 	where pa.project_id=pded.project_id and
1847 	pded.vendor_id= v.vendor_id and pded.vendor_site_id=vs.vendor_site_id
1848 	and pa.org_id=hr.organization_id
1849 	and pded.deduction_req_id = p_dctn_req_id;
1850 
1851 CURSOR C4 is
1852    select lookup.description reason,
1853      pta.task_number task_num,
1854      al.expenditure_type exp_type,
1855      hr.name exp_org,
1856      al.amount
1857 	from AP_INVOICE_LINES_INTERFACE al
1858 	, ap_interface_rejections ar,
1859 	AP_INVOICES_INTERFACE ad,
1860 	pa_tasks pta,hr_organization_units hr,
1861 	fnd_lookup_values lookup
1862 	where ar.parent_id=al.invoice_line_id
1863 	and ar.parent_table='AP_INVOICE_LINES_INTERFACE'
1864 	and al.invoice_id=ad.invoice_id
1865 	and ad.product_table = 'PA_DEDUCTIONS_ALL'
1866 	and al.task_id=pta.task_id
1867 	and hr.organization_id=al.expenditure_organization_id
1868 	and ar.reject_lookup_code = lookup.lookup_code
1869 	and lookup.lookup_type='REJECT CODE'
1870 	 and view_application_id=200
1871 	 and lookup.language=USERENV('LANG')
1872 	and   ad.reference_key1 = p_dctn_req_id;
1873 
1874 
1875   CURSOR C5 IS
1876       select lookup.description reason
1877    	from  ap_interface_rejections ar,
1878 	AP_INVOICES_INTERFACE ad,
1879 		fnd_lookup_values lookup
1880 	where ar.parent_id=ad.invoice_id
1881 	and ar.parent_table='AP_INVOICES_INTERFACE'
1882 	and ad.product_table = 'PA_DEDUCTIONS_ALL'
1883 	and ar.reject_lookup_code = lookup.lookup_code
1884 	and lookup.lookup_type='REJECT CODE'
1885 	 and view_application_id=200
1886 	 and lookup.language=USERENV('LANG')
1887 	and   ad.reference_key1 = p_dctn_req_id;
1888 
1889 
1890     l_ap_inv_int_rec         C1%ROWTYPE;
1891     l_dctn_req_hdr           C2%ROWTYPE;
1892     l_report_rec             C3%ROWTYPE;
1893    reject_dtls_rec           C4%ROWTYPE;
1894     reject_hdr_rec           C5%ROWTYPE;
1895 
1896      -- report related fields
1897   l_row_num_len      NUMBER := 11;
1898   l_contract_num_len NUMBER := 15;
1899   l_asset_num_len    NUMBER := 20;
1900   l_lessee_len       NUMBER := 25;
1901   l_sty_subclass_len NUMBER := 25;
1902   l_reject_code_len  NUMBER := 45;
1903   l_max_len          NUMBER := 150;
1904   l_prompt_len       NUMBER := 35;
1905 
1906 
1907   l_str_row_num      VARCHAR2(5);
1908   l_str_contract_num VARCHAR2(30);
1909   l_str_lessee       VARCHAR2(50);
1910   l_content          VARCHAR2(1000);
1911   l_header_len       NUMBER;
1912   counter  NUMBER;
1913   hdrcount NUMBER := 0;
1914   G_APP_NAME VARCHAR2(3) :='PA';
1915 
1916 Begin
1917   g_api_name := 'Import_DebitMemo';
1918 
1919      log_message ('In Import process', g_api_name);
1920 
1921      SELECT FND_GLOBAL.CONC_REQUEST_ID
1922      INTO   p_conc_request_id
1923      FROM   DUAL;
1924 
1925      IF P_DEBUG_MODE = 'Y' THEN
1926         log_message ('Conc request id'||p_conc_request_id, g_api_name);
1927      END IF;
1928 
1929      OPEN C2;
1930      FETCH C2 INTO l_dctn_req_hdr;
1931      CLOSE C2;
1932 
1933      OPEN C1;
1934      FETCH C1 INTO l_ap_inv_int_rec;
1935      IF C1%NOTFOUND THEN
1936 
1937         IF P_DEBUG_MODE = 'Y' THEN
1938           log_message ('Interface records not found, Interface failed', g_api_name);
1939         END IF;
1940 
1941 
1942         Update_Deduction_Status(p_dctn_req_id,
1943                                 'REJECTED');
1944         CLOSE C1;
1945        /* AddError_To_Stack( p_error_code => 'PA_DCTN_INT_FAILED'
1946                           ,p_hdr_or_txn => 'H'
1947                           ,p_token2_val => l_dctn_req_hdr.deduction_req_num);*/
1948         RETURN;
1949      END IF;
1950      CLOSE C1;
1951 
1952      IF P_DEBUG_MODE = 'Y' THEN
1953        log_message ('Before calling import API', g_api_name);
1954      END IF;
1955 
1956      IF AP_IMPORT_INVOICES_PKG.IMPORT_INVOICES(
1957 		p_batch_name,
1958 		p_gl_date,
1959 		p_hold_code,
1960 		p_hold_reason,
1961 		p_commit_cycles,
1962 		'Oracle Project Accounting',
1963 		l_ap_inv_int_rec.group_id,
1964 		p_conc_request_id,
1965 		p_debug_switch,
1966 		l_ap_inv_int_rec.org_id,
1967 		p_batch_error_flag,
1968 		p_invoices_fetched,
1969 		p_invoices_created,
1970 		p_total_invoice_amount,
1971 		p_print_batch,
1972 		'BackEnd')= TRUE THEN
1973 
1974         OPEN C1;
1975         FETCH C1 INTO l_ap_inv_int_rec;
1976         CLOSE C1;
1977         IF l_ap_inv_int_rec.status = 'REJECTED' THEN
1978           IF P_DEBUG_MODE = 'Y' THEN
1979            log_message ('Interface process rejected', g_api_name);
1980           END IF;
1981 
1982 
1983            Update_Deduction_Status(p_dctn_req_id,
1984                                    'FAILED');
1985 
1986 
1987        -- fetch header for the report
1988         OPEN C3;
1989         FETCH C3 INTO l_report_rec;
1990         CLOSE C3;
1991        -- display details in the log
1992 	    FND_FILE.PUT_LINE(FND_FILE.LOG, ' ');
1993 	    FND_FILE.PUT_LINE(FND_FILE.LOG, FND_MESSAGE.GET_STRING(G_APP_NAME,'DEDUCTION_NUMBER')||':' || l_report_rec.deduction_req_num);
1994 	    FND_FILE.PUT_LINE(FND_FILE.LOG, FND_MESSAGE.GET_STRING(G_APP_NAME,'DEBIT_MEMO_NUMBER')||':' ||l_report_rec.debit_memo_num);
1995 	    FND_FILE.PUT_LINE(FND_FILE.LOG, FND_MESSAGE.GET_STRING(G_APP_NAME,'DEDUCTION_DATE')||':'|| l_report_rec.deduction_req_date);
1996 
1997 	      FND_FILE.PUT_LINE(FND_FILE.LOG, 'Payables Interface Status : ' || 'Failed');
1998 
1999 	    FND_FILE.PUT_LINE(FND_FILE.LOG, ' ');
2000 
2001             FND_FILE.PUT_LINE(FND_FILE.OUTPUT,LPAD(SYSDATE,130));
2002             FND_FILE.PUT_LINE(FND_FILE.OUTPUT,RPAD(l_report_rec.hr_name,120));
2003        -- display the rejected header in the output file
2004 	     l_content := FND_MESSAGE.GET_STRING(G_APP_NAME,'DED_IMP_FAIL_REP');
2005 		l_header_len := LENGTH(l_content);
2006 		l_content :=    RPAD(LPAD(l_content,l_max_len/2),l_max_len/2);    -- center align header
2007 	    FND_FILE.PUT_LINE(FND_FILE.OUTPUT,l_content);
2008 	       FND_FILE.PUT_LINE(FND_FILE.OUTPUT, ' ');
2009 		  FND_FILE.PUT_LINE(FND_FILE.OUTPUT, ' ');
2010 
2011 	l_content:=RPAD(FND_MESSAGE.GET_STRING(G_APP_NAME,'DEDUCTION_NUMBER')||':'|| l_report_rec.deduction_req_num,60)||FND_MESSAGE.GET_STRING(G_APP_NAME,'DEBIT_MEMO_NUMBER')||':' ||l_report_rec.debit_memo_num;
2012 	     FND_FILE.PUT_LINE(FND_FILE.OUTPUT, l_content);
2013 
2014 	    l_content:=RPAD(FND_MESSAGE.GET_STRING(G_APP_NAME,'DEDUCTION_DATE')||':' || l_report_rec.deduction_req_date,60)||FND_MESSAGE.GET_STRING(G_APP_NAME,'DEBIT_MEMO_DATE')||':' || l_report_rec.debit_memo_date;
2015 	     FND_FILE.PUT_LINE(FND_FILE.OUTPUT, l_content);
2016 
2017 	    l_content:=RPAD(FND_MESSAGE.GET_STRING(G_APP_NAME,'PROJECT_NAME')||':' || l_report_rec.name,60)||FND_MESSAGE.GET_STRING(G_APP_NAME,'DEBIT_MEMO_CURRENCY')||':' || l_report_rec.currency_code;
2018 	     FND_FILE.PUT_LINE(FND_FILE.OUTPUT, l_content);
2019 
2020 	  l_content:=RPAD(FND_MESSAGE.GET_STRING(G_APP_NAME,'PROJECT_NUMBER')||':' || l_report_rec.segment1,60)||FND_MESSAGE.GET_STRING(G_APP_NAME,'SUPPLIER_NAME')||':' || l_report_rec.vendor_name;
2021 	     FND_FILE.PUT_LINE(FND_FILE.OUTPUT, l_content);
2022 
2023 	     l_content:=RPAD(FND_MESSAGE.GET_STRING(G_APP_NAME,'PAYABLES_INTERFACE_STATUS')||':'|| 'Failed',60)||FND_MESSAGE.GET_STRING(G_APP_NAME,'SUPPLIER_SITE')||':' || l_report_rec.vendor_site_code;
2024 	     FND_FILE.PUT_LINE(FND_FILE.OUTPUT, l_content);
2025 
2026 
2027 	    FND_FILE.PUT_LINE(FND_FILE.OUTPUT, ' ');
2028 
2029 -- check if failure at header level or line level
2030        FOR reject_hdr_rec IN C5
2031        LOOP
2032        hdrcount:=hdrcount+1;
2033        END LOOP;
2034 
2035       IF hdrcount > 0 THEN -- header level failure
2036 
2037       l_content:=RPAD(FND_MESSAGE.GET_STRING(G_APP_NAME,'REASON_FOR_FAILURE'),20);
2038        FND_FILE.PUT_LINE(FND_FILE.OUTPUT,l_content);
2039       FOR reject_hdr_rec IN C5
2040        LOOP
2041         FND_FILE.PUT_LINE(FND_FILE.OUTPUT,reject_hdr_rec.reason);
2042        END LOOP;
2043 
2044       ELSE --lines level failure
2045         -- Failed records report header
2046 
2047 	     l_content :=  FND_MESSAGE.GET_STRING(G_APP_NAME,'DED_PAY_IMP_FAIL_REP');
2048 		l_header_len := LENGTH(l_content);
2049 		l_content :=    RPAD(LPAD(l_content,l_max_len/2),l_max_len/2);    -- center align header
2050 	    FND_FILE.PUT_LINE(FND_FILE.OUTPUT,l_content);
2051 
2052 		l_content := RPAD('=',l_header_len,'=');                           -- underline header
2053 		l_content := RPAD(LPAD(l_content,l_max_len/2),l_max_len/2,'=');    -- center align
2054 	    FND_FILE.PUT_LINE(FND_FILE.OUTPUT,l_content);
2055 
2056 	    FND_FILE.PUT_LINE(FND_FILE.OUTPUT,' ');
2057 	    FND_FILE.PUT_LINE(FND_FILE.OUTPUT,' ');
2058 
2059 
2060         -- Table header
2061 		l_content :=    RPAD('-',l_row_num_len-1,'-') || ' '
2062 	             || RPAD('-',l_contract_num_len-1,'-') || ' '
2063 	             || RPAD('-',l_asset_num_len-1,'-') || ' '
2064 				 || RPAD('-',l_lessee_len-1,'-') || ' '
2065 				 || RPAD('-',l_sty_subclass_len-1,'-') || ' '
2066 				 || RPAD('-',l_reject_code_len-1,'-');
2067 
2068        FND_FILE.PUT_LINE(FND_FILE.OUTPUT,l_content);
2069 
2070        l_content :=    RPAD(FND_MESSAGE.GET_STRING(G_APP_NAME,'SERIAL_NO'),l_row_num_len-1) || ' '
2071 	                || RPAD(FND_MESSAGE.GET_STRING(G_APP_NAME,'TASK_NUMBER'),l_contract_num_len-1) || ' '
2072 	                || RPAD(FND_MESSAGE.GET_STRING(G_APP_NAME,'EXPENDITURE_TYPE'),l_asset_num_len-1) || ' '
2073                     || RPAD(FND_MESSAGE.GET_STRING(G_APP_NAME,'EXPENDITURE_ORG'),l_lessee_len-1) || ' '
2074                     || RPAD(FND_MESSAGE.GET_STRING(G_APP_NAME,'DEB_MEM_AMT'),l_sty_subclass_len-1) || ' '
2075                     || RPAD(FND_MESSAGE.GET_STRING(G_APP_NAME,'REASON_FOR_FAILURE'),l_reject_code_len-1);
2076 
2077 
2078 
2079        FND_FILE.PUT_LINE(FND_FILE.OUTPUT,l_content);
2080 
2081            l_content :=    RPAD('-',l_row_num_len-1,'-') || ' '
2082 	             || RPAD('-',l_contract_num_len-1,'-') || ' '
2083 	             || RPAD('-',l_asset_num_len-1,'-') || ' '
2084 				 || RPAD('-',l_lessee_len-1,'-') || ' '
2085 				 || RPAD('-',l_sty_subclass_len-1,'-') || ' '
2086 				 || RPAD('-',l_reject_code_len-1,'-');
2087 
2088        FND_FILE.PUT_LINE(FND_FILE.OUTPUT,l_content);
2089 
2090        -- initialize counter for serial number
2091         counter:=0;
2092 
2093         -- get details of the rejected records
2094         FOR reject_dtls_rec IN C4
2095 
2096 		   LOOP
2097                     counter:=counter+1;
2098 		l_content :=    RPAD(counter,l_row_num_len-1) || ' '
2099 	                || RPAD(reject_dtls_rec.task_num,l_contract_num_len-1) || ' '
2100 	                || RPAD(reject_dtls_rec.exp_type,l_asset_num_len-1) || ' '
2101                     || RPAD(reject_dtls_rec.exp_org,l_lessee_len-1) || ' '
2102                     || RPAD(reject_dtls_rec.amount,l_sty_subclass_len-1) || ' '
2103                     || RPAD(reject_dtls_rec.reason,l_reject_code_len-1);
2104 
2105                FND_FILE.PUT_LINE(FND_FILE.OUTPUT,l_content);
2106 
2107 		   END LOOP;
2108        END IF;
2109 
2110        -- delete the failed records from interface and Ap
2111            Delete_Failed_Rec(p_dctn_req_id);
2112 
2113         ELSE
2114          IF P_DEBUG_MODE = 'Y' THEN
2115            log_message ('Interface process successful', g_api_name);
2116          END IF;
2117          FND_FILE.PUT_LINE(FND_FILE.LOG,'Import Process successful');
2118            Update_Deduction_Status(p_dctn_req_id,
2119                                    'PROCESSED');
2120 
2121         END IF;
2122      Else
2123 
2124         IF P_DEBUG_MODE = 'Y' THEN
2125           log_message ('Import process failed', g_api_name);
2126         END IF;
2127 
2128         Update_Deduction_Status(p_dctn_req_id,
2129                                 'FAILED');
2130 
2131         Delete_Failed_Rec(p_dctn_req_id);
2132 
2133 
2134         RETURN;
2135      End If;
2136 
2137    ret_code := 0;
2138 
2139    EXCEPTION
2140      WHEN OTHERS THEN
2141        IF P_DEBUG_MODE = 'Y' THEN
2142         log_message ('In Others Exceptions :'||SQLERRM, g_api_name);
2143        END IF;
2144       errbuf := SQLERRM;
2145        ret_code := 2;
2146         Delete_Failed_Rec(p_dctn_req_id);
2147 
2148         Update_Deduction_Status(p_dctn_req_id,
2149                                 'FAILED');
2150 
2151 
2152    End Import_DebitMemo;
2153 
2154   PROCEDURE log_message (p_log_msg IN VARCHAR2,p_proc_name VARCHAR2) IS
2155   BEGIN
2156       pa_debug.write('log_message: ' || p_proc_name, 'log: ' || p_log_msg, 3);
2157   END log_message;
2158 
2159   PROCEDURE Delete_Failed_Rec(p_dctn_req_id NUMBER) IS
2160   BEGIN
2161   NULL;
2162 
2163         DELETE AP_INVOICE_LINES_INTERFACE WHERE invoice_id IN(
2164               SELECT invoice_id FROM AP_INVOICES_INTERFACE WHERE
2165               product_table = 'PA_DEDUCTIONS_ALL' and reference_key1 = to_char(p_dctn_req_id));
2166 
2167         DELETE AP_INVOICES_INTERFACE WHERE
2168               product_table = 'PA_DEDUCTIONS_ALL' and reference_key1 = to_char(p_dctn_req_id);
2169 
2170         DELETE AP_INVOICE_DISTRIBUTIONS_ALL WHERE invoice_id IN(
2171               SELECT invoice_id FROM AP_INVOICES_ALL WHERE
2172               product_table = 'PA_DEDUCTIONS_ALL' and reference_key1 = to_char(p_dctn_req_id));
2173 
2174         DELETE AP_INVOICE_LINES_ALL WHERE invoice_id IN(
2175               SELECT invoice_id FROM AP_INVOICES_ALL WHERE
2176               product_table = 'PA_DEDUCTIONS_ALL' and reference_key1 = to_char(p_dctn_req_id));
2177 
2178         DELETE AP_INVOICES_ALL WHERE
2179               product_table = 'PA_DEDUCTIONS_ALL' and reference_key1 = to_char(p_dctn_req_id);
2180 
2181   END Delete_Failed_Rec;
2182 
2183   Function Validate_DM( p_dctn_hdr       IN OUT NOCOPY g_dctn_hdrtbl
2184                        ,p_msg_count      OUT NOCOPY NUMBER
2185                        ,p_msg_data       OUT NOCOPY VARCHAR2
2186                        ,p_return_status  OUT NOCOPY VARCHAR2
2187                        ) Return Boolean Is
2188 
2189     CURSOR C1(p_debit_memo_num PA_DEDUCTIONS_ALL.debit_memo_num%TYPE,
2190               p_org_id         PA_DEDUCTIONS_ALL.org_id%TYPE,
2191               p_vendor_id      PA_DEDUCTIONS_ALL.vendor_id%TYPE,
2192               p_dctn_req_id    PA_DEDUCTIONS_ALL.deduction_req_id%TYPE) IS
2193       SELECT 'N'
2194       FROM   PA_DEDUCTIONS_ALL
2195       WHERE  debit_memo_num = p_debit_memo_num
2196       AND    org_id = p_org_id
2197       AND    vendor_id = p_vendor_id
2198       AND    deduction_req_id <> nvl(p_dctn_req_id,-99);
2199 
2200     CURSOR C2(p_debit_memo_num PA_DEDUCTIONS_ALL.debit_memo_num%TYPE,
2201               p_org_id         PA_DEDUCTIONS_ALL.org_id%TYPE,
2202               p_vendor_id      PA_DEDUCTIONS_ALL.vendor_id%TYPE) IS
2203       SELECT 'N'
2204       FROM   DUAL WHERE EXISTS (
2205                      SELECT 1
2206                      FROM   AP_INVOICES_ALL
2207                      WHERE  invoice_num = p_debit_memo_num
2208                      AND    vendor_id = p_vendor_id
2209                      AND    org_id = p_org_id
2210                      UNION ALL
2211                      SELECT 1
2212                      FROM   AP_INVOICES_INTERFACE
2213                      WHERE  invoice_num = p_debit_memo_num
2214                      AND    vendor_id = p_vendor_id
2215                      AND    org_id = p_org_id
2216                      AND    nvl(status, 'REJECTED') <> 'REJECTED');
2217 
2218     is_debit_memo_unique VARCHAR2(1) := 'Y';
2219     l_next_number        PA_DEDUCTIONS_ALL.debit_memo_num%TYPE;
2220 
2221     l_msg_count NUMBER;
2222     l_msg_data  VARCHAR2(4000);
2223     l_return_status VARCHAR2(1);
2224   Begin
2225     g_api_name := 'Validate_DM';
2226     p_return_status := 'S';
2227 
2228     IF P_DEBUG_MODE = 'Y' THEN
2229        log_message ('In validate debit memo procedure', g_api_name);
2230     END IF;
2231 
2232     FND_MSG_PUB.initialize;
2233 
2234     IF P_DEBUG_MODE = 'Y' THEN
2235        log_message ('DMNO '||p_dctn_hdr(1).debit_memo_num||' Org '||p_dctn_hdr(1).org_id||
2236                     ' Vendor Id '||p_dctn_hdr(1).vendor_id|| ' Deduction req id '||
2237                     p_dctn_hdr(1).deduction_req_id,'Validate Header');
2238 
2239     END IF;
2240     l_next_number := p_dctn_hdr(1).debit_memo_num ; /* 9401673 */
2241 
2242 --    Calling the client extension even in the case of the debit memo number is entered by the user.
2243 --    So, whatever the client extension returns is the final debit memo number. By default, Client extension
2244 --    returts the same value, which is passed to it.
2245 
2246 --    IF p_dctn_hdr(1).debit_memo_num IS NULL THEN
2247 
2248        IF P_DEBUG_MODE = 'Y' THEN
2249           log_message ('Before calling client extension', g_api_name);
2250        END IF;
2251 
2252        PA_DM_NUMBER_CLIENT_EXTN.get_next_number (
2253               p_project_id           => p_dctn_hdr(1).project_id
2254              ,p_vendor_id            => p_dctn_hdr(1).vendor_id
2255              ,p_vendor_site_id       => p_dctn_hdr(1).vendor_site_id
2256              ,p_org_id               => p_dctn_hdr(1).org_id
2257              ,p_po_header_id         => p_dctn_hdr(1).po_header_id
2258              ,p_ci_id                => p_dctn_hdr(1).ci_id
2259              ,p_dctn_req_date        => p_dctn_hdr(1).deduction_req_date
2260              ,p_debit_memo_date      => p_dctn_hdr(1).debit_memo_date
2261              ,p_next_number          => l_next_number
2262              ,x_return_status        => l_return_status
2263              ,x_msg_count            => l_msg_count
2264              ,x_msg_data             => l_msg_data);
2265 
2266         IF P_DEBUG_MODE = 'Y' THEN
2267            log_message ('After the client extension', g_api_name);
2268 
2269            log_message ('l_next_number '||l_next_number||
2270                         ' l_return_status '||l_return_status, g_api_name);
2271         END IF;
2272 
2273         IF l_next_number IS NULL AND l_return_status = 'S' THEN
2274 
2275           IF P_DEBUG_MODE = 'Y' THEN
2276             log_message ('Generating debit memo number using sequence', g_api_name);
2277           END IF;
2278 
2279           LOOP
2280              SELECT PA_DEDUCTIONS_DM_S.nextval
2281              INTO l_next_number FROM sys.DUAL;
2282 
2283              OPEN C1(l_next_number,
2284                      p_dctn_hdr(1).org_id,
2285                      p_dctn_hdr(1).vendor_id,
2286                      p_dctn_hdr(1).deduction_req_id);
2287              FETCH C1 INTO is_debit_memo_unique;
2288              CLOSE C1;
2289 
2290              IF is_debit_memo_unique = 'Y' THEN
2291                 OPEN C2(l_next_number,
2292                         p_dctn_hdr(1).org_id,
2293                         p_dctn_hdr(1).vendor_id ) ;
2294                 FETCH C2 INTO is_debit_memo_unique;
2295                 CLOSE C2;
2296              END IF;
2297 
2298              IF is_debit_memo_unique = 'Y' THEN
2299                 EXIT;
2300              END IF;
2301           END LOOP;
2302           p_dctn_hdr(1).debit_memo_num := l_next_number;
2303         ELSIF l_next_number IS NOT NULL THEN
2304 
2305           IF P_DEBUG_MODE = 'Y' THEN
2306             log_message ('validating the sequence generated by client extension', g_api_name);
2307           END IF;
2308 
2309           IF l_return_status = 'S' THEN
2310 
2311              IF P_DEBUG_MODE = 'Y' THEN
2312                log_message ('Client extension succesfully returned a debit memo number', g_api_name);
2313 
2314                log_message('return status '||l_return_status, g_api_name);
2315              END IF;
2316 
2317              OPEN C1(l_next_number,
2318                      p_dctn_hdr(1).org_id,
2319                      p_dctn_hdr(1).vendor_id,
2320                      p_dctn_hdr(1).deduction_req_id);
2321              FETCH C1 INTO is_debit_memo_unique;
2322              CLOSE C1;
2323              IF is_debit_memo_unique = 'N' THEN
2324                  is_debit_memo_unique := 'Y';
2325                    IF p_msg_data IS NULL THEN
2326                       p_return_status := 'E';
2327                       p_msg_data := 'PA_DCTN_CLX_DM_NUM_EXISTS';
2328                    END IF;
2329                   AddError_To_Stack( p_error_code => 'PA_DCTN_CLX_DM_NUM_EXISTS'
2330                                     ,p_hdr_or_txn => 'H'
2331                                     ,p_token2_val => l_next_number);
2332              END IF;
2333 
2334              IF p_msg_data <> 'PA_DCTN_CLX_DM_NUM_EXISTS' THEN
2335                 OPEN C2(l_next_number,
2336                         p_dctn_hdr(1).org_id,
2337                         p_dctn_hdr(1).vendor_id ) ;
2338                 FETCH C2 INTO is_debit_memo_unique;
2339                 CLOSE C2;
2340                IF is_debit_memo_unique = 'N' THEN
2341                   is_debit_memo_unique := 'Y';
2342                    IF p_msg_data IS NULL THEN
2343                       p_return_status := 'E';
2344                       p_msg_data := 'PA_DCTN_CLX_DM_NUM_EXISTS';
2345                    END IF;
2346 
2347                    AddError_To_Stack( p_error_code => 'PA_DCTN_CLX_DM_NUM_EXISTS'
2348                                      ,p_hdr_or_txn => 'H'
2349                                      ,p_token2_val => l_next_number);
2350                END IF;
2351              END IF;
2352              p_dctn_hdr(1).debit_memo_num := l_next_number;
2353 
2354           ELSIF l_return_status = 'E' THEN
2355             IF P_DEBUG_MODE = 'Y' THEN
2356              log_message ('Client extension failed while returning the sequence number', g_api_name);
2357             END IF;
2358 
2359              p_msg_count      := l_msg_count;
2360              p_msg_data       := l_msg_data;
2361              p_return_status  := l_return_status;
2362           END IF;
2363         END IF;
2364   --  END IF;
2365 
2366     IF p_return_status = 'S' THEN
2367        RETURN TRUE;
2368     ELSE
2369        RETURN FALSE;
2370     END IF;
2371   End Validate_DM;
2372 
2373   /*---------------------------------------------------------------------------------------------------------
2374     -- This function is to return the list of invoices which are assoiciated to a debit memo that is created
2375     -- out of a deduction request.
2376     -- Input parameters
2377     -- Parameters                Type           Required  Description
2378     --  p_vendor_Id              NUMBER         YES       vendor id
2379     --  p_vendor_site_id         NUMBER         YES       vendor site id
2380     --  ded_req_num              VARCHAR2       YES       deduction request id
2381   ----------------------------------------------------------------------------------------------------------*/
2382   Function Invoice_Dm_Map(p_vendor_id NUMBER,
2383                           p_vendor_site_id NUMBER,
2384                           ded_req_num IN VARCHAR2) RETURN VARCHAR2 IS
2385    CURSOR C1 IS
2386    SELECT invoice_num
2387    FROM   ap_invoices_all apinv
2388    WHERE  apinv.vendor_id = p_vendor_id
2389    AND    apinv.vendor_site_id = p_vendor_site_id
2390    AND   EXISTS
2391            (SELECT 1 FROM ap_invoice_distributions_all
2392             WHERE  invoice_id = apinv.invoice_id
2393             AND    parent_invoice_id =  ( SELECT invoice_id from ap_invoices_all
2394                                           WHERE  source = 'Oracle Project Accounting'
2395                                           AND    invoice_type_lookup_code = 'DEBIT'
2396                                           AND    product_table='PA_DEDUCTIONS_ALL'
2397                                           AND    reference_key1 = ded_req_num));
2398 
2399    rval VARCHAR2(300) := NULL;
2400   BEGIN
2401    g_api_name := 'Invoice_DM_Map';
2402    FOR arec in C1 LOOP
2403        if(rval is NULL)  then
2404           rval := arec.invoice_num;
2405        else
2406           rval := rval || ',' || arec.invoice_num;
2407        end if;
2408    END LOOP;
2409    return rval;
2410   EXCEPTION
2411   WHEN OTHERS THEN
2412     return '';
2413   END;
2414 
2415   Procedure AddError_To_Stack( p_error_code VARCHAR2
2416                               ,p_hdr_or_txn VARCHAR2 := 'H'
2417                               ,p_token1_val VARCHAR2 :=''
2418                               ,p_token2_val VARCHAR2 :=''
2419                               ,p_token3_val VARCHAR2 :=''
2420                               ,p_token4_val VARCHAR2 :='') IS
2421   BEGIN
2422 	FND_MESSAGE.SET_NAME  ('PA',p_error_code);
2423 
2424     IF  p_hdr_or_txn = 'T' THEN
2425     	FND_MESSAGE.SET_TOKEN ('LINE_NO', 'Line no: '||p_token1_val||' ');
2426 
2427         IF p_error_code = 'PA_EIDATE_NOT_MORETHAN_DRDATE' THEN
2428            FND_MESSAGE.SET_TOKEN ('EIDATE', p_token2_val);
2429 	       FND_MESSAGE.SET_TOKEN ('DRDATE', p_token3_val);
2430         END IF;
2431 
2432        IF p_error_code = 'PA_RTDATE_NOT_MORETHAN_DRDATE' THEN
2433           FND_MESSAGE.SET_TOKEN ('RTDATE', p_token2_val);
2434 	      FND_MESSAGE.SET_TOKEN ('DRDATE', p_token3_val);
2435        END IF;
2436         IF p_error_code = 'PA_DED_EXP_INV_TYPE' THEN
2437           FND_MESSAGE.SET_TOKEN ('EID', p_token2_val);
2438        END IF;
2439        END IF;
2440 
2441     IF p_hdr_or_txn = 'H' THEN
2442         IF p_error_code = 'PA_DCTN_HDR_NOT_EXISTS' THEN
2443            FND_MESSAGE.SET_TOKEN ('REQ_NUM', p_token2_val);
2444         END IF;
2445 
2446         IF p_error_code = 'PA_DCTN_IMPORT_FAILED' THEN
2447            FND_MESSAGE.SET_TOKEN ('DEB_MEMO_NUM', p_token2_val);
2448            FND_MESSAGE.SET_TOKEN ('REQ_NUM', p_token3_val);
2449         END IF;
2450 
2451         IF p_error_code = 'PA_DCTN_INT_FAILED' THEN
2452            FND_MESSAGE.SET_TOKEN ('REQ_NUM', p_token2_val);
2453         END IF;
2454 
2455         IF p_error_code = 'PA_DCTN_CLX_DM_NUM_EXISTS' THEN
2456            FND_MESSAGE.SET_TOKEN ('DEB_MEMO_NUM', p_token2_val);
2457         END IF;
2458     END IF;
2459 
2460 	FND_MSG_PUB.Add;
2461   END;
2462 
2463   /*Bug#9498500:Moved the procedure validate_unprocessed_ded() to PAAPVALS/B.pls
2464  ---------------------------------------------------------------------------------------------------------
2465     -- Bug 9307667
2466 	--  This procedure is to validate a retention invoice in payables. This is being called from Payables
2467     -- Input parameters
2468     --  Parameters                Type           Required  Description
2469     --  invoice_id              NUMBER         YES          invoice_id being validated
2470 	-- cmt_exist_flag           VARCHAR                     returns whether unprocessed dedns exist
2471      ---------------------------------------------------------------------------------------------------------
2472 	 Procedure validate_unprocessed_ded ( invoice_id IN ap_invoices_all.invoice_id%type,
2473 	                                       cmt_exist_flag OUT NOCOPY VARCHAR2)
2474 
2475 */
2476 
2477 
2478 END PA_DEDUCTIONS;