DBA Data[Home] [Help]

PACKAGE BODY: APPS.FA_MASS_RECLASS_PKG

Source


1 PACKAGE BODY FA_MASS_RECLASS_PKG AS
2 /* $Header: FAXMRCLB.pls 120.15 2009/04/16 14:59:57 bridgway ship $ */
3 
4 -- Mass reclass record from fa_mass_reclass table.
5 mr_rec     FA_MASS_REC_UTILS_PKG.mass_reclass_rec;
6 
7 g_log_level_rec fa_api_types.log_level_rec_type;
8 
9 /*====================================================================================+
10 |   PROCEDURE Do_Mass_Reclass                                                         |
11 +=====================================================================================*/
12 
13 
14 PROCEDURE Do_Mass_Reclass(
15                 p_mass_reclass_id    IN     NUMBER,
16                 p_parent_request_id  IN     NUMBER,
17                 p_total_requests     IN     NUMBER,
18                 p_request_number     IN     NUMBER,
19                 px_max_asset_id      IN OUT NOCOPY NUMBER,
20                 x_processed_count       OUT NOCOPY NUMBER,
21                 x_success_count         OUT NOCOPY number,
22                 x_failure_count         OUT NOCOPY number,
23                 x_return_status         OUT NOCOPY number) IS
24 
25    -- cursor to fetch mass reclass record from fa_mass_reclass
26    CURSOR mass_reclass IS
27    SELECT mr.mass_reclass_id,
28           mr.book_type_code,
29           mr.transaction_date_entered,
30           mr.concurrent_request_id,
31           mr.status,
32           mr.asset_type,
33           mr.location_id,
34           mr.employee_id,
35           mr.asset_key_id,
36           mr.from_cost,
37           mr.to_cost,
38           mr.from_asset_number,
39           mr.to_asset_number,
40           mr.from_date_placed_in_service,
41           mr.to_date_placed_in_service,
42           mr.from_category_id,
43           mr.to_category_id,
44           mr.segment1_low, mr.segment2_low, mr.segment3_low, mr.segment4_low,
45           mr.segment5_low, mr.segment6_low, mr.segment7_low, mr.segment8_low,
46           mr.segment9_low, mr.segment10_low, mr.segment11_low, mr.segment12_low,
47           mr.segment13_low, mr.segment14_low, mr.segment15_low, mr.segment16_low,
48           mr.segment17_low, mr.segment18_low, mr.segment19_low, mr.segment20_low,
49           mr.segment21_low, mr.segment22_low, mr.segment23_low, mr.segment24_low,
50           mr.segment25_low, mr.segment26_low, mr.segment27_low, mr.segment28_low,
51           mr.segment29_low, mr.segment30_low,
52           mr.segment1_high, mr.segment2_high, mr.segment3_high, mr.segment4_high,
53           mr.segment5_high, mr.segment6_high, mr.segment7_high, mr.segment8_high,
54           mr.segment9_high, mr.segment10_high, mr.segment11_high, mr.segment12_high,
55           mr.segment13_high, mr.segment14_high, mr.segment15_high, mr.segment16_high,
56           mr.segment17_high, mr.segment18_high, mr.segment19_high, mr.segment20_high,
57           mr.segment21_high, mr.segment22_high, mr.segment23_high, mr.segment24_high,
58           mr.segment25_high, mr.segment26_high, mr.segment27_high, mr.segment28_high,
59           mr.segment29_high, mr.segment30_high,
60           mr.include_fully_rsvd_flag,
61           mr.copy_cat_desc_flag,
62           mr.inherit_deprn_rules_flag,
63           mr.amortize_flag,
64           mr.created_by,
65           mr.creation_date,
66           mr.last_updated_by,
67           mr.last_update_login,
68           mr.last_update_date
69      FROM fa_mass_reclass mr
70     WHERE mass_reclass_id = p_mass_reclass_Id;
71 
72    -- assets that meet the user's selection criteria.
73    -- some assets selected by this cursor are discarded in the validation engine.
74    CURSOR mass_reclass_assets IS
75    SELECT ad.asset_id,
76           ad.asset_number,
77           ad.asset_category_id,
78           dh.assigned_to
79      FROM gl_code_combinations     gc,
80           fa_distribution_history  dh,
81           fa_book_controls         bc,
82           fa_books                 bk,
83           fa_additions_b           ad
84     WHERE ad.asset_type = nvl(mr_rec.asset_type, ad.asset_type)
85       AND ad.asset_number >= nvl(mr_rec.from_asset_number, ad.asset_number)
86       AND ad.asset_number <= nvl(mr_rec.to_asset_number, ad.asset_number)
87       AND nvl(ad.asset_key_ccid, -9999)  = nvl(mr_rec.asset_key_id,
88                                                nvl(ad.asset_key_ccid, -9999))
89       AND ad.asset_category_id = nvl(mr_rec.from_category_id, ad.asset_category_id)
90       AND bk.book_type_code = mr_rec.book_type_code
91       AND bk.book_type_code = bc.book_type_code
92       -- corp book should be currently effective.
93       AND nvl(bc.date_ineffective, sysdate+1) > sysdate
94       AND bk.asset_id = ad.asset_id
95       AND nvl(bk.disabled_flag, 'N') = 'N' --HH
96       AND bk.date_ineffective IS NULL -- pick the most recent row.
97       -- dpis, exp acct, employee, location, cost range: selection criteria
98       -- for corporate book only.
99       AND bk.date_placed_in_service >= nvl(mr_rec.from_dpis,
100                                            bk.date_placed_in_service)
101       AND bk.date_placed_in_service <= nvl(mr_rec.to_dpis,
102                                            bk.date_placed_in_service)
103       AND bk.cost >= nvl(mr_rec.from_cost, bk.cost)
104       AND bk.cost <= nvl(mr_rec.to_cost, bk.cost)
105       AND dh.asset_id = ad.asset_id
106       AND nvl(dh.assigned_to, -9999) = nvl(mr_rec.employee_id, nvl(dh.assigned_to, -9999))
107       AND dh.location_id = nvl(mr_rec.location_id, dh.location_id)
108       AND dh.date_ineffective IS NULL -- pick only the active distributions.
109       AND dh.code_combination_id = gc.code_combination_id
110       -- more check is done on retired asset in reclass validation engine.
111       -- more check is done on reserved asset in Check_Criteria function.
112       AND bk.period_counter_fully_retired IS NULL
113       -- cannot avoid the use of OR, since gc.segment1 can be null.
114       -- cannot use nvl(gc.segment1, 'NULL') for comparison, since
115       -- the value 'NULL' may fall between the range accidentally.
116       -- may break the OR to UNION later.
117       -- rule-based optimizer transforms OR to UNION ALL automatically
118       -- when it sees it being more efficient.  since the columns
119       -- in OR are not indexed, transforming to UNION ALL has
120       -- no gain in performance and using OR is unavoidable here
121       -- for the correctness of the program.
122       AND ((gc.segment1 between nvl(mr_rec.segment1_low, gc.segment1)
123                      and nvl(mr_rec.segment1_high, gc.segment1)) OR
124            (mr_rec.segment1_low IS NULL and mr_rec.segment1_high IS NULL))
125       AND ((gc.segment2 between nvl(mr_rec.segment2_low, gc.segment2)
126                      and nvl(mr_rec.segment2_high, gc.segment2)) OR
127            (mr_rec.segment2_low IS NULL and mr_rec.segment2_high IS NULL))
128       AND ((gc.segment3 between nvl(mr_rec.segment3_low, gc.segment3)
129                      and nvl(mr_rec.segment3_high, gc.segment3)) OR
130            (mr_rec.segment3_low IS NULL and mr_rec.segment3_high IS NULL))
131       AND ((gc.segment4 between nvl(mr_rec.segment4_low, gc.segment4)
132                      and nvl(mr_rec.segment4_high, gc.segment4)) OR
133            (mr_rec.segment4_low IS NULL and mr_rec.segment4_high IS NULL))
134       AND ((gc.segment5 between nvl(mr_rec.segment5_low, gc.segment5)
135                      and nvl(mr_rec.segment5_high, gc.segment5)) OR
136            (mr_rec.segment5_low IS NULL and mr_rec.segment5_high IS NULL))
137       AND ((gc.segment6 between nvl(mr_rec.segment6_low, gc.segment6)
138                      and nvl(mr_rec.segment6_high, gc.segment6)) OR
139            (mr_rec.segment6_low IS NULL and mr_rec.segment6_high IS NULL))
140       AND ((gc.segment7 between nvl(mr_rec.segment7_low, gc.segment7)
141                      and nvl(mr_rec.segment7_high, gc.segment7)) OR
142            (mr_rec.segment7_low IS NULL and mr_rec.segment7_high IS NULL))
143       AND ((gc.segment8 between nvl(mr_rec.segment8_low, gc.segment8)
144                      and nvl(mr_rec.segment8_high, gc.segment8)) OR
145            (mr_rec.segment8_low IS NULL and mr_rec.segment8_high IS NULL))
146       AND ((gc.segment9 between nvl(mr_rec.segment9_low, gc.segment9)
147                      and nvl(mr_rec.segment9_high, gc.segment9)) OR
148            (mr_rec.segment9_low IS NULL and mr_rec.segment9_high IS NULL))
149       AND ((gc.segment10 between nvl(mr_rec.segment10_low, gc.segment10)
150                      and nvl(mr_rec.segment10_high, gc.segment10)) OR
151            (mr_rec.segment10_low IS NULL and mr_rec.segment10_high IS NULL))
152       AND ((gc.segment11 between nvl(mr_rec.segment11_low, gc.segment11)
153                      and nvl(mr_rec.segment11_high, gc.segment11)) OR
154            (mr_rec.segment11_low IS NULL and mr_rec.segment11_high IS NULL))
155       AND ((gc.segment12 between nvl(mr_rec.segment12_low, gc.segment12)
156                      and nvl(mr_rec.segment12_high, gc.segment12)) OR
157            (mr_rec.segment12_low IS NULL and mr_rec.segment12_high IS NULL))
158       AND ((gc.segment13 between nvl(mr_rec.segment13_low, gc.segment13)
159                      and nvl(mr_rec.segment13_high, gc.segment13)) OR
160            (mr_rec.segment13_low IS NULL and mr_rec.segment13_high IS NULL))
161       AND ((gc.segment14 between nvl(mr_rec.segment14_low, gc.segment14)
162                      and nvl(mr_rec.segment14_high, gc.segment14)) OR
163            (mr_rec.segment14_low IS NULL and mr_rec.segment14_high IS NULL))
164       AND ((gc.segment15 between nvl(mr_rec.segment15_low, gc.segment15)
165                      and nvl(mr_rec.segment15_high, gc.segment15)) OR
166            (mr_rec.segment15_low IS NULL and mr_rec.segment15_high IS NULL))
167       AND ((gc.segment16 between nvl(mr_rec.segment16_low, gc.segment16)
168                      and nvl(mr_rec.segment16_high, gc.segment16)) OR
169            (mr_rec.segment16_low IS NULL and mr_rec.segment16_high IS NULL))
170       AND ((gc.segment17 between nvl(mr_rec.segment17_low, gc.segment17)
171                      and nvl(mr_rec.segment17_high, gc.segment17)) OR
172            (mr_rec.segment17_low IS NULL and mr_rec.segment17_high IS NULL))
173       AND ((gc.segment18 between nvl(mr_rec.segment18_low, gc.segment18)
174                      and nvl(mr_rec.segment18_high, gc.segment18)) OR
175            (mr_rec.segment18_low IS NULL and mr_rec.segment18_high IS NULL))
176       AND ((gc.segment19 between nvl(mr_rec.segment19_low, gc.segment19)
177                      and nvl(mr_rec.segment19_high, gc.segment19)) OR
178            (mr_rec.segment19_low IS NULL and mr_rec.segment19_high IS NULL))
179       AND ((gc.segment20 between nvl(mr_rec.segment20_low, gc.segment20)
180                      and nvl(mr_rec.segment20_high, gc.segment20)) OR
181            (mr_rec.segment20_low IS NULL and mr_rec.segment20_high IS NULL))
182       AND ((gc.segment21 between nvl(mr_rec.segment21_low, gc.segment21)
183                      and nvl(mr_rec.segment21_high, gc.segment21)) OR
184            (mr_rec.segment21_low IS NULL and mr_rec.segment21_high IS NULL))
185       AND ((gc.segment22 between nvl(mr_rec.segment22_low, gc.segment22)
186                      and nvl(mr_rec.segment22_high, gc.segment22)) OR
187            (mr_rec.segment22_low IS NULL and mr_rec.segment22_high IS NULL))
188       AND ((gc.segment23 between nvl(mr_rec.segment23_low, gc.segment23)
189                      and nvl(mr_rec.segment23_high, gc.segment23)) OR
190            (mr_rec.segment23_low IS NULL and mr_rec.segment23_high IS NULL))
191       AND ((gc.segment24 between nvl(mr_rec.segment24_low, gc.segment24)
192                      and nvl(mr_rec.segment24_high, gc.segment24)) OR
193            (mr_rec.segment24_low IS NULL and mr_rec.segment24_high IS NULL))
194       AND ((gc.segment25 between nvl(mr_rec.segment25_low, gc.segment25)
195                      and nvl(mr_rec.segment25_high, gc.segment25)) OR
196            (mr_rec.segment25_low IS NULL and mr_rec.segment25_high IS NULL))
197       AND ((gc.segment26 between nvl(mr_rec.segment26_low, gc.segment26)
198                      and nvl(mr_rec.segment26_high, gc.segment26)) OR
199            (mr_rec.segment26_low IS NULL and mr_rec.segment26_high IS NULL))
200       AND ((gc.segment27 between nvl(mr_rec.segment27_low, gc.segment27)
201                      and nvl(mr_rec.segment27_high, gc.segment27)) OR
202             (mr_rec.segment27_low IS NULL and mr_rec.segment27_high IS NULL))
203       AND ((gc.segment28 between nvl(mr_rec.segment28_low, gc.segment28)
204                      and nvl(mr_rec.segment28_high, gc.segment28)) OR
205            (mr_rec.segment28_low IS NULL and mr_rec.segment28_high IS NULL))
206       AND ((gc.segment29 between nvl(mr_rec.segment29_low, gc.segment29)
207                      and nvl(mr_rec.segment29_high, gc.segment29)) OR
208            (mr_rec.segment29_low IS NULL and mr_rec.segment29_high IS NULL))
209       AND ((gc.segment30 between nvl(mr_rec.segment30_low, gc.segment30)
210                      and nvl(mr_rec.segment30_high, gc.segment30)) OR
211            (mr_rec.segment30_low IS NULL and mr_rec.segment30_high IS NULL))
212       AND ad.asset_id > px_max_asset_id
213       AND MOD(ad.asset_id, p_total_requests) = (p_request_number - 1)
214     ORDER BY ad.asset_id;
215 
216    -- local variables
217    TYPE v30_tbl  IS TABLE OF VARCHAR2(30) INDEX BY BINARY_INTEGER;
218    TYPE num_tbl  IS TABLE OF NUMBER       INDEX BY BINARY_INTEGER;
219 
220    l_asset_number               v30_tbl;
221    l_asset_id                   num_tbl;
222    l_asset_category_id          num_tbl;
223    l_assigned_to                num_tbl;
224 
225    l_msg_count       NUMBER := 0;
226    l_msg_data        VARCHAR2(2000) := NULL;
227    l_return_status   VARCHAR2(1) := FND_API.G_RET_STS_ERROR;
228    l_rowcount        NUMBER;
229    l_warn_status     BOOLEAN := FALSE;
230 
231    -- to keep track of the last asset id that entered the mass_reclass_assets
232    -- cursor loop.  we need this to avoid DISTINCT in the SELECT statement
233    -- for mass_reclass_assets cursor.  asset may be selected multiple times
234    -- if it is multi-distributed and if more than one distribution lines
235    -- meet the reclass selection criteria(if at least one distribution line
236    -- meets user criteria, the asset is selected for reclass.)
237    l_last_asset       NUMBER(15) := NULL;
238    l_status           BOOLEAN := FALSE;
239    l_dummy_num        NUMBER;
240    l_cat_flex_struct  NUMBER;
241    l_concat_cat       VARCHAR2(220);
242    l_cat_segs         fa_rx_shared_pkg.Seg_Array;
243 
244    -- counter to keep track of the number of assets that entered the
245    -- mass_reclass_assets cursor loop and passed Check_Criteria.
246    -- this counter is reset to zero, at every 200 assets.
247    l_counter          NUMBER := 0;
248 
249    -- used for bulk fetch
250    l_batch_size       NUMBER;
251    l_loop_count       NUMBER;
252 
253    -- used for api call
254    l_trans_rec        FA_API_TYPES.trans_rec_type;
255    l_asset_hdr_rec    FA_API_TYPES.asset_hdr_rec_type;
256    l_asset_cat_rec    FA_API_TYPES.asset_cat_rec_type;
257    l_recl_opt_rec     FA_API_TYPES.reclass_options_rec_type;
258 
259    l_calling_fn       VARCHAR2(50) := 'FA_MASS_RECLASS_PKG.DO_RECLASS';
260    l_string           varchar2(250);
261 
262    mrcl_failure       EXCEPTION; -- mass reclass failure
263    done_exc           EXCEPTION;
264 
265 BEGIN
266 
267    px_max_asset_id := nvl(px_max_asset_id, 0);
268    x_processed_count := 0;
269    x_success_count := 0;
270    x_failure_count := 0;
271 
272 
273    if (not g_log_level_rec.initialized) then
274       if (NOT fa_util_pub.get_log_level_rec (
275                 x_log_level_rec =>  g_log_level_rec
276       )) then
277          raise  mrcl_failure;
278       end if;
279    end if;
280 
281    if (px_max_asset_id = 0) then
282 
283       FND_FILE.put(FND_FILE.output,'');
284       FND_FILE.new_line(FND_FILE.output,1);
285 
286       -- dump out the headings
287       fnd_message.set_name('OFA', 'FA_MASSRET_REPORT_COLUMN');
288       l_string := fnd_message.get;
289 
290       FND_FILE.put(FND_FILE.output,l_string);
291       FND_FILE.new_line(FND_FILE.output,1);
292 
293       fnd_message.set_name('OFA', 'FA_MASSRET_REPORT_LINE');
294       l_string := fnd_message.get;
295 
296       FND_FILE.put(FND_FILE.output,l_string);
297       FND_FILE.new_line(FND_FILE.output,1);
298 
299    end if;
300 
301    -- Fetch mass reclass record information.
302    OPEN  mass_reclass;
303    FETCH mass_reclass INTO mr_rec;
304    CLOSE mass_reclass;
305 
306    if not (fa_cache_pkg.fazcbc(X_book => mr_rec.book_type_code, p_log_level_rec => g_log_level_rec)) then
307       raise mrcl_failure;
308    end if;
309 
310    l_batch_size := nvl(fa_cache_pkg.fa_batch_size, 200);
311 
312    l_recl_opt_rec.copy_cat_desc_flag := mr_rec.copy_cat_desc_flag;
313    l_recl_opt_rec.redefault_flag     := mr_rec.redefault_flag;
314    l_asset_cat_rec.category_id       := mr_rec.to_category_id;
315    l_asset_hdr_rec.book_type_code    := mr_rec.book_type_code;
316 
317    /*===========================================================================
318      Check if reclass transaction date for the mass reclass record from
319      mass reclass form is in the current corporate book period.
320      (No prior period reclass is allowed.)
321     ===========================================================================*/
322 
323    if px_max_asset_id = 0 then
324       IF NOT Check_Trans_Date(
325             X_Corp_Book      => mr_rec.book_type_code,
326             X_Trans_Date     => mr_rec.trans_date_entered) THEN
327          RAISE mrcl_failure;
328       END IF;
329    end if;
330 
331    /*===========================================================================
332      Perform mass reclass.
333     ===========================================================================*/
334    IF (mr_rec.redefault_flag = 'YES') THEN
335       -- Depreciation rules will be redefaulted.
336       -- Reset g_deprn_count before initiating mass reclass transaction.
337       FA_LOAD_TBL_PKG.g_deprn_count := 0;
338 
339       -- Load depreciation rules table for the corporate book and all the
340       -- associated tax books for the new category.
341       -- Simulates caching effect.
342       FA_LOAD_TBL_PKG.Load_Deprn_Rules_Tbl(
343           p_corp_book       => mr_rec.book_type_code,
344           p_category_id     => mr_rec.to_category_id,
345           x_return_status   => l_status, p_log_level_rec => g_log_level_rec);
346       IF NOT l_status THEN
347          RAISE mrcl_failure;
348       END IF;
349    END IF;
350 
351    /* Get the new category code from the new category id. */
352    if not fa_cache_pkg.fazsys(g_log_level_rec) then
353       RAISE mrcl_failure;
354    end if;
355 
356    l_cat_flex_struct := fa_cache_pkg.fazsys_record.category_flex_structure;
357 
358    FA_RX_SHARED_PKG.Concat_Category(
359              struct_id      => l_cat_flex_struct,
360              ccid           => mr_rec.to_category_id,
361              concat_string  => l_concat_cat,
362              segarray       => l_cat_segs);
363 
364 
365    /* Loop all the qualified assets, and perform mass reclass. */
366    OPEN mass_reclass_assets;
367    FETCH mass_reclass_assets BULK COLLECT INTO
368          l_asset_id,
369          l_asset_number,
370          l_asset_category_id,
371          l_assigned_to
372    LIMIT l_batch_size;
373    close mass_reclass_assets;
374 
375    x_processed_count := l_asset_id.count;
376 
377    if (l_asset_id.count = 0) then
378       raise done_exc;
379    end if;
380 
381    for l_loop_count in 1..l_asset_id.count loop
382 
383       -- clear the debug stack for each asset
384       FA_DEBUG_PKG.Initialize;
385       -- reset the message level to prevent bogus errors
386       FA_SRVR_MSG.Set_Message_Level(message_level => 10, p_log_level_rec => g_log_level_rec);
387 
388       if NOT l_warn_status then
389          if not FA_ASSET_VAL_PVT.validate_assigned_to (
390                 p_transaction_type_code => 'RECLASS',
391                 p_assigned_to           => l_assigned_to(l_loop_count),
392                 p_date                  => mr_rec.trans_date_entered,
393                 p_calling_fn            => l_calling_fn,
394                 p_log_level_rec         => g_log_level_rec
395                ) then
396              l_warn_status := TRUE; -- set to warning when invalid employee encountered
397          end if;
398       end if;
399 
400       IF (l_asset_id(l_loop_count) <> l_last_asset OR l_last_asset IS NULL) THEN
401       -- Skip the reclass, if the asset has already entered this loop before.
402       -- Using l_last_asset to keep track of the last asset that entered the
403       -- cursor loop instead of using DISTINCT in the SELECT statement for
404       -- mass_reclass_assets cursor.
405 
406          -- Save the asset id for the next loop.
407          l_last_asset := l_asset_id(l_loop_count);
408 
409          IF Check_Criteria(
410                X_Asset_Id            => l_asset_id(l_loop_count),
411                X_Fully_Rsvd_Flag     => mr_rec.fully_rsvd_flag) THEN
412             -- Perform reclass only on the assets that meet all the user
413             -- selection criteria.
414 
415             fa_srvr_msg.add_message(
416                 calling_fn => NULL,
417                 name       => 'FA_SHARED_ASSET_NUMBER',
418                 token1     => 'NUMBER',
419                 value1     => l_asset_number(l_loop_count),
420                 p_log_level_rec => g_log_level_rec);
421 
422             IF (l_asset_category_id(l_loop_count) = mr_rec.to_category_id) THEN
423                -- Reclass and redefault are not processed on the asset, if
424                -- the new category is the same as the old category.
425                -- This asset is printed on the log with a message, but is not
426                -- counted as a Processed asset.
427                -- (The log prints number of assets processed, number of success,
428                --  number of failures.)
429 
430                -- List asset number and the message.
431                -- use the write_message util
432 
433                write_message(l_asset_number(l_loop_count),
434                              'FA_REC_NOT_PROCESSED');
435 
436                /*
437                fnd_message.set_name('OFA', 'FA_SHARED_ASSET_NUMBER');
438                fnd_message.set_token('NUMBER', l_asset_number(l_loop_count), FALSE);
439                fnd_msg_pub.add;
440                FA_SRVR_MSG.Add_Message(
441                      CALLING_FN => l_calling_fn,
442                      NAME       => 'FA_REC_NOT_PROCESSED',
443                      TOKEN1     => 'ASSET',
444                      VALUE1     => l_asset_number(l_loop_count));
445                */
446                -- Increment the counter.
447                -- Increment only the counter for messaging.  This asset is
448                -- not considered a Processed asset.
449                l_counter := l_counter + 1;
450 
451             ELSE
452                -- validation ok, null out then load the structs and process the adjustment
453                l_trans_rec.transaction_header_id     := NULL;
454                l_trans_rec.who_info.last_update_date := sysdate;
455                l_trans_rec.transaction_date_entered  := mr_rec.trans_date_entered;
456                l_trans_rec.mass_reference_id         := p_parent_request_id;
457                l_trans_rec.calling_interface         := 'FAMRCL';
458                l_trans_rec.mass_transaction_id       := p_mass_reclass_id;
459 
460                l_asset_hdr_rec.asset_id              := l_asset_id(l_loop_count);
461                l_asset_hdr_rec.period_of_addition    := null;
462 
463                if (mr_rec.amortize_flag = 'YES') then
464                   l_trans_rec.transaction_subtype := 'AMORTIZED';
465                else
466                   l_trans_rec.transaction_subtype := 'EXPENSED';
467                end if;
468 
469 
470                /* Call the new Reclass Public API for each asset. */
471 
472                FA_RECLASS_PUB.do_reclass (
473                       -- std parameters
474                       p_api_version         => 1.0,
475                       p_init_msg_list       => FND_API.G_FALSE,
476                       p_commit              => FND_API.G_FALSE,
477                       p_validation_level    => FND_API.G_VALID_LEVEL_FULL,
478                       p_calling_fn          => l_calling_fn,
479                       x_return_status       => l_return_status,
480                       x_msg_count           => l_msg_count,
481                       x_msg_data            => l_msg_data,
482                       -- api parameters
483                       px_trans_rec          => l_trans_rec,
484                       px_asset_hdr_rec      => l_asset_hdr_rec,
485                       px_asset_cat_rec_new  => l_asset_cat_rec,
486                       p_recl_opt_rec        => l_recl_opt_rec );
487 
488                IF (l_return_status = FND_API.G_RET_STS_SUCCESS) THEN
489                   FND_CONCURRENT.AF_COMMIT;
490                   l_counter       := l_counter + 1;
491                   x_success_count := x_success_count + 1;
492 
493                   write_message(l_asset_number(l_loop_count),
494                                 'FA_MCP_RECLASS_SUCCESS');
495 
496                ELSE
497                   /* 'W'(warning status) or error status. */
498                   -- Partial failure(failure in redefault only) is counted as failure.
499                   l_counter       := l_counter + 1;
500                   x_failure_count := x_failure_count + 1;
501                   write_message(l_asset_number(l_loop_count),
502                                 NULL);
503 
504                END IF;
505 
506                if (g_log_level_rec.statement_level) then
507                   fa_debug_pkg.dump_debug_messages(max_mesgs => 0, p_log_level_rec => g_log_level_rec);
508                end if;
509 
510             END IF; /* IF (l_category_id = mr_rec.to_category_id) */
511          END IF;  /* IF Check_Criteria */
512       END IF;  /* IF (l_asset_id <> l_last_asset OR l_last_asset IS NULL) */
513    END LOOP;
514 
515    IF (mr_rec.redefault_flag = 'YES') THEN
516       -- Reset g_deprn_count after completing mass reclass transaction.
517       FA_LOAD_TBL_PKG.g_deprn_count := 0;
518    END IF;
519 
520    FND_CONCURRENT.AF_COMMIT;
521 
522    px_max_asset_id  := l_asset_id(l_asset_id.count);
523    if (l_warn_status) then
524       x_return_status := 1;  -- return warning
525    else
526       x_return_status := 0;  -- success
527    end if;
528 
529 EXCEPTION
530    WHEN done_exc then
531         if (l_warn_status) then
532            x_return_status := 1;
533         else
534            x_return_status :=  0;
535         end if;
536 
537    WHEN mrcl_failure THEN
538         fa_srvr_msg.add_message(calling_fn => l_calling_fn, p_log_level_rec => g_log_level_rec);
539         FND_CONCURRENT.AF_ROLLBACK;
540         FA_LOAD_TBL_PKG.g_deprn_count := 0;
541         x_return_status := 2;
542 
543    WHEN OTHERS THEN
544         fa_srvr_msg.add_sql_error(calling_fn => l_calling_fn, p_log_level_rec => g_log_level_rec);
545         FND_CONCURRENT.AF_ROLLBACK;
546         FA_LOAD_TBL_PKG.g_deprn_count := 0;
547         x_return_status :=  2;
548 
549 END Do_Mass_Reclass;
550 
551 
552 /*====================================================================================+
553 |   FUNCTION Check_Trans_Date                                                         |
554 +=====================================================================================*/
555 
556 FUNCTION Check_Trans_Date(
557      X_Corp_Book          IN     VARCHAR2,
558      X_Trans_Date         IN     DATE
559      )     RETURN BOOLEAN IS
560    l_cp_open_date     DATE;
561    l_cp_close_date    DATE;
562    -- cursor to get the calendar period open date of the current corpote
563    -- book period.
564    CURSOR get_cp_open_close_date IS
565    SELECT calendar_period_open_date,
566           calendar_period_close_date
567      FROM fa_deprn_periods
568     WHERE book_type_code = X_Corp_Book
569       AND period_close_date IS NULL;
570 
571 BEGIN
572    -- Check if the transaction date is in the current corporate book period.
573    OPEN  get_cp_open_close_date;
574    FETCH get_cp_open_close_date
575     INTO l_cp_open_date,
576          l_cp_close_date;
577    CLOSE get_cp_open_close_date;
578 
579    IF (X_Trans_Date < l_cp_open_date OR
580        X_Trans_date > l_cp_close_date) THEN
581         FA_SRVR_MSG.Add_Message(
582          CALLING_FN => 'FA_MASS_RECLASS_PKG.Check_Trans_Date',
583          NAME       => 'FA_REC_INVALID_TRANS_DATE',  p_log_level_rec => g_log_level_rec);
584       RETURN (FALSE);
585    END IF;
586 
587    RETURN (TRUE);
588 
589 EXCEPTION
590    WHEN OTHERS THEN
591         FA_SRVR_MSG.Add_SQL_Error(
592              CALLING_FN => 'FA_MASS_RECLASS_PKG.Check_Trans_Date',  p_log_level_rec => g_log_level_rec);
593         RETURN (FALSE);
594 END Check_Trans_Date;
595 
596 
597 /*====================================================================================+
598 |   FUNCTION Check_Criteria                                                           |
599 +=====================================================================================*/
600 
601 FUNCTION Check_Criteria(
602      X_Asset_Id            IN     NUMBER,
603      X_Fully_Rsvd_Flag     IN     VARCHAR2
604      )     RETURN BOOLEAN IS
605 
606    l_book         VARCHAR2(30);
607    check_flag     VARCHAR2(15);
608 
609    -- cursor to get all the corporate and tax books the asset belongs to.
610    CURSOR book_cr IS
611    SELECT bk.book_type_code
612      FROM fa_book_controls bc, fa_books bk
613     WHERE bk.asset_id = X_Asset_Id
614       AND bk.date_ineffective IS NULL
615       AND bk.book_type_code = bc.book_type_code
616       AND bc.book_class IN ('CORPORATE', 'TAX')
617       AND nvl(bc.date_ineffective, sysdate+1) > sysdate;
618 
619    CURSOR check_not_rsvd IS
620    SELECT 'NOT RESERVED'
621      FROM fa_books bk
622     WHERE bk.asset_id = X_Asset_Id
623       AND bk.book_type_code = l_book
624       AND bk.date_ineffective IS NULL
625       AND bk.period_counter_fully_reserved IS NULL;
626 
627    CURSOR check_rsvd IS
628    SELECT 'RESERVED'
629      FROM fa_books bk
630     WHERE bk.asset_id = X_Asset_Id
631       AND bk.book_type_code = l_book
632       AND bk.date_ineffective IS NULL
633       AND bk.period_counter_fully_reserved IS NOT NULL;
634 
635 BEGIN
636    -- Check to make sure fully reserved asset selection criteria is met in
637    -- all the books the asset belongs to.
638    IF (X_Fully_Rsvd_Flag IS NOT NULL) THEN
639       -- if x_fully_rsvd_flag is null, then we don't care whether the asset is
640       -- reserved or not.
641       OPEN book_cr;
642       LOOP
643          FETCH book_cr INTO l_book;
644          EXIT WHEN book_cr%NOTFOUND;
645 
646          IF (X_Fully_Rsvd_Flag = 'YES') THEN
647             OPEN check_not_rsvd;
648             FETCH check_not_rsvd INTO check_flag;
649             IF (check_not_rsvd%FOUND) THEN
650                CLOSE check_not_rsvd;
651             RETURN (FALSE);
652             END IF;
653             CLOSE check_not_rsvd;
654          ELSIF (X_Fully_Rsvd_Flag = 'NO') THEN
655             OPEN check_rsvd;
656             FETCH check_rsvd INTO check_flag;
657             IF (check_rsvd%FOUND) THEN
658                CLOSE check_rsvd;
659                RETURN (FALSE);
660             END IF;
661             CLOSE check_rsvd;
662          END IF;
663 
664       END LOOP;
665 
666       CLOSE book_cr;
667 
668    END IF;
669 
670    RETURN (TRUE);
671 
672 EXCEPTION
673    WHEN OTHERS THEN
674         FA_SRVR_MSG.Add_SQL_Error(
675              CALLING_FN => 'FA_MASS_RECLASS_PKG.Check_Criteria',  p_log_level_rec => g_log_level_rec);
676         RETURN (FALSE);
677 
678 END Check_Criteria;
679 
680 -----------------------------------------------------------------------------
681 
682 PROCEDURE write_message
683               (p_asset_number    in varchar2,
684                p_message         in varchar2) IS
685 
686    l_message      varchar2(30);
687    l_mesg         varchar2(100);
688    l_string       varchar2(512);
689    l_calling_fn   varchar2(40);  -- conditionally populated below
690 
691 BEGIN
692 
693    -- first dump the message to the output file
694    -- set/translate/retrieve the mesg from fnd
695 
696    l_message := nvl(p_message,  'FA_MASSRCL_FAIL_TRX');
697 
698    if (l_message <> 'FA_MCP_RECLASS_SUCCESS' and
699        l_message <> 'FA_REC_NOT_PROCESSED')  then
700       l_calling_fn := 'fa_mass_reclass_pkg.do_reclass';
701    end if;
702 
703    fnd_message.set_name('OFA', l_message);
704    l_mesg := substrb(fnd_message.get, 1, 100);
705 
706    l_string       := rpad(p_asset_number, 15) || ' ' || l_mesg;
707 
708    FND_FILE.put(FND_FILE.output,l_string);
709    FND_FILE.new_line(FND_FILE.output,1);
710 
711    -- now process the messages for the log file
712    fa_srvr_msg.add_message
713        (calling_fn => l_calling_fn,
714         name       => l_message, p_log_level_rec => g_log_level_rec);
715 
716 EXCEPTION
717    when others then
718        raise;
719 
720 END write_message;
721 
722 END FA_MASS_RECLASS_PKG;