DBA Data[Home] [Help]

PACKAGE BODY: APPS.PA_INTEGRATION

Source


1 PACKAGE BODY pa_integration AS
2 --$Header: PAXPINTB.pls 120.6 2006/08/22 23:36:56 skannoji noship $
3 
4 l_invoice_id    NUMBER;
5 l_invoice_status Varchar2(30);
6 l_status_type    Varchar2(30);
7 
8 G_PrevPeriodName pa_cost_distribution_lines_all.gl_period_name%TYPE;
9 G_PrevPdStDate   DATE;
10 G_PrevPdEdDate   DATE;
11 G_PrevSOBId      NUMBER;
12 
13 -- FUNCTION get_period_name /*2835063*/
14     FUNCTION get_period_name RETURN  pa_cost_distribution_lines_all.pa_period_name%TYPE is
15     BEGIN
16          /* Please note that this function should be used only after ensuring that
17 	    get_raw_cdl_pa_date() is called, so that the returned variable's value has a
18 	    non-NULL value */
19       return  g_prvdr_pa_period_name;
20     end get_period_name;
21 
22 FUNCTION pending_vi_adjustments_exists( P_invoice_id IN NUMBER )
23                                         RETURN varchar2 IS
24 --
25 -- CDL's that are not yet transfered to AP
26 --
27 CURSOR pending_transfer IS
28 SELECT 'AP_PROJ_TASK_EXIST_PA'
29 FROM
30     PA_COST_DISTRIBUTION_LINES  CDL,
31     PA_EXPENDITURE_ITEMS   EI
32   WHERE
33    EI.EXPENDITURE_ITEM_ID = CDL.EXPENDITURE_ITEM_ID
34   AND CDL.TRANSFER_STATUS_CODE IN ('P','R','X')
35   AND EI.SYSTEM_LINKAGE_FUNCTION in ( 'VI','ER')
36   AND CDL.LINE_TYPE  = 'R'
37   AND CDL.system_reference2 = to_char(P_invoice_id);
38 --
39 -- Expenditure items that are
40 -- split/transfered but not cost distributed.
41 --
42 CURSOR pending_ei IS
43 SELECT 'AP_SPLIT_EXIST_PA'
44 FROM
45     PA_COST_DISTRIBUTION_LINES  CDL
46   WHERE
47       CDL.system_reference2 = to_char(P_invoice_id)
48   AND CDL.transfer_status_code||'' IN ('V','A')
49   AND CDL.line_type = 'R'
50   AND EXISTS
51     ( SELECT ' There are Splits/Transfers on EI'
52         FROM PA_EXPENDITURE_ITEMS   EI
53        WHERE EI.SYSTEM_LINKAGE_FUNCTION in ( 'VI', 'ER' )
54          AND EI.TRANSFERRED_FROM_EXP_ITEM_ID = CDL.EXPENDITURE_ITEM_ID
55          AND EI.ADJUSTED_EXPENDITURE_ITEM_ID IS NULL
56          AND EI.COST_DISTRIBUTED_FLAG||'' = 'N'
57      );
58 --
59 -- Expenditure items that are marked for recalc
60 --
61 
62 CURSOR pending_recalc IS
63 SELECT 'AP_RECALC_COST_PA'
64 FROM
65     PA_COST_DISTRIBUTION_LINES CDL
66 WHERE
67     CDL.system_reference2 = to_char(P_invoice_id)
68   AND CDL.transfer_status_code||'' IN ( 'V', 'A' )
69   AND CDL.line_type = 'R'
70   AND EXISTS
71     ( SELECT 'Marked for recalc'
72         FROM PA_EXPENDITURE_ITEMS EI
73        WHERE EI.SYSTEM_LINKAGE_FUNCTION in ( 'VI','ER')
74          AND EI.EXPENDITURE_ITEM_ID = CDL.EXPENDITURE_ITEM_ID
75          AND EI.COST_DISTRIBUTED_FLAG = 'N'
76      );
77 --
78 -- Checking for reversals
79 --
80 
81 CURSOR pending_reversed IS
82 SELECT 'AP_ADJ_EXIST_PA'
83 FROM
84     PA_COST_DISTRIBUTION_LINES  CDL
85   WHERE
86       CDL.system_reference2 = to_char(P_invoice_id)
87   AND CDL.transfer_status_code ||'' IN ('V','A')
88   AND CDL.line_type = 'R'
89   AND EXISTS
90     ( SELECT ' Reversed EI '
91         FROM PA_EXPENDITURE_ITEMS   EI
92        WHERE EI.SYSTEM_LINKAGE_FUNCTION in ( 'VI','ER')
93          AND EI.ADJUSTED_EXPENDITURE_ITEM_ID = CDL.EXPENDITURE_ITEM_ID
94          AND EI.COST_DISTRIBUTED_FLAG||'' = 'N'
95      );
96 
97 v_error_code  varchar2(30) := 'Y';
98 
99 BEGIN
100   OPEN pending_transfer;
101   FETCH pending_transfer INTO v_error_code;
102   IF ( v_error_code <> 'Y' ) THEN
103     CLOSE pending_transfer;
104     RETURN v_error_code;
105   END IF;
106   CLOSE pending_transfer;                        -- Added for Bug#5381711
107 
108   OPEN pending_ei;
109   FETCH pending_ei INTO v_error_code;
110   IF ( v_error_code <> 'Y' ) THEN
111     CLOSE pending_ei;
112     RETURN v_error_code;
113   END IF;
114   CLOSE pending_ei;                              -- Added for Bug#5381711
115 
116   OPEN pending_recalc;
117   FETCH pending_recalc INTO v_error_code;
118   IF ( v_error_code <> 'Y' ) THEN
119     CLOSE pending_recalc;
120     RETURN v_error_code;
121   END IF;
122   CLOSE pending_recalc;                          -- Added for Bug#5381711
123 
124   OPEN pending_reversed;
125   FETCH pending_reversed INTO v_error_code;
126   IF ( v_error_code <> 'Y' ) THEN
127     CLOSE pending_reversed;                      -- Modified for Bug#5381711
128     RETURN v_error_code;
129   END IF;
130   CLOSE pending_reversed;                        -- Added for Bug#5381711
131 
132 -- If you can get here, then there are no pending adjustments in PA
133 --
134   v_error_code := 'N';
135   RETURN v_error_code;
136 
137 EXCEPTION WHEN others THEN
138   RAISE;
139 END pending_vi_adjustments_exists;
140 
141 FUNCTION check_ap_invoices(p_invoice_id IN NUMBER,
142                            p_status_type IN VARCHAR2) RETURN VARCHAR2 IS
143 v_error_code      VARCHAR2(30) :='';
144 v_cancelled_date  DATE;
145 v_cancelled_by    NUMBER;
146 BEGIN
147    -- v_error_code := AP_PA_API_PKG.get_invoice_status(p_invoice_id,p_status_type); /* bug#5010877 */
148 
149    -- Added this section to replace the above function call.
150     IF p_status_type = 'ADJUSTMENTS' THEN
151 
152 	SELECT CANCELLED_DATE,
153 	       CANCELLED_BY
154 	INTO   v_cancelled_date,
155 	       v_cancelled_by
156 	FROM   ap_invoices_all
157 	WHERE  invoice_id = p_invoice_id;
158 
159       	If    (v_cancelled_date IS NOT NULL AND v_cancelled_by IS NOT NULL) THEN
160               v_error_code := 'PA_INV_CANCELLED';
161         else
162               v_error_code := 'N';
163         End if;
164 
165     END IF;
166 
167    RETURN(v_error_code);
168 
169 EXCEPTION WHEN OTHERS THEN
170   RAISE;
171 END check_ap_invoices;
172 
173 PROCEDURE init_ap_invoices IS
174 BEGIN
175    l_invoice_id := -1;
176    l_invoice_status := '';
177    l_status_type :='';
178 END init_ap_invoices;
179 
180 FUNCTION ap_invoice_status( p_invoice_id IN NUMBER,
181                             p_status_type In VARCHAR2) RETURN VARCHAR2 IS
182 pa_check_status VARCHAR2(30);  /* For Bug 1969501 */
183 BEGIN
184    IF (( l_invoice_id = p_invoice_id ) and (l_status_type = p_status_type)) THEN
185       RETURN l_invoice_status;
186    ELSE
187       l_invoice_id := p_invoice_id;
188       l_status_type := p_status_type;
189 
190       pa_check_status := pa_integration.check_ap_invoices(p_invoice_id,p_status_type);
191 
192       IF pa_check_status = 'N' THEN
193          l_invoice_status := 'N';
194       ELSIF pa_check_status = 'PA_INV_CANCELLED' THEN
195          l_invoice_status := 'C';
196       ELSE
197          l_invoice_status := 'Y';
198       END IF;
199       RETURN l_invoice_status;
200    END IF;
201 END ap_invoice_status;
202 
203 ---------------------------------------------------------------------------
204 --This Procedure refresh_pa_cache() is used by get_raw_cdl_date and get_raw_cdl_recvr_pa_date
205 --for caching purposes. Global variables defined in PAXPINTS.pls are used for caching.
206 ---------------------------------------------------------------------------
207 PROCEDURE refresh_pa_cache ( p_org_id   IN NUMBER ,
208                              p_expenditure_item_date  IN DATE ,
209                              p_accounting_date IN DATE,
210                              p_caller_flag     IN VARCHAR2
211                            )
212 IS
213 -- local variables
214   l_earliest_start_date  DATE ;
215   l_earliest_end_date  DATE ;
216   l_earliest_period_name pa_cost_distribution_lines_all.pa_period_name%TYPE;
217   l_pa_date           DATE ;
218   l_start_date        DATE ;               -- start date for the l_pa_date.
219   l_end_date          DATE ;               -- end date for the l_pa_date ( equals l_pa_date ).
220   l_period_name pa_cost_distribution_lines_all.pa_period_name%TYPE;
221 
222   l_prof_new_gldate_derivation VARCHAR2(1) := 'N' ;
223 
224 BEGIN
225   /* Changed from value_specific to value for bug 5472333 */
226   l_prof_new_gldate_derivation := NVL(fnd_profile.value('PA_EN_NEW_GLDATE_DERIVATION'), 'N') ;
227 
228   IF( l_prof_new_gldate_derivation = 'Y' )
229   THEN
230 /*
231  *SQL to select the earliest open PA_DATE.
232  *Select the earliest open date ONLY if the global earliest date is NOT yet populated.
233  *Because , earliest pa_date will remain the same for a run.
234  */
235 
236  IF ( p_caller_flag = 'R' AND g_r_earliest_pa_start_date IS NULL ) OR
237     ( p_caller_flag = 'P' AND g_p_earliest_pa_start_date IS NULL ) THEN
238 
239 -- Note : This SQL uses the p_accounting_date filter criteria.
240 
241       SELECT pap1.start_date
242             ,pap1.end_date
243             ,pap1.period_name
244         INTO l_earliest_start_date
245             ,l_earliest_end_date
246             ,l_earliest_period_name
247         FROM pa_periods_all pap1
248        WHERE pap1.status IN ('O','F')
249          AND NVL(pap1.org_id, -99) = NVL(p_org_id, -99)
250          AND pap1.start_date = ( SELECT MIN(pap.start_date)
251                                    FROM pa_periods_all pap
252                                   WHERE status IN ('O','F')
253                                     AND NVL( org_id, -99 ) = NVL( p_org_id, -99 )
254                                );
255  END IF ;
256 
257 -- SQL to select the PA_DATE for the current EI.
258 /* Code fix for Bug 1657231...
259    Added Begin... Exception...END to Handle No_Data_Found Exception */
260 
261 /*
262  * EPP.
263  * Modified the following sql to get p_accounting_date as l_pa_date
264  * rather then end_date.
265  */
266 BEGIN  /* Added for Bug 1657231 */
267       SELECT pap.start_date
268             ,pap.end_date
269             ,p_accounting_date
270             ,pap.period_name
271         INTO l_start_date
272             ,l_end_date
273             ,l_pa_date
274             ,l_period_name
275         FROM pa_periods_all pap
276        WHERE pap.status in ('O','F')
277          AND pap.end_date >= TRUNC(p_expenditure_item_date)
278          AND p_accounting_date BETWEEN pap.start_date and pap.end_date
279          AND NVL(org_id, -99) = NVL(p_org_id, -99) ;
280 
281 EXCEPTION
282    WHEN NO_DATA_FOUND THEN
283    l_pa_date := NULL;
284    l_period_name := NULL;
285 END; /* Added for Bug 1657231 */
286 
287 /*If the l_pa_date obtained is NULL, try to find a pa_date without the accounting-date
288  *check. This approach was used even previously.
289  *This SQL will FAIL - if there are more than one row in pa_periods_all - with the same end_date.
290  */
291 
292       IF ( l_pa_date IS NULL )
293       THEN
294         SELECT pap1.start_date
295               ,pap1.end_date
296               ,pap1.start_date
297               ,pap1.period_name
298           INTO l_start_date
299               ,l_end_date
300               ,l_pa_date
301               ,l_period_name
302           FROM pa_periods_all pap1
303          WHERE NVL(pap1.org_id, -99) = NVL(p_org_id, -99) /*Added While  fixing bug 1657231*/
304            AND pap1.start_date = ( SELECT MIN(pap.start_date)
305                                      FROM pa_periods_all pap
306                                     WHERE status IN ('O','F')
307                                       AND pap.start_date >= TRUNC(p_expenditure_item_date)
308                                       AND NVL(org_id, -99) = NVL(p_org_id, -99)
309                                  );
310       END IF; -- l_pa_date IS NULL
311 
312   ELSE -- profile option is not set.
313     /*
314      *SQL to select the earliest open PA_DATE.
315      *Select the earliest open date ONLY if the global earliest date is NOT yet populated.
316      *Because , earliest pa_date will remain the same for a run.
317      */
318 
319      IF ( p_caller_flag = 'R' AND g_r_earliest_pa_start_date IS NULL ) OR
320         ( p_caller_flag = 'P' AND g_p_earliest_pa_start_date IS NULL ) THEN
321 
322     -- Note : This SQL uses the p_accounting_date filter criteria.
323 
324           SELECT pap1.start_date
325                 ,pap1.end_date
326                 ,pap1.period_name
327             INTO l_earliest_start_date
328                 ,l_earliest_end_date
329                 ,l_earliest_period_name
330             FROM pa_periods_all pap1
331            WHERE pap1.status IN ('O', 'F')
332              AND NVL( pap1.org_id, -99 ) = NVL( p_org_id, -99 )
333              AND pap1.end_date = ( SELECT MIN(pap.end_date)
334                                      FROM pa_periods_all pap
335                                     WHERE pap.status IN ('O','F')
336      --                               AND p_accounting_date BETWEEN pap.start_date AND pap.end_date /* commented for bug 1982225 */
337                                       AND NVL( pap.org_id, -99 ) = NVL( p_org_id, -99 )
338                                  );
339      END IF ;
340 
341     -- SQL to select the PA_DATE for the current EI.
342     /* Code fix for Bug 1657231...
343        Added Begin... Exception...END to Handle No_Data_Found Exception */
344 
345     BEGIN  /* Added for Bug 1657231 */
346           SELECT pap.start_date
347                 ,pap.end_date
348                 ,pap.end_date
349                 ,pap.period_name
350             INTO l_start_date
351                 ,l_end_date
352                 ,l_pa_date
353                 ,l_period_name
354             FROM pa_periods_all pap
355            WHERE status in ('O','F')
356              AND pap.end_date >= TRUNC(p_expenditure_item_date)
357              AND p_accounting_date BETWEEN pap.start_date and pap.end_date
358              AND NVL(org_id, -99) = NVL(p_org_id, -99) ;
359 
360     EXCEPTION
361        WHEN NO_DATA_FOUND THEN
362        l_pa_date := NULL;
363        l_period_name := NULL;
364     END; /* Added for Bug 1657231 */
365 
366     /*If the l_pa_date obtained is NULL, try to find a pa_date without the accounting-date
367      *check. This approach was used even previously.
368      *This SQL will FAIL - if there are more than one row in pa_periods_all - with the same end_date.
369      */
370 
371           IF ( l_pa_date IS NULL )
372           THEN
373             SELECT pap1.start_date
374                   ,pap1.end_date
375                   ,pap1.end_date
376                   ,pap1.period_name
377               INTO l_start_date
378                   ,l_end_date
379                   ,l_pa_date
380                   ,l_period_name
381               FROM pa_periods_all pap1
382              WHERE pap1.end_date = ( SELECT MIN(pap.end_date)
383                                       FROM pa_periods_all pap
384                                      WHERE pap.status IN ('O','F')
385                                        AND pap.end_date >= TRUNC(p_expenditure_item_date)
386                                        AND NVL(pap.org_id, -99) = NVL(p_org_id, -99)
387                                    )
388                AND NVL(pap1.org_id, -99) = NVL(p_org_id, -99); /* Added While  fixing bug 1657231
389                                                              Although not related to the bug */
390           END IF;
391   END IF; -- profile check
392 
393       /*
394        * Populate global variables.
395        */
396       IF ( p_caller_flag = 'R' ) THEN
397         -- Populate receiver cache.
398         g_r_earliest_pa_start_date   := l_earliest_start_date ;
399         g_r_earliest_pa_end_date     := l_earliest_end_date ;
400         g_r_earliest_pa_period_name  := l_earliest_period_name ;
401         g_recvr_org_id            := p_org_id ;
402         g_recvr_pa_start_date     := l_start_date ;
403         g_recvr_pa_end_date       := l_end_date ;
404         g_recvr_pa_date           := l_pa_date ;
405         g_recvr_pa_period_name     := l_period_name ;
406       ELSIF ( p_caller_flag = 'P' ) THEN
407         -- Populate provider cache
408         g_p_earliest_pa_start_date  := l_earliest_start_date ;
409         g_p_earliest_pa_end_date    := l_earliest_end_date ;
410         g_p_earliest_pa_period_name := l_earliest_period_name ;
411         g_prvdr_org_id           := p_org_id ;
412         g_prvdr_pa_start_date    := l_start_date ;
413         g_prvdr_pa_end_date      := l_end_date ;
414         g_prvdr_pa_date          := l_pa_date ;
415         g_prvdr_pa_period_name    := l_period_name ;
416       END IF; -- caller flag
417 
418 EXCEPTION
419   WHEN NO_DATA_FOUND THEN
420     /*
421      * Earliest dates are NULLed to ensure that the cache gets
422      * refreshed the next time.
423      */
424       IF ( p_caller_flag = 'R' ) THEN
425         -- Populate receiver cache.
426         g_r_earliest_pa_start_date   := NULL ;
427         g_r_earliest_pa_end_date     := NULL ;
428         g_r_earliest_pa_period_name  := NULL ;
429         g_recvr_pa_start_date     := NULL ;
430         g_recvr_pa_end_date       := NULL ;
431         g_recvr_pa_date           := NULL ;
432         g_recvr_pa_period_name     := NULL ;
433       ELSIF ( p_caller_flag = 'P' ) THEN
434         -- Populate provider cache
435         g_p_earliest_pa_start_date  := NULL ;
436         g_p_earliest_pa_end_date    := NULL ;
437         g_p_earliest_pa_period_name := NULL ;
438         g_prvdr_pa_start_date    := NULL ;
439         g_prvdr_pa_end_date      := NULL ;
440         g_prvdr_pa_date          := NULL ;
441         g_recvr_pa_period_name    := NULL ;
442       END IF; -- caller flag
443   WHEN OTHERS THEN
444      RAISE ;
445 
446 END refresh_pa_cache ;
447 -------------------------------------------------------------------------------
448 -- Function - get_raw_cdl_pa_date
449 -- Comments are at Package specification level.
450 -- This function is created for Bug No : 1103257. Function will be called from
451 -- PAVVIT process ( Suppllier invoice interface from payables module ). This
452 -- function will ensure that PA_DATE populated for Raw CDLs will be always
453 -- Greater than Payables Accounting date for Raw CDLs.
454 --------------------------------------------------------------------------
455 --This function was modified to use caching. The actual DB access happens in
456 -- pa_integration.refresh_pa_cache().
457 --This is to get the pa_date for the provider part. The receiver part is done
458 -- by get_raw_cdl_recvr_pa_date().
459 --------------------------------------------------------------------------
460 FUNCTION get_raw_cdl_pa_date ( p_expenditure_item_date  IN DATE,
461                                p_accounting_date        IN DATE,
462                                p_org_id                 IN NUMBER
463                              )
464 RETURN DATE
465 IS
466   l_prof_new_gldate_derivation VARCHAR2(1);
467 BEGIN
468   /* Changed from value_specific to value for bug 5472333 */
469   l_prof_new_gldate_derivation := NVL(fnd_profile.value('PA_EN_NEW_GLDATE_DERIVATION'), 'N') ;
470 
471 
472   IF ( g_p_earliest_pa_start_date IS NOT NULL
473        and nvl(p_org_id,-99) = nvl(g_prvdr_org_id,-99) ) /* 1982225. cache should be referred only if orgs are same */
474 
475   THEN
476     -- values are already available in the provider_cache.
477     -- so, check the provider_cache and return pa_date accordingly.
478 
479     IF ( l_prof_new_gldate_derivation = 'Y')
480     THEN
481         IF ( p_accounting_date BETWEEN g_prvdr_pa_start_date AND g_prvdr_pa_end_date AND
482              p_expenditure_item_date  <= g_prvdr_pa_start_date )
483         THEN
484           return ( p_accounting_date ) ;
485         ELSIF ( p_accounting_date <= g_p_earliest_pa_start_date AND
486                 p_expenditure_item_date  <= g_p_earliest_pa_start_date )
487         THEN
488           g_prvdr_pa_start_date  := g_p_earliest_pa_start_date;
489           g_prvdr_pa_end_date    := g_p_earliest_pa_end_date;
490           g_prvdr_pa_period_name := g_p_earliest_pa_period_name;
491           return ( g_prvdr_pa_start_date ) ;
492         END IF ; -- p_accounting_date
493     ELSE
494       IF ( p_accounting_date BETWEEN g_prvdr_pa_start_date AND g_prvdr_pa_end_date AND
495             p_expenditure_item_date <= g_prvdr_pa_end_date )
496       THEN
497         return ( g_prvdr_pa_end_date );
498       ELSIF ( p_accounting_date <= g_p_earliest_pa_end_date AND
499               p_expenditure_item_date  <= g_p_earliest_pa_end_date )
500       THEN
501         g_prvdr_pa_start_date  := g_p_earliest_pa_start_date;
502         g_prvdr_pa_end_date    := g_p_earliest_pa_end_date;
503         g_prvdr_pa_period_name := g_p_earliest_pa_period_name;
504         return ( g_prvdr_pa_end_date ) ;
505       END IF; -- p_accounting_date
506     END IF ; -- profile
507   END IF ; -- g_p_earliest_pa_start_date
508 
509   /* If control comes here, it means that EITHER the cache is empty OR
510    * the provider Cache is NOT reusable.
511    * Access the DB and refresh cache and return pa_date.
512    */
513 
514     pa_integration.refresh_pa_cache( p_org_id , p_expenditure_item_date, p_accounting_date, 'P' );
515     RETURN ( g_prvdr_pa_date ) ;
516 EXCEPTION
517   WHEN OTHERS THEN
518     RAISE ;
519 
520 END get_raw_cdl_pa_date;
521 -------------------------------------------------------------------------------------------------------
522 --This is to get the pa_date for the receiver part. The provider part is done
523 -- by get_raw_cdl_pa_date().
524 --------------------------------------------------------------------------
525 
526 /**This is to get the pa_date for the receiver part **/
527 FUNCTION get_raw_cdl_recvr_pa_date ( p_expenditure_item_date  IN DATE,
528                                      p_accounting_date        IN DATE ,
529                                      p_org_id                 IN NUMBER
530                                    )
531 RETURN DATE
532 IS
533   l_prof_new_gldate_derivation VARCHAR2(1);
534 BEGIN
535   /* Changed from value_specific to value for bug 5472333 */
536   l_prof_new_gldate_derivation := NVL(fnd_profile.value('PA_EN_NEW_GLDATE_DERIVATION'), 'N') ;
537 
538   IF ( g_r_earliest_pa_start_date IS NOT NULL
539        and nvl(p_org_id,-99) = nvl(g_recvr_org_id,-99) )  /* 1982225. cache should be referred only if orgs are same */
540   THEN
541      -- receiver cache IS available.
542      -- Hence, try to re-use the receiver cache.
543 
544     IF ( l_prof_new_gldate_derivation = 'Y' )
545     THEN
546       IF ( p_accounting_date BETWEEN g_recvr_pa_start_date AND g_recvr_pa_end_date AND
547            p_expenditure_item_date <= g_recvr_pa_start_date )
548       THEN
549         return ( p_accounting_date ) ;
550       ELSIF ( p_accounting_date <= g_r_earliest_pa_start_date AND
551               p_expenditure_item_date <= g_r_earliest_pa_start_date )
552       THEN
553         g_recvr_pa_start_date  := g_p_earliest_pa_start_date;
554         g_recvr_pa_end_date    := g_p_earliest_pa_end_date;
555         g_recvr_pa_period_name := g_p_earliest_pa_period_name;
556         return ( g_recvr_pa_start_date ) ;
557       END IF ;
558     ELSE
559       IF ( p_accounting_date BETWEEN g_recvr_pa_start_date AND g_recvr_pa_end_date AND
560            p_expenditure_item_date <= g_recvr_pa_end_date )
561       THEN
562         return ( p_accounting_date ) ;
563       ELSIF ( p_accounting_date <= g_r_earliest_pa_end_date AND
564               p_expenditure_item_date <= g_r_earliest_pa_end_date )
565       THEN
566         g_recvr_pa_start_date  := g_p_earliest_pa_start_date;
567         g_recvr_pa_end_date    := g_p_earliest_pa_end_date;
568         g_recvr_pa_period_name := g_p_earliest_pa_period_name;
569         return ( g_recvr_pa_end_date ) ;
570       END IF ;
571     END IF; -- profile
572 
573     -- receiver cache is EMPTY.
574     -- Try to use the provider cache.
575 
576   ELSIF ( g_p_earliest_pa_start_date IS NOT NULL    /* 1982225 . we should check if prvdr cache is available or not. */
577           and NVL( g_prvdr_org_id, -99 ) = NVL( p_org_id, -99 ) )
578   THEN
579     IF ( l_prof_new_gldate_derivation = 'Y' )
580     THEN
581       IF ( p_accounting_date BETWEEN g_prvdr_pa_start_date AND g_prvdr_pa_end_date AND
582            p_expenditure_item_date <= g_prvdr_pa_start_date )
583       THEN
584          -- copy provider cache to receiver cache.
585          g_recvr_org_id               := g_prvdr_org_id ;
586          g_r_earliest_pa_start_date   := g_p_earliest_pa_start_date  ;
587          g_r_earliest_pa_end_date     := g_p_earliest_pa_end_date  ;
588          g_r_earliest_pa_period_name  := g_p_earliest_pa_period_name  ;
589          g_recvr_pa_start_date        := g_prvdr_pa_start_date ;
590          g_recvr_pa_end_date          := g_prvdr_pa_end_date ;
591          g_recvr_pa_period_name       := g_prvdr_pa_period_name ;
592          g_recvr_pa_date              := g_prvdr_pa_date ;
593          return ( p_accounting_date ) ;
594       ELSIF ( p_accounting_date <= g_p_earliest_pa_start_date AND
595               p_expenditure_item_date <= g_p_earliest_pa_start_date )
596       THEN
597          -- copy provider cache to receiver cache.
598          g_recvr_org_id               := g_prvdr_org_id ;
599          g_r_earliest_pa_start_date   := g_p_earliest_pa_start_date  ;
600          g_r_earliest_pa_end_date     := g_p_earliest_pa_end_date  ;
601          g_r_earliest_pa_period_name  := g_p_earliest_pa_period_name  ;
602          g_recvr_pa_start_date        := g_p_earliest_pa_start_date ;
603          g_recvr_pa_end_date          := g_p_earliest_pa_end_date ;
604          g_recvr_pa_period_name       := g_p_earliest_pa_period_name ;
605          g_recvr_pa_date              := g_prvdr_pa_date ;
606          return ( g_recvr_pa_start_date ) ;
607       END IF; --p_accounting_date
608     ELSE -- profile not set
609       IF ( p_accounting_date BETWEEN g_prvdr_pa_start_date AND g_prvdr_pa_end_date AND
610            p_expenditure_item_date <= g_prvdr_pa_end_date )
611       THEN
612          -- copy provider cache to receiver cache.
613          g_recvr_org_id               := g_prvdr_org_id ;
614          g_r_earliest_pa_start_date   := g_p_earliest_pa_start_date  ;
615          g_r_earliest_pa_end_date     := g_p_earliest_pa_end_date  ;
616          g_r_earliest_pa_period_name  := g_p_earliest_pa_period_name  ;
617          g_recvr_pa_start_date        := g_prvdr_pa_start_date ;
618          g_recvr_pa_end_date          := g_prvdr_pa_end_date ;
619          g_recvr_pa_period_name       := g_prvdr_pa_period_name ;
620          g_recvr_pa_date              := g_prvdr_pa_date ;
621          return ( g_recvr_pa_end_date ) ;
622       ELSIF ( p_accounting_date <= g_p_earliest_pa_end_date AND
623               p_expenditure_item_date <= g_p_earliest_pa_end_date )
624       THEN
625          -- copy provider cache to receiver cache.
626          g_recvr_org_id               := g_prvdr_org_id ;
627          g_r_earliest_pa_start_date   := g_p_earliest_pa_start_date  ;
628          g_r_earliest_pa_end_date     := g_p_earliest_pa_end_date  ;
629          g_r_earliest_pa_period_name  := g_p_earliest_pa_period_name  ;
630          g_recvr_pa_start_date        := g_p_earliest_pa_start_date ;
631          g_recvr_pa_end_date          := g_p_earliest_pa_end_date ;
632          g_recvr_pa_period_name       := g_p_earliest_pa_period_name ;
633          g_recvr_pa_date              := g_prvdr_pa_date ;
634          return ( g_p_earliest_pa_end_date ) ;
635       END IF; --p_accounting_date
636     END IF ;  -- profile
637   END IF ; -- recvr cache check
638  /*
639   *If control comes here,
640   *EITHER receiver cache is EMPTY or ( Both provider AND receiver caches are NOT reusable )
641   *hence hit the DB and populate/refresh receiver cache.
642   *then return g_recvr_pa_date.
643   */
644 
645     pa_integration.refresh_pa_cache ( p_org_id , p_expenditure_item_date , p_accounting_date, 'R' );
646     RETURN ( g_recvr_pa_date ) ;
647 EXCEPTION
648     WHEN OTHERS THEN
649       RAISE ;
650 END get_raw_cdl_recvr_pa_date ;
651 -------------------------------------------------------------------------------------------------------
652 
653 -- FUnction get_burden_cdl_pa_date
654 -- This function is created for Bug no : 1103257. FUnction will be called by
655 -- PACODTBC process (Distribute total burden cost). FUnction will ruturn the
656 -- Date to be populated as PA_DATE for Burden CDLs. FUnction will be called
657 -- only when the C and D types of the rows will be created for Supplier
658 -- Invoices.
659 ---------------------------------------------------------------------------
660 /*
661  * EPP.
662  * This function is NOT used anymore. Instead pa_utils2.get_pa_date is used
663  * since the functionality is same in both the procedures. Only the parameter
664  * is different.
665  */
666 FUNCTION get_burden_cdl_pa_date ( p_raw_cdl_date  IN DATE )
667     RETURN DATE
668 IS
669     l_pa_period_end_date  DATE;
670 BEGIN
671    SELECT     MIN(pap.end_date)
672      INTO     l_pa_period_end_date
673      FROM     pa_periods pap
674     WHERE     pap.status in ( 'O', 'F')
675       AND     pap.end_date >= p_raw_cdl_date;
676 
677    RETURN     l_pa_period_end_date;
678 END get_burden_cdl_pa_date;
679 ---------------------------------------------------------------------------
680 --End FUnction get_burden_cdl_pa_date
681 ---------------------------------------------------------------------------
682 /*
683  * EPP.
684  * This function can be called for both Provider and Receiver gl dates
685  * by passing the appropriate parameters.
686  */
687 FUNCTION get_gl_period_name ( p_gl_date         IN pa_cost_distribution_lines_all.gl_date%TYPE
688                              ,p_set_of_books_id IN pa_implementations_all.set_of_books_id%TYPE
689                             )
690 RETURN pa_cost_distribution_lines_all.gl_period_name%TYPE
691 IS
692     l_gl_period_name pa_cost_distribution_lines_all.gl_period_name%TYPE;
693     l_gl_start_date  DATE;
694     l_gl_end_date    DATE;
695 BEGIN
696 
697     If (trunc(p_gl_date) between trunc(G_PrevPdStDate) and trunc(G_PrevPdEdDate)) AND
698        G_PrevSOBId = p_set_of_books_id Then
699 
700        l_gl_period_name := G_PrevPeriodName;
701 
702     Else
703           SELECT PERIOD.period_name, PERIOD.start_date, PERIOD.end_date
704             INTO l_gl_period_name, l_gl_start_date, l_gl_end_date
705             FROM GL_PERIOD_STATUSES PERIOD
706            WHERE PERIOD.set_of_books_id = p_set_of_books_id
707              AND PERIOD.application_id = Pa_Period_Process_Pkg.Application_Id
708              AND PERIOD.adjustment_period_flag = 'N'
709              AND p_gl_date BETWEEN PERIOD.start_date AND PERIOD.end_date
710          ;
711 
712         G_PrevPeriodName := l_gl_period_name;
713         G_PrevPdStDate   := l_gl_start_date;
714         G_PrevPdEdDate   := l_gl_end_date;
715         G_PrevSOBId      := p_set_of_books_id;
716 
717      End If;
718 
719      RETURN     l_gl_period_name;
720 EXCEPTION
721 WHEN NO_DATA_FOUND
722 THEN
723   l_gl_period_name := NULL;
724   RETURN l_gl_period_name;
725 END get_gl_period_name;
726 ---------------------------------------------------------------------------
727 
728 /*
729  * The period information calculation is same for all transactions coming
730  * into PA thro transaction import. The following procedure does not distinguish
731  * between system linkages.
732  */
733 PROCEDURE get_period_information ( p_expenditure_item_date IN pa_expenditure_items_all.expenditure_item_date%TYPE
734                                   ,p_prvdr_gl_date IN pa_cost_distribution_lines_all.gl_date%TYPE
735                                   ,p_line_type IN pa_cost_distribution_lines_all.line_type%TYPE
736                                   ,p_prvdr_org_id IN pa_expenditure_items_all.org_id%TYPE
737                                   ,p_recvr_org_id IN pa_expenditure_items_all.org_id%TYPE
738                                   ,p_prvdr_sob_id IN pa_implementations_all.set_of_books_id%TYPE
739                                   ,p_recvr_sob_id IN pa_implementations_all.set_of_books_id%TYPE
740                                   ,x_prvdr_pa_date OUT NOCOPY pa_cost_distribution_lines_all.pa_date%TYPE
741                                   ,x_prvdr_pa_period_name OUT NOCOPY pa_cost_distribution_lines_all.pa_period_name%TYPE
742                                   ,x_prvdr_gl_period_name OUT NOCOPY pa_cost_distribution_lines_all.gl_period_name%TYPE
743                                   ,x_recvr_pa_date OUT NOCOPY pa_cost_distribution_lines_all.recvr_pa_date%TYPE
744                                   ,x_recvr_pa_period_name OUT NOCOPY pa_cost_distribution_lines_all.recvr_pa_period_name%TYPE
745                                   ,x_recvr_gl_date OUT NOCOPY pa_cost_distribution_lines_all.recvr_gl_date%TYPE
746                                   ,x_recvr_gl_period_name OUT NOCOPY pa_cost_distribution_lines_all.recvr_gl_period_name%TYPE
747                                   ,x_return_status OUT NOCOPY NUMBER
748                                   ,x_error_code OUT NOCOPY VARCHAR2
749                                   ,x_error_stage OUT NOCOPY NUMBER
750                                  )
751 IS
752     l_prvdr_pa_date        pa_cost_distribution_lines_all.pa_date%TYPE;
753     l_prvdr_pa_period_name pa_periods.period_name%TYPE;
754     l_prvdr_gl_period_name gl_periods.period_name%TYPE;
755 
756     l_recvr_pa_date        pa_cost_distribution_lines_all.pa_date%TYPE;
757     l_recvr_pa_period_name pa_periods.period_name%TYPE;
758     l_recvr_gl_date        pa_cost_distribution_lines_all.gl_date%TYPE;
759     l_recvr_gl_period_name gl_periods.period_name%TYPE;
760 
761     l_pa_gl_app_id NUMBER := 8721;
762     l_gl_app_id NUMBER := 101;
763 
764   /*
765    * Processing related variables.
766    */
767   l_return_status              VARCHAR2(1) := FND_API.G_RET_STS_UNEXP_ERROR;
768   l_error_code                 VARCHAR2(30);
769   l_error_stage                VARCHAR2(30);
770   l_debug_mode                 VARCHAR2(1);
771   l_stage                      NUMBER ;
772 
773   l_prof_new_gldate_derivation VARCHAR2(1) := 'N';
774   l_use_same_pa_gl_period_prvdr VARCHAR2(1) := 'N';
775   l_use_same_pa_gl_period_recvr VARCHAR2(1) := 'N';
776 BEGIN
777   pa_debug.init_err_stack('pa_integration.get_period_information');
778 
779   fnd_profile.get('PA_DEBUG_MODE',l_debug_mode);
780   l_debug_mode := NVL(l_debug_mode, 'N');
781 
782   pa_debug.set_process('PLSQL','LOG',l_debug_mode);
783 
784   l_stage := 100;
785   IF l_debug_mode = 'Y' THEN
786    pa_debug.g_err_stage := TO_CHAR(l_stage) || ':From get_period_information';
787    pa_debug.write_file(pa_debug.g_err_stage);
788   END IF;
789 
790   /*
791    * Populating setup related variables.
792    */
793   /* Changed from value_specific to value for bug 5472333 */
794   l_prof_new_gldate_derivation := NVL(fnd_profile.value('PA_EN_NEW_GLDATE_DERIVATION'), 'N') ;
795   l_use_same_pa_gl_period_prvdr := NVL(PA_PERIOD_PROCESS_PKG.Use_Same_PA_GL_Period(p_prvdr_org_id), 'N');
796   l_use_same_pa_gl_period_recvr := NVL(PA_PERIOD_PROCESS_PKG.Use_Same_PA_GL_Period(p_recvr_org_id), 'N');
797 
798     IF ( l_prof_new_gldate_derivation = 'Y' )
799     THEN
800       l_stage := 200;
801             /*
802              * Get Gl periods based on ei date.
803              */
804             l_prvdr_gl_period_name := pa_integration.get_gl_period_name( p_gl_date => p_prvdr_gl_date
805                                                                         ,p_set_of_books_id => p_prvdr_sob_id
806                                                                        );
807 
808             -- Bug 2248543 Added provider and receiver org_id check
809             if (nvl(p_prvdr_org_id,-99) <> nvl(p_recvr_org_id,-99)) then
810                 l_recvr_gl_date := pa_utils2.get_recvr_gl_date( p_reference_date => p_expenditure_item_date
811                                                            ,p_application_id => l_pa_gl_app_id
812                                                            ,p_set_of_books_id => p_recvr_sob_id
813                                                           );
814                 l_recvr_gl_period_name := pa_utils2.g_recvr_gl_period_name;
815             else
816                 l_recvr_gl_date := p_prvdr_gl_date;
817                 l_recvr_gl_period_name := l_prvdr_gl_period_name;
818             end if;
819 
820             /*
821              * Deriving PA period information for Provider.
822              */
823             IF ( l_use_same_pa_gl_period_prvdr = 'Y' )
824             THEN
825               l_stage := 300;
826               /*
827                * Copy Gl period information to Pa periods.
828                */
829               l_prvdr_pa_date := p_prvdr_gl_date;
830               l_prvdr_pa_period_name := l_prvdr_gl_period_name;
831             ELSE -- implementation option is not set
832               l_stage := 400;
833               /*
834                * Get Pa periods based on ei date.
835                */
836 
837               l_prvdr_pa_date := pa_utils2.get_pa_date
838                                                       ( p_ei_date  => p_expenditure_item_date
839                                                        ,p_gl_date  => SYSDATE
840                                                        ,p_org_id   => p_prvdr_org_id
841                                                       );
842               l_prvdr_pa_period_name := pa_utils2.g_prvdr_pa_period_name;
843 
844             END IF; -- implementations option
845             /*
846              * Deriving PA period information for Receiver.
847              */
848             IF ( l_use_same_pa_gl_period_recvr = 'Y' )
849             THEN
850               l_stage := 425;
851               /*
852                * Copy Gl period information to Pa periods.
853                */
854               l_recvr_pa_date := l_recvr_gl_date;
855               l_recvr_pa_period_name := l_recvr_gl_period_name;
856             ELSE -- implementation option is not set
857               l_stage := 450;
858               /*
859                * Get Pa periods based on ei date.
860                */
861 
862               -- Bug 2248543 Added provider and receiver org_id check
863               if (nvl(p_prvdr_org_id,-99) <> nvl(p_recvr_org_id,-99)) then
864                  l_recvr_pa_date := pa_utils2.get_recvr_pa_date
865                                                       ( p_ei_date  => p_expenditure_item_date
866                                                        ,p_gl_date  => SYSDATE
867                                                        ,p_org_id   => p_recvr_org_id
868                                                       );
869                  l_recvr_pa_period_name := pa_utils2.g_recvr_pa_period_name;
870               else
871                  l_recvr_pa_date := l_prvdr_pa_date;
872                  l_recvr_pa_period_name := l_prvdr_pa_period_name;
873               end if;
874 
875             END IF; -- implementations option
876     ELSE -- profile option is not set.
877       l_stage := 500;
878       /*
879        * Get Pa periods based on ei date.
880        */
881          l_prvdr_pa_date := pa_integration.get_raw_cdl_pa_date
882                                                       ( p_expenditure_item_date => p_expenditure_item_date
883                                                        ,p_accounting_date => p_prvdr_gl_date
884                                                        ,p_org_id => p_prvdr_org_id
885                                                       );
886          l_prvdr_pa_period_name := g_prvdr_pa_period_name;
887 
888          /*
889           * recvr_gl_date is not available from txn import.
890           * should find a way out.
891           */
892          -- Bug 2248543 Added provider and receiver org_id check
893          if (nvl(p_prvdr_org_id,-99) <> nvl(p_recvr_org_id,-99)) then
894             l_recvr_pa_date := pa_utils2.get_recvr_pa_date
895                                                       ( p_ei_date => p_expenditure_item_date
896                                                        ,p_gl_date => SYSDATE
897                                                        ,p_org_id => p_recvr_org_id
898                                                       );
899             l_recvr_pa_period_name := pa_utils2.g_recvr_pa_period_name;
900          else
901             l_recvr_pa_date := l_prvdr_pa_date;
902             l_recvr_pa_period_name := l_prvdr_pa_period_name;
903          end if;
904 
905       /*
906        * Get Gl periods based on above derived Pa date.
907        */
908          l_prvdr_gl_period_name := get_gl_period_name( p_gl_date => p_prvdr_gl_date
909                                                       ,p_set_of_books_id => p_prvdr_sob_id
910                                                      );
911 
912          -- Bug 2248543 Added provider and receiver org_id check
913          if (nvl(p_prvdr_org_id,-99) <> nvl(p_recvr_org_id,-99)) then
914              l_recvr_gl_date := pa_utils2.get_recvr_gl_date( p_reference_date => l_recvr_pa_date
915                                                         ,p_application_id => l_gl_app_id
916                                                         ,p_set_of_books_id => p_recvr_sob_id
917                                                        );
918              l_recvr_gl_period_name := pa_utils2.g_recvr_gl_period_name;
919          else
920              l_recvr_gl_date := p_prvdr_gl_date;
921              l_recvr_gl_period_name := l_prvdr_gl_period_name;
922          end if;
923 
924     END IF; -- profile option
925     l_stage := 600;
926 
927     /*
928      * Populate the out variables.
929      */
930     x_prvdr_pa_date := l_prvdr_pa_date;
931     x_prvdr_pa_period_name := l_prvdr_pa_period_name;
932     x_prvdr_gl_period_name := l_prvdr_gl_period_name;
933 
934     x_recvr_pa_date := l_recvr_pa_date;
935     x_recvr_pa_period_name := l_recvr_pa_period_name;
936     x_recvr_gl_date := l_recvr_gl_date;
937     x_recvr_gl_period_name := l_recvr_gl_period_name;
938 
939     x_return_status := 0;
940 
941     -- reset the error stack
942     PA_DEBUG.reset_err_stack;
943 
944 EXCEPTION
945   WHEN NO_DATA_FOUND THEN
946     x_prvdr_pa_date := NULL;
947     x_prvdr_pa_period_name := NULL;
948     x_prvdr_gl_period_name := NULL;
949 
950     x_recvr_pa_date := NULL;
951     x_recvr_pa_period_name := NULL;
952     x_recvr_gl_date := NULL;
953     x_recvr_gl_period_name := NULL;
954   WHEN OTHERS THEN
955      RAISE ;
956 END; -- get_period_information
957 
958 
959 END pa_integration;