DBA Data[Home] [Help]

PACKAGE BODY: APPS.FV_SLA_PROCESSING_PKG

Source


1 PACKAGE BODY FV_SLA_PROCESSING_PKG AS
2 --$Header: FVXLAACB.pls 120.33.12010000.2 2008/08/04 11:46:12 gnrajago ship $
3 
4 ---------------------------------------------------------------------------
5 ---------------------------------------------------------------------------
6 
7 G_PKG_NAME  CONSTANT  VARCHAR2(30)  :=  'FV_SLA_PROCESSING_PKG ';
8 G_FILE_NAME CONSTANT  VARCHAR2(12)  :=  'FVXLAACB.pls';
9 g_stage               VARCHAR2(500);
10 g_rownum              NUMBER := 0;
11 g_func_name           VARCHAR2(30);
12 ---------------------------------------------------------------------------
13 
14 --==========================================================================
15 ----Logging Declarations
16 --==========================================================================
17 C_STATE_LEVEL CONSTANT NUMBER	     :=	FND_LOG.LEVEL_STATEMENT;
18 C_PROC_LEVEL  CONSTANT  NUMBER	     :=	FND_LOG.LEVEL_PROCEDURE;
19 C_EVENT_LEVEL CONSTANT NUMBER	     :=	FND_LOG.LEVEL_EVENT;
20 C_EXCEP_LEVEL CONSTANT NUMBER	     :=	FND_LOG.LEVEL_EXCEPTION;
21 C_ERROR_LEVEL CONSTANT NUMBER	     :=	FND_LOG.LEVEL_ERROR;
22 C_UNEXP_LEVEL CONSTANT NUMBER	     :=	FND_LOG.LEVEL_UNEXPECTED;
23 g_log_level   CONSTANT NUMBER         := FND_LOG.G_CURRENT_RUNTIME_LEVEL;
24 g_path_name   CONSTANT VARCHAR2(40)  := 'fv.plsql.fvxlaacb.fv_sla_processing_pkg';
25 g_log_enabled BOOLEAN := FALSE;
26 g_adjustment_type VARCHAR2(30);
27 --
28 -- Linefeed character
29 --
30 CRLF          CONSTANT VARCHAR2(1) := FND_GLOBAL.newline;
31 
32 
33 
34 TYPE fv_ref_detail IS TABLE OF FV_EXTRACT_DETAIL_GT%ROWTYPE
35 INDEX BY BINARY_INTEGER;
36 
37 TYPE fv_extract_rec IS RECORD
38 (
39    event_id NUMBER,
40    line_number NUMBER,
41    fund_value fv_extract_detail_gt.fund_value%TYPE := 'X',
42    fund_category fv_extract_detail_gt.fund_category%TYPE DEFAULT 'N',
43    fund_expired_status fv_extract_detail_gt.fund_expired_status%TYPE DEFAULT 'NONE',
44    fund_time_frame fv_extract_detail_gt.fund_time_frame%TYPE DEFAULT 'NONE',
45    prior_year_flag fv_extract_detail_gt.prior_year_flag%TYPE DEFAULT 'N',
46    account_rule fv_extract_detail_gt.account_rule%TYPE DEFAULT 'DEFAULT',
47    receivable_with_advance fv_extract_detail_gt.receivable_with_advance%TYPE DEFAULT 'N'
48 );
49 
50 
51 /*PROCEDURE DEBUG(p_debug IN VARCHAR2);
52  *
53  * PROCEDURE DEBUG(p_debug IN VARCHAR2) IS PRAGMA AUTONOMOUS_TRANSACTION;
54  *       BEGIN
55  *
56  *
57  *             --fnd_log.string(FND_LOG.LEVEL_STATEMENT,'BCPSA',p_debug);
58  *                    INSERT INTO bcpsa_xla_temp
59  *                    VALUES(bcpsa_xla_temp_S.NEXTVAL,p_debug);
60  *                          COMMIT;
61  *
62  *                             EXCEPTION
63  *                                   WHEN others THEN
64  *                                          NULL;
65  *                                          END DEBUG;*/
66 
67 PROCEDURE trace (
68       p_level             IN NUMBER,
69       p_procedure_name    IN VARCHAR2,
70       p_debug_info        IN VARCHAR2
71 );
72 
73 PROCEDURE trace (
74       p_level             IN NUMBER,
75       p_procedure_name    IN VARCHAR2,
76       p_debug_info        IN VARCHAR2
77 )
78 IS
79 
80 BEGIN
81   IF (p_level >= g_log_level ) THEN
82     FND_LOG.STRING(p_level,
83                    p_procedure_name,
84                    p_debug_info);
85   END IF;
86 
87 END trace;
88 
89 
90 PROCEDURE po_extract
91 (
92   p_application_id               IN            NUMBER,
93   p_accounting_mode              IN            VARCHAR2
94 );
95 
96 PROCEDURE cst_extract
97 (
98   p_application_id               IN            NUMBER,
99   p_accounting_mode              IN            VARCHAR2
100 );
101 
102 PROCEDURE AP_extract
103 (
104   p_application_id               IN            NUMBER,
105   p_accounting_mode              IN            VARCHAR2
106 );
107 
108 PROCEDURE ar_extract
109 (
110   p_application_id               IN            NUMBER,
111   p_accounting_mode              IN            VARCHAR2
112 );
113 
114 FUNCTION get_anticipated_fund_amt( p_Fund_value        IN VARCHAR2,
115                                    p_Balancing_segment IN NUMBER,
116                                    p_Natural_segment   IN NUMBER,
117                                    p_Ledger_id         IN NUMBER,
118                                    p_coaid             IN  NUMBER,
119                                    p_Period_name       IN  VARCHAR2)
120 RETURN NUMBER;
121 
122 FUNCTION get_fund_value
123 (p_coaid        IN          NUMBER,
124  p_ccid         IN          NUMBER,
125  p_gl_account_segment OUT NOCOPY    NUMBER,
126  p_gl_balancing_segment OUT NOCOPY    NUMBER
127 )
128 RETURN VARCHAR2;
129 
130 FUNCTION pya_adj_amt_by_fund( p_coaid                 IN        NUMBER,
131                               p_event_id              IN        NUMBER,
132                               p_header_id             IN        NUMBER,
133                               p_fund_value            IN        VARCHAR2)
134 RETURN NUMBER;
135 
136 FUNCTION get_prior_year_status
137 (
138 p_application_id             IN         NUMBER,
139 p_ledger_id                  IN         NUMBER,
140 p_coa_id					 IN         NUMBER,
141 p_ccid                       IN         NUMBER,
142 p_gl_date                    IN         DATE
143 )
144 RETURN BOOLEAN;
145 
146  /*============================================================================
147  *  -- FV EXTRACT FOR XLA
148  *  -- Type         : public
149  *  -- Pre-reqs     : called from XLA Business event
150  *  -- Description  :
151  *  --                    This procedure invoked by SLA online accounting engine.
152  *  --                    All the federal sources required would be processed
153  *  --                    by this extract program to be used in federal Accounitng.
154  *  --
155  *  --  Logic :     *--------------------FV Extract Logic---------------
156  *  --                     Parameters :  Application_ID
157  *  --                                   Accounting Mode
158  *  --
159  *  --                 Begin
160  *  --                   .
161  *  --                 ------- verify if federal is installed
162  *  --                     IF  NOT federal installed Then
163  *  --                           RETURN TRUE
164  *  --                   END IF.
165  *  --
166  *  --                 IF   Accounting_mode in ('FUNDS_CHECK','FUNDS_RESERVE') THEN
167  *  --
168  *  --                          IF Application_id = 201 THEN -- Start PO
169  *  --                                    IF PO Transaction object is NOT NULL THEN
170  *  --                                         -- process logic and populate the FV reference object
171  *  --                                       Insert into FV_REF  ......values (event_id,line_num.,application_id .......)  -- columns for PO
172  *  --                              END IF
173  *  --                           END IF----- End PO
174  *  --
175  *  --
176  *  --                      IF Application_id = 501 THEN -- Start AP
177  *  --
178  *  --                               IF AP Transaction object is NOT NULL THEN
179  *  --                                 -- process logic and populate the FV reference object for AP events...
180  *  --                                   Insert into FV_REF  ......values (event_id,line_num,application_id........) -- columns for AP
181  *  --                              END IF
182  *  --                      END IF----- End AP
183  *  --                       ...
184  *  --                      ...
185  *  --                     .. Costing etc
186  *  --
187  *  --
188  *  --            END IF  --- check for accounting mode
189  *  --
190  *  --            RETURN TRUE
191  *  --
192  *  --            ------------------End FV Extract Logic---------------
193  *  --
194  * /*============================================================================*/
195 
196 PROCEDURE extract
197 (
198   p_application_id               IN            NUMBER,
199   p_accounting_mode              IN            VARCHAR2
200 )
201 IS
202 
203     l_debug_info                   VARCHAR2(240);
204     l_procedure_name               VARCHAR2(100) :='.EXTRACT';
205 
206 BEGIN
207 
208     l_procedure_name := g_path_name || l_procedure_name;
209     -------------------------------------------------------------------------
210     l_debug_info := 'Begin of procedure '||l_procedure_name;
211     trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
212     -------------------------------------------------------------------------
213     -------------------------------------------------------------------------
214 
215 
216     IF (p_application_id = 201) THEN
217         po_extract(p_application_id, p_accounting_mode);
218     ELSIF (p_application_id = 707) THEN
219         cst_extract(p_application_id, p_accounting_mode);
220     ELSIF (p_application_id = 200) THEN
221         ap_extract(p_application_id, p_accounting_mode);
222     ELSIF (p_application_id = 222) THEN
223         ar_extract(p_application_id, p_accounting_mode);
224     ELSE
225         RETURN;
226     END IF;
227 
228     -------------------------------------------------------------------------
229     l_debug_info := 'End of procedure '||l_procedure_name;
230     trace(C_PROC_LEVEL, l_procedure_name, l_debug_info);
231     -------------------------------------------------------------------------
232 
233 EXCEPTION
234 
235   WHEN OTHERS THEN
236      l_debug_info := 'Error in Federal SLA Processing ' || SQLERRM;
237      trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
238      FND_MESSAGE.SET_NAME('FND', 'FND_GENERIC_MESSAGE');
239      FND_MESSAGE.SET_TOKEN('MESSAGE' ,
240          'Procedure :fv_sla_processing_pkg.extract'|| CRLF||
241          'Error     :'||SQLERRM);
242      FND_MSG_PUB.ADD;
243      APP_EXCEPTION.RAISE_EXCEPTION;
244 
245 END extract;
246 
247 
248 FUNCTION get_account_valid_status
249 (
250 p_event_info IN xla_events_gt%ROWTYPE,
251 p_fv_extract_rec IN OUT NOCOPY fv_extract_rec
252 )
253 RETURN BOOLEAN
254 
255 IS
256     l_debug_info                   VARCHAR2(240);
257     l_procedure_name               VARCHAR2(100) := '.GET_ACCOUNT_VALID_STATUS';
258 
259 
260     /* Get the AR Invoice Extract Line Natural Segment Value */
261     CURSOR cur_ar_invline_natseg_value (p_event_id NUMBER,
262                                     p_line_number NUMBER)
263     IS
264     SELECT glseg.ar_gl_natural_segment_value inv_natseg_value
265       FROM  ar_gl_segments_ref_v glseg , ar_cust_trx_lines_l_v trxobj
266      WHERE trxobj.trx_line_dist_ccid = glseg.ar_gl_code_combination_id
267        AND trxobj.event_id = p_event_id
268        AND trxobj.line_number = p_line_number;
269 
270     /* Get the Transaction Customer Class for the invoice */
271     CURSOR cur_ar_inv_trx_custclass (p_event_id NUMBER)
272     IS
273     SELECT bill_customer_class_code
274       FROM ar_bill_to_customers_s_v trxcc
275      WHERE trxcc.event_id = p_event_id;
276 
277 
278     /* Get the AR Receipt and Miscellaneous Receipt Extract Natural Segment value */
279     CURSOR cur_ar_rct_natseg_value (p_event_id NUMBER,
280                                     p_line_number NUMBER)
281     IS
282     SELECT to_number(glseg.ar_gl_natural_segment_value) rct_natseg_value
283       FROM  ar_gl_segments_ref_v glseg , ar_distributions_l_v trxobj
284      WHERE  trxobj.dist_code_combination_id = glseg.ar_gl_code_combination_id
285       AND   trxobj.event_id = p_event_id
286       AND trxobj.line_number = p_line_number;
287 
288     /* Get the AR Receipt and Miscellaneous Receipt Distribution Source type value */
289     CURSOR cur_ar_rct_dist_type (p_event_id NUMBER,
290                                  p_line_number NUMBER)
291     IS
292     SELECT dist_source_type
293       FROM ar_distributions_l_v ardist
294      WHERE ardist.event_id = p_event_id
295        AND ardist.line_number = p_line_number;
296 
297     l_ar_inv_cust_class ar_bill_to_customers_s_v.bill_customer_class_code%TYPE;
298     l_ar_rct_dist_type ar_distributions_l_v.distribution_type%TYPE;
299     l_line_natseg_value NUMBER := 0;
300     l_inv_line_natseg_value NUMBER := 0;
301 
302 BEGIN
303     l_procedure_name := g_path_name || l_procedure_name;
304     -- ================================== FND_LOG ==================================
305     l_debug_info := 'Begin of procedure '||l_procedure_name;
306     trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
307     -- ================================== FND_LOG ==================================
308 
309     -- ================================== FND_LOG ==================================
310     l_debug_info := 'Event Type Information: '|| p_event_info.event_type_code ;
311     trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
312     -- ================================== FND_LOG ==================================
313 
314 
315     /* Invoice Ladder */
316     IF (p_event_info.event_type_code IN ('INV_CREATE', 'INV_UPDATE')) THEN
317 
318         /* Get the Customer Class Information */
319         OPEN cur_ar_inv_trx_custclass(p_event_info.event_id);
320         FETCH cur_ar_inv_trx_custclass INTO l_ar_inv_cust_class;
321         -- ================================== FND_LOG ==================================
322            l_debug_info := 'Bill to Customer Class is : ' || l_ar_inv_cust_class;
323            trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
324         -- ================================== FND_LOG ==================================
325         CLOSE cur_ar_inv_trx_custclass;
326 
327         -- ================================== FND_LOG ==================================
328            l_debug_info := 'Federal Fund Category is : ' || p_fv_extract_rec.fund_category ;
329            trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
330         -- ================================== FND_LOG ==================================
331 
332         /* Check the Customer Class Code for 'FEDERAL or 'NON-FEDERAL'
333          and Fund Category 'Reimbursable' for Distribution Revenue Account */
334         -- IF (NVL(l_ar_inv_cust_class, 'Not applicable') IN ('FEDERAL', 'NON-FEDERAL')) -- commented the condition for bug 5617346
335          IF (p_fv_extract_rec.fund_category IN ('R', 'S', 'T')) THEN
336             BEGIN
337                 /* Get the Natural Account Segment for Transaction Line */
338                 OPEN cur_ar_invline_natseg_value(p_fv_extract_rec.event_id,
339                                                  p_fv_extract_rec.line_number);
340                 FETCH cur_ar_invline_natseg_value INTO l_line_natseg_value;
341                 -- ======================================= FND_LOG =======================================
342                    l_debug_info := 'Invoice Natural Account Segment Value is : '|| l_line_natseg_value ;
343                    trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
344                 -- ======================================= FND_LOG =======================================
345                 CLOSE cur_ar_invline_natseg_value;
346             EXCEPTION
347                 WHEN OTHERS THEN
348                     IF cur_ar_invline_natseg_value%ISOPEN THEN
349                          CLOSE cur_ar_invline_natseg_value;
350                     END IF;
351                     l_debug_info := 'SQL Error encountered' ||SQLERRM ;
352                     trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
353                     RETURN FALSE;
354             END;
355             /* We need to check the Credit Account Natural Account Segments should fall in this range */
356             IF ((l_line_natseg_value BETWEEN 510000 AND 510099) OR (l_line_natseg_value BETWEEN 520000 AND 520099)) THEN
357                 -- ======================================= FND_LOG =======================================
358                 l_debug_info := 'Validated the Line Condition';
359                  trace(C_STATE_LEVEL, l_procedure_name, l_debug_info );
360                 -- ======================================= FND_LOG =======================================
361                 RETURN TRUE;
362             END IF;
363         END IF;
364         -- Return False if none matches the criteria
365         RETURN FALSE;
366 
367 
368     /* Receipt Ladder */
369     ELSIF (p_event_info.event_type_code IN ('RECP_CREATE', 'RECP_UPDATE', 'RECP_REVERSE')) THEN
370         BEGIN
371             -- Get the Natural Account Segment
372             OPEN cur_ar_rct_natseg_value(p_fv_extract_rec.event_id,
373                                          p_fv_extract_rec.line_number);
374             FETCH cur_ar_rct_natseg_value INTO l_line_natseg_value;
375             -- ================================== FND_LOG ==================================
376             l_debug_info := 'REC Line Natural Segment: ' || l_line_natseg_value;
377             trace(C_STATE_LEVEL, l_procedure_name, l_debug_info );
378             -- ================================== FND_LOG ==================================
379             CLOSE cur_ar_rct_natseg_value;
380         EXCEPTION
381             WHEN OTHERS THEN
382                 IF cur_ar_rct_natseg_value%ISOPEN THEN
383                     CLOSE cur_ar_rct_natseg_value;
384                 END IF;
385                 l_debug_info := 'SQL Error encountered';
386                 trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
387                 RETURN FALSE;
388         END;
389 
390         BEGIN
391             -- Get the Natural Account Segment of Invoice
392             OPEN cur_ar_invline_natseg_value(p_fv_extract_rec.event_id,
393                                              p_fv_extract_rec.line_number);
394             FETCH cur_ar_invline_natseg_value INTO l_inv_line_natseg_value;
395             -- ================================== FND_LOG ==================================
396             l_debug_info := 'REC Line Natural Segment of Invoice: ' || l_inv_line_natseg_value;
397             trace(C_STATE_LEVEL, l_procedure_name, l_debug_info );
398             -- ================================== FND_LOG ==================================
399             CLOSE cur_ar_invline_natseg_value;
400         EXCEPTION
401             WHEN OTHERS THEN
402                 IF cur_ar_invline_natseg_value%ISOPEN THEN
403                     CLOSE cur_ar_invline_natseg_value;
404                 END IF;
405                 l_debug_info := 'SQL Error encountered(1)';
406                 trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
407                 RETURN FALSE;
408         END;
409 
410         /* We need to check the Credit Receivable Account Natural Account
411            segments should fall in this range */
412         IF ((l_inv_line_natseg_value BETWEEN 141000 AND 141099) OR (l_inv_line_natseg_value BETWEEN 145000 AND 145099)) THEN
413             -- ================================== FND_LOG ==================================
414             l_debug_info := 'REV Line of Invoice Validated: Y and it could be for Refund of Advances or Prepayments';
415             trace(C_STATE_LEVEL, l_procedure_name, l_debug_info );
416             -- ================================== FND_LOG ==================================
417             p_fv_extract_rec.account_rule := 'Advance Refund';
418             RETURN TRUE;
422             trace(C_STATE_LEVEL, l_procedure_name, l_debug_info );
419         ELSIF ((l_line_natseg_value BETWEEN 141000 AND 141099) OR (l_line_natseg_value BETWEEN 145000 AND 145099)) THEN
420             -- ================================== FND_LOG ==================================
421             l_debug_info := 'REC Line Validated: Y and it could be for Refund of Advances or Prepayments';
423             -- ================================== FND_LOG ==================================
424             p_fv_extract_rec.account_rule := 'Advance Refund';
425             RETURN TRUE;
426         /* This condition is satisfied for Receipt for 'Reimbursable Order without Advances'
427            and 'Refunds of Overpayments', assigning it to 'Overpayment Refund' as default value
428            We will change this based on other conditions later in the code */
429 
430         ELSIF (l_line_natseg_value BETWEEN 131000 AND 131099) THEN
431             -- ================================== FND_LOG ==================================
432             l_debug_info := 'REC Line Validated: Y and ' || ' it could be for Refund of Overpayments or '
433                             || 'Reimbursable Order without Advances';
434             trace(C_STATE_LEVEL, l_procedure_name, l_debug_info );
435             -- ================================== FND_LOG ==================================
436             p_fv_extract_rec.account_rule := 'Overpayment Refund';
437             p_fv_extract_rec.receivable_with_advance := 'N';
438             RETURN TRUE;
439         ELSIF (l_line_natseg_value BETWEEN 231000 AND 231099) THEN
440             -- ================================== FND_LOG ==================================
441             l_debug_info := 'REC Line Validated: Y and ' || ' it could be for  '
442                             || 'Reimbursable Order with Advances';
443             trace(C_STATE_LEVEL, l_procedure_name, l_debug_info );
444             -- ================================== FND_LOG ==================================
445             p_fv_extract_rec.account_rule := 'Receivable With Advance';
446             p_fv_extract_rec.receivable_with_advance := 'Y';
447             RETURN TRUE;
448         ELSE
449             p_fv_extract_rec.receivable_with_advance := 'N';
450             RETURN FALSE;
451         END IF;
452 
453          -- Return False if none matches the criteria
454          RETURN FALSE;
455 
456 
457     /* Miscellaneous Receipt Ladder */
458     ELSIF (p_event_info.event_type_code IN ('MISC_RECP_CREATE', 'MISC_RECP_UPDATE', 'MISC_RECP_REVERSE')) THEN
459 
460         /* Check the Distribution Type */
461         OPEN cur_ar_rct_dist_type (p_fv_extract_rec.event_id,
462                                    p_fv_extract_rec.line_number);
463         FETCH cur_ar_rct_dist_type INTO l_ar_rct_dist_type;
464         -- ================================== FND_LOG ==================================
465         l_debug_info := 'Miscellaneous Receipt Distribution Type is: '|| l_ar_rct_dist_type ;
466         trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
467         -- ================================== FND_LOG ==================================
468         CLOSE cur_ar_rct_dist_type;
469 
470         -- It's a Credit Line for Miscellaneous Receipt
471         IF (l_ar_rct_dist_type = 'MISCCASH') THEN
472             /* Check Misc Receipt for Refund of Overpaymenmts */
473             IF (((p_fv_extract_rec.fund_expired_status = 'Unexpired') AND (p_fv_extract_rec.prior_year_flag = 'N')
474                   AND (p_fv_extract_rec.fund_category IN ('A', 'B', 'C', 'R','S', 'T'))
475                   AND (p_fv_extract_rec.fund_time_frame IN ('SINGLE', 'MULTIPLE', 'NO_YEAR'))) OR
476                   ((p_fv_extract_rec.fund_expired_status = 'Unexpired') AND (p_fv_extract_rec.prior_year_flag = 'Y')
477                   AND (p_fv_extract_rec.fund_time_frame IN ('MULTIPLE', 'NO_YEAR'))) OR
478                   ((p_fv_extract_rec.fund_expired_status = 'Expired') AND (p_fv_extract_rec.prior_year_flag = 'Y')
479                   AND (p_fv_extract_rec.fund_time_frame IN ('SINGLE', 'MULTIPLE', 'NO_YEAR')))) THEN
480                 -- ================================== FND_LOG ==================================
481                 l_debug_info := 'Misc Receipt is for Refund of Overpayments';
482                 trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
483                 -- ================================== FND_LOG ==================================
484                 BEGIN
485                     -- Get the Natural Account Segment
486                     OPEN cur_ar_rct_natseg_value(p_fv_extract_rec.event_id,
487                                                  p_fv_extract_rec.line_number);
488                     FETCH cur_ar_rct_natseg_value INTO l_line_natseg_value;
489                     -- ================================== FND_LOG ==================================
490                     l_debug_info := 'Misc Receipt Natural Account Segment is: ' ||l_line_natseg_value ;
491                     trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
492                     -- ================================== FND_LOG ==================================
493                     CLOSE cur_ar_rct_natseg_value;
494                 EXCEPTION
495                     WHEN OTHERS THEN
496                         IF cur_ar_rct_natseg_value%ISOPEN THEN
497                             CLOSE cur_ar_rct_natseg_value;
498                         END IF;
499                         -- ================================== FND_LOG ==================================
500                         l_debug_info := 'SQL Error encountered' ||SQLERRM ;
501                         trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
502                         -- ================================== FND_LOG ==================================
503                         RETURN FALSE;
504                 END;
508                     (l_line_natseg_value BETWEEN 152500 AND 152799) OR (l_line_natseg_value BETWEEN 156100 AND 156199) OR
505                 /* We need to check the Credit Account Natural Account segments should fall in this range */
506                 IF (
507                     (l_line_natseg_value BETWEEN 151100 AND 151299) OR (l_line_natseg_value BETWEEN 152200 AND 152299) OR
509                     (l_line_natseg_value BETWEEN 157100 AND 157299) OR (l_line_natseg_value BETWEEN 159100 AND 159199) OR
510                     (l_line_natseg_value BETWEEN 159100 AND 159199) OR (l_line_natseg_value BETWEEN 171100 AND 171299) OR
511                     (l_line_natseg_value BETWEEN 172000 AND 172099) OR (l_line_natseg_value BETWEEN 173000 AND 173099) OR
512                     (l_line_natseg_value BETWEEN 174000 AND 174099) OR (l_line_natseg_value BETWEEN 175000 AND 175099) OR
513                     (l_line_natseg_value BETWEEN 181000 AND 181099) OR (l_line_natseg_value BETWEEN 182000 AND 182099) OR
514                     (l_line_natseg_value BETWEEN 183000 AND 183099) OR (l_line_natseg_value BETWEEN 183200 AND 183299) OR
515                     (l_line_natseg_value BETWEEN 184000 AND 184099) OR (l_line_natseg_value BETWEEN 189000 AND 189099) OR
516                     (l_line_natseg_value BETWEEN 199000 AND 199099) OR (l_line_natseg_value BETWEEN 610000 AND 610099) OR
517                     (l_line_natseg_value BETWEEN 650000 AND 650099) OR (l_line_natseg_value BETWEEN 690000 AND 690099)
518                     ) THEN
519                     -- ================================== FND_LOG ==================================
520                     l_debug_info := 'Misc Receipt for Refund Overpayments CASH Line Validated ';
521                     trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
522                     -- ================================== FND_LOG ==================================
523                     RETURN TRUE;
524                 END IF;
525             -- Check Misc Receipt for Reimbursable Order without Advance */
526             ELSIF (p_fv_extract_rec.fund_category IN ('R', 'S', 'T')) THEN
527                 BEGIN
528                     -- Get the Natural Account Segment
529                     OPEN cur_ar_rct_natseg_value(p_fv_extract_rec.event_id,
530                                                  p_fv_extract_rec.line_number);
531                     FETCH cur_ar_rct_natseg_value INTO l_line_natseg_value;
532                     -- ================================== FND_LOG ==================================
533                     l_debug_info := 'Miscellaneous Receipt Natural Account Segment is: '|| l_line_natseg_value ;
534                     trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
535                     -- ================================== FND_LOG ==================================
536                     CLOSE cur_ar_rct_natseg_value;
537                 EXCEPTION
538                     WHEN OTHERS THEN
539                         IF cur_ar_rct_natseg_value%ISOPEN THEN
540                             CLOSE cur_ar_rct_natseg_value;
541                         END IF;
542                         l_debug_info := 'SQL Error encountered' || SQLERRM ;
543                         trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
544                         RETURN FALSE;
545                 END;
546                 /* We need to check the Credit Account Natural Account
547                    segments should fall in this range */
548                 IF ((l_line_natseg_value BETWEEN 510000 AND 510099) OR (l_line_natseg_value BETWEEN 520000 AND 520099)) THEN
549                     -- ================================== FND_LOG ==================================
550                     l_debug_info := 'Misc Receipt MISCCASH Distribution validated for Reimbursable Order without Advance' ;
551                     trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
552                     -- ================================== FND_LOG ==================================
553                     RETURN TRUE;
554                 END IF;
555             END IF;
556         END IF;
557          -- Return False if none matches the criteria
558          RETURN FALSE;
559 
560     -- End of Event Type IF
561     END IF;
562     -- Return False if none matches the criteria
563     RETURN FALSE;
564 
565     -- ================================== FND_LOG ==================================
566     l_debug_info := 'End of procedure'||l_procedure_name;
567     trace(C_PROC_LEVEL, l_procedure_name, l_debug_info);
568     -- ================================== FND_LOG ==================================
569 
570 
571 EXCEPTION
572     WHEN OTHERS THEN
573         l_debug_info := 'Error in Federal SLA Processing... ' || SQLERRM ;
574         trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
575         FND_MESSAGE.SET_NAME('FND', 'FND_GENERIC_MESSAGE');
576         FND_MESSAGE.SET_TOKEN('MESSAGE' ,
577             'Procedure :fv_sla_processing_pkg.get_account_valid_status'||CRLF||
578             'Error     :'||SQLERRM);
579         FND_MSG_PUB.ADD;
580         APP_EXCEPTION.RAISE_EXCEPTION;
581 
582 END get_account_valid_status;
583 
584 --
585 --
586 -- Function to derive the balance amount for the fund and antipicated segment
587 -- returns the period balances for the account
588 -- Logic
589 --    1. with the inputs constructs the CCID
590 --    2. queries the gl_balances for the period and returns the balances
591 --
592 --
593 FUNCTION get_anticipated_fund_amt( p_Fund_value        IN VARCHAR2,
594                                    p_Balancing_segment IN NUMBER,
595                                    p_Natural_segment   IN NUMBER,
596                                    p_Ledger_id         IN NUMBER,
597                                    p_coaid             IN  NUMBER,
601     l_debug_info                   VARCHAR2(240);
598                                    p_Period_name       IN  VARCHAR2)
599 RETURN NUMBER
600 IS
602     l_procedure_name               VARCHAR2(100) :='.GET_ANTICIPATED_FUND_AMT';
603 
604      CURSOR c_anticipated_acct IS
605      SELECT  ussgl_account --, template_id
606      FROM	Fv_Facts_Ussgl_Accounts
607      WHERE	anticipated_unanticipated = 'Y';
608 
609      CURSOR c_template_id is
610      SELECT template_id
611      FROM FV_PYA_FISCALYEAR_SEGMENT
612      WHERE set_of_books_id = p_ledger_id;
613 
614      CURSOR c_currency_code IS
615      SELECT currency_code
616      FROM gl_ledgers
617      WHERE ledger_id = p_Ledger_id;
618 
619      CURSOR c_period (c_ledger_id NUMBER,
620                       c_period_name VARCHAR2) IS
621      SELECT period_year, period_num
622      FROM gl_period_statuses
623      WHERE ledger_id = c_ledger_id
624        AND application_id = 101
625        AND period_name = c_period_name;
626 
627      l_anticipated_acct        VARCHAR2(30);
628      l_template_id             NUMBER;
629      l_currency_code           VARCHAR2(30);
630      l_ccid		    Gl_Code_Combinations.code_combination_id%TYPE;
631      l_fund_value	Fv_Fund_Parameters.fund_value%TYPE;
632      l_amount	    NUMBER;
633      l_tot_amount NUMBER := 0;
634 
635      -- Variable declartions for Dynamic SQL
636      l_fund_cur_id	INTEGER;
637      l_fund_select	VARCHAR2(2000);
638      l_fund_ret	    INTEGER;
639      l_period_year  NUMBER;
640      l_period_num   NUMBER;
641 
642      template_id_exception exception;
643      anticipated_exception exception;
644 
645 BEGIN
646 
647     l_procedure_name := g_path_name || l_procedure_name;
648     -------------------------------------------------------------------------
649     l_debug_info := 'Begin of procedure '||l_procedure_name;
650     trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
651     -------------------------------------------------------------------------
652     -------------------------------------------------------------------------
653     OPEN c_anticipated_acct;
654     FETCH c_anticipated_acct INTO l_anticipated_acct;
655     if c_anticipated_acct%notfound then
656      CLOSE c_anticipated_acct;
657      raise anticipated_exception;
658     end if;
659     CLOSE c_anticipated_acct;
660 
661     trace(C_STATE_LEVEL, l_procedure_name, 'l_anticipated_acct='||l_anticipated_acct);
662 
663     OPEN c_template_id;
664     FETCH c_template_id INTO l_template_id;
665     if c_template_id%notfound then
666       CLOSE c_template_id;
667       raise template_id_exception;
668     end if;
669     CLOSE c_template_id;
670 
671     trace(C_STATE_LEVEL, l_procedure_name, 'l_template_id='||l_template_id);
672 
673     OPEN c_currency_code;
674     FETCH c_currency_code into l_currency_code;
675     CLOSE c_currency_code;
676 
677     trace(C_STATE_LEVEL, l_procedure_name, 'l_currency_code='||l_currency_code);
678 
679     OPEN c_period (p_Ledger_id, p_Period_name);
680     FETCH c_period into l_period_year, l_period_num;
681     CLOSE c_period;
682     trace(C_STATE_LEVEL, l_procedure_name, 'l_period_year='||l_period_year);
683     trace(C_STATE_LEVEL, l_procedure_name, 'l_period_num='||l_period_num);
684 
685     -- get the ccid that contains this fund in its balancing segment
686     -- and this anticipated account in Natural account segment
687     -- assumption is federal would set up summary template for the anticpated account
688 
689 	   l_fund_cur_id := DBMS_SQL.OPEN_CURSOR;
690 
691 	   --Build the Select statement for getting the fund values and ccids
692 	   l_fund_select := 'SELECT code_combination_id ' ||
693 	                    ' FROM  Gl_Code_Combinations ' ||
694 	                    ' WHERE chart_of_accounts_id = :p_coaid AND '||
695 	                    'segment'||p_balancing_segment || ' = :p_fund_value AND ' ||
696                       'template_id = :p_template_id AND '||
697 	                    'Summary_flag = ''Y''' ;
698     -------------------------------------------------------------------------
699     trace(C_STATE_LEVEL, l_procedure_name, 'p_coaid='||p_coaid);
700     trace(C_STATE_LEVEL, l_procedure_name, 'p_fund_value='||p_fund_value);
701     trace(C_STATE_LEVEL, l_procedure_name, 'l_template_id='||l_template_id);
702     trace(C_STATE_LEVEL, l_procedure_name, 'l_fund_select='||l_fund_select);
703     -------------------------------------------------------------------------
704 
705     -------------------------------------------------------------------------
706     trace(C_STATE_LEVEL, l_procedure_name, 'parse');
707     -------------------------------------------------------------------------
708 	   DBMS_SQL.PARSE(l_fund_cur_id, l_fund_select, DBMS_SQL.Native);
709 	   DBMS_SQL.BIND_VARIABLE(l_fund_cur_id, ':p_coaid', p_coaid);
710 	   DBMS_SQL.BIND_VARIABLE(l_fund_cur_id, ':p_fund_value', p_fund_value, 25);
711 	   DBMS_SQL.BIND_VARIABLE(l_fund_cur_id, ':p_template_id', l_template_id, 30);
712 
713     -------------------------------------------------------------------------
714     trace(C_STATE_LEVEL, l_procedure_name, 'DEFINE_COLUMN');
715     -------------------------------------------------------------------------
716 	   DBMS_SQL.DEFINE_COLUMN(l_fund_cur_id,1,l_ccid);
717 
718 	   l_fund_ret := DBMS_SQL.EXECUTE(l_fund_cur_id);
719 
720      LOOP
721 	   -- Fetch the ccid's  from Gl_Code_Combinations
722     -------------------------------------------------------------------------
723     trace(C_STATE_LEVEL, l_procedure_name, 'FETCH_ROWS');
727     trace(C_STATE_LEVEL, l_procedure_name, 'EXIT');
724     -------------------------------------------------------------------------
725 	 	IF DBMS_SQL.FETCH_ROWS(l_fund_cur_id) = 0 THEN
726     -------------------------------------------------------------------------
728     -------------------------------------------------------------------------
729       EXIT;
730 	        ELSE
731     -------------------------------------------------------------------------
732     trace(C_STATE_LEVEL, l_procedure_name, 'COLUMN_VALUE');
733     -------------------------------------------------------------------------
734 		   DBMS_SQL.COLUMN_VALUE(l_fund_cur_id, 1,l_ccid);
735 		END IF;
736 
737 
738 		   /*SELECT SUM((begin_balance_dr - begin_balance_cr) +
739                         (period_net_dr - period_net_cr))
740 		   INTO  l_amount
741 	           FROM  Gl_Balances
742 	           WHERE    ledger_id          = p_Ledger_id
743 		    --AND	 currency_code	     = vp_currency_code
744 		   AND      code_combination_id = l_ccid
745 		   AND 	 period_name 	     = p_period_name;
746 
747 		SELECT  code_combination_id
748 		INTO    l_ccid
749 		FROM    gl_code_combinations
750 		WHERE   chart_of_accounts_id = p_coaid
751 	   	 AND     template_id = l_template_id
752 		 AND     summary_flag = 'Y';*/
753 
754       -------------------------------------------------------------------------
755       l_debug_info := 'Before calling calc_funds';
756       trace(C_PROC_LEVEL, l_procedure_name, l_debug_info);
757       -------------------------------------------------------------------------
758     -------------------------------------------------------------------------
759     trace(C_STATE_LEVEL, l_procedure_name, 'l_ccid='||l_ccid);
760     trace(C_STATE_LEVEL, l_procedure_name, 'l_template_id='||l_template_id);
761     trace(C_STATE_LEVEL, l_procedure_name, 'p_ledger_id='||p_ledger_id);
762     trace(C_STATE_LEVEL, l_procedure_name, 'p_period_name='||p_period_name);
763     trace(C_STATE_LEVEL, l_procedure_name, 'l_currency_code='||l_currency_code);
764     SELECT SUM((begin_balance_dr - begin_balance_cr) +
765                         (period_net_dr - period_net_cr))
766 		   INTO  l_amount
767 	           FROM  Gl_Balances
768 	           WHERE    ledger_id          = p_Ledger_id
769 		    AND	 currency_code	     = l_currency_code
770 		   AND      code_combination_id = l_ccid
771 		   AND 	 period_name 	     = p_period_name;
772     trace(C_STATE_LEVEL, l_procedure_name, ' gl_balances l_amount='||l_amount);
773     -------------------------------------------------------------------------
774 /*     l_amount := 0;
775 	   l_amount := 	   gl_funds_available_pkg.calc_funds(
776                                             l_ccid       ,
777                                             l_template_id,
778                                             p_ledger_id  ,
779                                             p_period_name,
780                                             l_currency_code);
781 
782     trace(C_STATE_LEVEL, l_procedure_name, ' gl_funds_available_pkg l_amount='||l_amount);
783 */
784       l_tot_amount := l_tot_amount + NVL(l_amount, 0);
785 
786     trace(C_STATE_LEVEL, l_procedure_name, ' gl_balances l_tot_amount='||l_tot_amount);
787 
788     SELECT SUM(NVL(accounted_dr,0) - NVL(accounted_cr,0))
789 		   INTO  l_amount
790 	           FROM  Gl_bc_packets gbc,
791                    gl_account_hierarchies gah
792 	           WHERE    gbc.ledger_id          = p_Ledger_id
793                AND gah.ledger_id = p_Ledger_id
794                AND gah.template_id = l_template_id
795                AND gah.summary_code_combination_id = l_ccid
796 		    AND	 gbc.currency_code	     = l_currency_code
797 		   AND      gbc.code_combination_id = gah.detail_code_combination_id
798 		   AND 	 gbc.period_year 	     = l_period_year
799        AND gbc.period_num <= l_period_num
800                    AND  gbc.status_code = 'A';
801     trace(C_STATE_LEVEL, l_procedure_name, ' gl_bc_packets l_amount='||l_amount);
802 
803       l_tot_amount := l_tot_amount + NVL(l_amount, 0);
804 
805     trace(C_STATE_LEVEL, l_procedure_name, ' gl_bc_packets l_tot_amount='||l_tot_amount);
806     END LOOP;
807     dbms_sql.close_cursor (l_fund_cur_id);
808       RETURN l_tot_amount;
809       -------------------------------------------------------------------------
810       l_debug_info := 'End of procedure '||l_procedure_name;
811       trace(C_PROC_LEVEL, l_procedure_name, l_debug_info);
812       -------------------------------------------------------------------------
813 
814 EXCEPTION
815 
816   WHEN template_id_exception then
817      l_debug_info := 'Error in Federal SLA processing ' || SQLERRM;
818      trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
819      FND_MESSAGE.SET_NAME('FND', 'FND_GENERIC_MESSAGE');
820      FND_MESSAGE.SET_TOKEN('MESSAGE' ,
821          'Get_Anticipated_Fund_Amt:No summary Template found for the ledger.Please Associate a Summary'||
822 		 'Template to the ledger in the Federal Financial Options form.');
823      FND_MSG_PUB.ADD;
824      APP_EXCEPTION.RAISE_EXCEPTION;
825 
826   WHEN anticipated_exception then
827      l_debug_info := 'Error in Federal SLA processing ' || SQLERRM;
828      trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
829      FND_MESSAGE.SET_NAME('FND', 'FND_GENERIC_MESSAGE');
830      FND_MESSAGE.SET_TOKEN('MESSAGE' ,
831          'Get_Anticipated_Fund_Amt:No anticipated account has been set. Please set an anticipated account in the USSGL Accounts form.');
832      FND_MSG_PUB.ADD;
833      APP_EXCEPTION.RAISE_EXCEPTION;
834 
835 
836   WHEN OTHERS THEN
837      l_debug_info := 'Error in Federal SLA processing ' || SQLERRM;
841          'Procedure :fv_sla_processing_pkg.get_anticipated_fund_amt'|| CRLF||
838      trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
839      FND_MESSAGE.SET_NAME('FND', 'FND_GENERIC_MESSAGE');
840      FND_MESSAGE.SET_TOKEN('MESSAGE' ,
842          'Error     :'||SQLERRM);
843      FND_MSG_PUB.ADD;
844      APP_EXCEPTION.RAISE_EXCEPTION;
845 
846 END get_anticipated_fund_amt;
847 
848 FUNCTION get_fund_value
849 (p_coaid                IN          NUMBER,
850  p_ccid                 IN          NUMBER,
851  p_gl_account_segment   OUT NOCOPY  NUMBER,
852  p_gl_balancing_segment OUT NOCOPY  NUMBER
853 )
854 RETURN VARCHAR2
855 IS
856     l_debug_info                   VARCHAR2(240);
857     l_procedure_name               VARCHAR2(100) :='.GET_FUND_VALUE';
858 
859     l_result			   BOOLEAN;
860     l_fund_value                   VARCHAR2(30);
861 BEGIN
862 
863     l_procedure_name := g_path_name || l_procedure_name;
864     -------------------------------------------------------------------------
865     l_debug_info := 'Begin of procedure '||l_procedure_name;
866     trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
867     -------------------------------------------------------------------------
868     -------------------------------------------------------------------------
869 
870         -- get the gl_account( natural account)
871         IF (NOT FND_FLEX_APIS.GET_QUALIFIER_SEGNUM(APPL_ID                => 101,
872                                                    KEY_FLEX_CODE          => 'GL#',
873                                                    STRUCTURE_NUMBER       => p_coaid,
874                                                    FLEX_QUAL_NAME         => 'GL_ACCOUNT',
875                                                    SEGMENT_NUMBER         => p_gl_account_segment))  THEN
876 
877               --Raise GET_QUALIFIER_SEGNUM_EXCEP;
878               NULL;
879         END IF;
880         --DEBUG('GL_Account_segment'||p_gl_account_segment);
881         -- get the gl_balancing
882         IF (NOT FND_FLEX_APIS.GET_QUALIFIER_SEGNUM(APPL_ID           => 101,
883                                                    KEY_FLEX_CODE     => 'GL#',
884                                                    STRUCTURE_NUMBER  => p_coaid,
885                                                    FLEX_QUAL_NAME    => 'GL_BALANCING',
886                                                    SEGMENT_NUMBER    => p_gl_balancing_segment))  THEN
887 
888              --Raise GET_QUALIFIER_SEGNUM_EXCEP;
889              NULL;
890         END IF;
891 
892        -- DEBUG('GL_balancing_segment'||p_gl_balancing_segment);
893 
894                          -- get the balancing segment value from the charge CCID
895          l_result :=   FND_FLEX_KEYVAL.validate_ccid (
896                         appl_short_name => 'SQLGL',
897                         key_flex_code => 'GL#',
898                         structure_number =>  p_coaid,
899                         combination_id =>  p_ccid);
900 
901          l_fund_value:=FND_FLEX_KEYVAL.segment_value(p_gl_balancing_segment);
902 
903         -- DEBUG('Charge CCID '||p_ccid);
904         -- DEBUG('Fund Value'||  l_fund_value);
905 
906       -------------------------------------------------------------------------
907       l_debug_info := 'End of procedure '||l_procedure_name;
908       trace(C_PROC_LEVEL, l_procedure_name, l_debug_info);
909       -------------------------------------------------------------------------
910 
911       RETURN l_fund_value;
912 
913 EXCEPTION
914 
915   WHEN OTHERS THEN
916      l_debug_info := 'Error in Federal SLA processing ' || SQLERRM;
917      trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
918      FND_MESSAGE.SET_NAME('FND', 'FND_GENERIC_MESSAGE');
919      FND_MESSAGE.SET_TOKEN('MESSAGE' ,
920          'Procedure :fv_sla_processing_pkg.get_fund_value'|| CRLF||
921          'Error     :'||SQLERRM);
922      FND_MSG_PUB.ADD;
923      APP_EXCEPTION.RAISE_EXCEPTION;
924 
925 END get_fund_value;
926 
927 FUNCTION get_fund_value
928 (p_coaid        IN          NUMBER,
929  p_ccid         IN          NUMBER
930 )
931 RETURN VARCHAR2
932 IS
933     l_debug_info                   VARCHAR2(240);
934     l_procedure_name               VARCHAR2(100) :='.GET_FUND_VALUE';
935 
936     l_gl_account_segment      NUMBER;
937     l_gl_balancing_segment      NUMBER;
938     l_result				  BOOLEAN;
939     l_fund_value              VARCHAR2(30);
940 BEGIN
941 
942     l_procedure_name := g_path_name || l_procedure_name;
943     -------------------------------------------------------------------------
944     l_debug_info := 'Begin of procedure '||l_procedure_name;
945     trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
946     -------------------------------------------------------------------------
947     -------------------------------------------------------------------------
948 
949         -- get the gl_account( natural account)
950         IF (NOT FND_FLEX_APIS.GET_QUALIFIER_SEGNUM(APPL_ID                => 101,
951                                                    KEY_FLEX_CODE          => 'GL#',
952                                                    STRUCTURE_NUMBER       => p_coaid,
953                                                    FLEX_QUAL_NAME         => 'GL_ACCOUNT',
954                                                    SEGMENT_NUMBER         => l_gl_account_segment))  THEN
955 
956               --Raise GET_QUALIFIER_SEGNUM_EXCEP;
957               NULL;
958         END IF;
959         --DEBUG('GL_Account_segment'||l_gl_account_segment);
960         -- get the gl_balancing
964                                                    FLEX_QUAL_NAME    => 'GL_BALANCING',
961         IF (NOT FND_FLEX_APIS.GET_QUALIFIER_SEGNUM(APPL_ID           => 101,
962                                                    KEY_FLEX_CODE     => 'GL#',
963                                                    STRUCTURE_NUMBER  => p_coaid,
965                                                    SEGMENT_NUMBER    => l_gl_balancing_segment))  THEN
966 
967              --Raise GET_QUALIFIER_SEGNUM_EXCEP;
968              NULL;
969         END IF;
970 
971        -- DEBUG('GL_balancing_segment'||l_gl_balancing_segment);
972 
973                          -- get the balancing segment value from the charge CCID
974          l_result :=   FND_FLEX_KEYVAL.validate_ccid (
975                         appl_short_name   => 'SQLGL',
976                         key_flex_code     => 'GL#',
977                         structure_number  =>  p_coaid,
978                         combination_id    =>  p_ccid);
979 
980          l_fund_value:=FND_FLEX_KEYVAL.segment_value(l_gl_balancing_segment);
981 
982         -- DEBUG('Charge CCID '||p_ccid);
983         -- DEBUG('Fund Value'||  l_fund_value);
984 
985       -------------------------------------------------------------------------
986       l_debug_info := 'End of procedure '||l_procedure_name;
987       trace(C_PROC_LEVEL, l_procedure_name, l_debug_info);
988       -------------------------------------------------------------------------
989 
990                 RETURN l_fund_value;
991 
992 EXCEPTION
993 
994   WHEN OTHERS THEN
995      l_debug_info := 'Error in federal sla processing ' ||SQLERRM;
996      trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
997      FND_MESSAGE.SET_NAME('FND', 'FND_GENERIC_MESSAGE');
998      FND_MESSAGE.SET_TOKEN('MESSAGE' ,
999          'Procedure :fv_sla_processing_pkg.get_fund_value'|| CRLF||
1000          'Error     :'||SQLERRM);
1001      FND_MSG_PUB.ADD;
1002      APP_EXCEPTION.RAISE_EXCEPTION;
1003 
1004 END get_fund_value;
1005 
1006 
1007 FUNCTION pya_adj_amt_by_fund( p_coaid                 IN        NUMBER,
1008                               p_event_id              IN        NUMBER,
1009                               p_header_id             IN        NUMBER,
1010                               p_fund_value            IN        VARCHAR2)
1011 RETURN NUMBER
1012 IS
1013     l_debug_info                   VARCHAR2(240);
1014     l_procedure_name               VARCHAR2(100) :='.PYA_ADJ_AMT_BY_FUND';
1015 
1016     CURSOR c_net_adj_amt (p_dist_id NUMBER) IS
1017     SELECT accounted_amt, event_type_code,code_combination_id  FROM PO_BC_DISTRIBUTIONS
1018     WHERE distribution_id = p_dist_id AND ae_event_id  =
1019         (SELECT max(ae_event_id) FROM PO_BC_DISTRIBUTIONS pbd
1020         WHERE distribution_id = p_dist_id
1021         AND main_or_backing_code = 'M'
1022         AND ae_event_id <> p_event_id
1023         AND distribution_type <> 'REQUISITION'
1024         AND EXISTS (select 1
1025                     from xla_ae_headers xah
1026                     where application_id = 201
1027                     and xah.event_id = pbd.ae_event_id
1028                     and xah.accounting_entry_status_code = 'F'));
1029 
1030         --currently we are using only po_bc_distributions only, but infuture we may
1031         --have to use gl_bc_packets or xla_events
1032 
1033     /*Get all the distribution ids in p_event_id event which belong to the same document*/
1034     CURSOR c_get_dist_ids IS
1035     SELECT pbd.distribution_id,pbd.code_combination_id,pbd.accounted_amt
1036     FROM PO_EXTRACT_DETAIL_V ped, PO_BC_DISTRIBUTIONS pbd
1037     WHERE ped.event_id = pbd.ae_event_id  --p_event_id AND
1038     AND ped.po_distribution_id = pbd.distribution_id
1039     AND pbd.header_id = p_header_id
1040     AND pbd.main_or_backing_code = 'M';
1041 
1042     l_fund_value_current    VARCHAR2(30); --l_fund_value            VARCHAR2(30);
1043     l_fund_value_old        VARCHAR2(30);
1044     l_net_amt_current       NUMBER;  --l_net_amt               NUMBER;
1045     l_net_amt_old           NUMBER;
1046     l_old_amt               c_net_adj_amt%ROWTYPE;
1047     l_po_distribution_id    NUMBER;
1048     l_code_combination_id   NUMBER;
1049     l_accounted_amt      NUMBER;
1050     l_old_event_type_code    VARCHAR2(30);
1051 BEGIN
1052 
1053     l_procedure_name := g_path_name || l_procedure_name;
1054     -------------------------------------------------------------------------
1055     l_debug_info := 'Begin of procedure '||l_procedure_name;
1056     trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
1057     -------------------------------------------------------------------------
1058     -------------------------------------------------------------------------
1059 
1060      l_net_amt_current := 0; --l_net_amt := 0;
1061      l_net_amt_old     := 0;
1062      OPEN c_get_dist_ids;
1063      LOOP
1064         FETCH c_get_dist_ids INTO l_po_distribution_id, l_code_combination_id , l_accounted_amt;
1065         EXIT WHEN c_get_dist_ids%NOTFOUND;
1066 
1067 --        l_fund_value := get_fund_value (p_coaid,l_code_combination_id);
1068         l_fund_value_current := get_fund_value (p_coaid,l_code_combination_id);
1069 
1070         -------------------------------------------------------------------------
1071         l_debug_info := 'l_fund_value:  '||l_fund_value_current; --l_fund_value;
1072         trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
1073         l_debug_info := 'p_fund_value:  '||p_fund_value;
1074         trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
1075         -------------------------------------------------------------------------
1076 
1080              IF c_net_adj_amt%FOUND THEN
1077 --        IF p_fund_value = l_fund_value THEN
1078              OPEN c_net_adj_amt (l_po_distribution_id);
1079              FETCH c_net_adj_amt INTO l_old_amt;
1081                 -------------------------------------------------------------------------
1082                 l_debug_info := 'Old event_type_code found: ' || l_old_amt.event_type_code;
1083                 trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
1084                 -------------------------------------------------------------------------
1085                 l_fund_value_old := get_fund_value (p_coaid,l_old_amt.code_combination_id);
1086                 IF p_fund_value = l_fund_value_old THEN
1087                     l_net_amt_old := l_net_amt_old + l_old_amt.accounted_amt;
1088                 END IF;
1089                 IF p_fund_value = l_fund_value_current THEN
1090                     l_old_event_type_code := l_old_amt.event_type_code;
1091                     IF (l_old_event_type_code = 'PO_PA_RESERVED' or l_old_event_type_code = 'RELEASE_RESERVED') THEN
1092      --                   l_net_amt := l_net_amt + l_accounted_amt ;
1093                         l_net_amt_current := l_net_amt_current + (l_old_amt.accounted_amt + l_accounted_amt) ;
1094     /*               ELSIF l_accounted_amt >= l_old_amt.accounted_amt THEN
1095                       l_net_amt := l_net_amt + l_accounted_amt ;  */
1096                     ELSE
1097     --                    l_net_amt := l_net_amt + (l_accounted_amt - l_old_amt.accounted_amt) ;
1098                         l_net_amt_current := l_net_amt_current + l_accounted_amt ;
1099                     END IF;
1100                 END IF;
1101              ELSE                         -- prev event not found i.e., first reserve action is happening on this distribution. Bug 5006499.
1102 --                l_net_amt := l_net_amt + l_accounted_amt ;
1103                 IF p_fund_value = l_fund_value_current THEN
1104                     l_net_amt_current := l_net_amt_current + l_accounted_amt ;
1105                 END IF;
1106     	     END IF;
1107              CLOSE c_net_adj_amt;
1108 --        END IF;
1109      END LOOP;
1110      CLOSE c_get_dist_ids;
1111 
1112     -------------------------------------------------------------------------
1113     l_debug_info := 'End of procedure'||l_procedure_name;
1114     trace(C_PROC_LEVEL, l_procedure_name, l_debug_info);
1115     -------------------------------------------------------------------------
1116 
1117 --     RETURN l_net_amt;
1118        RETURN (l_net_amt_current - l_net_amt_old) ;
1119 
1120 EXCEPTION
1121 
1122   WHEN OTHERS THEN
1123      IF c_get_dist_ids%ISOPEN THEN
1124          CLOSE c_get_dist_ids;
1125      END IF;
1126      l_debug_info := 'Error in Federal SLA processing - ' || SQLERRM;
1127      trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
1128      FND_MESSAGE.SET_NAME('FND', 'FND_GENERIC_MESSAGE');
1129      FND_MESSAGE.SET_TOKEN('MESSAGE' ,
1130          'Procedure :fv_sla_processing_pkg.pya_adj_amt_by_fund'|| CRLF||
1131          'Error     :'||SQLERRM);
1132      FND_MSG_PUB.ADD;
1133      APP_EXCEPTION.RAISE_EXCEPTION();
1134 
1135 END pya_adj_amt_by_fund;
1136 
1137 /*Fund details*/
1138 PROCEDURE get_fund_details
1139 (
1140 p_application_id           IN        NUMBER,
1141 p_ledger_id                IN        VARCHAR2,
1142 p_fund_value               IN        VARCHAR2,
1143 p_gl_date                  IN        DATE,
1144 p_fund_category            OUT NOCOPY          VARCHAR2,
1145 p_fund_status              OUT NOCOPY          VARCHAR2
1146 )
1147 IS
1148     l_debug_info                   VARCHAR2(240);
1149     l_procedure_name               VARCHAR2(100) :='.GET_FUND_DETAILS';
1150 
1151     CURSOR c_get_fund_details IS
1152     SELECT fund_category, fund_expire_date
1153       FROM FV_FUND_PARAMETERS
1154      WHERE FUND_VALUE=P_fund_value;
1155 
1156     l_fund_details            c_get_fund_details%ROWTYPE;
1157 
1158 BEGIN
1159 
1160     l_procedure_name := g_path_name || l_procedure_name;
1161     -------------------------------------------------------------------------
1162     l_debug_info := 'Begin of procedure '||l_procedure_name;
1163     trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
1164     -------------------------------------------------------------------------
1165     -------------------------------------------------------------------------
1166 
1167       p_fund_status    := NULL;
1168       p_fund_category  := NULL;
1169 
1170       -- get the fund category and expiration date
1171       OPEN c_get_fund_details;
1172       FETCH c_get_fund_details INTO l_fund_details;
1173       IF c_get_fund_details%FOUND THEN
1174            -- fund category
1175            IF p_application_id = 201 THEN
1176                IF l_fund_details.fund_category IN ('A','S') THEN
1177                     p_fund_category := 'A';
1178                ELSIF l_fund_details.fund_category IN ('B','T') THEN
1179                     p_fund_category := 'B';
1180                ELSE
1181                     p_fund_category := 'C';
1182                END IF;
1183            ELSIF p_application_id IN (707, 200, 222) THEN
1184                p_fund_category := l_fund_details.fund_category;
1185            END IF;
1186 
1187            -- fund expired
1188            IF l_fund_details.fund_expire_date < p_gl_date THEN
1189                  p_fund_status := 'Expired';
1190            ELSE
1191                  p_fund_status := 'Unexpired';
1192            END IF;
1193 
1194 
1195        ELSE
1196            p_fund_status     := NULL;
1197            p_fund_category   := NULL;
1201       -------------------------------------------------------------------------
1198       END IF;
1199       CLOSE c_get_fund_details;
1200 
1202       l_debug_info := 'End of procedure '||l_procedure_name;
1203       trace(C_PROC_LEVEL, l_procedure_name, l_debug_info);
1204       -------------------------------------------------------------------------
1205 EXCEPTION
1206   WHEN OTHERS THEN
1207      l_debug_info := 'Error in Federal SLA processing ' || SQLERRM;
1208      trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
1209      FND_MESSAGE.SET_NAME('FND', 'FND_GENERIC_MESSAGE');
1210      FND_MESSAGE.SET_TOKEN('MESSAGE' ,
1211          'Procedure :fv_sla_processing_pkg.get_fund_details'|| CRLF||
1212          'Error     :'||SQLERRM);
1213      FND_MSG_PUB.ADD;
1214      APP_EXCEPTION.RAISE_EXCEPTION;
1215 
1216 END get_fund_details;
1217 
1218 
1219 /*Fund details*/
1220 PROCEDURE get_fund_details
1221 (
1222 p_application_id           IN        NUMBER,
1223 p_ledger_id                IN        VARCHAR2,
1224 p_fund_value               IN        VARCHAR2,
1225 p_gl_date                  IN        DATE,
1226 p_fund_category            OUT NOCOPY          VARCHAR2,
1227 p_fund_status              OUT NOCOPY          VARCHAR2,
1228 p_fund_time_frame          OUT NOCOPY          VARCHAR2
1229 )
1230 IS
1231     l_debug_info                   VARCHAR2(240);
1232     l_procedure_name               VARCHAR2(100) :='.GET_FUND_DETAILS';
1233 
1234     CURSOR c_get_fund_details IS
1235     SELECT fund_category, fund_expire_date
1236       FROM FV_FUND_PARAMETERS
1237      WHERE FUND_VALUE = p_fund_value
1238        AND set_of_books_id = p_ledger_id ;
1239 
1240     /* Get the fund time frame */
1241     CURSOR c_get_fund_time_frame IS
1242     SELECT ts.time_frame
1243       FROM fv_treasury_symbols ts, fv_fund_parameters fp
1244      WHERE ts.treasury_symbol_id = fp.treasury_symbol_id
1245        AND fp.fund_value = p_fund_value
1246        AND ts.set_of_books_id = p_ledger_id;
1247 
1248 
1249     l_fund_details            c_get_fund_details%ROWTYPE;
1250     l_fund_time_frame         fv_treasury_symbols.time_frame%TYPE;
1251 
1252 BEGIN
1253 
1254     l_procedure_name := g_path_name || l_procedure_name;
1255     -------------------------------------------------------------------------
1256     l_debug_info := 'Begin of procedure '||l_procedure_name;
1257     trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
1258     -------------------------------------------------------------------------
1259     -------------------------------------------------------------------------
1260 
1261       p_fund_status     := NULL;
1262       p_fund_category   := NULL;
1263       p_fund_time_frame := NULL;
1264 
1265       -- get the fund category and expiration date
1266       OPEN c_get_fund_details;
1267       FETCH c_get_fund_details INTO l_fund_details;
1268       IF c_get_fund_details%FOUND THEN
1269            -- fund category
1270            IF p_application_id = 201 THEN
1271                IF l_fund_details.fund_category IN ('A','S') THEN
1272                     p_fund_category := 'A';
1273                ELSIF l_fund_details.fund_category IN ('B','T') THEN
1274                     p_fund_category := 'B';
1275                ELSE
1276                     p_fund_category := 'C';
1277                END IF;
1278            ELSIF p_application_id IN (707, 200, 222) THEN
1279                p_fund_category := l_fund_details.fund_category;
1280            END IF;
1281 
1282            -- fund expired
1283            IF l_fund_details.fund_expire_date < p_gl_date THEN
1284                  p_fund_status := 'Expired';
1285            ELSE
1286                  p_fund_status := 'Unexpired';
1287            END IF;
1288 
1289 
1290        ELSE
1291            p_fund_status     := NULL;
1292            p_fund_category   := NULL;
1293       END IF;
1294       CLOSE c_get_fund_details;
1295 
1296       -- get the fund time_frame
1297       OPEN c_get_fund_time_frame;
1298       FETCH c_get_fund_time_frame INTO l_fund_time_frame;
1299       IF c_get_fund_time_frame%FOUND THEN
1300           IF (p_application_id = 222) THEN
1301               -- Fund Time Frame
1302               p_fund_time_frame := l_fund_time_frame;
1303           END IF;
1304       ELSE
1305           p_fund_time_frame := NULL;
1306       END IF;
1307       CLOSE c_get_fund_time_frame;
1308 
1309 
1310       -------------------------------------------------------------------------
1311       l_debug_info := 'End of procedure '||l_procedure_name;
1312       trace(C_PROC_LEVEL, l_procedure_name, l_debug_info);
1313       -------------------------------------------------------------------------
1314 EXCEPTION
1315 
1316   WHEN OTHERS THEN
1317      l_debug_info := 'Exception in Federal SLA processing: ' || SQLERRM;
1318      trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
1319      FND_MESSAGE.SET_NAME('FND', 'FND_GENERIC_MESSAGE');
1320      FND_MESSAGE.SET_TOKEN('MESSAGE' ,
1321          'Procedure :fv_sla_processing_pkg.get_fund_details'|| CRLF||
1322          'Error     :'||SQLERRM);
1323      FND_MSG_PUB.ADD;
1324      APP_EXCEPTION.RAISE_EXCEPTION;
1325 
1326 END get_fund_details;
1327 
1328 
1329 FUNCTION get_prior_year_status
1330 (
1331 p_application_id             IN         NUMBER,
1332 p_ledger_id                  IN         NUMBER,
1333 p_coa_id					 IN         NUMBER,
1334 p_ccid                       IN         NUMBER,
1335 p_gl_date                    IN         DATE
1336 )
1337 RETURN BOOLEAN
1338 IS
1339 
1340     l_debug_info                   VARCHAR2(240);
1341     l_procedure_name               VARCHAR2(100) := '.GET_PRIOR_YEAR_STATUS';
1342 
1343 
1344     CURSOR c_get_bfy_segment IS
1345     SELECT application_column_name, fyr_segment_id
1346       FROM fv_pya_fiscalyear_segment
1347      WHERE set_of_books_id = p_ledger_id;
1348 
1349 
1350     CURSOR c_get_bfy_value (p_segment_id VARCHAR2, p_segment_value VARCHAR2 ) IS
1351     SELECT period_year
1352       FROM fv_pya_fiscalyear_map
1353      WHERE set_of_books_id = p_ledger_id
1354        AND fyr_segment_id = p_segment_id
1355        AND fyr_segment_value = p_segment_value;
1356 
1357 --Bug 7169941. Added condition to exclude Adjustment periods
1358 --Bug 7169941. Added trunc.
1359 
1360     CURSOR c_get_gl_fiscal_year IS
1361     SELECT period_year, period_name
1362       FROM gl_period_statuses
1363      WHERE ledger_id = p_ledger_id
1364        AND application_id = p_application_id
1365        AND (trunc(p_gl_date)  BETWEEN start_date AND end_date)
1366        and ADJUSTMENT_PERIOD_FLAG='N';
1367 
1368     l_transaction_year          c_get_gl_fiscal_year%ROWTYPE;
1369     l_bfy_segment               c_get_bfy_segment%ROWTYPE;
1370     l_bfy_value                 C_get_bfy_value%ROWTYPE;
1371     l_bfy_segment_value         VARCHAR2(25);
1372 
1373 BEGIN
1374 
1375     l_procedure_name := g_path_name || l_procedure_name;
1376     -------------------------------------------------------------------------
1377     l_debug_info := 'Begin of procedure '||l_procedure_name;
1378     trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
1379     -------------------------------------------------------------------------
1380     -------------------------------------------------------------------------
1381           g_adjustment_type := Null;
1382          -- Determine the prior year transaction
1383          OPEN c_get_bfy_segment;
1384          FETCH c_get_bfy_segment INTO l_bfy_segment;
1385          -- ================================== FND_LOG ==================================
1386          l_debug_info := 'BFY Segment column name: '|| l_bfy_segment.application_column_name ||
1387          ', BFY Segment column ID: ' || l_bfy_segment.fyr_segment_id;
1388          trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
1389          -- ================================== FND_LOG ==================================
1390          IF c_get_bfy_segment%NOTFOUND THEN
1391              RAISE NO_DATA_FOUND;
1392          END IF;
1393          CLOSE c_get_bfy_segment;
1394 
1395         -- DEBUG('Fiscal year segment '|| l_bfy_segment.application_column_name);
1396 
1397          EXECUTE IMMEDIATE 'SELECT ' || l_bfy_segment.application_column_name ||
1398                                       ' FROM gl_code_combinations WHERE code_combination_id = :x_ccid' ||
1399                                       ' AND  chart_of_accounts_id = :x_coaid '
1400          INTO l_bfy_segment_value USING p_ccid, p_coa_id;
1401          -- ================================== FND_LOG ==================================
1402          l_debug_info := 'BFY Segment value from gl_code_combinations table: '|| l_bfy_segment_value;
1403          trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
1404          -- ================================== FND_LOG ==================================
1405          -- DEBUG('Fiscal year segment value '||l_bfy_segment_value);
1406 
1407          OPEN  c_get_bfy_value (l_bfy_segment.fyr_segment_id ,
1408                                 l_bfy_segment_value);
1409          FETCH c_get_bfy_value INTO l_bfy_value;
1410          -- ================================== FND_LOG ==================================
1411          l_debug_info := 'BFY period year: '|| l_bfy_value.period_year;
1412          trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
1413          -- ================================== FND_LOG ==================================
1414          IF c_get_bfy_value%NOTFOUND THEN
1415              RAISE NO_DATA_FOUND;
1416          END IF;
1417          CLOSE c_get_bfy_value;
1418 
1419          -- get the fiscal year for the GL_DATE of the transction
1420          OPEN c_get_gl_fiscal_year;
1421          FETCH c_get_gl_fiscal_year INTO l_transaction_year;
1422          -- ================================== FND_LOG ==================================
1423          l_debug_info := 'Fiscal year: '|| l_transaction_year.period_year ;
1424          trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
1425          -- ================================== FND_LOG ==================================
1426          IF c_get_gl_fiscal_year%NOTFOUND THEN
1427              RAISE NO_DATA_FOUND;
1428          END IF;
1429          CLOSE c_get_gl_fiscal_year;
1430 
1431         -- DEBUG('Transaction year '|| l_transaction_year.period_year);
1432 
1433          IF l_transaction_year.period_year <> l_bfy_value.period_year THEN
1434               -------------------------------------------------------------------------
1435               l_debug_info := 'End of procedure'||l_procedure_name;
1436               trace(C_PROC_LEVEL, l_procedure_name, l_debug_info);
1437               -------------------------------------------------------------------------
1438              IF l_transaction_year.period_year > l_bfy_value.period_year THEN
1439                   g_adjustment_type := 'Upward';
1440               ELSIF l_transaction_year.period_year < l_bfy_value.period_year THEN
1441                   g_adjustment_type := 'Downward';
1442               END IF;
1443 
1444               RETURN TRUE;
1445          ELSE
1446               -------------------------------------------------------------------------
1447               l_debug_info := 'End of procedure'||l_procedure_name;
1448               trace(C_PROC_LEVEL, l_procedure_name, l_debug_info);
1449               -------------------------------------------------------------------------
1450               RETURN FALSE;
1451          END IF;
1452 
1453 EXCEPTION
1454   WHEN NO_DATA_FOUND THEN
1455      l_debug_info := 'Error: Federal setup is incomplete';
1456      trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
1457      FND_MESSAGE.SET_NAME('FND', 'FND_GENERIC_MESSAGE');
1458      FND_MESSAGE.SET_TOKEN('MESSAGE' ,
1459          'Procedure :fv_sla_processing_pkg.get_prior_year_status'|| CRLF||
1460          'Error     :Federal setup is incomplete');
1464   WHEN OTHERS THEN
1461      FND_MSG_PUB.ADD;
1462      APP_EXCEPTION.RAISE_EXCEPTION;
1463 
1465      l_debug_info := 'Error in Federal SLA processing ' || SQLERRM ;
1466      trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
1467      FND_MESSAGE.SET_NAME('FND', 'FND_GENERIC_MESSAGE');
1468      FND_MESSAGE.SET_TOKEN('MESSAGE' ,
1469          'Procedure :fv_sla_processing_pkg.get_prior_year_status'|| CRLF||
1470          'Error     :'||SQLERRM);
1471      FND_MSG_PUB.ADD;
1472      APP_EXCEPTION.RAISE_EXCEPTION;
1473 
1474 END get_prior_year_status;
1475 
1476 
1477 PROCEDURE determine_upward_downward( p_coaid NUMBER,
1478                                      p_ledger_id NUMBER,
1479                                      p_event_id NUMBER,
1480                                      p_fund_value VARCHAR2,
1481                                      p_net_pya_adj_amt OUT NOCOPY NUMBER,
1482                                      p_adjustment_type OUT NOCOPY VARCHAR2,
1483                                      p_gl_date DATE,
1484                                      p_gl_balancing_segment VARCHAR2,
1485                                      p_gl_account_segment VARCHAR2,
1486                                      p_anticipation OUT NOCOPY VARCHAR2,
1487                                      p_anticipated_amt OUT NOCOPY NUMBER,
1488                                      p_unanticipated_amt OUT NOCOPY NUMBER,
1489                                      p_entered_pya_diff_amt NUMBER,
1490                                      p_balance_amt OUT NOCOPY NUMBER
1491                                      ) IS
1492     l_debug_info              VARCHAR2(240);
1493     l_procedure_name          VARCHAR2(100):='.DETERMINE_UPWARD_DOWNWARD';
1494     l_header_id               NUMBER;
1495 
1496     CURSOR c_get_gl_fiscal_year(cp_ledger_id NUMBER, cp_gl_date DATE) IS
1497     SELECT period_year, period_name
1498     FROM    Gl_Period_Statuses
1499     WHERE   ledger_id = cp_ledger_id
1500     AND     cp_gl_date BETWEEN START_DATE AND end_date ;
1501 
1502     l_transaction_year        c_get_gl_fiscal_year%ROWTYPE;
1503     l_balance_amt             NUMBER;
1504 
1505 BEGIN
1506 --                 IF ( l_fv_extract_detail(l_index).ccid_changed_flag = 'N' ) THEN
1507 
1508                  SELECT po_header_id INTO l_header_id
1509 	             FROM po_extract_header_v
1510                  WHERE event_id = p_event_id;
1511 
1512                  p_net_pya_adj_amt := pya_adj_amt_by_fund(p_coaid,
1513                                                           p_event_id,
1514                                                           l_header_id,
1515                                                           p_fund_value);
1516 --                 END IF;
1517 
1518 --                 l_fv_extract_detail(l_index).net_pya_adj_amt:=   l_net_pya_adj_amt;
1519 
1520                 ------------------------------------------------------------
1521                 l_debug_info := 'Net PYA adj amount = ' || p_net_pya_adj_amt ;
1522                 trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
1523                 -------------------------------------------------------------
1524 
1525                  IF p_net_pya_adj_amt > 0 THEN   -- upward movement
1526                          p_adjustment_type := 'Upward';
1527                  ELSIF p_net_pya_adj_amt = 0 THEN   -- no movement
1528                         -- When the net effect of the prior year adjustments is zero,
1529                         ---the adjustments are booked for the individual distributions
1530  --                        l_fv_extract_detail(l_index).entered_pya_amt := l_fv_extract_detail(l_index).entered_pya_diff_amt;
1531  --                        l_fv_extract_detail(l_index).entered_pya_diff_amt := 0;
1532                          p_adjustment_type := 'None';
1533                   ELSE  --p_net_pya_adj_amt < 0 THEN -- Downward movement
1534                          p_adjustment_type := 'Downward';
1535                   END IF; -- pya adjustment type D,U,N
1536 
1537                 ------------------------------------------------------------
1538                 l_debug_info := 'PYA adjustment type = ' || p_adjustment_type;
1539                 trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
1540                 -------------------------------------------------------------
1541 
1542                   --
1543                   -- Downward PYA adjustment
1544                   -- Determine antipicated, unanticpated
1545                   --
1546 
1547                    IF p_adjustment_type = 'Downward' THEN
1548                        -- Find the Anticipated Account
1549                        --   BEGIN	/* Anti Acct */
1550                        -- get the fiscal year for the GL_DATE of the transction
1551                        OPEN c_get_gl_fiscal_year( p_ledger_id,
1552                     						      p_gl_date);
1553                        FETCH c_get_gl_fiscal_year INTO l_transaction_year;
1554                        CLOSE c_get_gl_fiscal_year;
1555 
1556                         -- get the balances from account
1557                         l_balance_amt:=get_anticipated_fund_amt(p_Fund_value => p_fund_value,
1558                                                  p_Balancing_segment => p_gl_balancing_segment,
1559                                                  p_Natural_segment => p_gl_account_segment,
1560                                                  p_Ledger_id => p_ledger_id,
1561                                                  p_coaid     => p_coaid,
1562                                                  p_Period_name=> l_transaction_year.period_name);
1563 
1564                         l_balance_amt := Nvl(l_balance_amt,0);
1565                         p_balance_amt := l_balance_amt;
1566                         --l_balance_amt := 0;
1570                         l_debug_info := 'balance in the anticipated account =  ' || l_balance_amt;
1567                         --psa_summ_det_combinations_v
1568 
1569                         ------------------------------------------------------------
1571                         trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
1572                         -------------------------------------------------------------
1573                         IF l_balance_amt <= 0 THEN
1574                              -- unanticapted
1575                              p_Anticipation := 'Unanticipated';
1576                              p_Anticipated_amt := 0;
1577                              p_UnAnticipated_amt := -1 * p_entered_pya_diff_amt;
1578                         ELSIF l_balance_amt > abs(p_net_pya_adj_amt) THEN
1579                             -- anticapted
1580                              p_Anticipation := 'Anticipated';
1581                              p_Anticipated_amt := -1 * p_entered_pya_diff_amt;
1582                              p_UnAnticipated_amt := 0;
1583                         ELSIF l_balance_amt < abs(p_net_pya_adj_amt) THEN
1584                              p_Anticipation := 'Partial';
1585                              p_Anticipated_amt := l_balance_amt;
1586                              p_UnAnticipated_amt := -1 * p_entered_pya_diff_amt - l_balance_amt;
1587                         END IF; -- anticiaped values
1588                         ------------------------------------------------------------
1589                         l_debug_info := 'Anticipation =  ' || p_Anticipation;
1590                         trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
1591                         -------------------------------------------------------------
1592                     END IF; -- end downward PYA adjustmemt
1593 END determine_upward_downward;
1594 
1595 
1596 PROCEDURE po_extract
1597 (
1598   p_application_id               IN            NUMBER,
1599   p_accounting_mode              IN            VARCHAR2
1600 )
1601 IS
1602 
1603   l_debug_info                   VARCHAR2(240);
1604   l_procedure_name               VARCHAR2(100):='.PO_EXTRACT';
1605 
1606 
1607     CURSOR c_ledger_info( p_event_id NUMBER ) IS
1608     SELECT chart_of_accounts_id coaid, gl.Ledger_id ledger_id
1609     FROM xla_events_gt xgt ,gl_ledgers gl
1610     WHERE gl.ledger_id = xgt.ledger_id
1611     AND   xgt.application_id = p_application_id
1612     AND   xgt.event_id = p_event_id;
1613 
1614     CURSOR c_req_extract_detail IS
1615     SELECT *
1616     FROM po_req_extract_detail_v
1617     where req_distribution_type = 'REQUISITION' ;
1618 
1619     CURSOR c_po_extract_detail IS
1620     SELECT *
1621     FROM po_extract_detail_v
1622     where po_distribution_type <> 'REQUISITION';
1623 
1624     CURSOR c_get_req_gl_date(p_event_id NUMBER) IS
1625     SELECT gl_date
1626     FROM po_req_extract_header_v
1627     WHERE event_id = p_event_id;
1628 
1629     CURSOR c_get_po_gl_date(p_event_id NUMBER) IS
1630     SELECT gl_date
1631     FROM po_extract_header_v
1632     WHERE event_id = p_event_id;
1633 
1634 
1635 
1636     CURSOR c_old_amt (p_dist_id NUMBER, p_event_id NUMBER) IS
1637     SELECT accounted_amt,event_type_code,code_combination_id  FROM PO_BC_DISTRIBUTIONS
1638     WHERE distribution_id = p_dist_id AND ae_event_id  =
1639         (SELECT max(ae_event_id) FROM PO_BC_DISTRIBUTIONS pbd
1640          WHERE pbd.distribution_id = p_dist_id
1641          AND pbd.ae_event_id <> p_event_id
1642          AND pbd.distribution_type <> 'REQUISITION'
1643          AND pbd.main_or_backing_code = 'M'
1644          AND EXISTS (select 1
1645                     from xla_ae_headers xah
1646                     where application_id = 201
1647                     and xah.event_id = pbd.ae_event_id
1648                     and xah.accounting_entry_status_code = 'F') );
1649 
1650     cursor c_event_type_code (p_event_id number) IS
1651     SELECT event_type_code
1652     FROM po_bc_distributions
1653     WHERE ae_event_id = p_event_id;
1654 
1655 
1656 
1657     l_accounting_mode         VARCHAR2(20);
1658     l_ledger_info             c_ledger_info%ROWTYPE;
1659     l_gl_balancing_segment    NUMBER;
1660     l_gl_account_segment      NUMBER;
1661     l_index                   NUMBER;
1662     l_fv_extract_detail       fv_ref_detail;
1663     l_req_extract_detail      c_req_extract_detail%ROWTYPE;
1664     l_po_extract_detail       c_po_extract_detail%ROWTYPE;
1665     l_gl_date		          DATE;
1666     l_pya                     BOOLEAN;
1667     l_net_pya_adj_amt         NUMBER;
1668 
1669     l_result				  BOOLEAN;
1670     l_fund_value              VARCHAR(30);
1671     l_old_fund_value          VARCHAR(30);
1672 
1673     l_old_amt                 c_old_amt%ROWTYPE;
1674     l_old_event_type_code     VARCHAR2(30);
1675     l_event_type_code         VARCHAR2(30);
1676     l_balance_amt             NUMBER;
1677 BEGIN
1678 
1679     l_procedure_name := g_path_name || l_procedure_name;
1680     -------------------------------------------------------------------------
1681     l_debug_info := 'Begin of procedure '||l_procedure_name;
1682     trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
1683     -------------------------------------------------------------------------
1684     -------------------------------------------------------------------------
1685 
1686 	IF (p_application_id <> 201) THEN
1687 		RETURN;
1688 	END IF;
1689 
1690      -- loop thru the requsition transaction objects for all distributions
1691      l_index:=0;
1692 
1693      ----------------------------------------------------------------------
1697 
1694      l_debug_info := 'Begin of Requisition ';
1695      trace(C_PROC_LEVEL, l_procedure_name, l_debug_info);
1696      ----------------------------------------------------------------------
1698      FOR l_req_extract_detail IN c_req_extract_detail LOOP
1699 
1700          -- Get the chart of accounts from legder and identify the segement qualifers
1701          -- gl_balancing and natural account
1702          --
1703          OPEN c_ledger_info(l_req_extract_detail.event_id);
1704          FETCH c_ledger_info INTO l_ledger_info;
1705         /* IF c_ledger_info%NOTFOUND THEN
1706               CLOSE c_ledger_info;
1707               RETURN ;
1708          END IF;*/
1709          CLOSE c_ledger_info;
1710 
1711           -------------------------------------------------------------------------
1712          l_debug_info := 'ledger id' ||l_ledger_info.ledger_id ;
1713          trace(C_PROC_LEVEL, l_procedure_name, l_debug_info);
1714          -------------------------------------------------------------------------
1715 
1716 
1717          l_index := l_index + 1;
1718          l_fv_extract_detail(l_index).event_id :=l_req_extract_detail.event_id;
1719          l_fv_extract_detail(l_index).Line_Number :=l_req_extract_detail.Line_number;
1720          l_fv_extract_detail(l_index).Application_id :=p_application_id;
1721          l_fund_value := get_fund_value(l_ledger_info.coaid,
1722                                         l_req_extract_detail.budget_account);
1723 
1724          -------------------------------------------------------------------------
1725          l_debug_info := 'Req Event ID: '||l_req_extract_detail.event_id;
1726          trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
1727          l_debug_info := 'Req Line Number : '||l_req_extract_detail.Line_number;
1728          trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
1729          -------------------------------------------------------------------------
1730 
1731          l_fv_extract_detail(l_index).fund_value :=l_fund_value;
1732 
1733          -------------------------------------------------------------------------
1734          l_debug_info := 'fund value' || l_fund_value;
1735          trace(C_PROC_LEVEL, l_procedure_name, l_debug_info);
1736          -------------------------------------------------------------------------
1737 
1738 
1739          OPEN c_get_req_gl_date(l_req_extract_detail.event_id);
1740          FETCH c_get_req_gl_date INTO l_gl_date;
1741          CLOSE c_get_req_gl_date;
1742 
1743           -------------------------------------------------------------------------
1744          l_debug_info := 'GL DATE' || l_gl_date;
1745          trace(C_PROC_LEVEL, l_procedure_name, l_debug_info);
1746          -------------------------------------------------------------------------
1747 
1748 
1749          -- get the fund category and expiration date
1750          get_fund_details( p_application_id,
1751                             l_ledger_info.ledger_id,
1752                             l_fund_value,
1753                             l_gl_date,
1754                             l_fv_extract_detail(l_index).fund_category,
1755                             l_fv_extract_detail(l_index).fund_expired_status );
1756 
1757          ----------------------------------------------------------------------
1758          l_debug_info := 'Fund Category '||l_fv_extract_detail(l_index).fund_category;
1759          trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
1760 
1761          l_debug_info := 'Fund Expired Status: '||l_fv_extract_detail(l_index).fund_expired_status;
1762          trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
1763          -----------------------------------------------------------------------
1764 
1765          -- prior year flag -- requsition donot have prior year transactions
1766          l_fv_extract_detail(l_index).prior_year_flag := 'N';
1767             -------------------------------------------------------------------------
1768          l_debug_info := 'Fund category... ' || l_fv_extract_detail(l_index).fund_category;
1769          trace(C_PROC_LEVEL, l_procedure_name, l_debug_info);
1770 
1771         l_debug_info := 'Fund Status.... ' || l_fv_extract_detail(l_index).fund_expired_status;
1772          trace(C_PROC_LEVEL, l_procedure_name, l_debug_info);
1773 
1774          -------------------------------------------------------------------------
1775      END LOOP;
1776 
1777      -------------------------------------------------------------------
1778      l_debug_info := 'End of Requisition ';
1779      trace(C_PROC_LEVEL, l_procedure_name, l_debug_info);
1780      -------------------------------------------------------------------
1781 
1782      ----------------------------------------------------------------------
1783      l_debug_info := 'Begin of PO ';
1784      trace(C_PROC_LEVEL, l_procedure_name, l_debug_info);
1785      ----------------------------------------------------------------------
1786 
1787     -- loop thru the PO transaction objects for all distributions
1788      FOR l_po_extract_detail IN c_po_extract_detail LOOP
1789 
1790         OPEN c_event_type_code(l_po_extract_detail.event_id);
1791         FETCH c_event_type_code INTO l_event_type_code;
1792         IF c_event_type_code%NOTFOUND THEN
1793               CLOSE c_event_type_code;
1794               RETURN;
1795          END IF;
1796          CLOSE c_event_type_code;
1797          --
1798          -- Get the chart of accounts from legder and identify the segement qualifers
1799          -- gl_balancing and natural account
1800          --
1801          OPEN c_ledger_info(l_po_extract_detail.event_id);
1802          FETCH c_ledger_info INTO l_ledger_info;
1806          END IF;
1803          IF c_ledger_info%NOTFOUND THEN
1804               CLOSE c_ledger_info;
1805               RETURN;
1807          CLOSE c_ledger_info;
1808          l_index := l_index + 1;
1809          l_fv_extract_detail(l_index).event_id :=l_po_extract_detail.event_id;
1810          l_fv_extract_detail(l_index).Line_Number :=l_po_extract_detail.Line_number;
1811          l_fv_extract_detail(l_index).Application_id :=p_application_id;
1812          l_fund_value := get_fund_value(l_ledger_info.coaid,
1813                                         l_po_extract_detail.budget_account,
1814                                         l_gl_account_segment,
1815                                         l_gl_balancing_segment);
1816          l_fv_extract_detail(l_index).fund_value :=l_fund_value;
1817          l_fv_extract_detail(l_index).old_ccid := NULL;
1818 --         l_fv_extract_detail(l_index).ccid_changed_flag := 'N';
1819 
1820          l_old_fund_value := NULL;
1821 --         l_fv_extract_detail(l_index).old_amt := 0;
1822 
1823          --------------------------------------------------------------------
1824          l_debug_info := 'PO Event ID: '||l_po_extract_detail.event_id;
1825          trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
1826          l_debug_info := 'PO Event Type: '||l_event_type_code;
1827          trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
1828          l_debug_info := 'PO Line Number : '||l_po_extract_detail.Line_number;
1829          trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
1830          l_debug_info := 'Fund Value: '||l_fund_value;
1831          trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
1832          --------------------------------------------------------------------
1833 
1834          OPEN c_get_po_gl_date(l_po_extract_detail.event_id);
1835          FETCH c_get_po_gl_date INTO l_gl_date;
1836          CLOSE c_get_po_gl_date;
1837 
1838          -- get the fund category and expiration date
1839          get_fund_details( p_application_id,
1840                             l_ledger_info.ledger_id,
1841                             l_fund_value,
1842                             l_gl_date,
1843                             l_fv_extract_detail(l_index).fund_category,
1844                             l_fv_extract_detail(l_index).fund_expired_status );
1845 
1846          -------------------------------------------------------------------
1847          l_debug_info := 'Fund Category '||l_fv_extract_detail(l_index).fund_category;
1848          trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
1849 
1850          l_debug_info := 'Fund Expired Status: '||l_fv_extract_detail(l_index).fund_expired_status;
1851          trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
1852          -------------------------------------------------------------------
1853 
1854           l_fv_extract_detail(l_index).entered_pya_amt := l_po_extract_detail.accounted_amt;
1855           l_fv_extract_detail(l_index).entered_pya_diff_amt := 0;
1856 
1857           -- prior year flag -- default current year
1858           l_fv_extract_detail(l_index).prior_year_flag := 'N';
1859           l_pya := get_prior_year_status (p_application_id,
1860                                           l_ledger_info.ledger_id,
1861 					                      l_ledger_info.coaid,
1862 					                      l_po_extract_detail.budget_account,
1863 		                                  	      l_gl_date );
1864 
1865             -- prior year transaction additional processs
1866           IF l_pya THEN
1867 
1868                -------------------------------------------------------------
1869                l_debug_info := 'l_pya is TRUE';
1870                trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
1871                -------------------------------------------------------------
1872 
1873              -- call the net amount for the PO document
1874              -- federal has requirements in case of  PYA  transactions  accounting has to
1875              ---be done on the differential amount of adjustments of price/quantity.
1876              ---For this , there is need for PO_EVENT_HANDLING to popluate the required additional columns for federal.
1877 
1878              -- Entered_Original_Amount(new)   	  original amount before the adjustment has happened  	 New (Ex:100 Price)
1879              -- Entered_Differential_Amount(new)  adjusted differential amount                          New (Ex; 20 Additional)
1880              -- Entered_Amount 	                   Actual 	No change (120=100+20)
1881              -- Request has been raised with PO event handling team
1882              -- would modify accordingly later when above colums are availble.
1883              -- call the required function to get the nwt by fund value
1884 
1885 
1886              l_fv_extract_detail(l_index).prior_year_flag := 'Y';
1887 
1888              IF (l_event_type_code = 'PO_PA_CANCELLED' or  l_event_type_code = 'RELEASE_CANCELLED' or
1889                  l_event_type_code = 'PO_PA_FINAL_CLOSED' or l_event_type_code = 'RELEASE_FINAL_CLOSED') THEN
1890                 NULL;    -- no further processing needed, Its Downward unanticipated.
1891                          -- Federal Purchasing Cancel PYA, Federal Purchasing PYA Final Close jlts will fire respectively
1892                          -- by virtue of conditions present on them.
1893              ELSE
1894                  l_net_pya_adj_amt := 0;
1895 
1896                  OPEN c_old_amt(l_po_extract_detail.po_distribution_id, l_po_extract_detail.event_id);
1897                  FETCH c_old_amt INTO l_old_amt;
1898 --                 CLOSE c_old_amt;
1899 
1900                  -- based on previous event type code
1901                  -- need to determine the PYA amount and Diff PYA amount
1902                  -- if previous event type is 'RESERVE' - only diff PYA amount --
1903                  -- upward movement
1907                  IF c_old_amt%NOTFOUND THEN
1904                  -- in case previous event  type is 'Unreserve' -- cost/qty decreased on PO dist
1905                  -- its a down adjustment
1906 
1908                     --IF l_po_extract_detail.accounted_amt >= nvl(l_old_amt.accounted_amt,0) THEN
1909                     l_fv_extract_detail(l_index).entered_pya_amt := 0;
1910                     l_fv_extract_detail(l_index).entered_pya_diff_amt := l_po_extract_detail.accounted_amt;
1911                  ELSE
1912                     l_old_event_type_code := l_old_amt.event_type_code;
1913                     IF (l_old_event_type_code = 'PO_PA_RESERVED' or
1914                             l_old_event_type_code = 'RELEASE_RESERVED' ) THEN     -- current amt < old amt
1915                         l_fv_extract_detail(l_index).entered_pya_amt := 0;
1916                         l_fv_extract_detail(l_index).entered_pya_diff_amt := l_po_extract_detail.accounted_amt;
1917                     ELSE  -- previous action is an unreserve action
1918                         IF (l_old_amt.code_combination_id = l_po_extract_detail.budget_account) THEN   --If CCID did not change
1919                             l_fv_extract_detail(l_index).entered_pya_amt := l_old_amt.accounted_amt;
1920                             l_fv_extract_detail(l_index).entered_pya_diff_amt := l_po_extract_detail.accounted_amt - l_old_amt.accounted_amt;
1921                         ELSE
1922 --                            l_fv_extract_detail(l_index).ccid_changed_flag := 'Y';
1923                             l_fv_extract_detail(l_index+1).old_ccid := l_old_amt.code_combination_id;
1924                             --l_fv_extract_detail(l_index).old_amt  := -1 * l_old_amt.accounted_amt;    -- we want to book a downward adjustment for old_amt, hence upward movement should be treated as -ve downward movement
1925                             l_old_fund_value := get_fund_value (l_ledger_info.coaid,l_old_amt.code_combination_id);
1926 
1927                             l_fv_extract_detail(l_index).entered_pya_amt := l_old_amt.accounted_amt;
1928                             l_fv_extract_detail(l_index).entered_pya_diff_amt := l_po_extract_detail.accounted_amt;
1929                             l_fv_extract_detail(l_index+1).entered_pya_diff_amt := -1 * l_old_amt.accounted_amt;     -- we want to book a downward adjustment for old_amt, hence upward movement should be treated as -ve downward movement
1930 --                                l_net_pya_adj_amt := -1 * l_old_amt.accounted_amt;           --mimic downward adjustment
1931                         END IF;
1932                     END IF;
1933                  END IF; --if c_old_amt%NOTFOUND
1934                  CLOSE c_old_amt;
1935  /*                l_old_event_type_code := l_old_amt.event_type_code;
1936 
1937                  IF l_po_extract_detail.accounted_amt >= nvl(l_old_amt.accounted_amt,0) THEN
1938                     l_fv_extract_detail(l_index).entered_pya_amt := 0;
1939                     l_fv_extract_detail(l_index).entered_pya_diff_amt := l_po_extract_detail.accounted_amt;
1940                  ELSIF (l_old_event_type_code = 'PO_PA_RESERVED' or
1941                             l_old_event_type_code = 'RELEASE_RESERVED' ) THEN     -- current amt < old amt
1942                         l_fv_extract_detail(l_index).entered_pya_amt := 0;
1943                         l_fv_extract_detail(l_index).entered_pya_diff_amt := l_po_extract_detail.accounted_amt;
1944                  ELSE  -- previous action is an unreserve action
1945                         l_fv_extract_detail(l_index).entered_pya_amt := l_old_amt.accounted_amt;
1946                         l_fv_extract_detail(l_index).entered_pya_diff_amt := l_po_extract_detail.accounted_amt - l_old_amt.accounted_amt;
1947                  END IF;  */
1948                -------------------------------------------------------------
1949                l_debug_info := 'Entered PYA amount = ' || l_fv_extract_detail(l_index).entered_pya_amt ;
1950                trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
1951                l_debug_info := 'Entered PYA diff amount = ' || l_fv_extract_detail(l_index).entered_pya_diff_amt ;
1952                trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
1953                -------------------------------------------------------------
1954 
1955                determine_upward_downward( l_ledger_info.coaid,
1956                                           l_ledger_info.ledger_id,
1957                                           l_po_extract_detail.event_id,
1958                                           l_fund_value,
1959                                           l_fv_extract_detail(l_index).net_pya_adj_amt,
1960                                           l_fv_extract_detail(l_index).adjustment_type ,
1961                                           l_gl_date,
1962                                           l_gl_balancing_segment,
1963                                           l_gl_account_segment,
1964                                           l_fv_extract_detail(l_index).Anticipation,
1965                                           l_fv_extract_detail(l_index).Anticipated_amt,
1966                                           l_fv_extract_detail(l_index).UnAnticipated_amt,
1967                                           l_fv_extract_detail(l_index).entered_pya_diff_amt,
1968                                           l_balance_amt
1969                                           );
1970                 IF l_fv_extract_detail(l_index).net_pya_adj_amt < 0 THEN       -- switch sign if downward adj because dist's upward movement should be trated as -ve downward
1971                     l_fv_extract_detail(l_index).entered_pya_diff_amt := -1 * l_fv_extract_detail(l_index).entered_pya_diff_amt;
1972                 END IF;
1973 
1974                 ------------------------------------------------------------
1975                 l_debug_info := 'Begin of inserting extra line - for adjustment entry';
1976                 trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
1980                     l_index := l_index+1;
1977                 -------------------------------------------------------------
1978 
1979                 IF nvl(l_old_fund_value,l_fund_value) <> l_fund_value THEN                                 --CCID change involves Fund Change
1981                     determine_upward_downward( l_ledger_info.coaid,
1982                                           l_ledger_info.ledger_id,
1983                                           l_po_extract_detail.event_id,
1984                                           l_old_fund_value,
1985                                           l_fv_extract_detail(l_index).net_pya_adj_amt,
1986                                           l_fv_extract_detail(l_index).adjustment_type ,
1987                                           l_gl_date,
1988                                           l_gl_balancing_segment,
1989                                           l_gl_account_segment,
1990                                           l_fv_extract_detail(l_index).Anticipation,
1991                                           l_fv_extract_detail(l_index).Anticipated_amt,
1992                                           l_fv_extract_detail(l_index).UnAnticipated_amt,
1993                                           l_fv_extract_detail(l_index).entered_pya_diff_amt,
1994                                           l_balance_amt);
1995                     IF l_fv_extract_detail(l_index).net_pya_adj_amt < 0 THEN
1996                         l_fv_extract_detail(l_index).entered_pya_diff_amt := -1 * l_fv_extract_detail(l_index).entered_pya_diff_amt;
1997 -- we want to book a downward adjustment for old_amt, hence upward movement should be treated as -ve downward movement
1998                     END IF;
1999 
2000                     l_fv_extract_detail(l_index).event_id :=l_po_extract_detail.event_id;
2001                     l_fv_extract_detail(l_index).Line_Number :=l_po_extract_detail.Line_number;
2002                     l_fv_extract_detail(l_index).Application_id :=p_application_id;
2003                     l_fv_extract_detail(l_index).fund_value :=l_old_fund_value;
2004 --                    l_fv_extract_detail(l_index).ccid_changed_flag := 'Y';
2005                      --------------------------------------------------------------------
2006                      l_debug_info := 'PO Event ID: '||l_po_extract_detail.event_id;
2007                      trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
2008                      l_debug_info := 'PO Event Type: '||l_event_type_code;
2009                      trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
2010                      l_debug_info := 'PO Line Number : '||l_po_extract_detail.Line_number;
2011                      trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
2012                      l_debug_info := 'Fund Value: '||l_fv_extract_detail(l_index).fund_value;
2013                      trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
2014                      --------------------------------------------------------------------
2015 
2016                      OPEN c_get_po_gl_date(l_po_extract_detail.event_id);
2017                      FETCH c_get_po_gl_date INTO l_gl_date;
2018                      CLOSE c_get_po_gl_date;
2019 
2020                      -- get the fund category and expiration date
2021                      get_fund_details( p_application_id,
2022                                         l_ledger_info.ledger_id,
2023                                         l_fv_extract_detail(l_index).fund_value,
2024                                         l_gl_date,
2025                                         l_fv_extract_detail(l_index).fund_category,
2026                                         l_fv_extract_detail(l_index).fund_expired_status );
2027 
2028                      -------------------------------------------------------------------
2029                      l_debug_info := 'Fund Category '||l_fv_extract_detail(l_index).fund_category;
2030                      trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
2031 
2032                      l_debug_info := 'Fund Expired Status: '||l_fv_extract_detail(l_index).fund_expired_status;
2033                      trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
2034                      -------------------------------------------------------------------
2035 
2036                       l_fv_extract_detail(l_index).entered_pya_amt := 0;
2037                       l_fv_extract_detail(l_index).prior_year_flag := 'Y';
2038 
2039                 ELSIF (nvl(l_old_amt.code_combination_id,l_po_extract_detail.budget_account) <> l_po_extract_detail.budget_account) THEN   --fund did not change, but CCID has changed
2040                     l_fv_extract_detail(l_index+1).net_pya_adj_amt := l_fv_extract_detail(l_index).net_pya_adj_amt;                        --since fund did not change, we can make use of the net_pya_adj_amt that has been calculated in teh previous step
2041                     l_index := l_index+1;
2042                     l_fv_extract_detail(l_index).event_id :=l_po_extract_detail.event_id;
2043                     l_fv_extract_detail(l_index).Line_Number :=l_po_extract_detail.Line_number;
2044                     l_fv_extract_detail(l_index).Application_id :=p_application_id;
2045                     l_fv_extract_detail(l_index).fund_value :=l_fund_value;
2046 --                    l_fv_extract_detail(l_index).ccid_changed_flag := 'Y';
2047                      --------------------------------------------------------------------
2048                      l_debug_info := 'PO Event ID: '||l_po_extract_detail.event_id;
2049                      trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
2050                      l_debug_info := 'PO Event Type: '||l_event_type_code;
2051                      trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
2052                      l_debug_info := 'PO Line Number : '||l_po_extract_detail.Line_number;
2056                      --------------------------------------------------------------------
2053                      trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
2054                      l_debug_info := 'Fund Value: '||l_fv_extract_detail(l_index).fund_value;
2055                      trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
2057 
2058                      l_fv_extract_detail(l_index).fund_category := l_fv_extract_detail(l_index-1).fund_category;
2059                      l_fv_extract_detail(l_index).fund_expired_status := l_fv_extract_detail(l_index-1).fund_expired_status;
2060 
2061                       l_fv_extract_detail(l_index).entered_pya_amt := 0;
2062                       l_fv_extract_detail(l_index).prior_year_flag := 'Y';
2063 
2064                     IF l_balance_amt <= 0 THEN
2065                          -- unanticapted
2066                          l_fv_extract_detail(l_index).Anticipation := 'Unanticipated';
2067                          l_fv_extract_detail(l_index).Anticipated_amt := 0;
2068                          l_fv_extract_detail(l_index).UnAnticipated_amt := -1 * l_fv_extract_detail(l_index).entered_pya_diff_amt;
2069                     ELSIF l_balance_amt > abs(l_fv_extract_detail(l_index).net_pya_adj_amt) THEN
2070                         -- anticapted
2071                          l_fv_extract_detail(l_index).Anticipation := 'Anticipated';
2072                          l_fv_extract_detail(l_index).Anticipated_amt := -1 * l_fv_extract_detail(l_index).entered_pya_diff_amt;
2073                          l_fv_extract_detail(l_index).UnAnticipated_amt := 0;
2074                     ELSIF l_balance_amt < abs(l_fv_extract_detail(l_index).net_pya_adj_amt) THEN
2075                          l_fv_extract_detail(l_index).Anticipation := 'Partial';
2076                          l_fv_extract_detail(l_index).Anticipated_amt := l_balance_amt;
2077                          l_fv_extract_detail(l_index).UnAnticipated_amt := -1 * l_fv_extract_detail(l_index).entered_pya_diff_amt - l_balance_amt;
2078                     END IF; -- anticiaped values
2079                     ------------------------------------------------------------
2080                     l_debug_info := 'Anticipation =  ' || l_fv_extract_detail(l_index).Anticipation;
2081                     trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
2082                     -------------------------------------------------------------
2083                     IF l_fv_extract_detail(l_index).net_pya_adj_amt < 0 THEN
2084                         l_fv_extract_detail(l_index).entered_pya_diff_amt := -1 * l_fv_extract_detail(l_index).entered_pya_diff_amt;
2085 -- we want to book a downward adjustment for old_amt, hence upward movement should be treated as -ve downward movement
2086                     END IF;
2087                 END IF;  -- IF l_old_fund_value <> l_fund_value
2088                 ------------------------------------------------------------
2089                 l_debug_info := 'End of inserting extra line - for adjustment entry';
2090                 trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
2091                 -------------------------------------------------------------
2092 
2093               END IF; -- IF condition on l_event_type_code
2094           END IF; -- end PYA
2095      END LOOP;  -- for PO objects
2096 
2097      ----------------------------------------------------------------------
2098      l_debug_info := 'End of PO ';
2099      trace(C_PROC_LEVEL, l_procedure_name, l_debug_info);
2100      ----------------------------------------------------------------------
2101 
2102 
2103      -- check if any req transactions are to be included
2104      FORALL  l_Index  IN l_fv_extract_detail.first..l_fv_extract_detail.last
2105          INSERT   INTO FV_EXTRACT_DETAIL_GT VALUES l_fv_extract_detail(l_index);
2106 
2107     -- ================================== FND_LOG ==================================
2108     l_debug_info := 'No of rows inserted into FV_EXTRACT_DETAIL_GT: '|| SQL%ROWCOUNT;
2109     trace(C_STATE_LEVEL, l_procedure_name, l_debug_info );
2110     -- ================================== FND_LOG ==================================
2111 
2112      l_index := 0;
2113 
2114      -------------------------------------------------------------------------
2115      l_debug_info := 'End of procedure'||l_procedure_name;
2116      trace(C_PROC_LEVEL, l_procedure_name, l_debug_info);
2117      -------------------------------------------------------------------------
2118 
2119 EXCEPTION
2120 
2121   WHEN OTHERS THEN
2122      l_debug_info := 'Error in Federal SLA processing - ' || SQLERRM;
2123      trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
2124      FND_MESSAGE.SET_NAME('FND', 'FND_GENERIC_MESSAGE');
2125      FND_MESSAGE.SET_TOKEN('MESSAGE' ,
2126          'Procedure :fv_sla_processing_pkg.get_fund_value'|| CRLF||
2127          'Error     :'||SQLERRM);
2128      FND_MSG_PUB.ADD;
2129      APP_EXCEPTION.RAISE_EXCEPTION();
2130 
2131 END po_extract;
2132 
2133 
2134 
2135 PROCEDURE cst_extract
2136 (
2137   p_application_id               IN            NUMBER,
2138   p_accounting_mode              IN            VARCHAR2
2139 )
2140 IS
2141 
2142   l_debug_info                   VARCHAR2(240);
2143   l_procedure_name               VARCHAR2(100):='.CST_EXTRACT';
2144 
2145     CURSOR c_ledger_info( p_event_id NUMBER ) IS
2146     SELECT chart_of_accounts_id coaid, gl.Ledger_id ledger_id
2147     FROM xla_events_gt xgt ,gl_ledgers gl
2148     WHERE gl.ledger_id = xgt.ledger_id
2149     AND   xgt.application_id = p_application_id
2150     AND   xgt.event_id = p_event_id;
2151 
2152     CURSOR c_rcv_extract_header(p_event_id NUMBER) IS
2153     SELECT *
2154     FROM CST_XLA_RCV_REF_V r_ref ,
2155     cst_xla_rcv_headers_v r
2156     WHERE r.event_id=p_event_id
2157           AND r.RCV_ACCOUNTING_EVENT_ID = r_ref.ref_rcv_accounting_event_id;
2158 
2162 
2159     CURSOR c_rcv_extract_detail IS
2160     SELECT *
2161     FROM cst_xla_rcv_lines_v;
2163     CURSOR c_po_dist_info(p_po_header_id NUMBER, p_po_distribution_id NUMBER) IS
2164 	SELECT *
2165 	FROM po_dists_ref_v pod
2166 	WHERE pod.po_header_id = p_po_header_id
2167 	AND pod.po_distribution_id = p_po_distribution_id;
2168 
2169 	CURSOR c_get_event_code(p_event_id NUMBER) IS
2170     SELECT  event_type_code
2171     FROM xla_events_gt
2172     WHERE event_id = p_event_id;
2173 
2174     CURSOR c_get_gl_fiscal_year(p_ledger_id NUMBER, p_gl_date DATE) IS
2175     SELECT period_year, period_name
2176     FROM    Gl_Period_Statuses
2177     WHERE   ledger_id = p_ledger_id
2178     AND     p_gl_date BETWEEN START_DATE AND end_date ;
2179 
2180     l_accounting_mode         VARCHAR2(20);
2181     l_ledger_info             c_ledger_info%ROWTYPE;
2182     l_gl_balancing_segment    NUMBER;
2183     l_gl_account_segment      NUMBER;
2184     l_index                   NUMBER;
2185     l_fv_extract_detail       fv_ref_detail;
2186     l_rcv_extract_detail_rec  c_rcv_extract_detail%ROWTYPE;
2187     l_rcv_extract_header_rec  c_rcv_extract_header%ROWTYPE;
2188     l_po_dist_info_rec        c_po_dist_info%ROWTYPE;
2189     l_get_event_code_rec      c_get_event_code%ROWTYPE;
2190     l_gl_date		          DATE;
2191     l_pya                     BOOLEAN;
2192     l_net_pya_adj_amt         NUMBER;
2193     l_balance_amt             NUMBER;
2194     l_result				  BOOLEAN;
2195     l_fund_value              VARCHAR(30);
2196     l_returned_quantity_net   NUMBER;
2197     l_amount_ordered          NUMBER;
2198     l_amount_delivered        NUMBER;
2199     l_amount_billed           NUMBER;
2200     l_transaction_year        c_get_gl_fiscal_year%ROWTYPE;
2201 BEGIN
2202 
2203     l_procedure_name := g_path_name || l_procedure_name;
2204     -------------------------------------------------------------------------
2205     l_debug_info := 'Begin of procedure '||l_procedure_name;
2206     trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
2207     -------------------------------------------------------------------------
2208     -------------------------------------------------------------------------
2209 
2210 	IF (p_application_id <> 707) THEN
2211 		RETURN;
2212 	END IF;
2213 
2214          l_index:=0;
2215 
2216          FOR l_rcv_extract_detail_rec IN c_rcv_extract_detail LOOP
2217 
2218              OPEN c_get_event_code( l_rcv_extract_detail_rec.event_id);
2219              FETCH c_get_event_code INTO l_get_event_code_rec;
2220              IF c_get_event_code%NOTFOUND THEN
2221                   CLOSE c_get_event_code;
2222                   RETURN;
2223              END IF;
2224              CLOSE c_get_event_code;
2225 
2226              trace(C_STATE_LEVEL, l_procedure_name, 'event type: ' ||
2227                    l_get_event_code_rec.event_type_code);
2228 	     trace(C_STATE_LEVEL, l_procedure_name, 'Accounted amount: ' ||
2229                    l_rcv_extract_detail_rec.accounted_amount);
2230 
2231 
2232              IF l_get_event_code_rec.event_type_code IN ('DELIVER_EXPENSE',
2233                                                          'RETURN_TO_RECEIVING',
2234                                                          'PO_DEL_INV', 'RET_RI_INV') THEN
2235 
2236                  OPEN c_rcv_extract_header( l_rcv_extract_detail_rec.event_id);
2237                  FETCH c_rcv_extract_header INTO l_rcv_extract_header_rec;
2238                  IF c_rcv_extract_header%NOTFOUND THEN
2239                       CLOSE c_rcv_extract_header;
2240                       RETURN;
2241                  END IF;
2242                  CLOSE c_rcv_extract_header;
2243 
2244                  OPEN c_po_dist_info( l_rcv_extract_header_rec.po_header_id,
2245                                       l_rcv_extract_header_rec.po_distribution_id);
2246                  FETCH c_po_dist_info INTO l_po_dist_info_rec;
2247                  IF c_po_dist_info%NOTFOUND THEN
2248                       CLOSE c_po_dist_info;
2249                       RETURN;
2250                  END IF;
2251                  CLOSE c_po_dist_info;
2252 
2253                  --
2254                  -- Get the chart of accounts from legder and identify the segement qualifers
2255                  -- gl_balancing and natural account
2256                  --
2257                  OPEN c_ledger_info( l_rcv_extract_detail_rec.event_id);
2258                  FETCH c_ledger_info INTO l_ledger_info;
2259                  IF c_ledger_info%NOTFOUND THEN
2260                       CLOSE c_ledger_info;
2261                       RETURN;
2262                  END IF;
2263                  CLOSE c_ledger_info;
2264 
2265                  l_index := l_index + 1;
2266                  l_fv_extract_detail(l_index).event_id:=l_rcv_extract_detail_rec.event_id;
2267                  l_fv_extract_detail(l_index).Line_Number:=l_rcv_extract_detail_rec.Line_number;
2268                  l_fv_extract_detail(l_index).Application_id :=p_application_id;
2269 
2270 
2271                  l_fund_value := get_fund_value(l_ledger_info.coaid,
2272                                                 l_po_dist_info_rec.budget_account,
2273                                                 l_gl_account_segment,
2274                                                 l_gl_balancing_segment);
2275                  l_fv_extract_detail(l_index).fund_value :=l_fund_value;
2276 
2277                  --DEBUG('Budget CCID '||l_po_dist_info_rec.code_combination_id);
2278                  --DEBUG('Fund Value'||  l_fund_value);
2279 
2280                    -- get the fund category and expiration date
2281                  get_fund_details( p_application_id,
2282                                    l_ledger_info.ledger_id,
2286 				   l_fv_extract_detail(l_index).fund_expired_status
2283 		                   l_fund_value,
2284 				   l_rcv_extract_header_rec.transaction_date,
2285 				   l_fv_extract_detail(l_index).fund_category,
2287 );
2288 /*Amount calculations*/
2289                  IF l_po_dist_info_rec.amount_ordered IS NULL OR l_po_dist_info_rec.amount_ordered = 0 THEN
2290                      l_amount_ordered := l_po_dist_info_rec.quantity_ordered*l_po_dist_info_rec.unit_price;
2291                  ELSE
2292                      l_amount_ordered := l_po_dist_info_rec.amount_ordered;
2293                  END IF;
2294                  IF l_po_dist_info_rec.amount_delivered IS NULL OR l_po_dist_info_rec.amount_delivered = 0 THEN
2295                      l_amount_delivered := l_po_dist_info_rec.quantity_delivered*l_po_dist_info_rec.unit_price;
2296                  ELSE
2297                      l_amount_delivered := l_po_dist_info_rec.amount_delivered;
2298                  END IF;
2299                  IF l_po_dist_info_rec.amount_billed IS NULL OR l_po_dist_info_rec.amount_billed = 0 THEN
2300                      l_amount_billed := l_po_dist_info_rec.quantity_billed*l_po_dist_info_rec.unit_price;
2301                  ELSE
2302                      l_amount_billed := l_po_dist_info_rec.amount_billed;
2303                  END IF;
2304 
2305                  trace(C_STATE_LEVEL, l_procedure_name, 'Amount ordered  ' || l_amount_ordered);
2306                  trace(C_STATE_LEVEL, l_procedure_name, 'Amount delivered  ' || l_amount_delivered);
2307                  trace(C_STATE_LEVEL, l_procedure_name, 'Amount Billed ' || l_amount_billed);
2308 
2309                  IF l_get_event_code_rec.event_type_code IN ('RETURN_TO_RECEIVING', 'RET_RI_INV') THEN
2310                      l_amount_delivered := l_amount_delivered + l_rcv_extract_detail_rec.accounted_amount;
2311                  END IF;
2312 
2313                  --l_fv_extract_detail(l_index).unexpended_obligation :=l_po_dist_info_rec.amount_ordered -
2314                  --                                                     (l_po_dist_info_rec.amount_delivered
2315                  --                                                      - l_rcv_extract_detail_rec.accounted_amount);
2316 
2317                  l_rcv_extract_detail_rec.accounted_amount := l_rcv_extract_detail_rec.accounted_amount;
2318                     if (l_rcv_extract_detail_rec.accounted_amount > (l_amount_ordered -  l_amount_delivered)) then
2319                         l_fv_extract_detail(l_index).unexpended_obligation := l_rcv_extract_detail_rec.accounted_amount;
2320                     End if;
2321 
2322                  trace(C_STATE_LEVEL, l_procedure_name, 'unexpended_obligation  ' ||
2323                        l_fv_extract_detail(l_index).unexpended_obligation);
2324 
2325 
2326                    IF l_amount_delivered < l_amount_ordered THEN
2327                     IF l_amount_delivered > l_amount_billed THEN
2328                        l_fv_extract_detail(l_index).unpaid_unexpended_obligation := l_amount_delivered - l_amount_billed;
2329                     ELSE
2330                        l_fv_extract_detail(l_index).unpaid_unexpended_obligation := 0;
2331                     END IF;
2332                     l_fv_extract_detail(l_index).paid_unexpended_obligation := l_rcv_extract_detail_rec.accounted_amount -
2333                                                                                l_fv_extract_detail(l_index).unpaid_unexpended_obligation;
2334                  ELSE
2335                     l_fv_extract_detail(l_index).unpaid_unexpended_obligation := l_amount_ordered - l_amount_billed;
2336                     l_fv_extract_detail(l_index).paid_unexpended_obligation := l_rcv_extract_detail_rec.accounted_amount -
2337                          l_fv_extract_detail(l_index).unpaid_unexpended_obligation - (l_amount_delivered - l_amount_ordered);
2338                    END IF;
2339 
2340                 trace(C_STATE_LEVEL, l_procedure_name, 'unpaid_unexpended_obligation  ' ||
2341                       l_fv_extract_detail(l_index).unpaid_unexpended_obligation);
2342                 trace(C_STATE_LEVEL, l_procedure_name, 'paid_unexpended_obligation  ' ||
2343                       l_fv_extract_detail(l_index).paid_unexpended_obligation);
2344 
2345                  /* Paid and unpaid amounts are not accounted separately while
2346                     recording a receipt. Following sources are not needed anymore*/
2347                  /* l_fv_extract_detail(l_index).unpaid_received_amt := l_rcv_extract_detail_rec.accounted_amount -
2348                                                                         l_fv_extract_detail(l_index).paid_unexpended_obligation;
2349                     l_fv_extract_detail(l_index).paid_received_amt :=   l_rcv_extract_detail_rec.accounted_amount -
2350                                                                         l_fv_extract_detail(l_index).unpaid_received_amt;
2351                  */
2352 
2353                  -- prior year flag -- requsition donot have prior year transactions*/
2354                  l_fv_extract_detail(l_index).prior_year_flag := 'N';
2355                  l_pya := get_prior_year_status ( 101,
2356                                                   l_ledger_info.ledger_id,
2357                                                   l_ledger_info.coaid,
2358 						  l_po_dist_info_rec.budget_account,
2359                                           	  l_rcv_extract_header_rec.transaction_date
2360                                                  );
2361 
2362                  IF l_pya THEN
2363                      IF l_get_event_code_rec.event_type_code = 'DELIVER_EXPENSE' THEN
2364                          IF l_po_dist_info_rec.quantity_delivered > l_po_dist_info_rec.quantity_ordered THEN
2365                              l_fv_extract_detail(l_index).prior_year_flag := 'Y';
2366                              l_fv_extract_detail(l_index).net_pya_adj_amt:= l_po_dist_info_rec.quantity_delivered -
2370                          SELECT sum(quantity) INTO l_returned_quantity_net  FROM RCV_TRANSACTIONS
2367                                                                             l_po_dist_info_rec.quantity_ordered;
2368                          END IF;
2369                      ELSIF l_get_event_code_rec.event_type_code = 'RETURN_TO_RECEIVING' THEN
2371                          WHERE po_header_id = l_rcv_extract_header_rec.po_header_id
2372                          AND po_distribution_id = l_rcv_extract_header_rec.po_distribution_id;
2373 
2374                          IF l_returned_quantity_net > l_po_dist_info_rec.quantity_ordered THEN
2375                              l_fv_extract_detail(l_index).prior_year_flag := 'Y';
2376                              l_fv_extract_detail(l_index).net_pya_adj_amt:= l_returned_quantity_net -
2377                                                                             l_po_dist_info_rec.quantity_ordered;
2378                          END IF;
2379                      END IF;
2380 
2381                      IF l_fv_extract_detail(l_index).prior_year_flag = 'Y' AND l_get_event_code_rec.event_type_code = 'RETURN_TO_RECEIVING' THEN
2382                             -- get the fiscal year for the GL_DATE of the transction
2383                             OPEN c_get_gl_fiscal_year( l_ledger_info.ledger_id,
2384                                                        l_rcv_extract_header_rec.transaction_date);
2385                             FETCH c_get_gl_fiscal_year INTO l_transaction_year;
2386                             CLOSE c_get_gl_fiscal_year;
2387                             -- get the balances from account
2388                             l_balance_amt:=get_anticipated_fund_amt(p_Fund_value                => l_fund_value,
2389                                                                     p_Balancing_segment         => l_gl_balancing_segment,
2390                                                                     p_Natural_segment           => l_gl_account_segment,
2391                                                                     p_Ledger_id                 => l_ledger_info.ledger_id,
2392                                                                     p_coaid                     => l_ledger_info.coaid,
2393                                                                     p_Period_name               => l_transaction_year.period_name);
2394 
2395                             l_balance_amt := Nvl(l_balance_amt,0);
2396                             --l_balance_amt := 0;
2397                             --psa_summ_det_combinations_v
2398                             IF l_balance_amt > l_fv_extract_detail(l_index).net_pya_adj_amt THEN
2399                                 -- anticapted
2400                                l_fv_extract_detail(l_index).Anticipation := 'Anticipated';
2401                                 l_fv_extract_detail(l_index).Anticipated_amt := l_balance_amt;
2402                                 l_fv_extract_detail(l_index).UnAnticipated_amt := 0;
2403                             ELSIF l_balance_amt = 0 THEN
2404                                  -- unanticapted
2405                                  l_fv_extract_detail(l_index).Anticipation := 'Unanticipated';
2406                                  l_fv_extract_detail(l_index).Anticipated_amt := 0;
2407                                  l_fv_extract_detail(l_index).UnAnticipated_amt := l_balance_amt;
2408                             ELSIF l_balance_amt < l_net_pya_adj_amt THEN
2409                                  l_fv_extract_detail(l_index).Anticipation := 'Partial';
2410                                  l_fv_extract_detail(l_index).Anticipated_amt := l_balance_amt;
2411                                 l_fv_extract_detail(l_index).UnAnticipated_amt := l_fv_extract_detail(l_index).net_pya_adj_amt - l_balance_amt;
2412                             END IF;
2413                        END IF;
2414                  END IF;
2415 
2416              END IF;
2417          END LOOP;
2418 
2419          FORALL  l_index  IN l_fv_extract_detail .first..l_fv_extract_detail.last
2420             INSERT   INTO FV_EXTRACT_DETAIL_GT VALUES l_fv_extract_detail(l_index);
2421          l_index := 0;
2422          -------------------------------------------------------------------------
2423          l_debug_info := 'End of procedure'||l_procedure_name;
2424          trace(C_PROC_LEVEL, l_procedure_name, l_debug_info);
2425          -------------------------------------------------------------------------
2426 EXCEPTION
2427 
2428   WHEN OTHERS THEN
2429      l_debug_info := 'Error in Federal CST SLA processing ';
2430      trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
2431      FND_MESSAGE.SET_NAME('FND', 'FND_GENERIC_MESSAGE');
2432      FND_MESSAGE.SET_TOKEN('MESSAGE' ,
2433          'Procedure :fv_sla_processing_pkg.cst_extract'|| CRLF||
2434          'Error     :'||SQLERRM);
2435      FND_MSG_PUB.ADD;
2436      APP_EXCEPTION.RAISE_EXCEPTION;
2437 
2438 END cst_extract;
2439 
2440 PROCEDURE ap_extract
2441 (
2442   p_application_id               IN            NUMBER,
2443   p_accounting_mode              IN            VARCHAR2
2444 )
2445 IS
2446 
2447 
2448   l_debug_info                   VARCHAR2(240);
2449   l_procedure_name               VARCHAR2(100):='.AP_EXTRACT';
2450 
2451     CURSOR c_ledger_info( p_event_id NUMBER ) IS
2452     SELECT chart_of_accounts_id coaid, gl.Ledger_id ledger_id
2453     FROM xla_events_gt xgt ,gl_ledgers gl
2454     WHERE gl.ledger_id = xgt.ledger_id
2455     AND   xgt.application_id = p_application_id
2456     AND   xgt.event_id = p_event_id;
2457 
2458     CURSOR c_ap_invoice_details IS
2459     SELECT  apinvdt.*
2460     FROM AP_EXTRACT_INVOICE_DTLS_BC_V apinvdt,
2461          XLA_EVENTS_GT xlagt
2462          where apinvdt.event_id = xlagt.event_id;
2463 
2464     CURSOR c_ap_invoice_header(p_event_id number) IS
2468          where apinvhd.event_id = xlagt.event_id;
2465     SELECT  apinvhd.*
2466     FROM AP_INVOICE_EXTRACT_HEADER_V apinvhd,
2467           XLA_EVENTS_GT xlagt
2469 
2470     CURSOR c_ap_payment_details IS
2471     SELECT  appaydd.*
2472     FROM AP_PAYMENT_EXTRACT_DETAILS_V appaydd,
2473          xla_events_gt xlagt
2474          where appaydd.event_id = xlagt.event_id;
2475 
2476     CURSOR c_ap_payment_header(p_event_id NUMBER) IS
2477     SELECT  appayhd.*
2478     FROM AP_PAYMENT_EXTRACT_HEADER_V appayhd,
2479        xla_events_gt xlagt
2480      where appayhd.event_id = xlagt.event_id;
2481 
2482     CURSOR c_po_dist_info(p_po_distribution_id NUMBER) IS
2483 	SELECT *
2484 	FROM po_distributions_all pod
2485 	WHERE pod.po_distribution_id = p_po_distribution_id;
2486 
2487 	CURSOR c_get_event_code(p_event_id NUMBER) IS
2488     SELECT  event_type_code
2489     FROM     xla_events_gt
2490     WHERE     event_id = p_event_id;
2491 
2492     CURSOR c_get_gl_fiscal_year(p_ledger_id NUMBER, p_gl_date DATE) IS
2493     SELECT period_year, period_name
2494     FROM    Gl_Period_Statuses
2495     WHERE   ledger_id = p_ledger_id
2496     AND     p_gl_date BETWEEN START_DATE AND end_date ;
2497 
2498     l_accounting_mode              VARCHAR2(20);
2499     l_ledger_info                  c_ledger_info%ROWTYPE;
2500     l_gl_balancing_segment         NUMBER;
2501     l_gl_account_segment           NUMBER;
2502     l_index                        NUMBER;
2503     l_federal_downward_amount      NUMBER;
2504     l_fv_extract_detail            fv_ref_detail;
2505     l_invoice_extract_detail_rec   c_ap_invoice_details%ROWTYPE;
2506     l_invoice_extract_header_rec   c_ap_invoice_header%ROWTYPE;
2507     l_payment_extract_detail_rec   c_ap_payment_details%ROWTYPE;
2508     l_payment_extract_header_rec   c_ap_payment_header%ROWTYPE;
2509     l_po_dist_info_rec             c_po_dist_info%ROWTYPE;
2510     l_get_event_code_rec           c_get_event_code%ROWTYPE;
2511     l_gl_date		               DATE;
2512     l_pya                          BOOLEAN;
2513     l_net_pya_adj_amt              NUMBER;
2514     l_balance_amt                  NUMBER;
2515     l_result				       BOOLEAN;
2516     l_fund_value                   VARCHAR(30);
2517     l_transaction_year        c_get_gl_fiscal_year%ROWTYPE;
2518 
2519 BEGIN
2520 
2521     l_procedure_name := g_path_name || l_procedure_name;
2522     -------------------------------------------------------------------------
2523     l_debug_info := 'Begin of procedure '||l_procedure_name;
2524     trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
2525     -------------------------------------------------------------------------
2526 
2527 	IF (p_application_id <> 200) THEN
2528 		RETURN;
2529 	END IF;
2530 
2531          l_index:=0;
2532         --Process invoice events
2533         FOR xla_rec in (select * from XLA_EVENTS_GT) loop
2534           trace (C_STATE_LEVEL, l_procedure_name, 'line_number='||xla_rec.line_number);
2535           trace (C_STATE_LEVEL, l_procedure_name, 'entity_id='||xla_rec.entity_id);
2536           trace (C_STATE_LEVEL, l_procedure_name, 'application_id='||xla_rec.application_id);
2537           trace (C_STATE_LEVEL, l_procedure_name, 'transaction_number='||xla_rec.transaction_number);
2538           trace (C_STATE_LEVEL, l_procedure_name, 'event_id='||xla_rec.event_id);
2539           trace (C_STATE_LEVEL, l_procedure_name, 'event_type_code='||xla_rec.event_type_code);
2540           trace (C_STATE_LEVEL, l_procedure_name, 'budgetary_control_flag='||xla_rec.budgetary_control_flag);
2541         end loop;
2542 
2543         FOR l_invoice_extract_detail_rec IN c_ap_invoice_details LOOP
2544               -------------------------------------------------------------------------
2545              l_debug_info := 'Inside Federal extract loop';
2546              trace(C_PROC_LEVEL, l_procedure_name, l_debug_info);
2547              l_debug_info := 'inv dist id '|| l_invoice_extract_detail_rec.inv_distribution_identifier;
2548              trace(C_PROC_LEVEL, l_procedure_name, l_debug_info);
2549              l_debug_info := 'event  id '|| l_invoice_extract_detail_rec.event_id;
2550              trace(C_PROC_LEVEL, l_procedure_name, l_debug_info);
2551             -------------------------------------------------------------------------
2552 
2553              OPEN c_get_event_code( l_invoice_extract_detail_rec.event_id);
2554              FETCH c_get_event_code INTO l_get_event_code_rec;
2555              IF c_get_event_code%NOTFOUND THEN
2556                   CLOSE c_get_event_code;
2557                   RETURN;
2558              END IF;
2559              CLOSE c_get_event_code;
2560 
2561 	    -------------------------------------------------------------------------
2562          l_debug_info := 'l_event_type_code'||l_get_event_code_rec.event_type_code;
2563          trace(C_PROC_LEVEL, l_procedure_name, l_debug_info);
2564          -------------------------------------------------------------------------
2565 
2566              IF l_get_event_code_rec.event_type_code IN
2567                   ('CREDIT MEMO ADJUSTED', 'CREDIT MEMO VALIDATED', 'CREDIT MEMO CANCELLED',
2568                    'DEBIT MEMO ADJUSTED', 'DEBIT MEMO VALIDATED', 'DEBIT MEMO CANCELLED',
2569                    'INVOICE ADJUSTED', 'INVOICE VALIDATED', 'INVOICE CANCELLED','PREPAYMENT ADJUSTED',
2570                    'PREPAYMENT CANCELLED','PREPAYMENT VALIDATED')
2571              THEN
2572 
2573 	  -------------------------------------------------------------------------
2574          l_debug_info := 'Inside the IF condition';
2575          trace(C_PROC_LEVEL, l_procedure_name, l_debug_info);
2579                  FETCH c_ap_invoice_header INTO l_invoice_extract_header_rec;
2576          -------------------------------------------------------------------------
2577 
2578 	         OPEN c_ap_invoice_header(l_invoice_extract_detail_rec.event_id);
2580                  IF c_ap_invoice_header%NOTFOUND THEN
2581                       CLOSE c_ap_invoice_header;
2582                       RETURN;
2583                  END IF;
2584                  CLOSE c_ap_invoice_header;
2585 
2586                  OPEN c_po_dist_info(l_invoice_extract_detail_rec.po_distribution_id);
2587                  FETCH c_po_dist_info INTO l_po_dist_info_rec;
2588                  IF c_po_dist_info%NOTFOUND THEN
2589                       CLOSE c_po_dist_info; -- change this to null if no processing needed
2590 --                      RETURN; comment by Senthil
2591                  END IF;
2592                  IF c_po_dist_info%ISOPEN THEN -- ashish
2593                  CLOSE c_po_dist_info;
2594                  END IF;
2595 
2596                  --
2597                  -- Get the chart of accounts from legder and identify the segement qualifers
2598                  -- gl_balancing and natural account
2599                  --
2600                  OPEN c_ledger_info( l_invoice_extract_detail_rec.event_id);
2601                  FETCH c_ledger_info INTO l_ledger_info;
2602                  IF c_ledger_info%NOTFOUND THEN
2603                       CLOSE c_ledger_info;
2604                       RETURN;
2605                  END IF;
2606                  CLOSE c_ledger_info;
2607 
2608                  l_index := l_index + 1;
2609                  l_fv_extract_detail(l_index).event_id := l_invoice_extract_detail_rec.event_id;
2610                  l_fv_extract_detail(l_index).Line_Number := l_invoice_extract_detail_rec.Line_number;
2611                  l_fv_extract_detail(l_index).Application_id := p_application_id;
2612 
2613 
2614                  l_fund_value := get_fund_value(l_ledger_info.coaid,
2615                                                 case
2616                                                       when l_invoice_extract_detail_rec.po_distribution_id is Not null
2617                                                       Then
2618                                                           l_po_dist_info_rec.code_combination_id
2619                                                       else
2620                                                       l_invoice_extract_detail_rec.aid_dist_ccid
2621                                                    end ,
2622                                                 l_gl_account_segment,
2623                                                 l_gl_balancing_segment);
2624                  l_fv_extract_detail(l_index).fund_value :=l_fund_value;
2625 
2626                  --DEBUG('Budget CCID '|| l_po_dist_info_rec.code_combination_id);
2627                  --DEBUG('Fund Value'||  l_fund_value);
2628 
2629                    -- get the fund category and expiration date
2630                  get_fund_details( p_application_id,
2631                                    l_ledger_info.ledger_id,
2632 				   l_fund_value,
2633 				   l_invoice_extract_detail_rec.aid_accounting_date,
2634 				   l_fv_extract_detail(l_index).fund_category,
2635 				   l_fv_extract_detail(l_index).fund_expired_status
2636                                  );
2637 
2638                  -- prior year flag -- requsition donot have prior year transactions
2639                  l_fv_extract_detail(l_index).prior_year_flag := 'N';
2640 
2641                  l_pya := get_prior_year_status ( p_application_id,
2642                                                   l_ledger_info.ledger_id,
2643                                                   l_ledger_info.coaid,
2644 						                          case
2645                                                       when l_invoice_extract_detail_rec.po_distribution_id is Not null
2646                                                       Then
2647                                                           l_po_dist_info_rec.code_combination_id
2648                                                       else
2649                                                       l_invoice_extract_detail_rec.aid_dist_ccid
2650                                                    end ,
2651                                                   l_invoice_extract_detail_rec.aid_accounting_date
2652                           );
2653 
2654                  IF l_pya THEN
2655 
2656                      l_fv_extract_detail(l_index).prior_year_flag := 'Y';
2657                      IF (l_invoice_extract_detail_rec.encumbrance_amount < 0) THEN
2658                          g_adjustment_type := 'Downward';
2659 
2660                          l_debug_info := 'Adjustment type set to Downward';
2661                          trace(C_PROC_LEVEL, l_procedure_name,l_debug_info);
2662 		    END IF;
2663 
2664                  END IF;
2665 
2666              END IF;
2667 
2668              /*Amount calculations*/
2669                 IF l_invoice_extract_detail_rec.po_distribution_id is not null Then
2670                      l_fv_extract_detail(l_index).paid_unexpended_obligation   :=l_invoice_extract_detail_rec.encumbrance_amount;
2671                      l_fv_extract_detail(l_index).unpaid_unexpended_obligation :=l_invoice_extract_detail_rec.encumbrance_amount;
2672                  ELSE
2673                     l_fv_extract_detail(l_index).paid_unexpended_obligation   :=l_invoice_extract_detail_rec.aid_amount;
2674                     l_fv_extract_detail(l_index).unpaid_unexpended_obligation :=l_invoice_extract_detail_rec.aid_amount;
2675                 END IF;
2676                  ---log to display the federal source values
2677                  -------------------------------------------------------
2681                  trace(C_PROC_LEVEL, l_procedure_name, l_debug_info);
2678                   l_debug_info := 'start of federal source values'||l_index;
2679                  trace(C_PROC_LEVEL, l_procedure_name, l_debug_info);
2680                  l_debug_info := 'event_id.........................'||l_fv_extract_detail(l_index).event_id;
2682                  l_debug_info := 'Line_Number......................'||l_fv_extract_detail(l_index).Line_Number;
2683                  trace(C_PROC_LEVEL, l_procedure_name, l_debug_info);
2684                  l_debug_info := 'fund_value.......................'||l_fv_extract_detail(l_index).fund_value;
2685                  trace(C_PROC_LEVEL, l_procedure_name, l_debug_info);
2686                  l_debug_info := 'fund_category....................'||l_fv_extract_detail(l_index).fund_category;
2687                  trace(C_PROC_LEVEL, l_procedure_name, l_debug_info);
2688                  l_debug_info := 'fund_expired_status..............'||l_fv_extract_detail(l_index).fund_expired_status;
2689                  trace(C_PROC_LEVEL, l_procedure_name, l_debug_info);
2690                  l_debug_info := 'prior_year_flag..................'||l_fv_extract_detail(l_index).prior_year_flag;
2691                  trace(C_PROC_LEVEL, l_procedure_name, l_debug_info);
2692                  l_debug_info := 'paid_unexpended_obligation.......'||l_fv_extract_detail(l_index).paid_unexpended_obligation;
2693                  trace(C_PROC_LEVEL, l_procedure_name, l_debug_info);
2694                  l_debug_info := 'unpaid_unexpended_obligation.....'||l_fv_extract_detail(l_index).unpaid_unexpended_obligation;
2695                  trace(C_PROC_LEVEL, l_procedure_name, l_debug_info);
2696 
2697                  -----------------------------------------------------------------
2698 
2699                 ---- check for downward and upward adjustment if prior year
2700                 l_fv_extract_detail(l_index).anticipation      := Null;
2701                 l_fv_extract_detail(l_index).anticipated_amt   := Null;
2702                 l_fv_extract_detail(l_index).unanticipated_amt := Null;
2703 
2704                 If l_fv_extract_detail(l_index).prior_year_flag = 'Y' THEN
2705 
2706                    l_fv_extract_detail(l_index).anticipation := g_adjustment_type;
2707                    l_fv_extract_detail(l_index).adjustment_type :=g_adjustment_type;
2708                    ------------------------------------------------------------
2709                    l_debug_info := 'Prior Year =  YES..' || l_fv_extract_detail(l_index).prior_year_flag;
2710                    trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
2711                    ------------------------------------------------------------
2712                     If g_adjustment_type = 'Upward' THEN
2713                         l_fv_extract_detail(l_index).anticipated_amt :=l_invoice_extract_detail_rec.aid_amount;
2714                         ------------------------------------------------------------
2715                         l_debug_info := 'Adjustmemt Type =  ' || g_adjustment_type;
2716                         trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
2717                         l_debug_info := 'balance in the anticipated account =  ' || l_balance_amt;
2718                         trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
2719                         -------------------------------------------------------------
2720                     ---- end upward adjustment ---------
2721                     ELSIF (g_adjustment_type = 'Downward')   THEN
2722                            l_federal_downward_amount := l_invoice_extract_detail_rec.aid_amount;
2723                         -- Find the Anticipated Account
2724                        --   BEGIN	/* Anti Acct */
2725                        -- get the fiscal year for the GL_DATE of the transction
2726                        OPEN c_get_gl_fiscal_year( l_ledger_info.ledger_id,
2727 				                                  l_invoice_extract_detail_rec.aid_accounting_date);
2728                        FETCH c_get_gl_fiscal_year INTO l_transaction_year;
2729                        CLOSE c_get_gl_fiscal_year;
2730 
2731                         -- get the balances from account
2732                         l_balance_amt:=get_anticipated_fund_amt(p_Fund_value => l_fund_value,
2733                                                  p_Balancing_segment => l_gl_balancing_segment,
2734                                                  p_Natural_segment => l_gl_account_segment,
2735                                                  p_Ledger_id => l_ledger_info.ledger_id,
2736                                                  p_coaid     => l_ledger_info.coaid,
2737                                                  p_Period_name=> l_transaction_year.period_name);
2738 
2739                         l_balance_amt := Nvl(l_balance_amt,0);
2740                         --l_balance_amt := 0;
2741                         --psa_summ_det_combinations_v
2742                         l_fv_extract_detail(l_index).Anticipation      := Null;
2743                         l_fv_extract_detail(l_index).Anticipated_amt   := Null;
2744                         l_fv_extract_detail(l_index).UnAnticipated_amt := Null;
2745                         ------------------------------------------------------------
2746                         l_debug_info := 'Adjustmemt Type =  ' || g_adjustment_type;
2747                         trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
2748                         l_debug_info := 'balance in the anticipated account =  ' || l_balance_amt;
2749                         trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
2750                         -------------------------------------------------------------
2751                         IF l_balance_amt <= 0 THEN
2752                              -- unanticapted
2753                              l_fv_extract_detail(l_index).Anticipation := 'UnAnticipated';
2757                             -- anticapted
2754                              l_fv_extract_detail(l_index).Anticipated_amt := 0;
2755                              l_fv_extract_detail(l_index).UnAnticipated_amt := abs(l_federal_downward_amount);
2756                         ELSIF l_balance_amt > abs(l_federal_downward_amount) THEN
2758                              l_fv_extract_detail(l_index).Anticipation := 'Anticipated';
2759                              l_fv_extract_detail(l_index).Anticipated_amt := abs(l_federal_downward_amount);
2760                              l_fv_extract_detail(l_index).UnAnticipated_amt := 0;
2761                         ELSIF l_balance_amt < abs(l_federal_downward_amount) THEN
2762                              l_fv_extract_detail(l_index).Anticipation := 'Partial';
2763                              l_fv_extract_detail(l_index).Anticipated_amt := abs(l_balance_amt);
2764                              l_fv_extract_detail(l_index).UnAnticipated_amt := abs(l_federal_downward_amount) - abs(l_balance_amt);
2765                         END IF; -- anticiaped values
2766                         ------------------------------------------------------------
2767                         l_debug_info := 'Anticipation =  ' || l_fv_extract_detail(l_index).Anticipation;
2768                         trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
2769                          l_debug_info := 'Anticipated Amount =  ' || l_fv_extract_detail(l_index).Anticipated_amt;
2770                         trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
2771                          l_debug_info := 'UnAnticipated Amount =  ' || l_fv_extract_detail(l_index).UnAnticipated_amt;
2772                         trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
2773 
2774                         -------------------------------------------------------------
2775                    -- end downward PYA adjustmemt
2776                     ELSE-- end downward anticipation
2777                         l_fv_extract_detail(l_index).Anticipation := Null;
2778                         l_fv_extract_detail(l_index).anticipated_amt := Null;
2779                         l_fv_extract_detail(l_index).unanticipated_amt :=Null;
2780 
2781                   END IF;
2782                 END IF;
2783                 -------------------------------------------------------------
2784                      l_debug_info := 'End of federal source............'||l_index;
2785                       trace(C_PROC_LEVEL, l_procedure_name, l_debug_info);
2786                -------------------------------------------------------------
2787          END LOOP;
2788 
2789        -- Process payment events
2790        -- Handled separtely in treasury confirmation
2791        -- start
2792 
2793               -------------------------------------------------------------
2794           l_debug_info := 'Begin of federal payment process.......sekhar.....'||l_index;
2795           trace(C_PROC_LEVEL, l_procedure_name, l_debug_info);
2796           -------------------------------------------------------------
2797 
2798 
2799        FOR l_payment_extract_detail_rec IN c_ap_payment_details LOOP
2800        -------------------------------------------------------------
2801           l_debug_info := 'Begin of federal payment process............'||l_index;
2802           trace(C_PROC_LEVEL, l_procedure_name, l_debug_info);
2803           -------------------------------------------------------------
2804 
2805              OPEN c_get_event_code( l_payment_extract_detail_rec.event_id);
2806              FETCH c_get_event_code INTO l_get_event_code_rec;
2807              IF c_get_event_code%NOTFOUND THEN
2808                   CLOSE c_get_event_code;
2809                   RETURN;
2810              END IF;
2811              CLOSE c_get_event_code;
2812 
2813              IF l_get_event_code_rec.event_type_code IN ('PAYMENT ADJUSTED', 'PAYMENT CREATED', 'PAYMENT CANCELLED') THEN
2814 
2815                  OPEN c_ap_payment_header(l_payment_extract_detail_rec.event_id);
2816                  FETCH c_ap_payment_header INTO l_payment_extract_header_rec;
2817                  IF c_ap_payment_header%NOTFOUND THEN
2818                       CLOSE c_ap_payment_header;
2819                       RETURN;
2820                  END IF;
2821                  CLOSE c_ap_payment_header;
2822 
2823                 /* OPEN c_po_dist_info(l_payment_extract_detail_rec.po_distribution_id);
2824                  FETCH c_po_dist_info INTO l_po_dist_info_rec;
2825                  IF c_po_dist_info%NOTFOUND THEN
2826                       CLOSE c_po_dist_info;
2827                       RETURN;
2828                  END IF;
2829                  CLOSE c_po_dist_info;*/
2830 
2831                  --
2832                  -- Get the chart of accounts from legder and identify the segement qualifers
2833                  -- gl_balancing and natural account
2834                  --
2835                  OPEN c_ledger_info( l_payment_extract_detail_rec.event_id);
2836                  FETCH c_ledger_info INTO l_ledger_info;
2837                  IF c_ledger_info%NOTFOUND THEN
2838                       CLOSE c_ledger_info;
2839                       RETURN;
2840                  END IF;
2841                  CLOSE c_ledger_info;
2842 
2843                  l_index := l_index + 1;
2844                  l_fv_extract_detail(l_index).event_id := l_payment_extract_detail_rec.event_id;
2845                  l_fv_extract_detail(l_index).Line_Number := l_payment_extract_detail_rec.Line_number;
2846                  l_fv_extract_detail(l_index).Application_id := p_application_id;
2847 
2848                  --DEBUG('Event ID'|| l_rcv_extract_detail_rec.event_id);
2849 
2850                  l_fund_value := get_fund_value(l_ledger_info.coaid,
2854                  l_fv_extract_detail(l_index).fund_value :=l_fund_value;
2851                                                 l_payment_extract_detail_rec.AID_DIST_CCID,
2852                                                 l_gl_account_segment,
2853                                                 l_gl_balancing_segment);
2855 
2856                  --DEBUG('Budget CCID '||l_po_dist_info_rec.code_combination_id);
2857                  --DEBUG('Fund Value'||  l_fund_value);
2858 
2859                    -- get the fund category and expiration date
2860                  get_fund_details( p_application_id,
2861                                    l_ledger_info.ledger_id,
2862 				   l_fund_value,
2863 				   l_payment_extract_header_rec.aph_accounting_date,
2864 				   l_fv_extract_detail(l_index).fund_category,
2865 				   l_fv_extract_detail(l_index).fund_expired_status
2866                                  );
2867 
2868                  -- prior year flag -- requsition donot have prior year transactions
2869                  l_fv_extract_detail(l_index).prior_year_flag := 'N';
2870                  l_pya := get_prior_year_status ( p_application_id,
2871                                                   l_ledger_info.ledger_id,
2872                          	                  l_ledger_info.coaid,
2873 						  l_payment_extract_detail_rec.AID_DIST_CCID,
2874                                           	  l_payment_extract_header_rec.aph_accounting_date
2875                           );
2876                  IF l_pya THEN
2877                      l_fv_extract_detail(l_index).prior_year_flag := 'Y';
2878                                             -- get the fiscal year for the GL_DATE of the transction
2879                            OPEN c_get_gl_fiscal_year( l_ledger_info.ledger_id,
2880       						      l_payment_extract_header_rec.aph_accounting_date);
2881                            FETCH c_get_gl_fiscal_year INTO l_transaction_year;
2882                            CLOSE c_get_gl_fiscal_year;
2883                                             -- get the balances from account
2884                     /* l_balance_amt:=get_anticipated_fund_amt(p_Fund_value             => l_fund_value,
2885                                                              p_Balancing_segment      => l_gl_balancing_segment,
2886                                                              p_Natural_segment        => l_gl_account_segment,
2887                                                              p_Ledger_id              => l_ledger_info.ledger_id,
2888                                                              p_coaid                  => l_ledger_info.coaid,
2889                                                              p_Period_name            => l_transaction_year.period_name);*/
2890                  END IF;
2891 
2892              END IF;
2893          END LOOP;
2894          --- end
2895          -- Handled separtely in treasury confirmation
2896 
2897          FORALL  l_Index  IN l_fv_extract_detail.first..l_fv_extract_detail.last
2898             INSERT INTO FV_EXTRACT_DETAIL_GT VALUES l_fv_extract_detail(l_index);
2899 
2900          l_debug_info := 'Number of Rows inserted into FV_EXTRACT_DETAIL_GT: '|| SQL%ROWCOUNT;
2901          trace(C_STATE_LEVEL, l_procedure_name, l_debug_info );
2902 
2903          l_index := 0;
2904 
2905          -------------------------------------------------------------------------
2906          l_debug_info := 'End of procedure'||l_procedure_name;
2907          trace(C_PROC_LEVEL, l_procedure_name, l_debug_info);
2908          -------------------------------------------------------------------------
2909 
2910 
2911 EXCEPTION
2912 
2913   WHEN OTHERS THEN
2914      l_debug_info := 'Error in Federal AP SLA processing ';
2915      trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
2916      FND_MESSAGE.SET_NAME('FND', 'FND_GENERIC_MESSAGE');
2917      FND_MESSAGE.SET_TOKEN('MESSAGE' ,
2918          'Procedure :fv_sla_processing_pkg.ap_extract'|| CRLF||
2919          'Error     :'||SQLERRM);
2920      FND_MSG_PUB.ADD;
2921      APP_EXCEPTION.RAISE_EXCEPTION;
2922 
2923 END ap_extract;
2924 
2925 
2926 
2927 PROCEDURE ar_extract
2928 (
2929   p_application_id               IN            NUMBER,
2930   p_accounting_mode              IN            VARCHAR2
2931 )
2932 IS
2933 
2934     l_debug_info                   VARCHAR2(240);
2935     l_procedure_name               VARCHAR2(100):='.AR_EXTRACT';
2936 
2937     /* Get the events type information from XLA_EVENTS for application AR */
2938     CURSOR cur_ar_event_type IS
2939     SELECT event_type_code
2940       FROM xla_events_gt
2941      WHERE application_id = p_application_id
2942      GROUP BY event_type_code;
2943 
2944     /* Get the Event Information */
2945     CURSOR cur_ar_event_info
2946     IS
2947     SELECT * FROM xla_events_gt;
2948 
2949     /* Get the Fund Category for the Invoice Default Receivable Account */
2950     CURSOR cur_ar_get_fund_catg (p_set_of_books_id NUMBER,
2951                                  p_fund_value VARCHAR2)
2952     IS
2953     SELECT fund_category
2954       FROM fv_fund_parameters
2955      WHERE set_of_books_id = p_set_of_books_id
2956        AND fund_value = p_fund_value;
2957 
2958     /* Get the AR Invoice Extract Details */
2959     CURSOR cur_ar_inv_extract_details IS
2960     SELECT *
2961       FROM ar_cust_trx_lines_l_v;
2962 
2963     /* Get the Transaction header ledger data */
2964     CURSOR cur_ledger_info (p_event_id NUMBER) IS
2965     SELECT led.ledger_id ledger_id, led.ldg_chart_of_accounts_id coa_id
2966       FROM ar_ledger_h_v led
2970     CURSOR cur_ar_inv_head_balseg_value (p_event_id NUMBER) IS
2967      WHERE led.event_id = p_event_id;
2968 
2969     /* Get the AR Invoice Extract Header Balancing Segment Value */
2971     SELECT glseg.ar_gl_balacing_segment_value inv_fund_value
2972       FROM  ar_gl_segments_ref_v glseg , ar_transactions_s_v trxobj
2973      WHERE trxobj.trx_receivable_ccid = glseg.ar_gl_code_combination_id
2974        AND trxobj.event_id = p_event_id;
2975 
2976     /* Get the AR Invoice Extract Detail Balancing Segment Value */
2977     CURSOR cur_ar_inv_balseg_value (p_event_id NUMBER,
2978                                     p_line_number NUMBER)
2979     IS
2980     SELECT glseg.ar_gl_balacing_segment_value inv_fund_value
2981       FROM  ar_gl_segments_ref_v glseg , ar_cust_trx_lines_l_v trxobj
2982      WHERE trxobj.trx_line_dist_ccid = glseg.ar_gl_code_combination_id
2983        AND trxobj.event_id = p_event_id
2984        AND trxobj.line_number = p_line_number;
2985 
2986     /* Get the AR Invoice Extract Header Natural Segment Value */
2987     CURSOR cur_ar_invhead_natseg_value (p_event_id NUMBER) IS
2988     SELECT glseg.ar_gl_natural_segment_value invhead_natseg_value
2989       FROM  ar_gl_segments_ref_v glseg , ar_transactions_s_v trxobj
2990      WHERE trxobj.trx_receivable_ccid = glseg.ar_gl_code_combination_id
2991        AND trxobj.event_id = p_event_id;
2992 
2993 
2994     /* Get the AR Cash Receipt Extract Line */
2995     CURSOR cur_ar_rct_extract_details (p_dist_source_type VARCHAR2) IS
2996     SELECT dist.event_id, dist.line_number, dist.dist_code_combination_id,
2997            trxobj.trx_line_dist_ccid
2998       FROM ar_distributions_l_v dist, ar_cust_trx_lines_l_v trxobj
2999      WHERE dist.dist_source_type = p_dist_source_type
3000        AND trxobj.event_id (+)   = dist.event_id
3001        AND trxobj.line_number (+) = dist.line_number;
3002 
3003 
3004     /* Get the AR Receipt Applied to Invoice Reveneue Accounts CCID */
3005     CURSOR cur_rct_app_trx_rev_natacct IS
3006     SELECT distinct trxobj.trx_line_dist_ccid
3007       FROM ar_distributions_l_v dist,
3008            ar_cust_trx_lines_l_v trxobj
3009      WHERE dist.dist_source_type = 'REC'
3010        AND trxobj.event_id  = dist.event_id
3011        AND trxobj.line_number = dist.line_number;
3012 
3013     /* Get the Natural Account Segment for a particular CCID */
3014     CURSOR cur_get_natacct (p_ccid NUMBER) IS
3015     SELECT to_number(glseg.ar_gl_natural_segment_value) natseg_value
3016       FROM ar_gl_segments_ref_v glseg
3017      WHERE glseg.ar_gl_code_combination_id = p_ccid;
3018 
3019     /* Get the Miscellaneous Receipt Extract Detail */
3020     CURSOR cur_misc_rct_extract_details IS
3021     SELECT *
3022       FROM ar_distributions_l_v;
3023 
3024     /* Get the AR Cash Receipt Application to Transaction lines */
3025     CURSOR cur_app_to_trx_balseg_val (p_event_id NUMBER,
3026                                       p_line_number NUMBER)
3027     IS
3028     SELECT glseg.ar_gl_balacing_segment_value inv_rev_fund_value
3029     FROM ar_gl_segments_ref_v glseg , ar_cust_trx_lines_l_v trxobj
3030      WHERE  trxobj.trx_line_dist_ccid = glseg.ar_gl_code_combination_id
3031       AND   trxobj.event_id = p_event_id
3032       AND   trxobj.line_number = p_line_number;
3033 
3034     /* Get the AR Miscellaneous Receipt Extract Balancing Segment Value */
3035     CURSOR cur_ar_rct_balseg_value (p_event_id NUMBER,
3036                                     p_line_number NUMBER)
3037     IS
3038     SELECT glseg.ar_gl_balacing_segment_value rct_fund_value
3039       FROM  ar_gl_segments_ref_v glseg , ar_distributions_l_v trxobj
3040      WHERE  trxobj.dist_code_combination_id = glseg.ar_gl_code_combination_id
3041       AND   trxobj.event_id = p_event_id
3042       AND   trxobj.line_number = p_line_number;
3043 
3044     l_fv_extract_detail fv_ref_detail;
3045     empty_fv_extract_detail fv_ref_detail; -- empty table declaration
3046     l_ar_event_type xla_events_gt.event_type_code%TYPE;
3047     l_ar_inv_extract_details cur_ar_inv_extract_details%ROWTYPE;
3048     l_ar_rct_extract_details cur_ar_rct_extract_details%ROWTYPE;
3049     l_misc_rct_extract_details cur_misc_rct_extract_details%ROWTYPE;
3050     l_fund_value fv_extract_detail_gt.fund_value%TYPE;
3051     l_head_fund_value fv_extract_detail_gt.fund_value%TYPE;
3052     l_head_fund_category fv_extract_detail_gt.fund_category%TYPE;
3053     l_fund_expired_status fv_extract_detail_gt.fund_expired_status%TYPE;
3054     l_fund_category fv_extract_detail_gt.fund_category%TYPE;
3055     l_fund_time_frame fv_extract_detail_gt.fund_time_frame%TYPE;
3056     l_prior_year_flag fv_extract_detail_gt.prior_year_flag%TYPE;
3057     l_account_valid_flag fv_extract_detail_gt.account_valid_flag%TYPE;
3058     l_ledger_info cur_ledger_info%ROWTYPE;
3059     l_fv_extract_rec fv_extract_rec;
3060     l_ar_event_info cur_ar_event_info%ROWTYPE;
3061     l_header_natseg_value NUMBER;
3062     l_natseg_value NUMBER;
3063     l_pya BOOLEAN := NULL;
3064     l_acct_valid BOOLEAN;
3065     l_acct_head_valid BOOLEAN;
3066     l_overall_acct_valid BOOLEAN := TRUE;
3067     l_index NUMBER;
3068     l_trx_type_reim BOOLEAN := FALSE;
3069     l_trx_type_over BOOLEAN := FALSE;
3070     l_trx_type_adv BOOLEAN := FALSE;
3071     l_account_rule fv_extract_detail_gt.account_rule%TYPE;
3072     l_receivable_with_advance VARCHAR2(1) := 'N';
3073 
3074 BEGIN
3075 
3076     l_procedure_name := g_path_name || l_procedure_name;
3077 
3078     -- ================================== FND_LOG ==================================
3079     l_debug_info := 'Begin of procedure '||l_procedure_name;
3080     trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
3084     IF (p_application_id <> 222) THEN
3081     -- ================================== FND_LOG ==================================
3082 
3083     /* Validate the application ID */
3085         RETURN;
3086     END IF;
3087     -- ================================== FND_LOG ==================================
3088     l_debug_info := 'Accounting Mode: ' || p_accounting_mode ;
3089     trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
3090     -- ================================== FND_LOG ==================================
3091 
3092     /* Validate the accounting mode */
3093     IF (p_accounting_mode NOT IN ('D', 'F')) THEN
3094         RETURN;
3095     END IF;
3096 
3097     -- ================================== FND_LOG ==================================
3098     l_debug_info := 'After validating Application ID:  ' || p_application_id ||
3099                      ' and Accounting Mode: '|| p_accounting_mode ;
3100     trace(C_STATE_LEVEL, l_procedure_name, l_debug_info );
3101     -- ================================== FND_LOG ==================================
3102 
3103     /* Get the Event Information of the transaction */
3104     OPEN cur_ar_event_info;
3105     FETCH cur_ar_event_info INTO l_ar_event_info;
3106     -- ================================== FND_LOG ==================================
3107     l_debug_info := 'AR Event Information -  Event ID: '|| l_ar_event_info.event_id;
3108     trace(C_STATE_LEVEL, l_procedure_name, l_debug_info );
3109     -- ================================== FND_LOG ==================================
3110     CLOSE cur_ar_event_info;
3111 
3112     /* Get the ledger_id */
3113     OPEN cur_ledger_info(l_ar_event_info.event_id);
3114     FETCH cur_ledger_info INTO l_ledger_info;
3115     -- ================================== FND_LOG ==================================
3116     l_debug_info := 'Ledger Information - Ledger ID: ' ||l_ledger_info.ledger_id || ' and COA ID: '|| l_ledger_info.coa_id;
3117     trace(C_STATE_LEVEL, l_procedure_name, l_debug_info );
3118     -- ================================== FND_LOG ==================================
3119     CLOSE cur_ledger_info;
3120 
3121     /* Open the cursor for checking event type code and process accordingly */
3122     OPEN cur_ar_event_type;
3123     FETCH cur_ar_event_type INTO l_ar_event_type;
3124     -- ================================== FND_LOG ==================================
3125     l_debug_info := 'AR Event Type is: ' || l_ar_event_type ;
3126     trace(C_STATE_LEVEL, l_procedure_name, l_debug_info );
3127     -- ================================== FND_LOG ==================================
3128     CLOSE cur_ar_event_type;
3129 
3130 
3131 
3132 
3133     /*==============================================================================*
3134      |                                                                              |
3135      |  Invoice Extract Processing                                                  |
3136      |  --------------------------                                                  |
3137      |  1. We validate the Natural Account Segment of REC Line.                     |
3138      |  2. We validate all the REV lines to have valid federal parameters.          |
3139      |  3. If any of the validation fails, we do not allow federal accounting lines |
3140      |     to be created and allow core AR/MFAR accounting to go through.           |
3141      |                                                                              |
3142      *==============================================================================*/
3143 
3144 
3145     /* Process Invoice Events */
3146     IF (l_ar_event_type IN ('INV_CREATE', 'INV_UPDATE')) THEN
3147 
3148         -- ================================== FND_LOG ==================================
3149         l_debug_info := 'Inside Invoice Event type';
3150         trace(C_STATE_LEVEL, l_procedure_name, l_debug_info );
3151         -- ================================== FND_LOG ==================================
3152 
3153         /* Initialize index */
3154         l_index := 0;
3155 
3156         /* Get Invoice Extract Lines Data */
3157         FOR l_ar_inv_extract_details IN cur_ar_inv_extract_details
3158         LOOP
3159             /* Process Revenue Lines Only */
3160             IF (l_ar_inv_extract_details.TRX_LINE_DIST_ACCOUNT_CLASS = 'REV') THEN
3161                 -- ================================== FND_LOG ==================================
3162                 l_debug_info := 'Processing Invoice REV LINE...';
3163                 trace(C_STATE_LEVEL, l_procedure_name, l_debug_info );
3164                 -- ================================== FND_LOG ==================================
3165 
3166                 /* Get the Fund Value */
3167                 OPEN cur_ar_inv_balseg_value (l_ar_inv_extract_details.event_id
3168                                               ,l_ar_inv_extract_details.line_number
3169                                              );
3170                 FETCH cur_ar_inv_balseg_value INTO l_fund_value;
3171                 -- ================================== FND_LOG ==================================
3172                 l_debug_info := 'Fund Value : ' || l_fund_value ;
3173                 trace(C_STATE_LEVEL, l_procedure_name, l_debug_info );
3174                 -- ================================== FND_LOG ==================================
3175                 CLOSE cur_ar_inv_balseg_value;
3176 
3177                 /* Get the Fund Information */
3178                 get_fund_details (p_application_id,
3179                                   l_ledger_info.ledger_id,
3180                                   l_fund_value,
3181                                   l_ar_event_info.event_date, -- GL Date of the Transaction
3185 
3182                                   l_fund_category,
3183                                   l_fund_expired_status,
3184                                   l_fund_time_frame);
3186                 /* Assign the fund infomation to a record */
3187                 l_fv_extract_rec.event_id            := l_ar_inv_extract_details.event_id ;
3188                 l_fv_extract_rec.line_number         := l_ar_inv_extract_details.line_number ;
3189                 l_fv_extract_rec.fund_value          := l_fund_value ;
3190                 l_fv_extract_rec.fund_category       := l_fund_category ;
3191 
3192                 /* Get the Account Valid Flag for the transaction */
3193                 l_acct_valid := get_account_valid_status (l_ar_event_info,
3194                                                           l_fv_extract_rec);
3195 
3196                 IF (l_acct_valid) THEN
3197                     l_account_valid_flag := 'Y';
3198                 ELSE
3199                     l_account_valid_flag := 'N';
3200                 END IF;
3201 
3202                 -- ================================== FND_LOG ==================================
3203                 l_debug_info := 'Fund Category: ' || l_fund_category;
3204                 trace(C_STATE_LEVEL, l_procedure_name, l_debug_info );
3205                 l_debug_info := 'Account Valid Status: ' || l_account_valid_flag;
3206                 trace(C_STATE_LEVEL, l_procedure_name, l_debug_info );
3207                 -- ================================== FND_LOG ==================================
3208 
3209                 IF NOT(l_acct_valid) THEN
3210                     -- ================================== FND_LOG ==================================
3211                     l_debug_info := 'REV account line is not valid';
3212                     trace(C_STATE_LEVEL, l_procedure_name, l_debug_info );
3213                     -- ================================== FND_LOG ==================================
3214 
3215                     -- Reset the account Valid Flag to 'N'
3216                     l_account_valid_flag := 'N';
3217 
3218                     l_overall_acct_valid := FALSE;
3219 
3220                     -- ================================== FND_LOG ==================================
3221                     l_debug_info := 'FEDERAL ACCOUNING CRITERIA IS NOT SATISFIED HENCE NOT ACCOUNTED';
3222                     trace(C_STATE_LEVEL, l_procedure_name, l_debug_info );
3223                     -- ================================== FND_LOG ==================================
3224 
3225                     -- Exit out of the Loop because REV line is NOT valid
3226                     EXIT;
3227                 END IF;
3228 
3229                 /* Assign the values to fv extract pl/sql table */
3230                 l_fv_extract_detail(l_index).event_id            :=  l_ar_inv_extract_details.event_id;
3231                 l_fv_extract_detail(l_index).line_number         :=  l_ar_inv_extract_details.line_number;
3232                 l_fv_extract_detail(l_index).application_id      :=  p_application_id;
3233                 l_fv_extract_detail(l_index).fund_category       :=  l_fund_category;
3234                 l_fv_extract_detail(l_index).account_valid_flag  :=  l_account_valid_flag;
3235 
3236                 /* Increment the index */
3237                 l_index := l_index + 1;
3238 
3239             /* Check for Default Receivables Account Line */
3240             ELSIF (l_ar_inv_extract_details.TRX_LINE_DIST_ACCOUNT_CLASS = 'REC') THEN
3241                 -- ================================== FND_LOG ==================================
3242                 l_debug_info := 'Processing Invoice DEF REC LINE...';
3243                 trace(C_STATE_LEVEL, l_procedure_name, l_debug_info );
3244                 -- ================================== FND_LOG ==================================
3245 
3246                 /* We need to check the Invoice Header Default Receivables Account Natural Account Segment
3247                    then decide about the overall account valid flag for the distributions */
3248 
3249                 -- Get the Balancing Account Segment
3250                 OPEN cur_ar_inv_head_balseg_value (l_ar_event_info.event_id);
3251                 FETCH cur_ar_inv_head_balseg_value INTO l_head_fund_value;
3252                 -- ================================== FND_LOG ==================================
3253                 l_debug_info := 'Invoice Receivables Acct Fund Value: ' ||l_head_fund_value|| ' No of Rows: ' || cur_ar_inv_head_balseg_value%ROWCOUNT;
3254                 trace(C_STATE_LEVEL, l_procedure_name, l_debug_info );
3255                 -- ================================== FND_LOG ==================================
3256                 CLOSE cur_ar_inv_head_balseg_value;
3257 
3258                 -- Get the fund Category
3259                 OPEN cur_ar_get_fund_catg (l_ledger_info.ledger_id,l_head_fund_value);
3260                 FETCH cur_ar_get_fund_catg INTO l_head_fund_category;
3261                 -- ================================== FND_LOG ==================================
3262                 l_debug_info := 'Invoice Receivables Acct Fund Category Value: ' ||l_head_fund_category;
3263                 trace(C_STATE_LEVEL, l_procedure_name, l_debug_info );
3264                 -- ================================== FND_LOG ==================================
3265                 CLOSE cur_ar_get_fund_catg;
3266 
3267 
3268                 BEGIN
3269                     -- Get the Natural Account Segment of the Default Receivables Account
3270                     OPEN cur_ar_invhead_natseg_value (l_ar_event_info.event_id);
3271                     FETCH cur_ar_invhead_natseg_value INTO l_header_natseg_value;
3272                     -- ================================== FND_LOG ==================================
3276                     CLOSE cur_ar_invhead_natseg_value;
3273                     l_debug_info := 'Invoice Receivables Natural Account Segment Value: ' ||l_header_natseg_value;
3274                     trace(C_STATE_LEVEL, l_procedure_name, l_debug_info );
3275                     -- ================================== FND_LOG ==================================
3277 
3278                     -- ================================== FND_LOG ==================================
3279                     l_debug_info := 'Validated the Invoice Receivables Natural Account Segment';
3280                     trace(C_STATE_LEVEL, l_procedure_name, l_debug_info );
3281                     -- ================================== FND_LOG ==================================
3282 
3283                     IF (l_header_natseg_value BETWEEN 131000 AND 131099) THEN
3284                         l_acct_head_valid := TRUE;
3285                         l_receivable_with_advance := 'N';
3286                     ELSIF (l_header_natseg_value BETWEEN 231000 AND 231099) THEN
3287                         l_acct_head_valid := TRUE;
3288                         l_receivable_with_advance := 'Y';
3289                     ELSE
3290                         l_acct_head_valid := FALSE;
3291                         l_receivable_with_advance := 'N';
3292                     END IF;
3293                 EXCEPTION
3294                     WHEN OTHERS THEN
3295                     IF cur_ar_invhead_natseg_value%ISOPEN THEN
3296                         CLOSE cur_ar_invhead_natseg_value;
3297                     END IF;
3298                     -- ================================== FND_LOG ==================================
3299                     l_debug_info := 'SQL Error encountered' || SQLERRM;
3300                     trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
3301                     -- ================================== FND_LOG ==================================
3302                     l_acct_head_valid := FALSE;
3303                 END;
3304 
3305                 IF (l_acct_head_valid) THEN
3306                     -- ================================== FND_LOG ==================================
3307                     l_debug_info := 'Invoice Def Receivables Acct Line Valid: Y';
3308                     trace(C_STATE_LEVEL, l_procedure_name, l_debug_info );
3309                     -- ================================== FND_LOG ==================================
3310                 ELSE
3311                     -- ================================== FND_LOG ==================================
3312                     l_debug_info := 'Invoice Def Receivables Acct Line Valid: N';
3313                     trace(C_STATE_LEVEL, l_procedure_name, l_debug_info );
3314                     -- ================================== FND_LOG ==================================
3315                     l_overall_acct_valid := FALSE;
3316 
3317                     -- ================================== FND_LOG ==================================
3318                     l_debug_info := 'FEDERAL ACCOUNING CRITERIA IS NOT SATISFIED HENCE NOT ACCOUNTED';
3319                     trace(C_STATE_LEVEL, l_procedure_name, l_debug_info );
3320                     -- ================================== FND_LOG ==================================
3321 
3322                     -- Exit out of the loop if Receivables Account is not Valid.
3323                     EXIT;
3324                 END IF;
3325             END IF;
3326         END LOOP;
3327         IF (l_acct_head_valid) THEN
3328            IF l_fv_extract_detail.COUNT> 0 THEN
3329                FOR l_index  IN l_fv_extract_detail.first..l_fv_extract_detail.last
3330                LOOP
3331                    l_fv_extract_detail(l_index).receivable_with_advance := l_receivable_with_advance;
3332                END LOOP;
3333            END IF;
3334         END IF;
3335 
3336 
3337 
3338     /*==============================================================================*
3339      |                                                                              |
3340      |  Cash Receipt Extract Processing                                             |
3341      |  -------------------------------                                             |
3342      |  1. We validate the REC line of the Cash Receipt that is Invoice Receivables |
3343      |     Line, that we get when we do application to an invoice.                  |
3344      |  2. We validate Receipt application to Invoice Revenue accounts.             |
3345      |  3. For Some Receipts we validate the Cash Line of the Receipt               |
3346      |  4. We populate account_rule column of the extract to indicate               |
3347      |     what kind of Receipt are we processing and later it's used in SLA JLT    |
3348      |     conditions. Following values are populated in account_rule:              |
3349      |     a) 'Order No Advance' signifying Reimbursable Order without Advance.     |
3350      |     b) 'Advance Refund' signifying Refund of Advances or Prepayments         |
3351      |     c) 'Overpayment Refund' signifying Refund of Overpayments.               |
3352      |  5. If any of validation fails, then we disallow the federal accounting      |
3353      |     lines to get created and allow core AR/MFAR accounting lines to get      |
3354      |     through.                                                                 |
3355      |                                                                              |
3356      *==============================================================================*/
3357 
3358 
3359     ELSIF (l_ar_event_type IN ('RECP_CREATE', 'RECP_UPDATE', 'RECP_REVERSE')) THEN
3360         -- ================================== FND_LOG ==================================
3361         l_debug_info := 'Inside Cash Receipt Event type';
3362         trace(C_STATE_LEVEL, l_procedure_name, l_debug_info );
3363         -- ================================== FND_LOG ==================================
3364 
3365         /* Initialize index */
3366         l_index := 0;
3367         -- ================================== FND_LOG ==================================
3368         l_debug_info := 'Processing Cash Receipt REC Line...';
3369         trace(C_STATE_LEVEL, l_procedure_name, l_debug_info );
3370         -- ================================== FND_LOG ==================================
3371         /* Get Receipt REC Line */
3372         OPEN cur_ar_rct_extract_details('REC');
3373         LOOP
3374             FETCH cur_ar_rct_extract_details INTO l_ar_rct_extract_details;
3375             IF (cur_ar_rct_extract_details%ROWCOUNT = 0) THEN
3376                 -- ================================== FND_LOG ==================================
3377                 l_debug_info := 'This Receipt is not applied to any Invoice. Exiting...';
3378                 trace(C_STATE_LEVEL, l_procedure_name, l_debug_info );
3379                 -- ================================== FND_LOG ==================================
3380                 RETURN;
3381             END IF;
3382             EXIT WHEN cur_ar_rct_extract_details%NOTFOUND;
3383 
3384             /* Assign the values to fv extract pl/sql table */
3385             l_fv_extract_detail(l_index).event_id       := l_ar_rct_extract_details.event_id;
3386             l_fv_extract_detail(l_index).line_number    := l_ar_rct_extract_details.line_number;
3387             l_fv_extract_detail(l_index).application_id := p_application_id;
3388 
3389             /* Get the Fund Value */
3390             OPEN cur_app_to_trx_balseg_val (l_ar_rct_extract_details.event_id
3391                                             ,l_ar_rct_extract_details.line_number
3392                                            );
3393             FETCH cur_app_to_trx_balseg_val INTO l_fund_value;
3394             -- ================================== FND_LOG ==================================
3395             l_debug_info := 'Fund Value : ' || l_fund_value ;
3396             trace(C_STATE_LEVEL, l_procedure_name, l_debug_info );
3397             -- ================================== FND_LOG ==================================
3398             CLOSE cur_app_to_trx_balseg_val;
3399 
3400             l_fv_extract_detail(l_index).fund_value := l_fund_value;
3401 
3402             /* Get the Fund Information */
3403             get_fund_details (p_application_id,
3404                               l_ledger_info.ledger_id,
3405                               l_fund_value,
3406                               l_ar_event_info.event_date, -- GL Date of the Transaction
3407                               l_fund_category,
3408                               l_fund_expired_status,
3409                               l_fund_time_frame);
3410 
3411             l_fv_extract_detail(l_index).fund_category       := l_fund_category;
3412             l_fv_extract_detail(l_index).fund_expired_status := l_fund_expired_status;
3413             l_fv_extract_detail(l_index).fund_time_frame     := l_fund_time_frame;
3414 
3415             -- ================================== FND_LOG ==================================
3416             l_debug_info := 'Fund Category: ' || l_fund_category;
3417             trace(C_STATE_LEVEL, l_procedure_name, l_debug_info );
3418             l_debug_info := 'Fund Expired Status: ' || l_fund_expired_status;
3419             trace(C_STATE_LEVEL, l_procedure_name, l_debug_info );
3420             l_debug_info := 'Fund Time Frame: ' || l_fund_time_frame;
3421             trace(C_STATE_LEVEL, l_procedure_name, l_debug_info );
3422             -- ================================== FND_LOG ==================================
3423 
3424             /* Get the Prior Year Status */
3425             l_pya := get_prior_year_status (p_application_id,
3426                                             l_ledger_info.ledger_id,
3427                           	            l_ledger_info.coa_id,
3428                                             l_ar_rct_extract_details.trx_line_dist_ccid,
3429                                             l_ar_event_info.event_date);
3430 
3431             IF (l_pya) THEN
3432                 l_fv_extract_detail(l_index).prior_year_flag := 'Y';
3433             ELSE
3434                 l_fv_extract_detail(l_index).prior_year_flag := 'N';
3435             END IF;
3436 
3437             -- ================================== FND_LOG ==================================
3438             l_debug_info := 'Prior year Flag: ' || l_fv_extract_detail(l_index).prior_year_flag;
3439             trace(C_STATE_LEVEL, l_procedure_name, l_debug_info );
3440             -- ================================== FND_LOG ==================================
3441 
3442             /* Assign the fund infomation to a record */
3443             l_fv_extract_rec.event_id            := l_fv_extract_detail(l_index).event_id;
3444             l_fv_extract_rec.line_number         := l_fv_extract_detail(l_index).line_number;
3445             l_fv_extract_rec.fund_value          := l_fv_extract_detail(l_index).fund_value;
3446             l_fv_extract_rec.fund_category       := l_fv_extract_detail(l_index).fund_category;
3447             l_fv_extract_rec.fund_expired_status := l_fv_extract_detail(l_index).fund_expired_status;
3448             l_fv_extract_rec.fund_time_frame     := l_fv_extract_detail(l_index).fund_time_frame;
3449             l_fv_extract_rec.prior_year_flag     := l_fv_extract_detail(l_index).prior_year_flag;
3450 
3451             /* Get the Account Valid Flag for the Cash Receipt */
3452             l_acct_valid := get_account_valid_status (l_ar_event_info,
3453                                                       l_fv_extract_rec);
3454 
3455             /* Assign the account rule information to pl/sql table */
3456             l_fv_extract_detail(l_index).account_rule := l_fv_extract_rec.account_rule;
3457             l_fv_extract_detail(l_index).receivable_with_advance := l_fv_extract_rec.receivable_with_advance;
3458             l_account_rule := l_fv_extract_rec.account_rule;
3459 
3460             IF (l_acct_valid) THEN
3461                 l_fv_extract_detail(l_index).account_valid_flag := 'Y';
3462                 l_acct_head_valid := TRUE;
3463             ELSE
3464                 l_fv_extract_detail(l_index).account_valid_flag := 'N';
3465                 l_overall_acct_valid := FALSE;
3466                 l_acct_head_valid := FALSE;
3467                 -- Exit out the loop;
3468                 EXIT;
3469             END IF;
3470 
3471             -- ================================== FND_LOG ==================================
3472             l_debug_info := 'Account Valid Status: ' ||l_fv_extract_detail(l_index).account_valid_flag;
3473             trace(C_STATE_LEVEL, l_procedure_name, l_debug_info );
3474             -- ================================== FND_LOG ==================================
3475 
3476             /* Increment the index */
3477             l_index := l_index + 1;
3478 
3479         END LOOP;
3480 
3481         CLOSE cur_ar_rct_extract_details;
3482 
3483         /* Now First check for Refunds of Advances or Prepayments */
3484         IF ((l_acct_head_valid) AND (l_account_rule = 'Advance Refund')) THEN
3485             -- Get Receipt CASH Line */
3486             OPEN cur_ar_rct_extract_details('CASH');
3487             FETCH cur_ar_rct_extract_details INTO l_ar_rct_extract_details;
3488             CLOSE cur_ar_rct_extract_details;
3489             BEGIN
3490                 OPEN cur_get_natacct(l_ar_rct_extract_details.dist_code_combination_id);
3491                 FETCH cur_get_natacct INTO l_natseg_value;
3492                 -- ================================== FND_LOG ==================================
3493                 l_debug_info := 'CASH Line natural account: ' || l_natseg_value;
3494                 trace(C_STATE_LEVEL, l_procedure_name, l_debug_info );
3495                 -- ================================== FND_LOG ==================================
3496                 CLOSE cur_get_natacct;
3497                 -- Check the Natural Account Segment of the line
3498                 IF (l_natseg_value BETWEEN 101001 AND 101099) THEN
3502                     -- ================================== FND_LOG ==================================
3499                     /* Now we are sure that this particular receipt is for the 'Refunds of Advances or Prepayment'.
3500                        So directly jump to the condition that insert the records to fv_extract_detail_gt table */
3501                     l_overall_acct_valid := TRUE;
3503                     l_debug_info := 'CASH line validated: Y' || ' for Refund of Advance or Prepayment';
3504                     trace(C_STATE_LEVEL, l_procedure_name, l_debug_info );
3505                     -- ================================== FND_LOG ==================================
3506                     GOTO insert_row;
3507                 ELSE
3508                     l_overall_acct_valid := FALSE;
3509                 END IF;
3510             EXCEPTION
3511             WHEN OTHERS THEN
3512                 IF cur_get_natacct%ISOPEN THEN
3513                     CLOSE cur_get_natacct;
3514                 END IF;
3515                 l_debug_info := 'SQL Error encountered';
3516                 trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
3517                 l_overall_acct_valid := FALSE;
3518             END;
3519         END IF;
3520 
3521         /* Above check failed for Receipt for the Refunds of Advances or Prepayments case
3522            Now we need to proceed and check whether the Receipt is for :
3523            1) Refunds of Overpayments OR
3524            2) Reimbursable Order without Advance */
3525 
3526         -- Now check for the Receipt Applied to Invoice Revenue Accounts */
3527         IF (l_acct_head_valid) THEN
3528             FOR x_code_combination_id IN cur_rct_app_trx_rev_natacct
3529             LOOP
3530                 BEGIN
3531                     /* Get the Natural Account Segment for Transaction Line */
3532                     OPEN cur_get_natacct(x_code_combination_id.trx_line_dist_ccid);
3533                     FETCH cur_get_natacct INTO l_natseg_value;
3534                     -- ================================== FND_LOG ==================================
3535                     l_debug_info := 'Receipt Applied to Invoice Revenue Line natural account: ' || l_natseg_value;
3536                     trace(C_STATE_LEVEL, l_procedure_name, l_debug_info );
3537                     -- ================================== FND_LOG ==================================
3538                     CLOSE cur_get_natacct;
3539                     IF ((l_natseg_value BETWEEN 510000 AND 510099) OR (l_natseg_value BETWEEN 520001 AND 520099))
3540                        AND NOT(l_trx_type_over) THEN
3541                         -- Invoice Revenue Account matched for Reimbursable Order without Advance
3542                         l_trx_type_reim := TRUE;
3543                         l_trx_type_over := FALSE;
3544                     ELSIF (
3545                         (l_natseg_value BETWEEN 141001 AND 141299) OR (l_natseg_value BETWEEN 142200 AND 142299) OR
3546                         (l_natseg_value BETWEEN 151100 AND 151299) OR (l_natseg_value BETWEEN 152200 AND 152299) OR
3547                         (l_natseg_value BETWEEN 152500 AND 152799) OR (l_natseg_value BETWEEN 156100 AND 156199) OR
3548                         (l_natseg_value BETWEEN 157100 AND 157299) OR (l_natseg_value BETWEEN 159100 AND 159199) OR
3549                         (l_natseg_value BETWEEN 159100 AND 159199) OR (l_natseg_value BETWEEN 171100 AND 171299) OR
3550                         (l_natseg_value BETWEEN 172000 AND 172099) OR (l_natseg_value BETWEEN 173000 AND 173099) OR
3551                         (l_natseg_value BETWEEN 174000 AND 174099) OR (l_natseg_value BETWEEN 175000 AND 175099) OR
3552                         (l_natseg_value BETWEEN 181000 AND 181099) OR (l_natseg_value BETWEEN 182000 AND 182099) OR
3553                         (l_natseg_value BETWEEN 183000 AND 183099) OR (l_natseg_value BETWEEN 183200 AND 183299) OR
3554                         (l_natseg_value BETWEEN 184000 AND 184099) OR (l_natseg_value BETWEEN 189000 AND 189099) OR
3555                         (l_natseg_value BETWEEN 199000 AND 199099) OR (l_natseg_value BETWEEN 610000 AND 610099) OR
3556                         (l_natseg_value BETWEEN 650000 AND 650099) OR (l_natseg_value BETWEEN 690000 AND 690099))
3557                          AND NOT(l_trx_type_reim)THEN
3558                         -- Invoice Revenue Account matched for Refunds of Overpayments
3559                         l_trx_type_over := TRUE;
3560                         l_trx_type_reim := FALSE;
3561                     ELSE
3562                         l_overall_acct_valid := FALSE;
3563                         l_trx_type_reim := FALSE;
3564                         l_trx_type_over := FALSE;
3565                         /* Exit out of loop as REV line failed the validation */
3566                         EXIT;
3567                     END IF;
3568                 EXCEPTION
3569                     WHEN OTHERS THEN
3570                         IF cur_get_natacct%ISOPEN THEN
3571                              CLOSE cur_get_natacct;
3572                         END IF;
3573                         l_debug_info := 'SQL Error encountered' ||SQLERRM ;
3574                         trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
3575                         l_overall_acct_valid := FALSE;
3576                         l_trx_type_reim := FALSE;
3577                         l_trx_type_over := FALSE;
3578                         -- Exit Loop
3579                         EXIT;
3580                 END;
3581             END LOOP;
3582         END IF;
3583 
3584         /* We are now changing the account_rule of the Receipt if it's a 'Reimbursable Order without Advances'
3585            Otherwise we are not changing if matches the 'Refunds of Overpayments'.
3586            if no criteria matches we are clearing out the account_rule  */
3587 
3588         IF ((l_acct_head_valid = TRUE) AND (l_overall_acct_valid = TRUE) AND (l_trx_type_reim = TRUE)) THEN
3592            -- ================================== FND_LOG ==================================
3589            -- ================================== FND_LOG ==================================
3590            l_debug_info := 'Receipt Validated for Reimbursable Order without Advance';
3591            trace(C_STATE_LEVEL, l_procedure_name, l_debug_info );
3593            IF l_fv_extract_detail.COUNT> 0 THEN
3594                FOR l_index  IN l_fv_extract_detail.first..l_fv_extract_detail.last
3595                LOOP
3596                    l_fv_extract_detail(l_index).account_rule := 'Order No Advance';
3597                END LOOP;
3598            END IF;
3599         ELSIF ((l_acct_head_valid = TRUE) AND (l_overall_acct_valid = TRUE) AND (l_trx_type_over = TRUE)) THEN
3600            -- ================================== FND_LOG ==================================
3601            l_debug_info := 'Receipt Validated for Refund of Overpayments';
3602            trace(C_STATE_LEVEL, l_procedure_name, l_debug_info );
3603            -- ================================== FND_LOG ==================================
3604             NULL;
3605         -- The Invoice Revenue line is neither a 'Reimbursable Order without Advance' or 'Refunds of Overpayments'
3606         ELSE
3607             IF l_fv_extract_detail.COUNT > 0 THEN
3608                 FOR l_index  IN l_fv_extract_detail.first..l_fv_extract_detail.last
3609                 LOOP
3610                     l_fv_extract_detail(l_index).account_rule := 'DEFAULT';
3611                     l_fv_extract_detail(l_index).account_valid_flag := 'N';
3612                 END LOOP;
3613             END IF;
3614             -- ================================== FND_LOG ==================================
3615             l_debug_info := 'FEDERAL ACCOUNING CRITERIA IS NOT SATISFIED HENCE NOT ACCOUNTED';
3616             trace(C_STATE_LEVEL, l_procedure_name, l_debug_info );
3617             -- ================================== FND_LOG ==================================
3618         END IF;
3619 
3620 
3621 
3622 
3623     /*==============================================================================*
3624      |                                                                              |
3625      |  Miscellaneous Receipt Extract Processing                                    |
3626      |  ----------------------------------------                                    |
3627      |  1. We validate the Natural Account Segment of CASH line of the              |
3628      |     Misc Cash Receipt.                                                       |
3629      |  2. We validate the MISCCASH distribution lines for all federal parameters.  |
3630      |  3. If any of the above validation fails, then we disallow the federal       |
3631      |     accounting lines to get created and allow core AR/MFAR accounting lines  |
3632      |     to get through.                                                          |
3633      |                                                                              |
3634      *==============================================================================*/
3635 
3636 
3637     ELSIF (l_ar_event_type IN ('MISC_RECP_CREATE', 'MISC_RECP_UPDATE', 'MISC_RECP_REVERSE')) THEN
3638 
3639         -- ================================== FND_LOG ==================================
3640         l_debug_info := 'Inside Miscellaneous Receipt Event type';
3641         trace(C_STATE_LEVEL, l_procedure_name, l_debug_info );
3642         -- ================================== FND_LOG ==================================
3643 
3644         /* Initialize index */
3645         l_index := 0;
3646 
3647         /* Get Receipt and Miscellaneous Receipt Data */
3648         FOR x_misc_rct_extract_details IN cur_misc_rct_extract_details
3649         LOOP
3650 
3651             IF (x_misc_rct_extract_details.DIST_SOURCE_TYPE = 'CASH') THEN
3652                 -- ================================== FND_LOG ==================================
3653                 l_debug_info := 'Processing Miscellaneous Distribution Type: '
3654                 || x_misc_rct_extract_details.DIST_SOURCE_TYPE ;
3655                 trace(C_STATE_LEVEL, l_procedure_name, l_debug_info );
3656                 -- ================================== FND_LOG ==================================
3657                 -- We need to validate the Natural Account Segment of CASH account of Miscellaneous Receipt
3658                 -- to be between 101000 and 101099
3659                 BEGIN
3660                     -- Get the Natural Account Segment of the Default Cash Account
3661                     OPEN cur_get_natacct(x_misc_rct_extract_details.dist_code_combination_id);
3662                     FETCH cur_get_natacct INTO l_natseg_value;
3663                     -- ================================== FND_LOG ==================================
3664                     l_debug_info := 'CASH Line natural account: ' || l_natseg_value;
3665                     trace(C_STATE_LEVEL, l_procedure_name, l_debug_info );
3666                     -- ================================== FND_LOG ==================================
3667                     CLOSE cur_get_natacct;
3668                     -- Check the Natural Account Segment of the line
3669                     IF (l_natseg_value BETWEEN 101001 AND 101099) THEN
3670                         -- ================================== FND_LOG ==================================
3671                         l_debug_info := 'Validated the Miscellaneous Receipt CASH Natural Account Segment';
3672                         trace(C_STATE_LEVEL, l_procedure_name, l_debug_info );
3673                         -- ================================== FND_LOG ==================================
3674                         l_acct_head_valid := TRUE;
3675                     ELSE
3676                         l_acct_head_valid := FALSE;
3677                     END IF;
3678                 EXCEPTION
3679                     WHEN OTHERS THEN
3683                     -- ================================== FND_LOG ==================================
3680                     IF cur_get_natacct%ISOPEN THEN
3681                         CLOSE cur_get_natacct;
3682                     END IF;
3684                     l_debug_info := 'SQL Error encountered' || SQLERRM;
3685                     trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
3686                     -- ================================== FND_LOG ==================================
3687                     l_acct_head_valid := FALSE;
3688                 END;
3689                 IF (l_acct_head_valid) THEN
3690                     -- ================================== FND_LOG ==================================
3691                     l_debug_info := 'Misc Receipt Def CASH Acct Line Valid: Y' ;
3692                     trace(C_STATE_LEVEL, l_procedure_name, l_debug_info );
3693                     -- ================================== FND_LOG ==================================
3694                 ELSE
3695                     -- ================================== FND_LOG ==================================
3696                     l_debug_info := 'Misc Receipt Def CASH Acct Line Valid: N' ;
3697                     trace(C_STATE_LEVEL, l_procedure_name, l_debug_info );
3698                     -- ================================== FND_LOG ==================================
3699                     l_overall_acct_valid := FALSE;
3700                     -- ================================== FND_LOG ==================================
3701                     l_debug_info := 'FEDERAL ACCOUNING CRITERIA IS NOT SATISFIED HENCE NOT ACCOUNTED';
3702                     trace(C_STATE_LEVEL, l_procedure_name, l_debug_info );
3703                     -- ================================== FND_LOG ==================================
3704 
3705                     -- Exit out of the loop if Misc Receipt CASH Account is not Valid.
3706                     EXIT;
3707                 END IF;
3708 
3709             ELSIF (x_misc_rct_extract_details.DIST_SOURCE_TYPE = 'MISCCASH') THEN
3710                 -- ================================== FND_LOG ==================================
3711                 l_debug_info := 'Processing Miscellaneous Distribution Type: '
3712                 || x_misc_rct_extract_details.DIST_SOURCE_TYPE ;
3713                 trace(C_STATE_LEVEL, l_procedure_name, l_debug_info );
3714                 -- ================================== FND_LOG ==================================
3715 
3716                 /* Assign the values to fv extract pl/sql table */
3717                 l_fv_extract_detail(l_index).event_id       := x_misc_rct_extract_details.event_id;
3718                 l_fv_extract_detail(l_index).line_number    := x_misc_rct_extract_details.line_number;
3719                 l_fv_extract_detail(l_index).application_id := p_application_id;
3720 
3721                 /* Get the Fund Value */
3722                 OPEN cur_ar_rct_balseg_value (x_misc_rct_extract_details.event_id
3723                                              ,x_misc_rct_extract_details.line_number
3724                                              );
3725                 FETCH cur_ar_rct_balseg_value INTO l_fund_value;
3726                 -- ================================== FND_LOG ==================================
3727                 l_debug_info := 'Fund Value : ' || l_fund_value ;
3728                 trace(C_STATE_LEVEL, l_procedure_name, l_debug_info );
3729                 -- ================================== FND_LOG ==================================
3730                 CLOSE cur_ar_rct_balseg_value;
3731 
3732                 l_fv_extract_detail(l_index).fund_value := l_fund_value;
3733 
3734                 /* Get the Fund Information */
3735                 get_fund_details (p_application_id,
3736                                   l_ledger_info.ledger_id,
3737                                   l_fund_value,
3738                                   l_ar_event_info.event_date, -- GL Date of the Transaction
3739                                   l_fund_category,
3740                                   l_fund_expired_status,
3741                                   l_fund_time_frame);
3742 
3743                 l_fv_extract_detail(l_index).fund_category       := l_fund_category;
3744                 l_fv_extract_detail(l_index).fund_expired_status := l_fund_expired_status;
3745                 l_fv_extract_detail(l_index).fund_time_frame     := l_fund_time_frame;
3746 
3747                 -- ================================== FND_LOG ==================================
3748                 l_debug_info := 'Fund Category: ' || l_fund_category;
3749                 trace(C_STATE_LEVEL, l_procedure_name, l_debug_info );
3750                 l_debug_info := 'Fund Expired Status: ' || l_fund_expired_status;
3751                 trace(C_STATE_LEVEL, l_procedure_name, l_debug_info );
3752                 l_debug_info := 'Fund Time Frame: ' || l_fund_time_frame;
3753                 trace(C_STATE_LEVEL, l_procedure_name, l_debug_info );
3754                 -- ================================== FND_LOG ==================================
3755 
3756                 -- Calculate only for non- Reimbursable Order Misc Receipts
3757                 IF (l_fund_category NOT IN ('R', 'S', 'T')) THEN
3758                     /* Get the Prior Year Status */
3759                     l_pya := get_prior_year_status (p_application_id,
3760                                                     l_ledger_info.ledger_id,
3761                                                     l_ledger_info.coa_id,
3762                                                     x_misc_rct_extract_details.dist_code_combination_id,
3763                                                     l_ar_event_info.event_date);
3764 
3765                     IF (l_pya) THEN
3766                         l_fv_extract_detail(l_index).prior_year_flag := 'Y';
3767                     ELSE
3771                     -- ================================== FND_LOG ==================================
3768                         l_fv_extract_detail(l_index).prior_year_flag := 'N';
3769                     END IF;
3770 
3772                     l_debug_info := 'Prior year Flag: ' ||l_fv_extract_detail(l_index).prior_year_flag;
3773                     trace(C_STATE_LEVEL, l_procedure_name, l_debug_info );
3774                     -- ================================== FND_LOG ==================================
3775 
3776                 END IF;
3777 
3778                 /* Assign the fund infomation to a record */
3779                 l_fv_extract_rec.event_id            := l_fv_extract_detail(l_index).event_id;
3780                 l_fv_extract_rec.line_number         := l_fv_extract_detail(l_index).line_number;
3781                 l_fv_extract_rec.fund_value          := l_fv_extract_detail(l_index).fund_value;
3782                 l_fv_extract_rec.fund_category       := l_fv_extract_detail(l_index).fund_category;
3783                 l_fv_extract_rec.fund_expired_status := l_fv_extract_detail(l_index).fund_expired_status;
3784                 l_fv_extract_rec.fund_time_frame     := l_fv_extract_detail(l_index).fund_time_frame;
3785                 l_fv_extract_rec.prior_year_flag     := l_fv_extract_detail(l_index).prior_year_flag;
3786 
3787                 /* Get the Account Valid Flag for the Miscellaneous Receipt */
3788                 l_acct_valid := get_account_valid_status (l_ar_event_info,
3789                                                           l_fv_extract_rec);
3790 
3791                 IF (l_acct_valid) THEN
3792                     l_fv_extract_detail(l_index).account_valid_flag := 'Y';
3793                 ELSE
3794                     -- ================================== FND_LOG ==================================
3795                     l_debug_info := 'Misc Receipt Account Validation failed for Distribution Line: '
3796                     || x_misc_rct_extract_details.DIST_SOURCE_TYPE;
3797                     trace(C_STATE_LEVEL, l_procedure_name, l_debug_info );
3798                     -- ================================== FND_LOG ==================================
3799 
3800                     l_fv_extract_detail(l_index).account_valid_flag := 'N';
3801                     l_overall_acct_valid := FALSE;
3802 
3803                     -- ================================== FND_LOG ==================================
3804                     l_debug_info := 'FEDERAL ACCOUNING CRITERIA IS NOT SATISFIED HENCE NOT ACCOUNTED';
3805                     trace(C_STATE_LEVEL, l_procedure_name, l_debug_info );
3806                     -- ================================== FND_LOG ==================================
3807 
3808                     -- Exit Out of the loop
3809                     EXIT;
3810                 END IF;
3811 
3812                 -- ================================== FND_LOG ==================================
3813                 l_debug_info := 'Account Valid Status: ' || l_fv_extract_detail(l_index).account_valid_flag;
3814                 trace(C_STATE_LEVEL, l_procedure_name, l_debug_info );
3815                 -- ================================== FND_LOG ==================================
3816 
3817                 /* Increment the index */
3818                 l_index := l_index + 1;
3819             END IF;
3820         END LOOP;
3821     END IF;
3822 
3823     <<insert_row>>
3824     IF l_fv_extract_detail.COUNT<> 0 THEN
3825 
3826         /* Set Overall Account Valid Flag */
3827         IF (l_overall_acct_valid = FALSE) THEN
3828             FOR l_index  IN l_fv_extract_detail.first..l_fv_extract_detail.last
3829             LOOP
3830                 l_fv_extract_detail(l_index).account_valid_flag := 'N';
3831             END LOOP;
3832         END IF;
3833         /* Insert data into FV_EXTRACT_DETAILS_GT table */
3834         FORALL  l_index  IN l_fv_extract_detail.first..l_fv_extract_detail.last
3835             INSERT INTO fv_extract_detail_gt VALUES l_fv_extract_detail(l_index);
3836             -- ================================== FND_LOG ==================================
3837             l_debug_info := 'No of rows inserted into FV_EXTRACT_DETAIL_GT: '|| SQL%ROWCOUNT;
3838             trace(C_STATE_LEVEL, l_procedure_name, l_debug_info );
3839             -- ================================== FND_LOG ==================================
3840     ELSIF l_fv_extract_detail.COUNT = 0 THEN
3841         -- ================================== FND_LOG ==================================
3842         l_debug_info := 'FEDERAL ACCOUNING CRITERIA IS NOT SATISFIED HENCE NOT ACCOUNTED';
3843         trace(C_STATE_LEVEL, l_procedure_name, l_debug_info );
3844         -- ================================== FND_LOG ==================================
3845     END IF;
3846     -- ================================== FND_LOG ==================================
3847      l_debug_info := 'End of procedure '||l_procedure_name;
3848      trace(C_PROC_LEVEL, l_procedure_name, l_debug_info);
3849     -- ================================== FND_LOG ==================================
3850 
3851 EXCEPTION
3852 
3853 WHEN OTHERS THEN
3854      -- ================================== FND_LOG ==================================
3855      l_debug_info := 'ERROR encountered in Federal AR SLA Processing: ' || SQLERRM;
3856      trace(C_STATE_LEVEL, l_procedure_name, l_debug_info);
3857      -- ================================== FND_LOG ==================================
3858      FND_MESSAGE.SET_NAME('FND', 'FND_GENERIC_MESSAGE');
3859      FND_MESSAGE.SET_TOKEN('MESSAGE' ,
3860          'Procedure :fv_sla_processing_pkg.ar_extract'|| CRLF||
3861          'Error     :'||SQLERRM);
3862      FND_MSG_PUB.ADD;
3863      APP_EXCEPTION.RAISE_EXCEPTION;
3864 
3865 END ar_extract;
3866 
3867 PROCEDURE preaccounting
3868 (
3869   p_application_id               IN            NUMBER,
3870   p_ledger_id                    IN            INTEGER,
3871   p_process_category             IN            VARCHAR2,
3872   p_end_date                     IN            DATE,
3873   p_accounting_mode              IN            VARCHAR2,
3874   p_valuation_method             IN            VARCHAR2,
3875   p_security_id_int_1            IN            INTEGER,
3876   p_security_id_int_2            IN            INTEGER,
3877   p_security_id_int_3            IN            INTEGER,
3878   p_security_id_char_1           IN            VARCHAR2,
3879   p_security_id_char_2           IN            VARCHAR2,
3880   p_security_id_char_3           IN            VARCHAR2,
3881   p_report_request_id            IN            INTEGER
3882 ) IS
3883 
3884 l_log_module         VARCHAR2(240);
3885 BEGIN
3886     NULL;
3887 END;
3888 
3889 PROCEDURE postprocessing
3890 (
3891   p_application_id               IN            NUMBER,
3892   p_accounting_mode              IN            VARCHAR2
3893 )
3894  IS
3895 
3896  l_log_module         VARCHAR2(240);
3897 
3898 BEGIN
3899     NULL;
3900 END;
3901 
3902 
3903 PROCEDURE postaccounting
3904 (
3905   p_application_id               IN            NUMBER,
3906   p_ledger_id                    IN            INTEGER,
3907   p_process_category             IN            VARCHAR2,
3908   p_end_date                     IN            DATE,
3909   p_accounting_mode              IN            VARCHAR2,
3910   p_valuation_method             IN            VARCHAR2,
3911   p_security_id_int_1            IN            INTEGER,
3912   p_security_id_int_2            IN            INTEGER,
3913   p_security_id_int_3            IN            INTEGER,
3914   p_security_id_char_1           IN            VARCHAR2,
3915   p_security_id_char_2           IN            VARCHAR2,
3916   p_security_id_char_3           IN            VARCHAR2,
3917   p_report_request_id            IN            INTEGER
3918 )
3919  IS
3920 l_log_module         VARCHAR2(240);
3921 
3922 BEGIN
3923     NULL;
3924 END;
3925 
3926 END fv_sla_processing_pkg;