DBA Data[Home] [Help]

PACKAGE BODY: APPS.GL_AUTOREVERSE_DATE_PKG

Source


1 PACKAGE BODY GL_AUTOREVERSE_DATE_PKG as
2 /* $Header: glustarb.pls 120.5 2005/05/05 01:43:45 kvora ship $ */
3 
4 -- private functions
5 PROCEDURE get_business_day( X_Date_Rule                 VARCHAR2,
6                             X_Trxn_Calendar_Id          NUMBER,
7                             X_Je_Source                 VARCHAR2,
8                             X_Reversal_Date    IN OUT NOCOPY   DATE) IS
9 
10   NORMAL_EXIT         EXCEPTION;
11 
12   eff_date_rule       VARCHAR2(1);
13   business_day_flag   VARCHAR2(1);
14 
15   CURSOR get_effective_date_rule IS
16       SELECT effective_date_rule_code
17       FROM   gl_je_sources
18       WHERE  je_source_name = X_Je_Source;
19 
20   CURSOR is_business_day IS
21       SELECT business_day_flag
22       FROM   gl_transaction_dates
23       WHERE  transaction_calendar_id = X_Trxn_Calendar_Id
24       AND    transaction_date = X_Reversal_Date;
25 
26   CURSOR roll_backward IS
27       SELECT max(transaction_date)
28       FROM   gl_transaction_dates
29       WHERE  transaction_calendar_id = X_Trxn_Calendar_Id
30       AND    business_day_flag = 'Y'
31       AND    transaction_date <= X_Reversal_Date;
32 
33   CURSOR roll_forward IS
34       SELECT min(transaction_date)
35       FROM   gl_transaction_dates
36       WHERE  transaction_calendar_id = X_Trxn_Calendar_Id
37       AND    business_day_flag = 'Y'
38       AND    transaction_date >= X_Reversal_Date;
39 
40 BEGIN
41 
42     IF (X_Je_Source = 'Manual') THEN
43     -- Manual source journals created by Enter Journals form
44     -- should always have the business day rolled
45        eff_date_rule := 'R';
46     ELSE
47        OPEN get_effective_date_rule;
48        FETCH get_effective_date_rule INTO eff_date_rule;
49 
50        IF (get_effective_date_rule%NOTFOUND) THEN
51          CLOSE get_effective_date_rule;
52          Error_Buffer := 'Cannot find effective date rule for this source '
53                    ||X_Je_Source;
54          Raise GET_REV_PERIOD_DATE_FAILED;
55        END IF;
56 
57        -- 1. Reversal date is valid when effective date rule is Leave Alone
58        IF eff_date_rule = 'L' THEN
59           Raise NORMAL_EXIT;
60        END IF;
61     END IF;
62 
63     OPEN is_business_day;
64     FETCH is_business_day INTO business_day_flag;
65 
66     IF (is_business_day%NOTFOUND) THEN
67       CLOSE is_business_day;
68       Error_Buffer := 'The reversal date '||X_Reversal_Date||
69                  ' is not in the transaction calendar.';
70       Raise GET_REV_PERIOD_DATE_FAILED;
71     END IF;
72 
73     -- 2. Exit normal if business day
74     IF (business_day_flag = 'Y') THEN
75       Raise NORMAL_EXIT;
76     END IF;
77 
78     -- 3. Error out non-business day when effective date rule is fail
79     IF (business_day_flag = 'N' AND eff_date_rule = 'F') THEN
80        Error_Buffer := 'The reversal date '||X_Reversal_Date||
81                   ' is not a business day.';
82        Raise GET_REV_PERIOD_DATE_FAILED;
83     END IF;
84 
85     -- 4. now the effective date can only be Roll Date
86     --    Roll to find a business day
87     IF X_Date_Rule = 'LAST_DAY' THEN
88        OPEN roll_backward;
89        FETCH roll_backward INTO X_Reversal_Date;
90 
91        IF (X_Reversal_Date IS NULL) THEN
92           CLOSE roll_backward;
93           Error_Buffer := 'Cannot find a business day by rolling backwards from '
94                      ||X_Reversal_Date;
95           Raise GET_REV_PERIOD_DATE_FAILED;
96        END IF;
97     ELSE
98        OPEN roll_forward;
99        FETCH roll_forward INTO X_Reversal_Date;
100 
101        IF (X_Reversal_Date IS NULL) THEN
102           CLOSE roll_forward;
103           Error_Buffer := 'Cannot find a business day by rolling forward from '
104                      ||X_Reversal_Date;
105           Raise GET_REV_PERIOD_DATE_FAILED;
106        END IF;
107     END IF;
108 
109 
110 EXCEPTION
111     WHEN NORMAL_EXIT THEN
112         null;
113     WHEN OTHERS THEN
114         Error_Buffer := 'get_business_day.'||Error_Buffer;
115         Raise;
116 END get_business_day;
117 
118 PROCEDURE get_reversal_date(X_Reversal_Period           VARCHAR2,
119                             X_Adj_Period_Flag           VARCHAR2,
120                             X_Period_Rule               VARCHAR2,
121                             X_Date_Rule                 VARCHAR2,
122                             X_Cons_Ledger               VARCHAR2,
123                             X_Trxn_Calendar_Id          NUMBER,
124                             X_Je_Source                 VARCHAR2,
125                             X_Je_Date                   DATE,
126                             X_Start_Date                DATE,
127                             X_End_Date                  DATE,
128                             X_Reversal_Date    IN OUT NOCOPY   DATE) IS
129   NORMAL_EXIT      EXCEPTION;
130   WRONG_CRITERIA   EXCEPTION;
131   reversal_date    DATE;
132 BEGIN
133       ------    ADB Consolidation Ledger  -----------
134       -- When the reversal period rule is same period, use the journal's
135       -- date as the reversal date. For an average journal, this should
136       -- be the 1st day of the month. When the reversal period rule
137       -- is NEXT_(ADJ_)PERIOD, use the 1st day of the reversal period.
138 
139       IF X_Cons_Ledger = 'Y' THEN
140          IF X_Period_Rule = 'SAME_PERIOD' THEN
141             reversal_date := X_Je_Date;
142          ELSE
143             reversal_date := X_Start_Date;
144          END IF;
145          Raise NORMAL_EXIT;
146       END IF;
147 
148       ------    ADB Non-Consolidation Ledger ----------
149       -- 1. get reversal date from date_rule
150 
151       IF X_Period_Rule = 'SAME_PERIOD' THEN
152 
153          IF X_Date_Rule = 'NEXT_DAY' THEN
154             reversal_date := X_Je_Date + 1;
155             IF reversal_date > X_End_Date THEN
156                Error_Buffer := 'Cannot find a valid reversal date; '
157                              ||'The next day '||reversal_date
158                              ||' is outside the reversal period '
159                              ||X_Reversal_Period||'.';
160 
161                Raise GET_REV_PERIOD_DATE_FAILED;
162             END IF;
163          ELSIF X_Date_Rule = 'LAST_DAY' THEN
164             reversal_date := X_End_Date;
165          ELSE
166             Raise WRONG_CRITERIA;
167          END IF;
168       ELSE -- next (non-adj) period
169          IF X_Date_Rule = 'FIRST_DAY' THEN
170             reversal_date := X_Start_Date;
171          ELSIF X_Date_Rule = 'LAST_DAY' THEN
172             reversal_date := X_End_Date;
173          ELSE
174             Raise WRONG_CRITERIA;
175          END IF;
176       END IF;
177       -- 2. No effective date check for Adjusting Period
178       -- IF X_Adj_Period_Flag = 'Y' THEN
179       --   Raise NORMAL_EXIT;
180       -- END IF;
181 
182       -- 3. Check if reversal date is business day. If not, find one.
183       get_business_day(X_Date_Rule, X_Trxn_Calendar_Id, X_Je_Source,
184                        reversal_date);
185       -- 4. Check if reversal date is still in the reversal period.
186       IF (reversal_date < X_Start_Date OR reversal_date > X_End_Date) THEN
187          Error_Buffer := 'Cannot find a businness day within the reversal period '||X_Reversal_Period||' as reversal date.';
188          Raise GET_REV_PERIOD_DATE_FAILED;
189       END IF;
190       IF ( reversal_date < X_Je_Date) THEN
191          Error_Buffer := 'Cannot find a valid reversal date because the first valid day is before the journal date.';
192          Raise GET_REV_PERIOD_DATE_FAILED;
193       END IF;
194 
195       X_Reversal_Date := reversal_date;
196 
197 EXCEPTION
198     WHEN NORMAL_EXIT THEN
199         X_Reversal_Date := reversal_date;
200     WHEN WRONG_CRITERIA THEN
201         Error_Buffer := 'Invalid REVERSAL_DATE_CODE, '||X_Date_Rule||', in GL_AUTOREVERSE_OPTIONS.';
202         Raise GET_REV_PERIOD_DATE_FAILED;
203     WHEN OTHERS THEN
204         Error_Buffer := '.get_reversal_date.'||Error_Buffer;
205         Raise;
206 END get_reversal_date;
207 
208      -- Public Procedure
209 
210 PROCEDURE get_reversal_period_date(X_Ledger_Id    	      NUMBER,
211                                    X_Je_Category              VARCHAR2,
212                                    X_Je_Source                VARCHAR2,
213                                    X_Je_Period_Name           VARCHAR2,
214                                    X_Je_Date                  DATE,
215                                    X_Reversal_Method  IN OUT NOCOPY  VARCHAR2,
216                                    X_Reversal_Period  IN OUT NOCOPY  VARCHAR2,
217                                    X_Reversal_Date    IN OUT NOCOPY  DATE) IS
218     adb_lgr           VARCHAR2(1);
219     cons_lgr          VARCHAR2(1);
220     trxn_calendar_id  VARCHAR2(15);
221     method_code       VARCHAR2(1);
222     period_rule       VARCHAR2(30);
223     date_rule         VARCHAR2(30);
224     reversal_period   VARCHAR2(15);
225     adj_period_flag   VARCHAR2(1);
226     pstatus           VARCHAR2(1);
227     period_set        VARCHAR2(15);
228     v_period_type        VARCHAR2(15);
229     reversal_date     DATE;
230     start_date        DATE;
231     end_date          DATE;
232     l_criteria_set_id NUMBER :=0;
233 
234     CURSOR get_lgr IS
235     SELECT enable_average_balances_flag,
236            consolidation_ledger_flag,
237            transaction_calendar_id,
238            period_set_name,
239            accounted_period_type,
240 	   criteria_set_id
241     FROM   gl_ledgers
242     WHERE  ledger_id = X_Ledger_Id;
243 
244     CURSOR get_criteria IS
245     SELECT decode(method_code,'C','Y','N'),
246            reversal_period_code,reversal_date_code
247     FROM   gl_autoreverse_options
248     WHERE  criteria_set_id = l_Criteria_Set_Id
249     AND    je_category_name = X_Je_Category;
250 
251 
252     CURSOR same_period IS
253     SELECT period_name,closing_status,start_date,end_date,
254            adjustment_period_flag
255     FROM   gl_period_statuses p
256     WHERE  p.application_id = 101
257     AND    p.ledger_id = X_Ledger_Id
258     AND    p.period_name = X_Je_Period_Name;
259 
260     CURSOR next_period IS
261     SELECT period_name, closing_status, start_date, end_date,
262            adjustment_period_flag
263     FROM   gl_period_statuses p1
264     WHERE  p1.application_id = 101
265     AND    p1.ledger_id = X_Ledger_Id
266     AND    p1.effective_period_num =
267      ( SELECT min(effective_period_num)
268        FROM   gl_period_statuses p1
269        WHERE  p1.application_id = 101
270        AND    p1.ledger_id = X_Ledger_Id
271        AND    p1.effective_period_num >
272           ( SELECT effective_period_num
273             FROM gl_period_statuses p2
274             WHERE p2.application_id = 101
275             AND   p2.ledger_id = X_Ledger_Id
276             AND   p2.period_name = X_Je_Period_Name));
277 
278     CURSOR next_nonadj_period IS
279     SELECT period_name, closing_status, start_date, end_date
280     FROM   gl_period_statuses p
281     WHERE  p.application_id = 101
282     AND    p.ledger_id = X_Ledger_Id
283     AND    p.effective_period_num =
284      ( SELECT min(effective_period_num)
285        FROM   gl_period_statuses p1
286        WHERE  p1.application_id = 101
287        AND    p1.ledger_id = X_Ledger_Id
288        AND    adjustment_period_flag = 'N'
289        AND    p1.effective_period_num >
290           ( SELECT effective_period_num
291             FROM gl_period_statuses p2
292             WHERE p2.application_id = 101
293             AND   p2.ledger_id = X_Ledger_Id
294             AND   p2.period_name = X_Je_Period_Name));
295 
296      -- When the journal'next day falls into the next period,
297      -- reverse into the next non-adj period if the journal period is non-adj,
298      -- reverse into the next adjusting period if the journal period is adj.
299      -- note: min() neccessary because there may be overlapping adj periods
300      CURSOR next_day_to_period IS
301         SELECT period_name, closing_status, start_date, end_date
302         FROM   gl_period_statuses p
303         WHERE  p.application_id = 101
304         AND    p.ledger_id = X_Ledger_Id
305         AND    p.effective_period_num =
306           ( SELECT min(effective_period_num)
307             FROM   gl_period_statuses p1
308             WHERE  p1.application_id = 101
309             AND    p1.ledger_id = X_Ledger_Id
310             AND    reversal_date between p1.start_date and p1.end_date
311             AND    p1.adjustment_period_flag = adj_period_flag);
312 
313 BEGIN
314 
315     Error_Buffer := Null;
316 
317     OPEN get_lgr;
318     FETCH get_lgr INTO adb_lgr,cons_lgr,trxn_calendar_id,
319                   period_set,v_period_type,l_criteria_set_id;
320 
321     if (get_lgr%NOTFOUND) then
322       CLOSE get_lgr;
323       Error_Buffer := 'Cannot find ledger info for ledger id '
324                       ||X_Ledger_Id;
325       Raise NO_DATA_FOUND;
326     end if;
327 
328     if (l_criteria_set_id IS NULL) THEN
329 
330       get_default_reversal_data
331                        (X_Category_name        => X_Je_Category,
332                         X_adb_lgr_flag         =>adb_lgr,
333                         X_cons_lgr_flag        =>cons_lgr,
334                         X_Reversal_Method_code =>method_code,
335                         X_Reversal_Period_code =>period_rule,
336                         X_Reversal_Date_code   =>date_rule) ;
337 
338      CLOSE get_lgr;
339     else
340 
341        CLOSE get_lgr;
342        OPEN get_criteria;
343        FETCH get_criteria INTO method_code,period_rule,date_rule;
344 
348             'Cannot find reversal criteria for je category '||X_Je_Category;
345        if (get_criteria%NOTFOUND) then
346           CLOSE get_criteria;
347         Error_Buffer :=
349         Raise NO_DATA_FOUND;
350        end if;
351 
352 	CLOSE get_criteria;
353 
354     end if;
355 
356     IF (period_rule = 'NO_DEFAULT') THEN
357        Raise NO_DEFAULT;
358     ELSIF (period_rule = 'SAME_PERIOD') THEN
359 
360        OPEN same_period;
361        FETCH same_period INTO reversal_period,pstatus,start_date,end_date,
362                               adj_period_flag;
363        IF (same_period%NOTFOUND) THEN
364 
365             CLOSE same_period;
366             Error_Buffer := 'Invalid journal period '||X_Je_Period_Name;
367             Raise GET_REV_PERIOD_DATE_FAILED;
368        END IF;
369        CLOSE same_period;
370 
371     ELSIF (period_rule = 'NEXT_PERIOD') THEN
372        OPEN next_period;
373        FETCH next_period INTO reversal_period,pstatus,start_date,end_date,
374                               adj_period_flag;
375        IF (next_period%NOTFOUND) THEN
376             CLOSE next_period;
377             Error_Buffer := 'Cannot find the next period of '||X_Je_Period_Name;
378             Raise GET_REV_PERIOD_DATE_FAILED;
379        END IF;
380 
381        CLOSE next_period;
382     ELSIF (period_rule = 'NEXT_NON_ADJ_PERIOD') THEN
383        OPEN next_nonadj_period;
384        FETCH next_nonadj_period INTO reversal_period,pstatus,
385                                      start_date,end_date;
386        IF (next_nonadj_period%NOTFOUND) THEN
387             CLOSE next_nonadj_period;
388             Error_Buffer := 'Cannot find the next non-adjusting period of '||X_Je_Period_Name;
389             Raise GET_REV_PERIOD_DATE_FAILED;
390        END IF;
391        CLOSE next_nonadj_period;
392     ELSIF (period_rule = 'NEXT_DAY') THEN
393 
394      IF (adb_lgr  <> 'Y' OR
395           (adb_lgr =  'Y' AND cons_lgr =  'Y')) THEN
396             method_code := 'N';
397             Raise NO_DEFAULT;
398      ELSE
399 
400        reversal_date := X_Je_date + 1;
401 
402        -- Fetch the journal period info
403        OPEN same_period;
404        FETCH same_period INTO reversal_period,pstatus,start_date,end_date,
405                                   adj_period_flag;
406 
407        IF (same_period%NOTFOUND) THEN
408            CLOSE same_period;
409            Error_Buffer := 'Invalid journal period '||X_Je_Period_Name;
410            Raise GET_REV_PERIOD_DATE_FAILED;
411        END IF;
412        CLOSE same_period;
413 
414        -- Reset reversal date to a business day
415        -- when neccessary
416        -- IF adj_period_flag = 'N' THEN
417            get_business_day('NEXT_DAY', trxn_calendar_id, X_Je_Source,
418                        reversal_date);
419        -- END IF;
420 
421       -- if the reversal is not in the journal period, find the reversal period
422        IF ( reversal_date > end_date) THEN
423            OPEN next_day_to_period;
424            FETCH next_day_to_period INTO reversal_period,pstatus,
425                                      start_date,end_date;
426 
427            IF (next_day_to_period%NOTFOUND) THEN
428                CLOSE next_day_to_period;
429                Error_Buffer := 'Cannot find a reversal period for the next day '||reversal_date;
430                Raise GET_REV_PERIOD_DATE_FAILED;
431            END IF;
432            CLOSE next_day_to_period;
433        END IF;
434 
435      END IF; -- check for adb_lgr ends
436 
437     ELSE
438         Error_Buffer := 'Invalid Reversal_Period_Code in GL_REVERSE_OPTIONS for '||X_Je_Category;
439         Raise GET_REV_PERIOD_DATE_FAILED;
440     END IF;
441 
442     IF NOT (pstatus = 'O' OR pstatus = 'F') THEN
443        Error_Buffer := 'Reversal period '||reversal_period
444                   ||' is not open or futur-enterable';
445        Raise GET_REV_PERIOD_DATE_FAILED;
446     END IF;
447 
448     IF (adb_lgr = 'Y' AND period_rule <> 'NEXT_DAY') THEN
449 
450         -- If the X_Date_Rule is NULL then default the date rules
451 	-- as follows. When a new criteria set is created in Journal
452 	-- reversal criteria form then we don't know the type of ledger
453 	-- and so it is not able to default the date rule.
454 	-- Now it is the time to default it.
455 
456       IF ((Date_Rule IS NULL) AND (cons_lgr = 'N')) THEN
457          IF (X_JE_CATEGORY = 'Income Statement Close') OR
458               (X_JE_CATEGORY = 'Income Offset') THEN
459 	       date_rule := 'LAST_DAY';
460 	    ELSIF (X_JE_CATEGORY = 'Balance Sheet Close') THEN
461 	       date_rule := 'FIRST_DAY';
462          END IF;
463       END IF;
464 
465       get_reversal_date(reversal_period,adj_period_flag,
466                         period_rule,date_rule,cons_lgr,trxn_calendar_id,
467                         X_Je_Source,X_Je_Date,start_date,end_date,
468                         reversal_date);
469     END IF;
470 
471     X_Reversal_Period := reversal_period;
472     X_Reversal_Date := reversal_date;
473     X_Reversal_Method := method_code;
474 
475     -- populate message buffer for debugging
476     Error_Buffer := 'Get reversal info. Category='||X_Je_Category
480                     ||',Reversal Period='||X_Reversal_Period
477                     ||',Source='||X_Je_Source
478                     ||',Je Period='||X_Je_Period_Name||',Je Date='||X_Je_Date
479                     ||',Reversal Method='||X_Reversal_Method
481                     ||',Reversal Date='||to_char(X_Reversal_Date);
482 EXCEPTION
483     WHEN NO_DEFAULT THEN
484          X_Reversal_Method := method_code;
485          Error_Buffer := 'Get reversal info. Category='||X_Je_Category
486                     ||',Source='||X_Je_Source
487                     ||',Je Period='||X_Je_Period_Name||',Je Date='||X_Je_Date
488                     ||',Reversal Method='||X_Reversal_Method
489                     ||',Reversal Period Rule='||period_rule;
490     WHEN GET_REV_PERIOD_DATE_FAILED THEN
491 
492          Error_Buffer :=
493                     'GL_AUTOREVERSE_DATE_PKG.get_reversal_period_date.'
494                     ||Error_Buffer
495                     ||' Package parameters: Category='||X_Je_Category
496                     ||',Source='||X_Je_Source
497                     ||',Je Period='||X_Je_Period_Name||',Je Date='||X_Je_Date
498                     ||',Reversal Period Rule='||period_rule
499                     ||',Reversal Date Rule='||date_rule;
500          Raise;
501     WHEN OTHERS THEN
502          Error_Buffer :=
503                     'GL_AUTOREVERSE_DATE_PKG.get_reversal_period_date.'
504                     ||Error_Buffer||' : '||SUBSTRB(SQLERRM,1,100)
505                     ||' Package parameters: Category='||X_Je_Category
506                     ||',Source='||X_Je_Source
507                     ||',Je Period='||X_Je_Period_Name||',Je Date='||X_Je_Date
508                     ||',Reversal Period Rule='||period_rule
509                     ||',Reversal Date Rule='||date_rule;
510          Raise;
511          -- APP_EXCEPTION.raise_exception;
512 END get_reversal_period_date;
513 
514  -- Public procedure
515 
516 PROCEDURE GET_DEFAULT_REVERSAL_DATA
517                        (X_Category_name             VARCHAR2,
518                         X_adb_lgr_flag             VARCHAR2 DEFAULT 'N',
519                         X_cons_lgr_flag            VARCHAR2 DEFAULT 'N' ,
520                         X_Reversal_Method_code     IN OUT NOCOPY  VARCHAR2,
521                         X_Reversal_Period_code     IN OUT NOCOPY  VARCHAR2,
522                         X_Reversal_Date_code       IN OUT NOCOPY  VARCHAR2) IS
523 
524    BEGIN
525         IF ((X_CATEGORY_NAME = 'Income Statement Close') OR
526             (X_CATEGORY_NAME = 'Income Offset')OR
527              (X_CATEGORY_NAME = 'MRC Open Balances') OR
528               (X_CATEGORY_NAME = 'Revalue Profit/Loss')) THEN
529 
530 		 X_Reversal_Method_Code := 'Y';
531         ELSE
532 	         X_Reversal_Method_Code := 'N';
533 	END IF;
534 
535         IF ((X_CATEGORY_NAME = 'Income Statement Close') OR
536 	     (X_CATEGORY_NAME = 'Income Offset')) THEN
537 
538     	    	 X_Reversal_Period_code := 'SAME_PERIOD';
539 
540         ELSIF (X_CATEGORY_NAME = 'Balance Sheet Close') THEN
541 		 X_Reversal_Period_code := 'NEXT_PERIOD';
542         ELSE
543 		 X_Reversal_Period_code := 'NO_DEFAULT';
544         END IF;
545 
546        IF (X_adb_lgr_flag = 'Y') AND
547 	    (X_cons_lgr_flag = 'N') THEN
548 
549          IF (X_CATEGORY_NAME = 'Income Statement Close') OR
550              (X_CATEGORY_NAME = 'Income Offset') THEN
551 
552 	      X_Reversal_Date_code := 'LAST_DAY';
553 
554 	  ELSIF (X_CATEGORY_NAME = 'Balance Sheet Close') THEN
555 
556 		X_Reversal_Date_code := 'FIRST_DAY';
557           ELSE
558 		X_Reversal_Date_code := NULL;
559           END IF;
560        ELSE
561 		X_Reversal_Date_code := NULL;
562        END IF;
563 
564    EXCEPTION
565 	WHEN OTHERS THEN
566 	  Error_Buffer := '.get_defualt_reversal_data'||Error_Buffer;
567           Raise;
568   END GET_DEFAULT_REVERSAL_DATA;
569 
570  -- Public procedure
571 
572 PROCEDURE Get_Default_Reversal_Method
573                        (X_Ledger_Id                NUMBER,
574 			X_Category_name            VARCHAR2,
575                         X_Reversal_Method_code     IN OUT NOCOPY  VARCHAR2) IS
576 
577 
578 	adb_flag VARCHAR2(1);
579         cons_flag VARCHAR2(1);
580         reversal_period_rule  VARCHAR2(15);
581 	reversal_date_rule    VARCHAR2(15);
582 
583   BEGIN
584 	   SELECT DECODE(method_code,'C', 'Y', 'N'),
585                   gll.enable_average_balances_flag,
586            	  gll.consolidation_ledger_flag
587 	   INTO
588 		  X_Reversal_Method_code,
589                   adb_flag, cons_flag
590  	   FROM   GL_LEDGERS gll, GL_AUTOREVERSE_OPTIONS glao
591 	   WHERE  gll.ledger_id            = X_Ledger_Id
592 	   AND    glao.criteria_set_id(+)  = gll.Criteria_Set_Id
593            AND    glao.je_category_name(+) = X_Category_Name;
594 
595           -- The following call returns at least reversal method.
596 	  -- Journal Import, Recurring journal programs requires
597 	  -- reversal method code.
598 
599 	   IF (X_Reversal_Method_code IS NULL) THEN
600 
601               get_default_reversal_data
602                        (X_Category_name        => X_Category_Name,
603                         X_adb_lgr_flag         =>adb_flag,
604                         X_cons_lgr_flag        =>cons_flag,
605                         X_Reversal_Method_code =>X_Reversal_Method_code,
606                         X_Reversal_Period_code =>Reversal_Period_rule ,
607                         X_Reversal_Date_code   =>Reversal_Date_rule) ;
608           END IF;
609 
610 END Get_Default_Reversal_Method;
611 
612 END GL_AUTOREVERSE_DATE_PKG;