DBA Data[Home] [Help]

PACKAGE BODY: APPS.FA_RX_GROUP

Source


1 PACKAGE BODY FA_RX_GROUP AS
2 /* $Header: farxgab.pls 120.15.12010000.2 2008/07/31 07:20:55 sbhaskar ship $ */
3 
4 -- global variables
5 g_print_debug boolean := fa_cache_pkg.fa_print_debug;
6 
7 
8 PROCEDURE get_group_asset_info (
9   p_book_type_code          IN  VARCHAR2,
10   p_start_fiscal_year       IN  VARCHAR2,
11   p_end_fiscal_year         IN  VARCHAR2,
12   p_major_category_low      IN  VARCHAR2,
13   p_major_category_high     IN  VARCHAR2,
14   p_minor_category_low      IN  VARCHAR2,
15   p_minor_category_high     IN  VARCHAR2,
16   p_category_segment_name   IN  VARCHAR2,
17   p_category_segment_low    IN  VARCHAR2,
18   p_category_segment_high   IN  VARCHAR2,
19   p_asset_number_low        IN  VARCHAR2,
20   p_asset_number_high       IN  VARCHAR2,
21   p_drill_down              IN  VARCHAR2,
22   p_request_id              IN  NUMBER,
23   p_user_id                 IN  NUMBER,
24   x_retcode                 OUT NOCOPY NUMBER,
25   x_errbuf                  OUT NOCOPY VARCHAR2)
26 IS
27   l_info_rec                    info_rec_type;
28 
29   l_application_id              fa_system_controls.fa_application_id%TYPE;
30   l_category_flex_structure     fa_system_controls.category_flex_structure%TYPE;
31 
32   l_param_where_stmt            VARCHAR2(1000);
33   l_group_sql_stmt              VARCHAR2(5000);
34   l_sql_stmt                    VARCHAR2(5000);
35 
36   l_group_adjustment_amount     NUMBER;
37   l_second_half_add_rec_cost    NUMBER;
38   l_second_half_grp_adjustment  NUMBER;
39   l_second_half_mem_adjustment  NUMBER;
40   l_group_reclass_in            NUMBER;
41   l_group_reclass_out           NUMBER;
42   l_all_reduced_deprn_amount    NUMBER;
43   l_non_cip_num                 NUMBER;
44 
45   l_message                     VARCHAR2(30);
46 
47   TYPE group_csrtype IS REF CURSOR;
48   l_group_csr        group_csrtype;
49   l_group_rec        group_rec_type;
50   l_member_rec       group_rec_type;
51 
52   TYPE amount_csrtype IS REF CURSOR;
53   l_amount_csr       amount_csrtype;
54 
55   main_err           EXCEPTION;
56 BEGIN
57   IF g_print_debug THEN
58     fa_rx_util_pkg.debug('get_group_asset_info: '
59                          || 'farx_ga.get_group_asset_info()+');
60     fa_rx_util_pkg.debug('get_group_asset_info: '
61                          || 'book: ' || p_book_type_code);
62     fa_rx_util_pkg.debug('get_group_asset_info: '
63                          || 'fiscal year from: ' || p_start_fiscal_year);
64     fa_rx_util_pkg.debug('get_group_asset_info: '
65                          || 'fiscal year to: ' || p_end_fiscal_year);
66     fa_rx_util_pkg.debug('get_group_asset_info: '
67                          || 'user_id: ' || p_user_id);
68     fa_rx_util_pkg.debug('get_group_asset_info: '
69                          || 'request_id: ' || p_request_id);
70   END IF;
71   l_message := 'get_group_asset_info start';
72 
73 
74   ----------------------------------------------
75   -- Initialization
76   ----------------------------------------------
77   l_info_rec.book_type_code := p_book_type_code;
78   l_info_rec.request_id := p_request_id;
79   l_info_rec.user_id := p_user_id;
80 
81   -- Get organization name, functional currency and flex structure
82   SELECT sc.fa_application_id,
83          sc.category_flex_structure,
84          sob.name,
85          sob.currency_code,
86          bc.set_of_books_id,
87          bc.deprn_calendar
88     INTO l_application_id,
89          l_category_flex_structure,
90          l_info_rec.organization_name,
91          l_info_rec.functional_currency_code,
92          l_info_rec.set_of_books_id,
93          l_info_rec.deprn_calendar
94     FROM fa_system_controls sc,
95          fa_book_controls bc,
96          gl_sets_of_books sob,
97          fnd_currencies cur
98    WHERE bc.book_type_code = p_book_type_code
99      AND sob.set_of_books_id = bc.set_of_books_id
100      AND sob.currency_code = cur.currency_code;
101 
102   IF g_print_debug THEN
103     fa_rx_util_pkg.debug('get_group_asset_info: '
104                          || 'set_of_books_id: ' || l_info_rec.set_of_books_id);
105     fa_rx_util_pkg.debug('get_group_asset_info: '
106                          || 'deprn_calendar: ' || l_info_rec.deprn_calendar);
107   END IF;
108   l_message := 'initialization end';
109 
110 
111   -- Create select and where clauses for categories paramters
112   get_category_sql(l_application_id,
113                    l_category_flex_structure,
114                    'BASED_CATEGORY',
115                    p_major_category_low,
116                    p_major_category_high,
117                    l_info_rec.major_cat_select_stmt,
118                    l_param_where_stmt);
119 
120   get_category_sql(l_application_id,
121                    l_category_flex_structure,
122                    'MINOR_CATEGORY',
123                    p_minor_category_low,
124                    p_minor_category_high,
125                    l_info_rec.minor_cat_select_stmt,
126                    l_sql_stmt);
127   l_param_where_stmt := l_param_where_stmt || l_sql_stmt;
128 
129   get_category_sql(l_application_id,
130                    l_category_flex_structure,
131                    p_category_segment_name,
132                    p_category_segment_low,
133                    p_category_segment_high,
134                    l_info_rec.other_cat_select_stmt,
135                    l_sql_stmt);
136   l_param_where_stmt := l_param_where_stmt || l_sql_stmt;
137 
138 
139   -- Add group asset number where clause
140   IF p_asset_number_low = p_asset_number_high THEN
141     l_param_where_stmt := l_param_where_stmt || ' AND ad.asset_number = '''
142                           || p_asset_number_low || '''';
143 
144   ELSIF p_asset_number_low IS NOT NULL
145     AND p_asset_number_high IS NOT NULL THEN
146     l_param_where_stmt := l_param_where_stmt || ' AND ad.asset_number
147                           BETWEEN ''' ||
148                           p_asset_number_low || '''' || ' AND  ''' ||
149                           p_asset_number_high || '''';
150 
151   ELSIF p_asset_number_low IS NOT NULL THEN
152     l_param_where_stmt := l_param_where_stmt || ' AND ad.asset_number >= '''
153                           || p_asset_number_low || '''';
154 
155   ELSIF p_asset_number_high IS NOT NULL THEN
156     l_param_where_stmt := l_param_where_stmt || ' AND ad.asset_number <= '''
157                           || p_asset_number_high || '''';
158   END IF;
159 
160   IF g_print_debug THEN
161     fa_rx_util_pkg.debug('get_group_asset_info: '
162                          || 'l_param_where_stmt:' || l_param_where_stmt);
163   END IF;
164   l_message := 'category sql end';
165 
166 
167   IF NOT fa_cache_pkg.fazcbc(p_book_type_code) THEN
168     raise main_err;
169   END IF;
170 
171 
172   -----------------------------------------------------
173   -- Main logic
174   --   Fiscal Year Loop -> Group Loop -> Member Loop
175   -----------------------------------------------------
176 
177   l_info_rec.fiscal_year := p_start_fiscal_year;
178 
179   LOOP
180     EXIT WHEN l_info_rec.fiscal_year > p_end_fiscal_year;
181 
182 
183     -- Get first and last depreciated period counter of the fiscal year
184     -- Bug #2846317 - can report open period if it's depreciated
185     SELECT MIN(period_counter),
186            MAX(period_counter)
187       INTO l_info_rec.min_period_counter,
188            l_info_rec.max_period_counter
189       FROM fa_deprn_periods
190      WHERE book_type_code = p_book_type_code
191        AND fiscal_year = l_info_rec.fiscal_year
192        AND NVL(deprn_run, 'N') = 'Y';
193 
194 
195     -- Exit if no period is depreciated in fiscal year
196     EXIT WHEN l_info_rec.max_period_counter IS NULL;
197 
198     l_message := 'fiscal year loop (1)';
199 
200 
201     --------------------------------------------------------------
202     -- <Group Query Loop>
203     -- Query group assets matching to the report parameter.
204     --------------------------------------------------------------
205 
206     -- Create main query for group
207     l_group_sql_stmt :=
208       'SELECT
209         ad.asset_number,
210         ad.description,
211         ad.asset_type, '
212         || l_info_rec.major_cat_select_stmt || ','
213         || l_info_rec.minor_cat_select_stmt || ','
214         || l_info_rec.other_cat_select_stmt || ',
215         bk.date_placed_in_service,
216         bk.deprn_method_code,
217         br.rule_name,
218         bk.tracking_method,
219         bk.adjusted_rate,
220         NULL,
221         NVL(bk.cost, 0) + NVL(bk.cip_cost, 0),
222         NVL(bk.salvage_value, 0),
223         NVL(bk.adjusted_recoverable_cost, 0),
224         NVL(prev.cost, 0) + NVL(prev.cip_cost, 0) - NVL(prev.deprn_reserve, 0),
225         NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL,
226         0,
227         NVL(bk.terminal_gain_loss_amount, 0),
228         NULL, NULL,
229         NVL(ds.adjusted_cost, 0),
230         NULL, NULL,
231         NVL(ds.ytd_deprn, 0),
232         NVL(ds.deprn_reserve, 0),
233         NULL, NULL,
234         ad.asset_id,
235         NULL,
236         DECODE(bk.life_in_months, NULL, NULL,
237           TO_CHAR(FLOOR(bk.life_in_months / 12)) || ''.'' ||
238           TO_CHAR(MOD(bk.life_in_months, 12))),
239         met.deprn_basis_rule,
240         met.exclude_salvage_value_flag,
241         NVL(bk.reduction_rate, 0),
242         bk.depreciation_option,
243         bk.recognize_gain_loss,
244         bk.exclude_proceeds_from_basis,
245         NULL, NULL,
246         ds.period_counter ';
247 
248     -- Add from clause
249     get_from_sql_stmt(l_info_rec, NULL, l_sql_stmt);
250     l_group_sql_stmt := l_group_sql_stmt || l_sql_stmt;
251 
252     -- Add where clause
253     get_where_sql_stmt(l_info_rec, NULL, l_sql_stmt);
254     l_group_sql_stmt := l_group_sql_stmt || l_sql_stmt || l_param_where_stmt;
255 
256     IF g_print_debug THEN
257       fa_rx_util_pkg.debug('get_group_asset_info: '
258                            || 'l_group_sql_stmt:' || l_group_sql_stmt);
259     END IF;
260     l_message := 'fiscal year loop (2)';
261 
262 
263 
264     -- Group query loop start
265     OPEN l_group_csr FOR l_group_sql_stmt;
266     LOOP
267       FETCH l_group_csr INTO l_group_rec;
268       EXIT WHEN l_group_csr%NOTFOUND;
269 
270       l_message := 'group loop (1)';
271 
272       IF g_print_debug THEN
273         fa_rx_util_pkg.debug('get_group_asset_info: '
274                           || 'group_asset: ' || l_group_rec.asset_number);
275       END IF;
276 
277       ----------------------------------------------------------
278       -- Query add/adj/retirement amount in the FY
279       ----------------------------------------------------------
280 
281       -- Query fa_retirements
282       -- (retiring member asset is allowed only in current period)
283       SELECT NVL(SUM(ret.proceeds_of_sale), 0),
284              NVL(SUM(ret.cost_of_removal), 0),
285              NVL(SUM(ret.nbv_retired), 0),
286              NVL(SUM(ret.cost_retired), 0),
287              NVL(SUM(ret.reserve_retired), 0),
288              NVL(SUM(ret.recapture_amount), 0)
289         INTO l_group_rec.proceeds_of_sale,
290              l_group_rec.cost_of_removal,
291              l_group_rec.net_proceeds,
292              l_group_rec.cost_retired,
293              l_group_rec.reserve_retired,
294              l_group_rec.recapture_amount
295         FROM fa_retirements ret,
296              fa_book_controls bc,
297              fa_fiscal_year fy,
298              fa_transaction_headers thg,
299              fa_transaction_headers thm
300        WHERE bc.book_type_code = p_book_type_code
301          AND fy.fiscal_year = l_info_rec.fiscal_year
302          AND fy.fiscal_year_name = bc.fiscal_year_name
303          AND thm.book_type_code = bc.book_type_code
304          AND thm.transaction_date_entered
305              BETWEEN fy.start_date and fy.end_date
306          AND thg.book_type_code = bc.book_type_code
307          AND thg.asset_id = l_group_rec.asset_id
308          AND thg.member_transaction_header_id = thm.transaction_header_id
309          AND ret.transaction_header_id_in = thm.transaction_header_id
310          AND ret.status <> 'DELETED';
311 
312 
313       l_message := 'group loop (2)';
314 
315       -- Get group level adjustments amount
316       --   Query transactions that occurred during the fiscal year,
317       --   includeing back dated transactions.
318       --   But exclude transanctions that happened during the
319       --   non-depreciated period, even if it's back dated one.
320 
321       SELECT NVL(SUM(DECODE(adj.debit_credit_flag,
322                             'DR', adj.adjustment_amount,
323                             'CR', -adj.adjustment_amount, 0)), 0),
324              NVL(SUM(DECODE(GREATEST(thg.transaction_date_entered,
325                                      fy.mid_year_date),
326                             thg.transaction_date_entered,
327                             DECODE(adj.debit_credit_flag,
328                                    'DR', adj.adjustment_amount,
329                                    'CR', -adj.adjustment_amount, 0),
330                             0)), 0)
331         INTO l_group_adjustment_amount,
332              l_second_half_grp_adjustment
333         FROM fa_adjustments adj,
334              fa_book_controls bc,
335              fa_fiscal_year fy,
336              fa_transaction_headers thg
337        WHERE thg.asset_id = l_group_rec.asset_id
338          AND thg.book_type_code = p_book_type_code
339          AND thg.member_transaction_header_id IS NULL
340          AND thg.transaction_header_id = adj.transaction_header_id
341          AND adj.period_counter_created
342              BETWEEN l_info_rec.min_period_counter
343                  and l_info_rec.max_period_counter
344          AND adj.adjustment_type = 'COST'
345          AND fy.fiscal_year = l_info_rec.fiscal_year
346          AND fy.fiscal_year_name = bc.fiscal_year_name
347          AND bc.book_type_code = p_book_type_code;
348 
349       l_message := 'group loop (3)';
350 
351 
352       -- Get member level addition, adjustment and retirement amount
353       get_trx_amount_sql(l_group_rec, l_info_rec, NULL, l_sql_stmt);
354 
355        OPEN l_amount_csr FOR l_sql_stmt;
356       FETCH l_amount_csr
357        INTO l_second_half_add_rec_cost,
358             l_second_half_mem_adjustment,
359             l_group_rec.second_half_addition,
360             l_group_rec.addition_amount,
361             l_group_rec.adjustment_amount;
362       CLOSE l_amount_csr;
363 
364       l_message := 'group loop (4)';
365 
366 
367       -- Get group reclass amount
368       SELECT NVL(SUM(bkm.cost), 0) - NVL(SUM(adj.adjustment_amount), 0)
369         INTO l_group_reclass_in
370         FROM fa_adjustments adj,
371              fa_transaction_headers thg,
372              fa_books bkm,
373              (SELECT bk_pre.asset_id,
374                      bk_pre.group_asset_id
375                 FROM fa_books bk_pre,
376                      fa_deprn_summary ds_pre,
377                      fa_deprn_periods dp_pre
378                WHERE bk_pre.book_type_code = p_book_type_code
379                  AND dp_pre.book_type_code = bk_pre.book_type_code
380                  AND dp_pre.period_counter + 1 = l_info_rec.min_period_counter
381                  AND dp_pre.period_close_date BETWEEN bk_pre.date_effective
382                      AND NVL(bk_pre.date_ineffective, dp_pre.period_close_date)
383                  AND ds_pre.book_type_code = bk_pre.book_type_code
384                  AND ds_pre.asset_id = bk_pre.asset_id
385                  AND ds_pre.period_counter = (
386                      SELECT MAX(ds3.period_counter)
387                        FROM fa_deprn_summary ds3
388                       WHERE ds_pre.book_type_code = ds3.book_type_code
389                         AND ds_pre.asset_id = ds3.asset_id
390                         AND ds3.period_counter < l_info_rec.min_period_counter
391                  )
392              ) prev
393        WHERE adj.asset_id = l_group_rec.asset_id
394          AND adj.book_type_code = p_book_type_code
395          AND thg.transaction_header_id = adj.transaction_header_id
396          AND adj.period_counter_created
397              BETWEEN l_info_rec.min_period_counter
398                  and l_info_rec.max_period_counter
399          AND adj.source_type_code = 'ADJUSTMENT'
400          AND adj.adjustment_type = 'RESERVE'
401          AND thg.member_transaction_header_id = bkm.transaction_header_id_in
402          AND NVL(bkm.group_asset_id, -1) = l_group_rec.asset_id
403          AND prev.asset_id = bkm.asset_id
404          AND NVL(prev.group_asset_id, -1) <> l_group_rec.asset_id;
405 
406       SELECT NVL(SUM(bkm.cost), 0) - NVL(SUM(adj.adjustment_amount), 0)
407         INTO l_group_reclass_out
408         FROM fa_adjustments adj,
409              fa_transaction_headers thg,
410              fa_books bkm
411        WHERE adj.asset_id = l_group_rec.asset_id
412          AND adj.book_type_code = p_book_type_code
413          AND thg.transaction_header_id = adj.transaction_header_id
414          AND adj.period_counter_created
415              BETWEEN l_info_rec.min_period_counter
416                  and l_info_rec.max_period_counter
417          AND adj.source_type_code = 'ADJUSTMENT'
418          AND adj.adjustment_type = 'RESERVE'
419          AND thg.member_transaction_header_id = bkm.transaction_header_id_in
420          AND NVL(bkm.group_asset_id, -1) <> l_group_rec.asset_id;
421 
422       l_message := 'group loop (4-2)';
423 
424 
425       ----------------------------------------------------------
426       -- Calculate and set each column
427       ----------------------------------------------------------
428       -- Convert life_year_month to number
429       l_group_rec.life_year_month :=
430         fnd_number.canonical_to_number(l_group_rec.life_year_month_string);
431 
432       -- Addition during first/second half of the fiscal year
433       IF NVL(l_group_rec.rule_name, ' ') <> FA_RXGA_HALF_YEAR_RULE THEN
434         l_group_rec.first_half_addition := NULL;
435         l_group_rec.second_half_addition := NULL;
436       ELSE
437         l_group_rec.first_half_addition :=
438             l_group_rec.addition_amount - l_group_rec.second_half_addition;
439       END IF;
440 
441       -- Adjustment amount
442       --  = group level COST trx + member level COST/CIP COST trx
443       --    - (member addition + member retirement) + group reclass
444       l_group_rec.adjustment_amount :=
445             l_group_adjustment_amount + l_group_rec.adjustment_amount
446             - (l_group_rec.addition_amount - l_group_rec.cost_retired)
447             + (l_group_reclass_in - l_group_reclass_out);
448 
449       -- Net proceeds
450       IF NVL(l_group_rec.exclude_proceeds_from_basis, 'N') = 'Y' THEN
451         -- Set net proceeds = 0 for class 10.1
452         l_group_rec.net_proceeds := 0;
453       END IF;
454 
455 
456       -- NBV before depreciation
457       l_group_rec.nbv_before_deprn
458           := l_group_rec.beginning_nbv + l_group_rec.addition_amount
459            + l_group_rec.adjustment_amount - l_group_rec.net_proceeds;
460 
461 
462       -- Depreciable basis adjustment / Reduced NBV
463       -- (only applicable for 50% rule)
464       IF NOT (NVL(l_group_rec.rule_name, ' ')
465           IN (FA_RXGA_POSITIVE_REDUCTION, FA_RXGA_HALF_YEAR_RULE)) THEN
466         l_group_rec.deprn_basis_adjustment := NULL;
467         l_group_rec.reduced_nbv := NULL;
468 
469       ELSIF l_group_rec.max_period_counter < l_info_rec.min_period_counter THEN
470 
471         -- Set zero if there was no depreciation during the fiscal year.
472         l_group_rec.deprn_basis_adjustment := 0;
473         l_group_rec.reduced_nbv := 0;
474 
475       ELSE
476         -- for class 90 (CIP group)
477         -- If all the member assets are CIP, adjusted_cost is alyways 0.
478         IF l_group_rec.reduced_nbv = 0
479           AND NVL(l_group_rec.rule_name, ' ') = FA_RXGA_POSITIVE_REDUCTION THEN
480 
481           SELECT COUNT(*)
482             INTO l_non_cip_num
483             FROM fa_books bk, fa_additions ad
484            WHERE bk.book_type_code = p_book_type_code
485              AND bk.group_asset_id = l_group_rec.asset_id
486              AND ad.asset_type <> 'CIP'
487              AND bk.asset_id = ad.asset_id;
488 
489           IF NVL(l_non_cip_num, 0) = 0 THEN
490             l_group_rec.reduced_nbv := l_group_rec.nbv_before_deprn;
491           END IF;
492         END IF;
493 
494         -- Reduced NBV (adjusted cost has already been set)
495         IF l_group_rec.deprn_basis_rule = fa_std_types.FAD_DBR_NBV
496            AND NVL(l_group_rec.exclude_salvage_value_flag, 'NO') = 'YES' THEN
497           l_group_rec.reduced_nbv :=
498               l_group_rec.reduced_nbv + l_group_rec.salvage_value;
499         END IF;
500 
501         -- Depreciable basis adjustment
502         l_group_rec.deprn_basis_adjustment :=
503             l_group_rec.nbv_before_deprn - l_group_rec.reduced_nbv;
504       END IF;
505 
506 
507       -- Reduced/Regular/Annual depreciation amount
508       IF NVL(l_group_rec.rule_name, ' ') <> FA_RXGA_HALF_YEAR_RULE THEN
509 
510         -- Set NULL if depreciable basis rule is not
511         -- Year End Balance with Half Year Rule.
512         l_group_rec.regular_deprn_amount := NULL;
513         l_group_rec.reduced_deprn_amount := NULL;
514 
515       ELSIF l_group_rec.max_period_counter < l_info_rec.min_period_counter THEN
516         -- Set zero if there was no depreciation during the fiscal year.
517         l_group_rec.reduced_deprn_amount := 0;
518         l_group_rec.regular_deprn_amount := 0;
519         l_group_rec.annual_deprn_amount := 0;
520 
521       ELSE
522         -- calculate reduced deprn amount, which assumed reduction rate
523         -- was applied to the entire NBV before deprn
524         l_all_reduced_deprn_amount :=
525            l_group_rec.nbv_before_deprn * (1 - l_group_rec.reduction_rate)
526            * l_group_rec.adjusted_rate;
527         IF NOT fa_utils_pkg.faxtru(l_all_reduced_deprn_amount,
528                                    p_book_type_code) THEN
529           raise main_err;
530         END IF;
531 
532         IF g_print_debug THEN
533           fa_rx_util_pkg.debug('l_all_reduced_deprn_amount: '
534                          || l_all_reduced_deprn_amount);
535           fa_rx_util_pkg.debug('annual_deprn_amount: '
536                          || l_group_rec.annual_deprn_amount);
537         END IF;
538 
539         IF l_group_rec.annual_deprn_amount = l_all_reduced_deprn_amount THEN
540           l_group_rec.reduced_deprn_amount := l_group_rec.annual_deprn_amount;
541         ELSE
542           l_group_rec.reduced_deprn_amount := (l_second_half_add_rec_cost
543             + l_second_half_grp_adjustment + l_second_half_mem_adjustment)
544             * l_group_rec.adjusted_rate * (1 - l_group_rec.reduction_rate);
545           IF NOT fa_utils_pkg.faxtru(l_group_rec.reduced_deprn_amount,
546                                      p_book_type_code) THEN
547             raise main_err;
548           END IF;
549         END IF;
550 
551         -- Regular depreciation amount
552         l_group_rec.regular_deprn_amount :=
553             l_group_rec.annual_deprn_amount - l_group_rec.reduced_deprn_amount;
554       END IF;
555 
556       -- Ending NBV
557       -- Bug #2873705
558       l_group_rec.ending_nbv := l_group_rec.cost
559                               - l_group_rec.deprn_reserve
560                               + l_group_rec.terminal_gain_loss_amount;
561 
562       -- Terminal Loss
563       -- Bug #2876230 - set terminal loss only
564       IF l_group_rec.terminal_gain_loss_amount < 0 THEN
565         l_group_rec.terminal_gain_loss_amount
566             := l_group_rec.terminal_gain_loss_amount * -1;
567       ELSE
568         l_group_rec.terminal_gain_loss_amount := 0;
569       END IF;
570 
571       l_message := 'group loop (5)';
572 
573 
574       ----------------------------------------------------------
575       -- Insert only group / Query member assets
576       ----------------------------------------------------------
577       IF NVL(p_drill_down, 'N') <> 'Y' THEN
578 
579         -- Insert only group info into interface table
580         insert_data(l_info_rec, l_group_rec, l_member_rec);
581 
582         l_message := 'group loop (6)';
583 
584       ELSE
585         -- Query member assets that belong to the group
586         l_info_rec.member_query_mode := 'EXISTS';
587         query_member_assets(l_info_rec, l_group_rec);
588 
589         -- Query member assets that no longer belong to the group
590         l_info_rec.member_query_mode := 'NOT EXISTS';
591         query_member_assets(l_info_rec, l_group_rec);
592 
593       END IF; -- drill down y/n
594 
595     END LOOP;  -- group query loop
596     CLOSE l_group_csr;
597 
598 
599     l_info_rec.fiscal_year := l_info_rec.fiscal_year + 1;
600   END LOOP;  -- fiscal year loop
601 
602   IF g_print_debug THEN
603     fa_rx_util_pkg.debug('get_group_asset_info: '
604                          || 'farx_ga.get_group_asset_info()-');
605   END IF;
606 
607 EXCEPTION
608   WHEN OTHERS THEN
609     IF g_print_debug THEN
610       fa_rx_util_pkg.log(sqlcode);
611       fa_rx_util_pkg.log(sqlerrm);
612       fa_rx_util_pkg.log(l_message);
613     END IF;
614 
615     IF sqlcode <> 0 THEN
616       fa_rx_conc_mesg_pkg.log(sqlerrm);
617     END IF;
618 
619     IF l_group_csr%ISOPEN THEN
620       CLOSE l_group_csr;
621     END IF;
622     IF l_amount_csr%ISOPEN THEN
623       CLOSE l_amount_csr;
624     END IF;
625 
626     x_retcode := 2;
627     IF g_print_debug THEN
628       fa_rx_util_pkg.debug('get_group_asset_info: '
629                            || 'farx_ga.get_group_asset_info(EXCEPTION)-');
630     END IF;
631 
632 END get_group_asset_info;
633 
634 
635 -------------------------------------------------------------------
636 --
637 -- Function: get_category_sql
638 --   This function returns select clause and where clause for each
639 --   category.
640 --
641 -------------------------------------------------------------------
642 PROCEDURE get_category_sql (
643   p_application_id          IN  NUMBER,
644   p_category_flex_structure IN  NUMBER,
645   p_qualifier               IN  VARCHAR2,
646   p_category_low            IN  VARCHAR2,
647   p_category_high           IN  VARCHAR2,
648   x_select_stmt             OUT NOCOPY VARCHAR2,
649   x_where_stmt              OUT NOCOPY VARCHAR2)
650 IS
651 BEGIN
652   IF g_print_debug THEN
653     fa_rx_util_pkg.debug('get_category_sql: '
654                          || 'p_application_id: ' || p_application_id);
655     fa_rx_util_pkg.debug('get_category_sql: ' || 'p_category_flex_structure: '
656                          || p_category_flex_structure);
657     fa_rx_util_pkg.debug('get_category_sql: '
658                          || 'p_qualifier: ' || p_qualifier);
659     fa_rx_util_pkg.debug('get_category_sql: '
660                          || 'p_category_low: ' || p_category_low);
661     fa_rx_util_pkg.debug('get_category_sql: '
662                          || 'p_category_high: ' || p_category_high);
663   END IF;
664 
665 
666   -- Create select clause for category
667   IF p_qualifier IS NULL THEN
668     x_select_stmt := 'null';
669   ELSE
670     BEGIN
671       x_select_stmt :=
672         fa_rx_flex_pkg.flex_sql(p_application_id, 'CAT#',
673                                 p_category_flex_structure, 'cat',
674                                 'SELECT', p_qualifier);
675     EXCEPTION
676       WHEN OTHERS THEN
677         x_select_stmt := 'null';
678     END;
679   END IF;
680 
681 
682   -- Create where clause
683   IF p_category_low = p_category_high THEN
684     x_where_stmt := ' AND ' ||
685                     fa_rx_flex_pkg.flex_sql(
686                       p_application_id,
687                       'CAT#',
688                       p_category_flex_structure,
689                       'cat',
690                       'WHERE',
691                       p_qualifier,
692                       '=',
693                       p_category_low);
694 
695   ELSIF p_category_low IS NOT NULL AND p_category_high IS NOT NULL THEN
696     x_where_stmt := ' AND ' ||
697                     fa_rx_flex_pkg.flex_sql(
698                       p_application_id,
699                       'CAT#',
700                       p_category_flex_structure,
701                       'cat',
702                       'WHERE',
703                       p_qualifier,
704                       'BETWEEN',
705                       p_category_low,
706                       p_category_high);
707 
708   ELSIF p_category_low IS NOT NULL THEN
709     x_where_stmt := ' AND ' ||
710                     fa_rx_flex_pkg.flex_sql(
711                       p_application_id,
712                       'CAT#',
713                       p_category_flex_structure,
714                       'cat',
715                       'WHERE',
716                       p_qualifier,
717                       '>=',
718                       p_category_low);
719 
720   ELSIF p_category_high IS NOT NULL THEN
721     x_where_stmt := ' AND ' ||
722                     fa_rx_flex_pkg.flex_sql(
723                       p_application_id,
724                       'CAT#',
725                       p_category_flex_structure,
726                       'cat',
727                       'WHERE',
728                       p_qualifier,
729                       '<=',
730                       p_category_high);
731   END IF;
732 
733 EXCEPTION
734   WHEN OTHERS THEN
735     IF g_print_debug THEN
736       fa_rx_util_pkg.debug('get_category_sql: '
737                            || 'farx_ga.get_category_sql(EXCEPTION)-');
738     END IF;
739     raise;
740 END get_category_sql;
741 
742 
743 -------------------------------------------------------------------
744 --
745 -- Function: get_from_sql_stmt
746 --   This function returns from clause for group query and member
747 --   query.
748 --
749 -------------------------------------------------------------------
750 PROCEDURE get_from_sql_stmt (
751   p_info_rec           IN  info_rec_type,
752   p_group_asset_id     IN  NUMBER,
753   x_sql_stmt           OUT NOCOPY VARCHAR2)
754 IS
755 BEGIN
756 
757   -- Subquery is to get fa_books and fa_deprn_summary,
758   -- which are used to calculate beginning NBV.
759   -- Subquery doesn't necessarily get the previous year info.
760   -- If there was no depreciation calculation in the previous year,
761   -- subquery gets the max period counter prior to the fiscal year.
762 
763   x_sql_stmt := ' FROM
764     fa_additions ad,
765     fa_books bk,
766     fa_categories_b cat,
767     fa_deprn_basis_rules br,
768     fa_methods met,
769     fa_deprn_periods dp,
770     fa_deprn_summary ds,
771     ( SELECT bk_pre.asset_id,
772              bk_pre.group_asset_id,
773              bk_pre.cost,
774              bk_pre.cip_cost,
775              ds_pre.deprn_reserve
776         FROM fa_books bk_pre,
777              fa_deprn_summary ds_pre,
778              fa_deprn_periods dp_pre,
779              fa_additions ad_pre
780        WHERE bk_pre.book_type_code = ''' || p_info_rec.book_type_code || '''
781          AND dp_pre.book_type_code = bk_pre.book_type_code
782          AND dp_pre.period_counter + 1 = ' || p_info_rec.min_period_counter || '
783          AND dp_pre.period_close_date BETWEEN bk_pre.date_effective
784              AND NVL(bk_pre.date_ineffective, dp_pre.period_close_date)
785          AND ds_pre.book_type_code = bk_pre.book_type_code
786          AND ds_pre.asset_id = bk_pre.asset_id
787          AND ds_pre.period_counter = (
788              SELECT MAX(ds3.period_counter)
789                FROM fa_deprn_summary ds3
790               WHERE ds_pre.book_type_code = ds3.book_type_code
791                 AND ds_pre.asset_id = ds3.asset_id
792                 AND ds3.period_counter < ' || p_info_rec.min_period_counter || '
793          )
794          AND ad_pre.asset_id = bk_pre.asset_id ';
795 
796 
797   -- slightly different depends on whether it is for group or member
798   IF p_group_asset_id IS NULL THEN
799     x_sql_stmt := x_sql_stmt ||
800       'AND ad_pre.asset_type = ''GROUP'') prev ';
801   ELSE
802     x_sql_stmt := x_sql_stmt ||
803       'AND bk_pre.group_asset_id = ' || p_group_asset_id || ') prev ';
804   END IF;
805 
806 EXCEPTION
807   WHEN OTHERS THEN
808     IF g_print_debug THEN
809       fa_rx_util_pkg.debug('get_from_sql_stmt: '
810                            || 'farx_ga.get_from_sql_stmt(EXCEPTION)-');
811     END IF;
812     raise;
813 END get_from_sql_stmt;
814 
815 
816 -------------------------------------------------------------------
817 --
818 -- Function: get_where_sql_stmt
819 --   This function returns where clause for group query and member
820 --   query.
821 --
822 -------------------------------------------------------------------
823 PROCEDURE get_where_sql_stmt (
824   p_info_rec           IN  info_rec_type,
825   p_group_asset_id     IN  NUMBER,
826   x_sql_stmt           OUT NOCOPY VARCHAR2)
827 IS
828 BEGIN
829 
830   -- This where clause ges fa_books, which corresponds to
831   -- the last depreciated period in the fiscal year.
832 
833   -- This also gets fa_deprn_summary no matter what.
834   -- There is at least deprn_source_code = 'BOOKS' row for every asset.
835   -- fa_deprn_summary.period_counter will be the max period
836   -- including the current fiscal year.
837 
838   x_sql_stmt :=
839    'WHERE bk.book_type_code = ''' || p_info_rec.book_type_code || '''
840       AND bk.asset_id = ad.asset_id
841       AND ad.asset_category_id = cat.category_id
842       AND met.deprn_basis_rule_id = br.deprn_basis_rule_id (+)
843       AND bk.deprn_method_code = met.method_code
844       AND NVL(bk.life_in_months, 0) = NVL(met.life_in_months, 0)
845       AND dp.book_type_code = bk.book_type_code
846       AND dp.period_counter = ' || p_info_rec.max_period_counter || '
847       AND ((dp.period_close_date IS NULL
848             AND bk.date_ineffective IS NULL)
849        OR (dp.period_close_date BETWEEN bk.date_effective
850             AND NVL(bk.date_ineffective, dp.period_close_date)))
851       AND ds.book_type_code = bk.book_type_code
852       AND ds.asset_id = bk.asset_id
853       AND ds.period_counter = (
854           SELECT MAX(ds2.period_counter)
855             FROM fa_deprn_summary ds2
856            WHERE ds2.book_type_code = ds.book_type_code
857              AND ds2.asset_id = ds.asset_id
858              AND ds2.period_counter <= ' || p_info_rec.max_period_counter || ' )
859       AND bk.asset_id = prev.asset_id (+)';
860 
861 
862   -- slightly different depends on whether it is for group or member
863   IF p_group_asset_id IS NULL THEN
864     x_sql_stmt := x_sql_stmt ||
865       ' AND ad.asset_type = ''GROUP''';
866   ELSIF p_info_rec.member_query_mode = 'EXISTS' THEN
867     x_sql_stmt := x_sql_stmt ||
868       ' AND bk.group_asset_id = ' || p_group_asset_id ||
869       ' AND bk.asset_id = amt.asset_id (+)
870         AND bk.asset_id = ret.asset_id (+) ';
871   ELSE
872     x_sql_stmt := x_sql_stmt ||
873       ' AND prev.group_asset_id = ' || p_group_asset_id ||
874       ' AND NVL(bk.group_asset_id, -1) <> ' || p_group_asset_id ||
875       ' AND bk.asset_id = amt.asset_id (+)
876         AND bk.asset_id = ret.asset_id (+) ';
877   END IF;
878 
879 EXCEPTION
880   WHEN OTHERS THEN
881     IF g_print_debug THEN
882       fa_rx_util_pkg.debug('get_where_sql_stmt: '
883                            || 'farx_ga.get_where_sql_stmt(EXCEPTION)-');
884     END IF;
885     raise;
886 END get_where_sql_stmt;
887 
888 
889 -------------------------------------------------------------------
890 --
891 -- Function: get_trx_amount_sql
892 --   This function returns sql statement for addition, adjustment
893 --   and retirement query.
894 --
895 -------------------------------------------------------------------
896 PROCEDURE get_trx_amount_sql (
897   p_group_rec          IN  group_rec_type,
898   p_info_rec           IN  info_rec_type,
899   p_group_asset_id     IN  NUMBER,
900   x_sql_stmt           OUT NOCOPY VARCHAR2)
901 IS
902 BEGIN
903 
904   -- If it's group, need to query the following amount
905   -- to calculate reduced/regular depreciation amount.
906   --   1. recoverable cost of member asset added during the second
907   --      half of the fiscal year
908   --   2. adjustment amount occurred during the second half of the
909   --      fiscal year
910 
911   IF p_group_asset_id IS NULL THEN
912     x_sql_stmt := '
913       SELECT NVL(SUM(DECODE(
914         GREATEST(thm.transaction_date_entered, fy.mid_year_date),
915         thm.transaction_date_entered,
916         DECODE(adj.source_type_code || ''-'' || adj.adjustment_type
917                || ''-'' || adj.debit_credit_flag,
918                ''ADDITION-COST-DR'', ';
919 
920     IF p_group_rec.deprn_basis_rule = fa_std_types.FAD_DBR_NBV
921        AND NVL(p_group_rec.exclude_salvage_value_flag, 'NO') = 'YES' THEN
922       x_sql_stmt := x_sql_stmt || '
923                     bkm.recoverable_cost + bkm.salvage_value,
924                     0), 0)), 0) second_half_add_rec_cost, ';
925     ELSE
926       x_sql_stmt := x_sql_stmt || '
927                     bkm.recoverable_cost,
928                     0), 0)), 0) second_half_add_rec_cost, ';
929     END IF;
930 
931     x_sql_stmt := x_sql_stmt || '
932       NVL(SUM(DECODE(GREATEST(thm.transaction_date_entered, fy.mid_year_date),
933           thm.transaction_date_entered, DECODE(adj.adjustment_type,
934           ''COST'',
935             DECODE(adj.source_type_code,
936                    ''ADDITION'', 0,
937                    ''RETIREMENT'', 0,
938                    DECODE(adj.debit_credit_flag,
939                           ''DR'', adj.adjustment_amount,
940                           ''CR'', -adj.adjustment_amount,
941                           0)),
942           ''CIP COST'',
943             DECODE(adj.source_type_code,
944                    ''ADDITION'', 0,
945                    ''RETIREMENT'', 0,
946                    DECODE(adj.debit_credit_flag,
947                           ''DR'', adj.adjustment_amount,
948                           ''CR'', -adj.adjustment_amount,
949                           0)), 0), 0)), 0)
950       second_half_mem_adjustment, ';
951 
952   ELSE
953     x_sql_stmt := '(SELECT adj.asset_id, ';
954   END IF;
955 
956 
957   -- Query transactions that occurred during the fiscal year.
958   -- (includeing back dated transactions)
959   -- but exclude transanctions that happened during the open period
960   -- (even if it's back dated one.)
961   -- Note: cip adjustment is treated as addition (class 90)
962 
963   x_sql_stmt := x_sql_stmt || '
964     NVL(SUM(DECODE(GREATEST(thm.transaction_date_entered, fy.mid_year_date),
965       thm.transaction_date_entered,
966       DECODE(adj.source_type_code || ''-'' || adj.adjustment_type || ''-''
967                 || adj.debit_credit_flag,
968               ''ADDITION-COST-DR'', adj.adjustment_amount,
969               ''ADDITION-COST-CR'', -adj.adjustment_amount,
970               ''CIP ADDITION-COST-DR'', adj.adjustment_amount,
971               ''CIP ADDITION-COST-CR'', -adj.adjustment_amount,
972               ''CIP ADJUSTMENT-COST-DR'', adj.adjustment_amount,
973               0), 0)), 0)
974       second_half_addition,
975     NVL(SUM(DECODE(adj.source_type_code || ''-'' || adj.adjustment_type
976       || ''-'' || adj.debit_credit_flag,
977       ''ADDITION-COST-DR'', adj.adjustment_amount,
978       ''ADDITION-COST-CR'', -adj.adjustment_amount,
979       ''CIP ADDITION-CIP COST-DR'', adj.adjustment_amount,
980       ''CIP ADDITION-CIP COST-CR'', -adj.adjustment_amount,
981       ''CIP ADJUSTMENT-CIP COST-DR'', adj.adjustment_amount,
982       0)), 0)
983       addition_amount,
984     NVL(SUM(DECODE(adj.adjustment_type || ''-'' || adj.debit_credit_flag,
985       ''COST-DR'', adj.adjustment_amount,
986       ''COST-CR'', -adj.adjustment_amount,
987       ''CIP COST-DR'', adj.adjustment_amount,
988       ''CIP COST-CR'', -adj.adjustment_amount, 0)), 0)
989       adjustment_amount
990    FROM fa_adjustments adj,
991         fa_book_controls bc,
992         fa_fiscal_year fy,
993         fa_transaction_headers thm,
994         fa_books bkm
995   WHERE bkm.group_asset_id = ' || p_group_rec.asset_id || '
996     AND adj.asset_id = bkm.asset_id
997     AND bkm.transaction_header_id_in = thm.transaction_header_id
998     AND adj.book_type_code = ''' || p_info_rec.book_type_code || '''
999     AND adj.period_counter_created
1000         BETWEEN ' || p_info_rec.min_period_counter ||
1001         ' and ' || p_info_rec.max_period_counter || '
1002     AND adj.transaction_header_id = thm.transaction_header_id
1003     AND fy.fiscal_year = ' || p_info_rec.fiscal_year || '
1004     AND fy.fiscal_year_name = bc.fiscal_year_name
1005     AND bc.book_type_code = adj.book_type_code ';
1006 
1007   IF p_group_asset_id IS NOT NULL THEN
1008     x_sql_stmt := x_sql_stmt || 'GROUP BY adj.asset_id) amt ';
1009   END IF;
1010 
1011 EXCEPTION
1012   WHEN OTHERS THEN
1013     IF g_print_debug THEN
1014       fa_rx_util_pkg.debug('get_trx_amount_sql: '
1015                            || 'farx_ga.get_trx_amount_sql(EXCEPTION)-');
1016     END IF;
1017     raise;
1018 END get_trx_amount_sql;
1019 
1020 
1021 
1022 -------------------------------------------------------------------
1023 --
1024 -- Function: get_retirement_sql
1025 --   This function returns sql statement for retirement amount
1026 --   for member assets.
1027 --
1028 -------------------------------------------------------------------
1029 PROCEDURE get_retirement_sql (
1030   p_info_rec           IN  info_rec_type,
1031   p_group_asset_id     IN  NUMBER,
1032   x_sql_stmt           OUT NOCOPY VARCHAR2)
1033 IS
1034 BEGIN
1035   x_sql_stmt := '(SELECT ret.asset_id,
1036     NVL(SUM(ret.proceeds_of_sale), 0) proceeds_of_sale,
1037     NVL(SUM(ret.cost_of_removal), 0) cost_of_removal,
1038     NVL(SUM(ret.cost_retired), 0) cost_retired,
1039     NVL(SUM(ret.reserve_retired), 0) reserve_retired
1040    FROM fa_retirements ret,
1041         fa_book_controls bc,
1042         fa_fiscal_year fy,
1043         fa_transaction_headers thm,
1044         fa_books bkm
1045   WHERE bkm.group_asset_id = ' || p_group_asset_id || '
1046     AND bc.book_type_code = ''' || p_info_rec.book_type_code || '''
1047     AND fy.fiscal_year = ' || p_info_rec.fiscal_year || '
1048     AND fy.fiscal_year_name = bc.fiscal_year_name
1049     AND thm.book_type_code = bc.book_type_code
1050     AND bkm.book_type_code = bc.book_type_code
1051     AND thm.transaction_date_entered
1052         BETWEEN fy.start_date and fy.end_date
1053     AND ret.asset_id = thm.asset_id
1054     AND bkm.asset_id = thm.asset_id
1055     AND bkm.transaction_header_id_in = thm.transaction_header_id
1056     AND ret.transaction_header_id_in = thm.transaction_header_id
1057     AND ret.status <> ''DELETED''
1058   GROUP BY ret.asset_id) ret ';
1059 
1060 EXCEPTION
1061   WHEN OTHERS THEN
1062     IF g_print_debug THEN
1063       fa_rx_util_pkg.debug('get_retirement_sql: '
1064                            || 'farx_ga.get_retirement_sql(EXCEPTION)-');
1065     END IF;
1066     raise;
1067 END get_retirement_sql;
1068 
1069 
1070 -------------------------------------------------------------------
1071 --
1072 -- Function: insert_data
1073 --   This function inserts data into fa_group_rep_itf.
1074 --
1075 -------------------------------------------------------------------
1076 PROCEDURE insert_data (
1077   p_info_rec                  IN  info_rec_type,
1078   p_group_rec                 IN  group_rec_type,
1079   p_member_rec                IN  group_rec_type)
1080 IS
1081 BEGIN
1082   INSERT INTO fa_group_rep_itf (
1083       request_id, created_by, creation_date,
1084       last_updated_by, last_update_date, last_update_login,
1085       organization_name, functional_currency_code,
1086       set_of_books_id, book_type_code, deprn_calendar, fiscal_year,
1087       grp_asset_number, grp_description, grp_asset_type,
1088       grp_major_category, grp_minor_category, grp_other_category,
1089       grp_date_placed_in_service, grp_deprn_method_code,
1090       grp_rule_name, grp_tracking_method,
1091       grp_adjusted_rate, grp_life_year_month,
1092       grp_cost, grp_salvage_value,
1093       grp_adjusted_recoverable_cost, grp_beginning_nbv,
1094       grp_first_half_addition, grp_second_half_addition,
1095       grp_addition_amount, grp_adjustment_amount,
1096       grp_net_proceeds, grp_proceeds_of_sale, grp_cost_of_removal,
1097       grp_cost_retired, grp_reserve_retired,
1098       grp_recapture_amount, grp_terminal_gain_loss_amount,
1099       grp_nbv_before_deprn, grp_deprn_basis_adjustment,
1100       grp_reduced_nbv,
1101       grp_regular_deprn_amount, grp_reduced_deprn_amount,
1102       grp_annual_deprn_amount, grp_deprn_reserve, grp_ending_nbv,
1103       mem_asset_number, mem_description, mem_asset_type,
1104       mem_major_category, mem_minor_category, mem_other_category,
1105       mem_date_placed_in_service, mem_deprn_method_code,
1106       mem_rule_name, mem_adjusted_rate, mem_life_year_month,
1107       mem_cost, mem_salvage_value,
1108       mem_adjusted_recoverable_cost, mem_beginning_nbv,
1109       mem_first_half_addition, mem_second_half_addition,
1110       mem_addition_amount, mem_adjustment_amount,
1111       mem_net_proceeds, mem_proceeds_of_sale, mem_cost_of_removal,
1112       mem_cost_retired, mem_reserve_retired,
1113       mem_nbv_before_deprn, mem_deprn_basis_adjustment,
1114       mem_reduced_nbv,
1115       mem_annual_deprn_amount, mem_deprn_reserve, mem_ending_nbv,
1116       mem_status
1117   ) VALUES (
1118       p_info_rec.request_id, p_info_rec.user_id, sysdate,
1119       p_info_rec.user_id, sysdate, p_info_rec.user_id,
1120       p_info_rec.organization_name, p_info_rec.functional_currency_code,
1121       p_info_rec.set_of_books_id, p_info_rec.book_type_code,
1122       p_info_rec.deprn_calendar, p_info_rec.fiscal_year,
1123       p_group_rec.asset_number,
1124       p_group_rec.description,
1125       p_group_rec.asset_type,
1126       p_group_rec.major_category,
1127       p_group_rec.minor_category,
1128       p_group_rec.other_category,
1129       p_group_rec.date_placed_in_service,
1130       p_group_rec.deprn_method_code,
1131       p_group_rec.rule_name,
1132       p_group_rec.tracking_method,
1133       p_group_rec.adjusted_rate,
1134       p_group_rec.life_year_month,
1135       p_group_rec.cost,
1136       p_group_rec.salvage_value,
1137       p_group_rec.adjusted_recoverable_cost,
1138       p_group_rec.beginning_nbv,
1139       p_group_rec.first_half_addition,
1140       p_group_rec.second_half_addition,
1141       p_group_rec.addition_amount,
1142       p_group_rec.adjustment_amount,
1143       p_group_rec.net_proceeds,
1144       p_group_rec.proceeds_of_sale,
1145       p_group_rec.cost_of_removal,
1146       p_group_rec.cost_retired,
1147       p_group_rec.reserve_retired,
1148       p_group_rec.recapture_amount,
1149       p_group_rec.terminal_gain_loss_amount,
1150       p_group_rec.nbv_before_deprn,
1151       p_group_rec.deprn_basis_adjustment,
1152       p_group_rec.reduced_nbv,
1153       p_group_rec.regular_deprn_amount,
1154       p_group_rec.reduced_deprn_amount,
1155       p_group_rec.annual_deprn_amount,
1156       p_group_rec.deprn_reserve,
1157       p_group_rec.ending_nbv,
1158       p_member_rec.asset_number,
1159       p_member_rec.description,
1160       p_member_rec.asset_type,
1161       p_member_rec.major_category,
1162       p_member_rec.minor_category,
1163       p_member_rec.other_category,
1164       p_member_rec.date_placed_in_service,
1165       p_member_rec.deprn_method_code,
1166       p_member_rec.rule_name,
1167       p_member_rec.adjusted_rate,
1168       p_member_rec.life_year_month,
1169       p_member_rec.cost,
1170       p_member_rec.salvage_value,
1171       p_member_rec.adjusted_recoverable_cost,
1172       p_member_rec.beginning_nbv,
1173       p_member_rec.first_half_addition,
1174       p_member_rec.second_half_addition,
1175       p_member_rec.addition_amount,
1176       p_member_rec.adjustment_amount,
1177       p_member_rec.net_proceeds,
1178       p_member_rec.proceeds_of_sale,
1179       p_member_rec.cost_of_removal,
1180       p_member_rec.cost_retired,
1181       p_member_rec.reserve_retired,
1182       p_member_rec.nbv_before_deprn,
1183       p_member_rec.deprn_basis_adjustment,
1184       p_member_rec.reduced_nbv,
1185       p_member_rec.annual_deprn_amount,
1186       p_member_rec.deprn_reserve,
1187       p_member_rec.ending_nbv,
1188       p_member_rec.status);
1189 
1190 EXCEPTION
1191   WHEN OTHERS THEN
1192     IF g_print_debug THEN
1193       fa_rx_util_pkg.debug('insert_data: '
1194                            || 'farx_ga.insert_data(EXCEPTION)-');
1195     END IF;
1196     raise;
1197 END insert_data;
1198 
1199 
1200 -------------------------------------------------------------------
1201 --
1202 -- Function: query_member_assets
1203 --   This function queries member assets.
1204 --
1205 -------------------------------------------------------------------
1206 PROCEDURE query_member_assets (
1207   p_info_rec         IN  info_rec_type,
1208   p_group_rec        IN  group_rec_type)
1209 IS
1210   l_message          VARCHAR2(30);
1211   l_member_sql_stmt  VARCHAR2(10000);
1212   l_sql_stmt         VARCHAR2(5000);
1213 
1214   l_group_reclass_in  NUMBER;
1215   l_group_reclass_out NUMBER;
1216 
1217   TYPE group_csrtype IS REF CURSOR;
1218   l_member_csr       group_csrtype;
1219   l_member_rec       group_rec_type;
1220 BEGIN
1221   ---------------------------------------------------
1222   -- <Member query loop>
1223   -- Query member assets belong to the group
1224   ---------------------------------------------------
1225   l_message := 'member loop (1)';
1226 
1227   -- Create query for member asset
1228   --   Don't use asset_type to identify cost or cip_cost because
1229   --   you cannot get right amount once the asset is capitalized
1230 
1231   l_member_sql_stmt :=
1232     'SELECT
1233       ad.asset_number,
1234       ad.description,
1235       ad.asset_type, '
1236       || p_info_rec.major_cat_select_stmt || ','
1237       || p_info_rec.minor_cat_select_stmt || ','
1238       || p_info_rec.other_cat_select_stmt || ',
1239       bk.date_placed_in_service,
1240       bk.deprn_method_code,
1241       br.rule_name,
1242       NULL,
1243       bk.adjusted_rate,
1244       NULL,
1245       NVL(bk.cost, 0) + NVL(bk.cip_cost, 0),
1246       NVL(bk.salvage_value, 0),
1247       NVL(bk.adjusted_recoverable_cost, 0),
1248       NVL(prev.cost, 0) + NVL(prev.cip_cost, 0) - NVL(prev.deprn_reserve, 0),
1249       NULL,
1250       NVL(amt.second_half_addition, 0),
1251       NVL(amt.addition_amount, 0),
1252       NVL(amt.adjustment_amount, 0),
1253       NULL,
1254       NVL(ret.proceeds_of_sale, 0),
1255       NVL(ret.cost_of_removal, 0),
1256       NVL(ret.cost_retired, 0),
1257       NVL(ret.reserve_retired, 0),
1258       NULL, NULL, NULL, NULL,
1259       NVL(ds.adjusted_cost, 0),
1260       NULL, NULL,
1261       NVL(ds.ytd_deprn, 0),
1262       NVL(ds.deprn_reserve,  0),
1263       NULL, NULL,
1264       ad.asset_id,
1265       prev.group_asset_id,
1266       DECODE(bk.life_in_months, NULL, NULL,
1267         TO_CHAR(FLOOR(bk.life_in_months / 12)) || ''.'' ||
1268         TO_CHAR(MOD(bk.life_in_months, 12))),
1269       met.deprn_basis_rule,
1270       met.exclude_salvage_value_flag,
1271       NULL, NULL, NULL, NULL,
1272       bk.period_counter_fully_retired,
1273       bk.period_counter_fully_reserved,
1274       ds.period_counter ';
1275 
1276   l_message := 'member loop (2)';
1277 
1278   -- Add from clause
1279   get_from_sql_stmt(p_info_rec, p_group_rec.asset_id, l_sql_stmt);
1280   l_member_sql_stmt := l_member_sql_stmt || l_sql_stmt || ', ';
1281 
1282   get_trx_amount_sql(p_group_rec, p_info_rec,
1283                      p_group_rec.asset_id, l_sql_stmt);
1284   l_member_sql_stmt := l_member_sql_stmt || l_sql_stmt || ', ';
1285 
1286   get_retirement_sql(p_info_rec, p_group_rec.asset_id, l_sql_stmt);
1287   l_member_sql_stmt := l_member_sql_stmt || l_sql_stmt;
1288 
1289   -- Add where clause
1290   get_where_sql_stmt(p_info_rec, p_group_rec.asset_id, l_sql_stmt);
1291   l_member_sql_stmt := l_member_sql_stmt || l_sql_stmt;
1292 
1293   -- Exclude assets which became fully retired before this FY
1294   -- (adjusted cost > 0 is for Canada's class 13)
1295   IF NVL(p_group_rec.recognize_gain_loss, 'NO') = 'YES' THEN
1296     l_member_sql_stmt := l_member_sql_stmt
1297         || ' AND NVL(bk.period_counter_fully_retired,'
1298         || p_info_rec.min_period_counter
1299         || ') >= ' || p_info_rec.min_period_counter
1300         || ' AND bk.adjusted_cost > 0 ';
1301   END IF;
1302 
1303   l_message := 'member loop (3)';
1304 
1305 
1306   -- Member query loop start
1307   OPEN l_member_csr FOR l_member_sql_stmt;
1308   LOOP
1309     FETCH l_member_csr INTO l_member_rec;
1310     EXIT WHEN l_member_csr%NOTFOUND;
1311 
1312     l_message := 'member loop (4)';
1313 
1314     ---------------------------------------------------
1315     -- query group reclass amounts
1316     ---------------------------------------------------
1317     l_group_reclass_in := 0;
1318     l_group_reclass_out := 0;
1319 
1320     -- Asset that no longer belongs to the group
1321     IF p_info_rec.member_query_mode = 'NOT EXISTS' THEN
1322       l_message := 'member loop (4-1)';
1323 
1324       BEGIN
1325         SELECT NVL(bkm.cost, 0) - NVL(adj.adjustment_amount, 0)
1326           INTO l_group_reclass_out
1327           FROM fa_adjustments adj,
1328                fa_transaction_headers thg,
1329                fa_books bkm
1330          WHERE adj.asset_id = p_group_rec.asset_id
1331            AND adj.book_type_code = p_info_rec.book_type_code
1332            AND thg.transaction_header_id = adj.transaction_header_id
1333            AND adj.period_counter_created
1334                BETWEEN p_info_rec.min_period_counter
1335                    and p_info_rec.max_period_counter
1336            AND adj.source_type_code = 'ADJUSTMENT'
1337            AND adj.adjustment_type = 'RESERVE'
1338            AND thg.member_transaction_header_id = bkm.transaction_header_id_in
1339            AND NVL(bkm.group_asset_id, -1) <> p_group_rec.asset_id
1340            AND bkm.asset_id = l_member_rec.asset_id;
1341 
1342       EXCEPTION
1343         WHEN OTHERS THEN
1344           null;
1345       END;
1346       l_message := 'member loop (4-2)';
1347 
1348       l_member_rec.cost := 0;
1349       l_member_rec.salvage_value := 0;
1350       l_member_rec.adjusted_recoverable_cost := 0;
1351       l_member_rec.reduced_nbv := 0;
1352       l_member_rec.annual_deprn_amount := 0;
1353       l_member_rec.deprn_reserve := 0;
1354 
1355     -- standalone/other group -> this group
1356     ELSIF l_member_rec.addition_amount = 0
1357       AND NVL(l_member_rec.pre_group_asset_id, -1) <> p_group_rec.asset_id THEN
1358       l_message := 'member loop (4-3)';
1359 
1360       BEGIN
1361         SELECT NVL(bkm.cost, 0) - NVL(adj.adjustment_amount, 0)
1362           INTO l_group_reclass_in
1363           FROM fa_adjustments adj,
1364                fa_transaction_headers thg,
1365                fa_books bkm
1366          WHERE adj.asset_id = p_group_rec.asset_id
1367            AND adj.book_type_code = p_info_rec.book_type_code
1368            AND thg.transaction_header_id = adj.transaction_header_id
1369            AND adj.period_counter_created
1370                BETWEEN p_info_rec.min_period_counter
1371                    and p_info_rec.max_period_counter
1372            AND adj.source_type_code = 'ADJUSTMENT'
1373            AND adj.adjustment_type = 'RESERVE'
1374            AND thg.member_transaction_header_id = bkm.transaction_header_id_in
1375            AND NVL(bkm.group_asset_id, -1) = p_group_rec.asset_id;
1376 
1377       EXCEPTION
1378         WHEN OTHERS THEN
1379           null;
1380       END;
1381       l_message := 'member loop (4-4)';
1382     END IF;
1383 
1384 
1385     ---------------------------------------------------
1386     -- Calculate and set each column
1387     ---------------------------------------------------
1388     -- Convert life_year_month to number
1389     l_member_rec.life_year_month :=
1390       fnd_number.canonical_to_number(l_member_rec.life_year_month_string);
1391 
1392     -- Addition during first/second half of the fiscal year
1393     -- Note: checking group's depreciable basis rule.
1394     IF NVL(p_group_rec.rule_name, ' ') <> FA_RXGA_HALF_YEAR_RULE THEN
1395       l_member_rec.first_half_addition := NULL;
1396       l_member_rec.second_half_addition := NULL;
1397     ELSE
1398       l_member_rec.first_half_addition :=
1399         l_member_rec.addition_amount - l_member_rec.second_half_addition;
1400     END IF;
1401 
1402     -- Adjustment amount
1403     --  = member level COST/CIP COST transactions
1404     --    - (member additions + member retirement)
1405     --    + group reclass amounts
1406     l_member_rec.adjustment_amount := l_member_rec.adjustment_amount
1407         - (l_member_rec.addition_amount - l_member_rec.cost_retired)
1408         + (l_group_reclass_in - l_group_reclass_out);
1409 
1410     -- Net proceeds
1411     IF NVL(p_group_rec.exclude_proceeds_from_basis, 'N') = 'Y' THEN
1412       -- Set proceeds = 0 for class 10.1
1413       l_member_rec.net_proceeds := 0;
1414     ELSE
1415       l_member_rec.net_proceeds :=
1416         l_member_rec.proceeds_of_sale - l_member_rec.cost_of_removal;
1417     END IF;
1418 
1419 
1420     IF p_group_rec.tracking_method IS NULL then
1421 
1422       -- Set NULL to depreciation amount related columns
1423       -- when member tracking is off
1424       l_member_rec.beginning_nbv := NULL;
1425       l_member_rec.nbv_before_deprn := NULL;
1426       l_member_rec.deprn_basis_adjustment := NULL;
1427       l_member_rec.reduced_nbv := NULL;
1428       l_member_rec.annual_deprn_amount := NULL;
1429       l_member_rec.deprn_reserve := NULL;
1430       l_member_rec.ending_nbv := NULL;
1431       l_member_rec.deprn_method_code := NULL;
1432       l_member_rec.rule_name := NULL;
1433       l_member_rec.adjusted_rate := NULL;
1434       l_member_rec.life_year_month := NULL;
1435 
1436     ELSE
1437       -- Set group's method if tracking is not calculated by member method
1438       IF NOT (NVL(p_group_rec.tracking_method, '') = 'CALCULATE'
1439         AND NVL(p_group_rec.depreciation_option, '') = 'MEMBER') THEN
1440         l_member_rec.deprn_method_code := p_group_rec.deprn_method_code;
1441         l_member_rec.rule_name := p_group_rec.rule_name;
1442         l_member_rec.adjusted_rate := p_group_rec.adjusted_rate;
1443         l_member_rec.life_year_month := p_group_rec.life_year_month;
1444         l_member_rec.deprn_basis_rule := p_group_rec.deprn_basis_rule;
1445         l_member_rec.exclude_salvage_value_flag := p_group_rec.exclude_salvage_value_flag;
1446       END IF;
1447 
1448       -- Group reclass is treated like an addition to the group
1449       IF NVL(l_member_rec.pre_group_asset_id, 0) <> p_group_rec.asset_id THEN
1450         l_member_rec.beginning_nbv := 0;
1451       END IF;
1452 
1453       -- NBV before depreciation
1454       l_member_rec.nbv_before_deprn
1455         := l_member_rec.beginning_nbv + l_member_rec.addition_amount
1456          + l_member_rec.adjustment_amount - l_member_rec.net_proceeds;
1457 
1458       -- Annual depreciation amount
1459       -- (Set zero if there was no depreciation during the fiscal year)
1460       IF l_member_rec.max_period_counter < p_info_rec.min_period_counter THEN
1461         l_member_rec.annual_deprn_amount := 0;
1462       END IF;
1463 
1464 
1465       -- Reduced NBV / Deprn basis adjustment
1466       -- (only applicable for 50% rule)
1467       IF NOT (NVL(p_group_rec.rule_name, ' ')
1468           IN (FA_RXGA_POSITIVE_REDUCTION, FA_RXGA_HALF_YEAR_RULE)) THEN
1469         l_member_rec.deprn_basis_adjustment := NULL;
1470         l_member_rec.reduced_nbv := NULL;
1471 
1472       ELSIF l_member_rec.max_period_counter < p_info_rec.min_period_counter THEN
1473         -- Set zero if there was no depreciation during the fiscal year
1474         l_member_rec.deprn_basis_adjustment := 0;
1475         l_member_rec.reduced_nbv := 0;
1476 
1477       ELSE
1478         -- Reduced NBV (adjusted cost has already been set)
1479         IF l_member_rec.deprn_basis_rule = fa_std_types.FAD_DBR_NBV
1480            AND NVL(l_member_rec.exclude_salvage_value_flag, 'NO') = 'YES' THEN
1481           l_member_rec.reduced_nbv :=
1482               l_member_rec.reduced_nbv + l_member_rec.salvage_value;
1483         END IF;
1484 
1485         -- Depreciable basis adjustment
1486         l_member_rec.deprn_basis_adjustment :=
1487           l_member_rec.nbv_before_deprn - l_member_rec.reduced_nbv;
1488       END IF;
1489 
1490       -- Endign NBV
1491       l_member_rec.ending_nbv := l_member_rec.cost - l_member_rec.deprn_reserve;
1492 
1493     END IF;
1494 
1495     -- status
1496     -- bug #2846290
1497     IF NVL(l_member_rec.period_counter_fully_retired,
1498            p_info_rec.max_period_counter + 1) <= p_info_rec.max_period_counter THEN
1499       l_member_rec.status := 'FULLY RETIRED';
1500     ELSIF NVL(l_member_rec.period_counter_fully_reserved,
1501               p_info_rec.max_period_counter + 1) <= p_info_rec.max_period_counter THEN
1502       l_member_rec.status := 'FULLY RESERVED';
1503     END IF;
1504 
1505     l_message := 'member loop (5)';
1506 
1507 
1508     -- Insert into interface table
1509     insert_data(p_info_rec, p_group_rec, l_member_rec);
1510 
1511     l_message := 'member loop (6)';
1512 
1513   END LOOP;  -- member query loop
1514   CLOSE l_member_csr;
1515 
1516 EXCEPTION
1517   WHEN OTHERS THEN
1518     IF g_print_debug THEN
1519       fa_rx_util_pkg.log(sqlcode);
1520       fa_rx_util_pkg.log(sqlerrm);
1521       fa_rx_util_pkg.log(l_message);
1522       fa_rx_util_pkg.debug('query_member_assets: '
1523                            || 'farx_ga.query_member_assets(EXCEPTION)-');
1524     END IF;
1525 
1526     IF sqlcode <> 0 THEN
1527       fa_rx_conc_mesg_pkg.log(sqlerrm);
1528     END IF;
1529 
1530     fnd_message.set_name('OFA', l_message);
1531     IF l_message = 'FA_SHARED_INSERT_FAIL' THEN
1532       fnd_message.set_token('TABLE', 'FA_GROUP_REP_ITF');
1533     END IF;
1534     fa_rx_conc_mesg_pkg.log(fnd_message.get);
1535 
1536     IF l_member_csr%ISOPEN THEN
1537       CLOSE l_member_csr;
1538     END IF;
1539 
1540     raise;
1541 END query_member_assets;
1542 
1543 
1544 END FA_RX_GROUP;