DBA Data[Home] [Help]

PACKAGE BODY: APPS.GME_POST_MIGRATION

Source


1 PACKAGE BODY gme_post_migration AS
2 /* $Header: GMEVRCBB.pls 120.9 2007/01/26 23:05:29 snene noship $ */
3   g_migration_run_id    NUMBER;
4   g_debug               VARCHAR2 (5)  := fnd_profile.VALUE ('AFLOG_LEVEL');
5   PROCEDURE recreate_open_batches(err_buf  OUT NOCOPY VARCHAR2,
6                                   ret_code OUT NOCOPY VARCHAR2) IS
7     l_api_name              VARCHAR2(30) := 'RECREATE_OPEN_BATCHES';
8     l_item_rec              mtl_system_items_vl%ROWTYPE;
9     l_batch_header          gme_batch_header%ROWTYPE;
10     l_batch_tbl             gme_common_pvt.batch_headers_tab;
11     l_mtl_dtl_mig_tbl       gme_post_migration.mtl_dtl_mig_tab;
12     l_mtl_dtl_tbl           gme_common_pvt.material_details_tab;
13     l_in_mtl_dtl_tbl        gme_common_pvt.material_details_tab;
14     l_steps_mig_tbl         gme_post_migration.steps_mig_tab;
15     l_steps_tbl             gme_common_pvt.steps_tab;
16     l_activities_mig_tbl    gme_post_migration.activ_mig_tab;
17     l_activities_tbl        gme_common_pvt.activities_tab;
18     l_resources_mig_tbl     gme_post_migration.rsrc_mig_tab;
19     l_resources_tbl         gme_common_pvt.resources_tab;
20     l_proc_param_mig_tbl    gme_post_migration.process_param_mig_tab;
21     l_proc_param_tbl        gme_post_migration.process_param_tab;
22     l_rsrc_txns_mig_tbl     gme_post_migration.rsrc_txns_mig_tab;
23     l_rsrc_txns_tbl         gme_post_migration.rsrc_txns_tab;
24     l_trolin_tbl            inv_move_order_pub.trolin_tbl_type;
25     l_wip_entity_id         NUMBER;
26     l_organization_id       NUMBER;
27     l_old_batchstep_id      NUMBER;
28     l_old_bstep_activ_id    NUMBER;
29     l_old_bstep_rsrc_id     NUMBER;
30     l_item_id               NUMBER;
31     l_current_org_id        NUMBER := 0;
32     l_temp_qty              NUMBER := 0;
33     l_msg_count             NUMBER := 0;
34     l_actv_count            NUMBER := 0;
35     l_rsrc_count            NUMBER := 0;
36     l_pprm_count            NUMBER := 0;
37     l_rtxn_count            NUMBER := 0;
38     l_return_status         VARCHAR2(1);
39     l_def_whse              VARCHAR2(4);
40     l_subinventory          VARCHAR2(10);
41     l_msg_data              VARCHAR2(2000);
42     l_batch_prefix          VARCHAR2(30) := FND_PROFILE.VALUE('GME_BATCH_PREFIX');
43     l_fpo_prefix            VARCHAR2(30) := FND_PROFILE.VALUE('GME_FPO_PREFIX');
44     l_prefix                VARCHAR2(30);
45     l_item_no               VARCHAR2(32);
46     setup_failed            EXCEPTION;
47     calc_mtl_req_date_err   EXCEPTION;
48     create_mo_hdr_err       EXCEPTION;
49     create_mo_line_err      EXCEPTION;
50     item_not_defined        EXCEPTION;
51 
52     CURSOR Cur_get_batches IS
53       SELECT *
54       FROM   gme_batch_header_mig
55       WHERE  NVL(migrated_batch_ind, ' ') <> 'M'
56              AND organization_id IS NOT NULL
57       ORDER BY batch_id;
58     CURSOR Cur_get_materials(v_batch_id NUMBER) IS
59       SELECT *
60       FROM   gme_material_details_mig
61       WHERE  batch_id = v_batch_id
62       ORDER BY line_type, line_no;
63     CURSOR Cur_item_mst(v_item_id NUMBER) IS
64       SELECT item_no
65       FROM   ic_item_mst
66       WHERE  item_id = v_item_id;
67     CURSOR Cur_get_item(v_org_id            NUMBER,
68                         v_inventory_item_id NUMBER) IS
69       SELECT *
70       FROM   mtl_system_items_vl
71       WHERE  organization_id = v_org_id
72              AND inventory_item_id = v_inventory_item_id;
73     CURSOR Cur_get_trans_whse(v_trans_id NUMBER) IS
74       SELECT whse_code
75       FROM   ic_tran_pnd
76       WHERE  trans_id = v_trans_id;
77     CURSOR Cur_get_steps(v_batch_id NUMBER) IS
78       SELECT *
79       FROM   gme_batch_steps_mig
80       WHERE  batch_id = v_batch_id
81       ORDER BY batchstep_no;
82     CURSOR Cur_get_activities(v_batchstep_id NUMBER) IS
83       SELECT *
84       FROM   gme_batch_step_activ_mig
85       WHERE  batchstep_id = v_batchstep_id;
86     CURSOR Cur_get_resources(v_batchstep_activity_id NUMBER) IS
87       SELECT *
88       FROM   gme_batch_step_resources_mig
89       WHERE  batchstep_id = v_batchstep_activity_id;
90     CURSOR Cur_get_process_params(v_batchstep_resource_id NUMBER) IS
91       SELECT *
92       FROM   gme_process_parameters_mig
93       WHERE  batchstep_resource_id = v_batchstep_resource_id;
94     CURSOR Cur_get_rsrc_txns(v_batchstep_rsrc_id NUMBER) IS
95       SELECT *
96       FROM   gme_resource_txns_mig
97       WHERE  line_id = v_batchstep_rsrc_id;
98   BEGIN
99     IF (g_debug IS NOT NULL) THEN
100       gme_debug.log_initialize('Migration');
101     END IF;
102     IF (g_debug <= gme_debug.g_log_procedure) THEN
103       gme_debug.put_line('Start procedure '||l_api_name);
104     END IF;
105     g_migration_run_id := gma_migration.gma_migration_start ('GME', 'RECREATE_OPEN_BATCHES');
106     IF (g_debug <= gme_debug.g_log_statement) THEN
107       gme_debug.put_line('Migration RUN ID = '||g_migration_run_id);
108     END IF;
109     FOR get_batches IN Cur_get_batches LOOP
110       BEGIN
111         IF (g_debug <= gme_debug.g_log_statement) THEN
112           gme_debug.put_line('Current batch is '||get_batches.plant_code||'-'||get_batches.batch_no);
113         END IF;
114       	gme_common_pvt.set_timestamp;
115       	IF (l_current_org_id <> get_batches.organization_id) THEN
116           IF (g_debug <= gme_debug.g_log_statement) THEN
117             gme_debug.put_line('Doing setup for org = '||get_batches.organization_id);
118           END IF;
119       	  IF NOT (gme_common_pvt.setup(p_org_id => get_batches.organization_id)) THEN
120       	    RAISE setup_failed;
121       	  END IF;
122       	  l_current_org_id := get_batches.organization_id;
123       	END IF;
124         IF (l_batch_header.batch_type = 0) THEN
125           l_prefix := l_batch_prefix;
126         ELSE
127           l_prefix := l_fpo_prefix;
128         END IF;
129       	UPDATE gme_batch_header
130       	SET batch_no = SUBSTR(batch_no,1,30)||'-M'
131       	WHERE batch_id = get_batches.batch_id;
132       	UPDATE wip_entities
133       	SET wip_entity_name = wip_entity_name||'-M'
134       	WHERE entity_type = DECODE(get_batches.batch_type, 10, gme_common_pvt.g_wip_entity_type_fpo, gme_common_pvt.g_wip_entity_type_batch)
135       	      AND organization_id = get_batches.organization_id
136       	      AND wip_entity_name = l_prefix||get_batches.batch_no;
137         IF (g_debug <= gme_debug.g_log_statement) THEN
138           gme_debug.put_line('Start batch header');
139         END IF;
140       	/* Process batch header record */
141       	build_batch_hdr(p_batch_header_mig => get_batches,
142                         x_batch_header     => l_batch_header);
143         SELECT wip_entities_s.NEXTVAL INTO l_wip_entity_id FROM DUAL;
144         l_batch_header.plant_code              := NULL;
145         l_batch_header.batch_status            := 1;
146         l_batch_header.enforce_step_dependency := 0;
147         l_batch_header.terminated_ind          := 0;
148         l_batch_header.enhanced_pi_ind         := 'N';
149         l_batch_header.batch_id                := l_wip_entity_id;
150         l_batch_header.wip_whse_code           := NULL;
151         IF (g_debug <= gme_debug.g_log_statement) THEN
152           gme_debug.put_line('Before wip entities');
153         END IF;
154         INSERT INTO wip_entities
155                    (wip_entity_id, organization_id
156                    ,last_update_date, last_updated_by
157                    ,creation_date, created_by
158                    ,wip_entity_name
159                    ,entity_type
160                    ,gen_object_id)
161         VALUES     (l_wip_entity_id, l_batch_header.organization_id
162                    ,gme_common_pvt.g_timestamp, gme_common_pvt.g_user_ident
163                    ,gme_common_pvt.g_timestamp, gme_common_pvt.g_user_ident
164                    ,l_prefix||l_batch_header.batch_no
165                    ,DECODE (l_batch_header.batch_type
166                    ,0, gme_common_pvt.g_wip_entity_type_batch
167                    ,gme_common_pvt.g_wip_entity_type_fpo)
168                    ,mtl_gen_object_id_s.NEXTVAL);
169         IF (g_debug <= gme_debug.g_log_statement) THEN
170           gme_debug.put_line('After wip entities');
171         END IF;
172         l_batch_tbl(1) := l_batch_header;
173         FORALL a IN 1..l_batch_tbl.count
174           INSERT INTO gme_batch_header VALUES l_batch_tbl(a);
175         IF (g_debug <= gme_debug.g_log_statement) THEN
176           gme_debug.put_line('After batch header');
177         END IF;
178       	/* Process material details records */
179       	OPEN Cur_get_materials(get_batches.batch_id);
180       	FETCH Cur_get_materials BULK COLLECT INTO l_mtl_dtl_mig_tbl;
181       	CLOSE Cur_get_materials;
182         IF (g_debug <= gme_debug.g_log_statement) THEN
183           gme_debug.put_line('No. of materials = '||l_mtl_dtl_mig_tbl.count);
184         END IF;
185       	build_mtl_dtl(p_mtl_dtl_mig => l_mtl_dtl_mig_tbl,
186                       x_mtl_dtl     => l_mtl_dtl_tbl);
187         FOR i IN 1..l_mtl_dtl_tbl.count LOOP
188           OPEN Cur_get_item(l_mtl_dtl_tbl(i).organization_id, l_mtl_dtl_tbl(i).inventory_item_id);
189           FETCH Cur_get_item INTO l_item_rec;
190           IF (Cur_get_item%NOTFOUND) THEN
191             CLOSE Cur_get_item;
192             l_item_id := l_mtl_dtl_tbl(i).item_id;
193             RAISE item_not_defined;
194           END IF;
195           CLOSE Cur_get_item;
196           IF (l_item_rec.primary_uom_code <> l_mtl_dtl_tbl(i).dtl_um) THEN
197             l_temp_qty := inv_convert.inv_um_convert(item_id              => l_mtl_dtl_tbl(i).inventory_item_id
198                                                     ,organization_id      => l_mtl_dtl_tbl(i).organization_id
199                                                     ,PRECISION            => gme_common_pvt.g_precision
200                                                     ,from_quantity        => l_mtl_dtl_tbl(i).original_qty
201                                                     ,from_unit            => l_mtl_dtl_tbl(i).dtl_um
202                                                     ,to_unit              => l_item_rec.primary_uom_code
203                                                     ,from_name            => NULL
204                                                     ,to_name              => NULL);
205           ELSE
206             l_temp_qty := l_mtl_dtl_tbl(i).original_qty;
207           END IF;
208           /* Locator_id contains the default trans_id, we will try to put default subinventory on material using this */
209           l_subinventory := NULL;
210           IF (l_mtl_dtl_tbl(i).locator_id IS NOT NULL) THEN
211             OPEN Cur_get_trans_whse(l_mtl_dtl_tbl(i).locator_id);
212             FETCH Cur_get_trans_whse INTO l_def_whse;
213             CLOSE Cur_get_trans_whse;
214             get_subinventory(p_whse_code       => l_def_whse,
215                              x_subinventory    => l_subinventory,
216                              x_organization_id => l_organization_id);
217             IF (l_organization_id <> l_mtl_dtl_tbl(i).organization_id) THEN
218               l_subinventory := NULL;
219             END IF;
220           END IF;
221           SELECT gem5_line_id_s.NEXTVAL INTO l_mtl_dtl_tbl(i).material_detail_id FROM DUAL;
222           l_mtl_dtl_tbl(i).batch_id             := l_batch_header.batch_id;
223           l_mtl_dtl_tbl(i).actual_qty           := 0;
224           l_mtl_dtl_tbl(i).wip_plan_qty         := NULL;
225           l_mtl_dtl_tbl(i).backordered_qty      := 0;
226           l_mtl_dtl_tbl(i).dispense_ind         := 'N';
227           l_mtl_dtl_tbl(i).original_primary_qty := l_temp_qty;
228           l_mtl_dtl_tbl(i).subinventory         := l_subinventory;
229           l_mtl_dtl_tbl(i).locator_id           := NULL;
230           l_mtl_dtl_tbl(i).revision             := NULL;
231         END LOOP;
232 
233         FORALL a IN 1..l_mtl_dtl_tbl.count
234           INSERT INTO gme_material_details VALUES l_mtl_dtl_tbl(a);
235         IF (g_debug <= gme_debug.g_log_statement) THEN
236           gme_debug.put_line('After materials');
237         END IF;
238         /* Process batch step records */
239         l_steps_tbl.delete;
240         l_activities_tbl.delete;
241         l_resources_tbl.delete;
242         l_proc_param_tbl.delete;
243         l_rsrc_txns_tbl.delete;
244       	OPEN Cur_get_steps(get_batches.batch_id);
245       	FETCH Cur_get_steps BULK COLLECT INTO l_steps_mig_tbl;
246       	CLOSE Cur_get_steps;
247         IF (g_debug <= gme_debug.g_log_statement) THEN
248           gme_debug.put_line('No.of steps = '||l_steps_mig_tbl.count);
249         END IF;
250         build_steps(p_steps_mig => l_steps_mig_tbl,
251                     x_steps     => l_steps_tbl);
252         FOR i IN 1..l_steps_tbl.count LOOP
253           l_old_batchstep_id := l_steps_tbl(i).batchstep_id;
254           SELECT gme_batch_step_s.NEXTVAL INTO l_steps_tbl(i).batchstep_id FROM DUAL;
255           l_steps_tbl(i).batch_id          := l_batch_header.batch_id;
256           l_steps_tbl(i).step_status       := 1;
257           l_steps_tbl(i).actual_start_date := NULL;
258           l_steps_tbl(i).actual_cmplt_date := NULL;
259           l_steps_tbl(i).step_close_date   := NULL;
260           l_steps_tbl(i).terminated_ind    := NULL;
261           /* Process batch step activity records */
262           OPEN Cur_get_activities(l_old_batchstep_id);
263           FETCH Cur_get_activities BULK COLLECT INTO l_activities_mig_tbl;
264           CLOSE Cur_get_activities;
265           l_actv_count := l_activities_tbl.count;
266           build_activities(p_activities_mig => l_activities_mig_tbl,
267                            x_activities     => l_activities_tbl);
268           IF (g_debug <= gme_debug.g_log_statement) THEN
269             gme_debug.put_line('No. of activities = '||l_activities_mig_tbl.count);
270           END IF;
271           FOR j IN (l_actv_count + 1)..l_activities_tbl.count LOOP
272             l_old_bstep_activ_id := l_activities_tbl(j).batchstep_activity_id;
273             SELECT gme_batch_step_activity_s.NEXTVAL INTO l_activities_tbl(j).batchstep_activity_id FROM DUAL;
274             l_activities_tbl(j).batch_id          := l_batch_header.batch_id;
275             l_activities_tbl(j).batchstep_id      := l_steps_tbl(i).batchstep_id;
276             l_activities_tbl(j).actual_start_date := NULL;
277             l_activities_tbl(j).actual_cmplt_date := NULL;
278             /* Process batch step resource records */
279             OPEN Cur_get_resources(l_old_bstep_activ_id);
280             FETCH Cur_get_resources BULK COLLECT INTO l_resources_mig_tbl;
281             CLOSE Cur_get_resources;
282             l_rsrc_count := l_resources_tbl.count;
283             build_resources(p_resources_mig => l_resources_mig_tbl,
284                             x_resources     => l_resources_tbl);
285             IF (g_debug <= gme_debug.g_log_statement) THEN
286               gme_debug.put_line('No. of resources = '||l_resources_mig_tbl.count);
287             END IF;
288             FOR k IN (l_rsrc_count + 1)..l_resources_tbl.count LOOP
289               l_old_bstep_rsrc_id := l_resources_tbl(k).batchstep_resource_id;
290               SELECT gem5_batchstepline_id_s.NEXTVAL INTO l_resources_tbl(k).batchstep_resource_id FROM DUAL;
291               l_resources_tbl(k).batch_id              := l_batch_header.batch_id;
292               l_resources_tbl(k).batchstep_id          := l_steps_tbl(i).batchstep_id;
293               l_resources_tbl(k).batchstep_activity_id := l_activities_tbl(j).batchstep_activity_id;
294               l_resources_tbl(k).actual_start_date     := NULL;
295               l_resources_tbl(k).actual_cmplt_date     := NULL;
296               /* Process the process parameter records for the resource */
297               OPEN Cur_get_process_params(l_old_bstep_rsrc_id);
298               FETCH Cur_get_process_params BULK COLLECT INTO l_proc_param_mig_tbl;
299               CLOSE Cur_get_process_params;
300               l_pprm_count := l_proc_param_tbl.count;
301               build_parameters(p_parameters_mig => l_proc_param_mig_tbl,
302                                x_parameters     => l_proc_param_tbl);
303               IF (g_debug <= gme_debug.g_log_statement) THEN
304                 gme_debug.put_line('No. of process params = '||l_proc_param_mig_tbl.count);
305               END IF;
306               FOR m IN (l_pprm_count + 1)..l_proc_param_tbl.count LOOP
307               	SELECT gme_process_parameters_id_s.NEXTVAL INTO l_proc_param_tbl(m).process_param_id FROM DUAL;
308               	l_proc_param_tbl(m).batch_id              := l_batch_header.batch_id;
309               	l_proc_param_tbl(m).batchstep_id          := l_steps_tbl(i).batchstep_id;
310               	l_proc_param_tbl(m).batchstep_activity_id := l_activities_tbl(j).batchstep_activity_id;
311               	l_proc_param_tbl(m).batchstep_resource_id := l_resources_tbl(k).batchstep_resource_id;
312               END LOOP; /* Process parameters Loop */
313               OPEN Cur_get_rsrc_txns(l_old_bstep_rsrc_id);
314               FETCH Cur_get_rsrc_txns BULK COLLECT INTO l_rsrc_txns_mig_tbl;
315               CLOSE Cur_get_rsrc_txns;
316               l_rtxn_count := l_rsrc_txns_tbl.count;
317               build_rsrc_txns(p_rsrc_txns_mig => l_rsrc_txns_mig_tbl,
318                               x_rsrc_txns     => l_rsrc_txns_tbl);
319               IF (g_debug <= gme_debug.g_log_statement) THEN
320                 gme_debug.put_line('No. of rsrc txns = '||l_rsrc_txns_mig_tbl.count);
321               END IF;
322               FOR n IN (l_rtxn_count + 1)..l_rsrc_txns_tbl.count LOOP
323               	SELECT gem5_poc_trans_id_s.NEXTVAL INTO l_rsrc_txns_tbl(n).poc_trans_id FROM DUAL;
324               	l_rsrc_txns_tbl(n).orgn_code := NULL;
325               	l_rsrc_txns_tbl(n).doc_id    := l_batch_header.batch_id;
326               	l_rsrc_txns_tbl(n).line_id   := l_resources_tbl(k).batchstep_resource_id;
327               END LOOP; /* Resource Txns Loop */
328             END LOOP; /* Resources Loop */
329           END LOOP; /* Activities Loop */
330         END LOOP; /* Steps Loop */
331         IF (g_debug <= gme_debug.g_log_statement) THEN
332           gme_debug.put_line('After steps processing now inserting all step data');
333         END IF;
334         FORALL a IN 1..l_steps_tbl.count
335           INSERT INTO gme_batch_steps VALUES l_steps_tbl(a);
336         IF (g_debug <= gme_debug.g_log_statement) THEN
337           gme_debug.put_line('After insert steps');
338         END IF;
339         FORALL a IN 1..l_activities_tbl.count
340           INSERT INTO gme_batch_step_activities VALUES l_activities_tbl(a);
341         IF (g_debug <= gme_debug.g_log_statement) THEN
342           gme_debug.put_line('After insert activities');
343         END IF;
344         FORALL a IN 1..l_resources_tbl.count
345           INSERT INTO gme_batch_step_resources VALUES l_resources_tbl(a);
346         IF (g_debug <= gme_debug.g_log_statement) THEN
347           gme_debug.put_line('After insert resources');
348         END IF;
349         FORALL a IN 1..l_proc_param_tbl.count
350           INSERT INTO gme_process_parameters VALUES l_proc_param_tbl(a);
351         IF (g_debug <= gme_debug.g_log_statement) THEN
352           gme_debug.put_line('After insert process params');
353         END IF;
354         FORALL a IN 1..l_rsrc_txns_tbl.count
355           INSERT INTO gme_resource_txns VALUES l_rsrc_txns_tbl(a);
356         IF (g_debug <= gme_debug.g_log_statement) THEN
357           gme_debug.put_line('After insert rsrc txns');
358         END IF;
359         create_step_dependencies(p_old_batch_id => get_batches.batch_id,
360                                  p_new_batch_id => l_batch_header.batch_id);
361         IF (g_debug <= gme_debug.g_log_statement) THEN
362           gme_debug.put_line('After create dependencies');
363         END IF;
364         create_item_step_assoc(p_old_batch_id => get_batches.batch_id,
365                                p_new_batch_id => l_batch_header.batch_id);
366         IF (g_debug <= gme_debug.g_log_statement) THEN
367           gme_debug.put_line('After create associations');
368         END IF;
369         create_batch_step_charges(p_old_batch_id => get_batches.batch_id,
370                                   p_new_batch_id => l_batch_header.batch_id);
371         IF (g_debug <= gme_debug.g_log_statement) THEN
372           gme_debug.put_line('After create charges');
373         END IF;
374         create_batch_step_transfers(p_old_batch_id => get_batches.batch_id,
375                                     p_new_batch_id => l_batch_header.batch_id);
376         IF (g_debug <= gme_debug.g_log_statement) THEN
377           gme_debug.put_line('After create transfers');
378         END IF;
379         FOR i IN 1..l_mtl_dtl_tbl.count LOOP
380           gme_common_pvt.calc_mtl_req_date(p_batch_header_rec      => l_batch_header
381                                           ,p_batchstep_rec         => NULL
382                                           ,p_mtl_dtl_rec           => l_mtl_dtl_tbl(i)
383                                           ,x_mtl_req_date          => l_mtl_dtl_tbl(i).material_requirement_date
384                                           ,x_return_status         => l_return_status);
385           IF (l_return_status <> fnd_api.g_ret_sts_success) THEN
386             RAISE calc_mtl_req_date_err;
387           END IF;
388         END LOOP;
389         IF (g_debug <= gme_debug.g_log_statement) THEN
390           gme_debug.put_line('After mtl_req_date');
391         END IF;
392         IF l_batch_header.batch_type = 0 AND NVL (l_batch_header.update_inventory_ind, 'Y') = 'Y' THEN
393           gme_move_orders_pvt.create_move_order_hdr
394               (p_organization_id           => l_batch_header.organization_id
395               ,p_move_order_type           => gme_common_pvt.g_invis_move_order_type
396               ,x_move_order_header_id      => l_batch_header.move_order_header_id
397               ,x_return_status             => l_return_status);
398           IF (l_return_status <> fnd_api.g_ret_sts_success) THEN
399             RAISE create_mo_hdr_err;
400           ELSE
401             l_in_mtl_dtl_tbl := l_mtl_dtl_tbl;
402             gme_move_orders_pvt.create_move_order_lines
403                  (p_move_order_header_id      => l_batch_header.move_order_header_id
404                  ,p_move_order_type           => gme_common_pvt.g_invis_move_order_type
405                  ,p_material_details_tbl      => l_in_mtl_dtl_tbl
406                  ,x_material_details_tbl      => l_mtl_dtl_tbl
407                  ,x_trolin_tbl                => l_trolin_tbl
408                  ,x_return_status             => l_return_status);
409             IF (l_return_status <> fnd_api.g_ret_sts_success) THEN
410               RAISE create_mo_line_err;
411             END IF;
412           END IF;
413         END IF;
414         IF (g_debug <= gme_debug.g_log_statement) THEN
415           gme_debug.put_line('After create move order');
416         END IF;
417         UPDATE gme_batch_header
418         SET move_order_header_id = l_batch_header.move_order_header_id
419         WHERE batch_id = l_batch_header.batch_id;
420 
421         FOR a IN 1..l_mtl_dtl_tbl.count LOOP
422           UPDATE gme_material_details
423           SET move_order_line_id = l_mtl_dtl_tbl(a).move_order_line_id,
424               material_requirement_date = l_mtl_dtl_tbl(a).material_requirement_date
425           WHERE material_detail_id = l_mtl_dtl_tbl(a).material_detail_id;
426         END LOOP;
427         IF (g_debug <= gme_debug.g_log_statement) THEN
428           gme_debug.put_line('After update material');
429         END IF;
430         create_batch_mapping(p_batch_header_mig => get_batches,
431                              p_batch_header     => l_batch_header);
432         UPDATE gme_batch_header_mig
433         SET migrated_batch_ind = 'M'
434         WHERE batch_id = get_batches.batch_id;
435         IF (g_debug <= gme_debug.g_log_statement) THEN
436           gme_debug.put_line('Done batch basic processing');
437         END IF;
438       EXCEPTION
439       	WHEN item_not_defined THEN
440           ROLLBACK;
441           OPEN Cur_item_mst(l_item_id);
442           FETCH Cur_item_mst INTO l_item_no;
443           CLOSE Cur_item_mst;
444           gma_common_logging.gma_migration_central_log
445                  (p_run_id              => g_migration_run_id,
446                   p_log_level           => fnd_log.level_error,
447                   p_message_token       => 'INV_IC_INVALID_ITEM_ORG',
448                   p_table_name          => 'GME_BATCH_HEADER',
449                   p_context             => 'RECREATE_OPEN_BATCHES',
450                   p_app_short_name      => 'INV',
451                   p_token1              => 'ORG',
452                   p_param1              => gme_common_pvt.g_organization_code,
453                   p_token2              => 'ITEM',
454                   p_param2              => l_item_no);
455         WHEN setup_failed OR calc_mtl_req_date_err OR create_mo_hdr_err OR create_mo_line_err THEN
456           ROLLBACK;
457           gme_common_pvt.count_and_get(x_count  => l_msg_count
458                                       ,x_data   => l_msg_data);
459           gma_common_logging.gma_migration_central_log
460                      (p_run_id              => g_migration_run_id,
461                       p_log_level           => fnd_log.level_error,
462                       p_message_token       => 'GME_BATCH_MIG_FAILED',
463                       p_table_name          => 'GME_BATCH_HEADER',
464                       p_context             => 'RECREATE_OPEN_BATCHES',
465                       p_app_short_name      => 'GME',
466                       p_token1              => 'BATCH_NO',
467                       p_param1              => get_batches.plant_code||'-'||get_batches.batch_no,
468                       p_token2              => 'MSG',
469                       p_param2              => l_msg_data);
470         WHEN OTHERS THEN
471           IF (g_debug <= gme_debug.g_log_unexpected) THEN
472             gme_debug.put_line('When others in '||l_api_name||' '||SQLERRM);
473           END IF;
474           ROLLBACK;
475           gma_common_logging.gma_migration_central_log
476                      (p_run_id              => g_migration_run_id,
477                       p_log_level           => fnd_log.level_error,
478                       p_message_token       => 'GME_BATCH_MIG_FAILED',
479                       p_table_name          => 'GME_BATCH_HEADER',
480                       p_context             => 'RECREATE_OPEN_BATCHES',
481                       p_app_short_name      => 'GME',
482                       p_token1              => 'BATCH_NO',
483                       p_param1              => get_batches.plant_code||'-'||get_batches.batch_no,
484                       p_token2              => 'MSG',
485                       p_param2              => SQLERRM);
486       END;
487       COMMIT;
488     END LOOP;
489     IF (g_debug <= gme_debug.g_log_statement) THEN
490       gme_debug.put_line('Create phantom links');
491     END IF;
492     create_phantom_links;
493     IF (g_debug <= gme_debug.g_log_statement) THEN
494       gme_debug.put_line('Create Reservations/Pending Lots');
495     END IF;
496     /* Bug 5620671 Added param completed ind */
497     create_txns_reservations(0);
498     IF (g_debug <= gme_debug.g_log_statement) THEN
499       gme_debug.put_line('Release batches');
500     END IF;
501     gme_common_pvt.g_transaction_header_id := NULL;
502     release_batches;
503     IF (g_debug <= gme_debug.g_log_statement) THEN
504       gme_debug.put_line('Create transactions');
505     END IF;
506     /* Bug 5620671 Added param completed ind */
507     create_txns_reservations(1);
508     IF (g_debug <= gme_debug.g_log_statement) THEN
509       gme_debug.put_line('Insert lab lots');
510     END IF;
511     insert_lab_lots;
512     IF (g_debug <= gme_debug.g_log_statement) THEN
513       gme_debug.put_line('Close Steps');
514     END IF;
515     close_steps;
516     /* Bug 5703541 Added update stmt and loop for mtl_lot_conv_audit */
517     IF (g_debug <= gme_debug.g_log_statement) THEN
518       gme_debug.put_line('Update mtl_lot_conv_audit');
519     END IF;
520     FOR get_rec IN (SELECT old_batch_id, new_batch_id FROM gme_batch_mapping_mig
521                     WHERE old_batch_id IN (SELECT DISTINCT(batch_id) FROM mtl_lot_conv_audit)) LOOP
522       UPDATE mtl_lot_conv_audit
523       SET batch_id = get_rec.new_batch_id
524       WHERE batch_id = get_rec.old_batch_id;
525     END LOOP;
526 
527     IF (g_debug <= gme_debug.g_log_statement) THEN
528       gme_debug.put_line('Call QM');
529     END IF;
530     gmd_qc_migb12.gmd_qc_migrate_batch_id(p_migration_run_id => g_migration_run_id,
531                                           p_commit           => FND_API.G_TRUE,
532                                           x_exception_count  => l_msg_count);
533     IF (g_debug <= gme_debug.g_log_procedure) THEN
534       gme_debug.put_line('End procedure '||l_api_name);
535     END IF;
536     gma_migration.gma_migration_end (l_run_id => g_migration_run_id);
537   EXCEPTION
538     WHEN OTHERS THEN
539       IF (g_debug <= gme_debug.g_log_unexpected) THEN
540         gme_debug.put_line('When others in '||l_api_name||' '||SQLERRM);
541       END IF;
542       gma_common_logging.gma_migration_central_log
543                   (p_run_id              => g_migration_run_id,
544                    p_log_level           => fnd_log.level_unexpected,
545                    p_message_token       => 'GMA_MIGRATION_DB_ERROR',
546                    p_table_name          => 'GME_BATCH_HEADER',
547                    p_context             => 'RECREATE_OPEN_BATCHES',
548                    p_db_error            => SQLERRM,
549                    p_app_short_name      => 'GMA');
550   END recreate_open_batches;
551 
552   PROCEDURE build_batch_hdr(p_batch_header_mig   IN gme_batch_header_mig%ROWTYPE,
553                             x_batch_header       OUT NOCOPY gme_batch_header%ROWTYPE) IS
554   BEGIN
555     x_batch_header.batch_id                   := p_batch_header_mig.batch_id;
556     x_batch_header.plant_code                 := p_batch_header_mig.plant_code;
557     x_batch_header.batch_no                   := p_batch_header_mig.batch_no;
558     x_batch_header.batch_type                 := p_batch_header_mig.batch_type;
559     x_batch_header.prod_id                    := p_batch_header_mig.prod_id;
560     x_batch_header.prod_sequence              := p_batch_header_mig.prod_sequence;
561     x_batch_header.recipe_validity_rule_id    := p_batch_header_mig.recipe_validity_rule_id;
562     x_batch_header.formula_id                 := p_batch_header_mig.formula_id;
563     x_batch_header.routing_id                 := p_batch_header_mig.routing_id;
564     x_batch_header.plan_start_date            := p_batch_header_mig.plan_start_date;
565     x_batch_header.actual_start_date          := p_batch_header_mig.actual_start_date;
566     x_batch_header.due_date                   := p_batch_header_mig.due_date;
567     x_batch_header.plan_cmplt_date            := p_batch_header_mig.plan_cmplt_date;
568     x_batch_header.actual_cmplt_date          := p_batch_header_mig.actual_cmplt_date;
569     x_batch_header.batch_status               := p_batch_header_mig.batch_status;
570     x_batch_header.priority_value             := p_batch_header_mig.priority_value;
571     x_batch_header.priority_code              := p_batch_header_mig.priority_code;
572     x_batch_header.print_count                := p_batch_header_mig.print_count;
573     x_batch_header.fmcontrol_class            := p_batch_header_mig.fmcontrol_class;
574     x_batch_header.wip_whse_code              := p_batch_header_mig.wip_whse_code;
575     x_batch_header.batch_close_date           := p_batch_header_mig.batch_close_date;
576     x_batch_header.poc_ind                    := p_batch_header_mig.poc_ind;
577     x_batch_header.actual_cost_ind            := p_batch_header_mig.actual_cost_ind;
578     x_batch_header.update_inventory_ind       := p_batch_header_mig.update_inventory_ind;
579     x_batch_header.last_update_date           := p_batch_header_mig.last_update_date;
580     x_batch_header.last_updated_by            := p_batch_header_mig.last_updated_by;
581     x_batch_header.creation_date              := p_batch_header_mig.creation_date;
582     x_batch_header.created_by                 := p_batch_header_mig.created_by;
583     x_batch_header.last_update_login          := p_batch_header_mig.last_update_login;
584     x_batch_header.delete_mark                := p_batch_header_mig.delete_mark;
585     x_batch_header.text_code                  := p_batch_header_mig.text_code;
586     x_batch_header.parentline_id              := p_batch_header_mig.parentline_id;
587     x_batch_header.fpo_id                     := p_batch_header_mig.fpo_id;
588     x_batch_header.attribute1                 := p_batch_header_mig.attribute1;
589     x_batch_header.attribute2                 := p_batch_header_mig.attribute2;
590     x_batch_header.attribute3                 := p_batch_header_mig.attribute3;
591     x_batch_header.attribute4                 := p_batch_header_mig.attribute4;
592     x_batch_header.attribute5                 := p_batch_header_mig.attribute5;
593     x_batch_header.attribute6                 := p_batch_header_mig.attribute6;
594     x_batch_header.attribute7                 := p_batch_header_mig.attribute7;
595     x_batch_header.attribute8                 := p_batch_header_mig.attribute8;
596     x_batch_header.attribute9                 := p_batch_header_mig.attribute9;
597     x_batch_header.attribute10                := p_batch_header_mig.attribute10;
598     x_batch_header.attribute11                := p_batch_header_mig.attribute11;
599     x_batch_header.attribute12                := p_batch_header_mig.attribute12;
600     x_batch_header.attribute13                := p_batch_header_mig.attribute13;
601     x_batch_header.attribute14                := p_batch_header_mig.attribute14;
602     x_batch_header.attribute15                := p_batch_header_mig.attribute15;
603     x_batch_header.attribute16                := p_batch_header_mig.attribute16;
604     x_batch_header.attribute17                := p_batch_header_mig.attribute17;
605     x_batch_header.attribute18                := p_batch_header_mig.attribute18;
606     x_batch_header.attribute19                := p_batch_header_mig.attribute19;
607     x_batch_header.attribute20                := p_batch_header_mig.attribute20;
608     x_batch_header.attribute21                := p_batch_header_mig.attribute21;
609     x_batch_header.attribute22                := p_batch_header_mig.attribute22;
610     x_batch_header.attribute23                := p_batch_header_mig.attribute23;
611     x_batch_header.attribute24                := p_batch_header_mig.attribute24;
612     x_batch_header.attribute25                := p_batch_header_mig.attribute25;
613     x_batch_header.attribute26                := p_batch_header_mig.attribute26;
614     x_batch_header.attribute27                := p_batch_header_mig.attribute27;
615     x_batch_header.attribute28                := p_batch_header_mig.attribute28;
616     x_batch_header.attribute29                := p_batch_header_mig.attribute29;
617     x_batch_header.attribute30                := p_batch_header_mig.attribute30;
618     x_batch_header.attribute_category         := p_batch_header_mig.attribute_category;
619     x_batch_header.automatic_step_calculation := p_batch_header_mig.automatic_step_calculation;
620     x_batch_header.gl_posted_ind              := p_batch_header_mig.gl_posted_ind;
621     x_batch_header.firmed_ind                 := p_batch_header_mig.firmed_ind;
622     x_batch_header.finite_scheduled_ind       := p_batch_header_mig.finite_scheduled_ind;
623     x_batch_header.order_priority             := p_batch_header_mig.order_priority;
624     x_batch_header.attribute31                := p_batch_header_mig.attribute31;
625     x_batch_header.attribute32                := p_batch_header_mig.attribute32;
626     x_batch_header.attribute33                := p_batch_header_mig.attribute33;
627     x_batch_header.attribute34                := p_batch_header_mig.attribute34;
628     x_batch_header.attribute35                := p_batch_header_mig.attribute35;
629     x_batch_header.attribute36                := p_batch_header_mig.attribute36;
630     x_batch_header.attribute37                := p_batch_header_mig.attribute37;
631     x_batch_header.attribute38                := p_batch_header_mig.attribute38;
632     x_batch_header.attribute39                := p_batch_header_mig.attribute39;
633     x_batch_header.attribute40                := p_batch_header_mig.attribute40;
634     x_batch_header.migrated_batch_ind         := p_batch_header_mig.migrated_batch_ind;
635     x_batch_header.enforce_step_dependency    := p_batch_header_mig.enforce_step_dependency;
636     x_batch_header.terminated_ind             := p_batch_header_mig.terminated_ind;
637     x_batch_header.enhanced_pi_ind            := p_batch_header_mig.enhanced_pi_ind;
638     x_batch_header.laboratory_ind             := p_batch_header_mig.laboratory_ind;
639     x_batch_header.move_order_header_id       := p_batch_header_mig.move_order_header_id;
640     x_batch_header.organization_id            := p_batch_header_mig.organization_id;
641     x_batch_header.terminate_reason_id        := p_batch_header_mig.terminate_reason_id;
642   END build_batch_hdr;
643 
644   PROCEDURE build_mtl_dtl(p_mtl_dtl_mig   IN  gme_post_migration.mtl_dtl_mig_tab,
645                           x_mtl_dtl       OUT NOCOPY gme_common_pvt.material_details_tab) IS
646   BEGIN
647     FOR i IN 1..p_mtl_dtl_mig.count LOOP
648       x_mtl_dtl(i).material_detail_id        := p_mtl_dtl_mig(i).material_detail_id;
649       x_mtl_dtl(i).batch_id                  := p_mtl_dtl_mig(i).batch_id;
650       x_mtl_dtl(i).formulaline_id            := p_mtl_dtl_mig(i).formulaline_id;
651       x_mtl_dtl(i).line_no                   := p_mtl_dtl_mig(i).line_no;
652       x_mtl_dtl(i).item_id                   := p_mtl_dtl_mig(i).item_id;
653       x_mtl_dtl(i).line_type                 := p_mtl_dtl_mig(i).line_type;
654       x_mtl_dtl(i).plan_qty                  := p_mtl_dtl_mig(i).plan_qty;
655       x_mtl_dtl(i).item_um                   := p_mtl_dtl_mig(i).item_um;
656       x_mtl_dtl(i).item_um2                  := p_mtl_dtl_mig(i).item_um2;
657       x_mtl_dtl(i).actual_qty                := p_mtl_dtl_mig(i).actual_qty;
658       x_mtl_dtl(i).release_type              := p_mtl_dtl_mig(i).release_type;
659       x_mtl_dtl(i).scrap_factor              := p_mtl_dtl_mig(i).scrap_factor;
660       x_mtl_dtl(i).scale_type                := p_mtl_dtl_mig(i).scale_type;
661       x_mtl_dtl(i).phantom_type              := p_mtl_dtl_mig(i).phantom_type;
662       x_mtl_dtl(i).cost_alloc                := p_mtl_dtl_mig(i).cost_alloc;
663       x_mtl_dtl(i).alloc_ind                 := p_mtl_dtl_mig(i).alloc_ind;
664       x_mtl_dtl(i).cost                      := p_mtl_dtl_mig(i).cost;
665       x_mtl_dtl(i).text_code                 := p_mtl_dtl_mig(i).text_code;
666       x_mtl_dtl(i).phantom_id                := p_mtl_dtl_mig(i).phantom_id;
667       x_mtl_dtl(i).rounding_direction        := p_mtl_dtl_mig(i).rounding_direction;
668       x_mtl_dtl(i).creation_date             := p_mtl_dtl_mig(i).creation_date;
669       x_mtl_dtl(i).created_by                := p_mtl_dtl_mig(i).created_by;
670       x_mtl_dtl(i).last_update_date          := p_mtl_dtl_mig(i).last_update_date;
671       x_mtl_dtl(i).last_updated_by           := p_mtl_dtl_mig(i).last_updated_by;
672       x_mtl_dtl(i).attribute1                := p_mtl_dtl_mig(i).attribute1;
673       x_mtl_dtl(i).attribute2                := p_mtl_dtl_mig(i).attribute2;
674       x_mtl_dtl(i).attribute3                := p_mtl_dtl_mig(i).attribute3;
675       x_mtl_dtl(i).attribute4                := p_mtl_dtl_mig(i).attribute4;
676       x_mtl_dtl(i).attribute5                := p_mtl_dtl_mig(i).attribute5;
677       x_mtl_dtl(i).attribute6                := p_mtl_dtl_mig(i).attribute6;
678       x_mtl_dtl(i).attribute7                := p_mtl_dtl_mig(i).attribute7;
679       x_mtl_dtl(i).attribute8                := p_mtl_dtl_mig(i).attribute8;
680       x_mtl_dtl(i).attribute9                := p_mtl_dtl_mig(i).attribute9;
681       x_mtl_dtl(i).attribute10               := p_mtl_dtl_mig(i).attribute10;
682       x_mtl_dtl(i).attribute11               := p_mtl_dtl_mig(i).attribute11;
683       x_mtl_dtl(i).attribute12               := p_mtl_dtl_mig(i).attribute12;
684       x_mtl_dtl(i).attribute13               := p_mtl_dtl_mig(i).attribute13;
685       x_mtl_dtl(i).attribute14               := p_mtl_dtl_mig(i).attribute14;
686       x_mtl_dtl(i).attribute15               := p_mtl_dtl_mig(i).attribute15;
687       x_mtl_dtl(i).attribute16               := p_mtl_dtl_mig(i).attribute16;
688       x_mtl_dtl(i).attribute17               := p_mtl_dtl_mig(i).attribute17;
689       x_mtl_dtl(i).attribute18               := p_mtl_dtl_mig(i).attribute18;
690       x_mtl_dtl(i).attribute19               := p_mtl_dtl_mig(i).attribute19;
691       x_mtl_dtl(i).attribute20               := p_mtl_dtl_mig(i).attribute20;
692       x_mtl_dtl(i).attribute21               := p_mtl_dtl_mig(i).attribute21;
693       x_mtl_dtl(i).attribute22               := p_mtl_dtl_mig(i).attribute22;
694       x_mtl_dtl(i).attribute23               := p_mtl_dtl_mig(i).attribute23;
695       x_mtl_dtl(i).attribute24               := p_mtl_dtl_mig(i).attribute24;
696       x_mtl_dtl(i).attribute25               := p_mtl_dtl_mig(i).attribute25;
697       x_mtl_dtl(i).attribute26               := p_mtl_dtl_mig(i).attribute26;
698       x_mtl_dtl(i).attribute27               := p_mtl_dtl_mig(i).attribute27;
699       x_mtl_dtl(i).attribute28               := p_mtl_dtl_mig(i).attribute28;
700       x_mtl_dtl(i).attribute29               := p_mtl_dtl_mig(i).attribute29;
701       x_mtl_dtl(i).attribute30               := p_mtl_dtl_mig(i).attribute30;
702       x_mtl_dtl(i).attribute_category        := p_mtl_dtl_mig(i).attribute_category;
703       x_mtl_dtl(i).last_update_login         := p_mtl_dtl_mig(i).last_update_login;
704       x_mtl_dtl(i).scale_rounding_variance   := p_mtl_dtl_mig(i).scale_rounding_variance;
705       x_mtl_dtl(i).scale_multiple            := p_mtl_dtl_mig(i).scale_multiple;
706       x_mtl_dtl(i).contribute_yield_ind      := p_mtl_dtl_mig(i).contribute_yield_ind;
707       x_mtl_dtl(i).contribute_step_qty_ind   := p_mtl_dtl_mig(i).contribute_step_qty_ind;
708       x_mtl_dtl(i).wip_plan_qty              := p_mtl_dtl_mig(i).wip_plan_qty;
709       x_mtl_dtl(i).original_qty              := p_mtl_dtl_mig(i).original_qty;
710       x_mtl_dtl(i).by_product_type           := p_mtl_dtl_mig(i).by_product_type;
711       x_mtl_dtl(i).backordered_qty           := p_mtl_dtl_mig(i).backordered_qty;
712       x_mtl_dtl(i).dispense_ind              := p_mtl_dtl_mig(i).dispense_ind;
713       x_mtl_dtl(i).dtl_um                    := p_mtl_dtl_mig(i).dtl_um;
714       x_mtl_dtl(i).inventory_item_id         := p_mtl_dtl_mig(i).inventory_item_id;
715       x_mtl_dtl(i).locator_id                := p_mtl_dtl_mig(i).locator_id;
716       x_mtl_dtl(i).material_requirement_date := p_mtl_dtl_mig(i).material_requirement_date;
717       x_mtl_dtl(i).move_order_line_id        := p_mtl_dtl_mig(i).move_order_line_id;
718       x_mtl_dtl(i).organization_id           := p_mtl_dtl_mig(i).organization_id;
719       x_mtl_dtl(i).original_primary_qty      := p_mtl_dtl_mig(i).original_primary_qty;
720       x_mtl_dtl(i).phantom_line_id           := p_mtl_dtl_mig(i).phantom_line_id;
721       x_mtl_dtl(i).revision                  := p_mtl_dtl_mig(i).revision;
722       x_mtl_dtl(i).subinventory              := p_mtl_dtl_mig(i).subinventory;
723     END LOOP;
724   END build_mtl_dtl;
725 
726   PROCEDURE build_steps(p_steps_mig   IN  gme_post_migration.steps_mig_tab,
727                         x_steps       OUT NOCOPY gme_common_pvt.steps_tab) IS
728   BEGIN
729     FOR i IN 1..p_steps_mig.count LOOP
730       x_steps(i).batch_id              := p_steps_mig(i).batch_id;
731       x_steps(i).batchstep_id          := p_steps_mig(i).batchstep_id;
732       x_steps(i).routingstep_id        := p_steps_mig(i).routingstep_id;
733       x_steps(i).batchstep_no          := p_steps_mig(i).batchstep_no;
734       x_steps(i).oprn_id               := p_steps_mig(i).oprn_id;
735       x_steps(i).plan_step_qty         := p_steps_mig(i).plan_step_qty;
736       x_steps(i).actual_step_qty       := p_steps_mig(i).actual_step_qty;
737       x_steps(i).step_qty_uom          := p_steps_mig(i).step_qty_uom;
738       x_steps(i).backflush_qty         := p_steps_mig(i).backflush_qty;
739       x_steps(i).plan_start_date       := p_steps_mig(i).plan_start_date;
740       x_steps(i).actual_start_date     := p_steps_mig(i).actual_start_date;
741       x_steps(i).due_date              := p_steps_mig(i).due_date;
742       x_steps(i).plan_cmplt_date       := p_steps_mig(i).plan_cmplt_date;
743       x_steps(i).actual_cmplt_date     := p_steps_mig(i).actual_cmplt_date;
744       x_steps(i).step_close_date       := p_steps_mig(i).step_close_date;
745       x_steps(i).step_status           := p_steps_mig(i).step_status;
746       x_steps(i).priority_code         := p_steps_mig(i).priority_code;
747       x_steps(i).priority_value        := p_steps_mig(i).priority_value;
748       x_steps(i).delete_mark           := p_steps_mig(i).delete_mark;
749       x_steps(i).steprelease_type      := p_steps_mig(i).steprelease_type;
750       x_steps(i).max_step_capacity     := p_steps_mig(i).max_step_capacity;
751       x_steps(i).max_step_capacity_uom := p_steps_mig(i).max_step_capacity_uom;
752       x_steps(i).plan_charges          := p_steps_mig(i).plan_charges;
753       x_steps(i).actual_charges        := p_steps_mig(i).actual_charges;
754       x_steps(i).mass_ref_uom          := p_steps_mig(i).mass_ref_uom;
755       x_steps(i).plan_mass_qty         := p_steps_mig(i).plan_mass_qty;
756       x_steps(i).volume_ref_uom        := p_steps_mig(i).volume_ref_uom;
757       x_steps(i).plan_volume_qty       := p_steps_mig(i).plan_volume_qty;
758       x_steps(i).text_code             := p_steps_mig(i).text_code;
759       x_steps(i).actual_mass_qty       := p_steps_mig(i).actual_mass_qty;
760       x_steps(i).actual_volume_qty     := p_steps_mig(i).actual_volume_qty;
761       x_steps(i).last_update_date      := p_steps_mig(i).last_update_date;
762       x_steps(i).creation_date         := p_steps_mig(i).creation_date;
763       x_steps(i).created_by            := p_steps_mig(i).created_by;
764       x_steps(i).last_updated_by       := p_steps_mig(i).last_updated_by;
765       x_steps(i).last_update_login     := p_steps_mig(i).last_update_login;
766       x_steps(i).attribute_category    := p_steps_mig(i).attribute_category;
767       x_steps(i).attribute1            := p_steps_mig(i).attribute1;
768       x_steps(i).attribute2            := p_steps_mig(i).attribute2;
769       x_steps(i).attribute3            := p_steps_mig(i).attribute3;
770       x_steps(i).attribute4            := p_steps_mig(i).attribute4;
771       x_steps(i).attribute5            := p_steps_mig(i).attribute5;
772       x_steps(i).attribute6            := p_steps_mig(i).attribute6;
773       x_steps(i).attribute7            := p_steps_mig(i).attribute7;
774       x_steps(i).attribute8            := p_steps_mig(i).attribute8;
775       x_steps(i).attribute9            := p_steps_mig(i).attribute9;
776       x_steps(i).attribute10           := p_steps_mig(i).attribute10;
777       x_steps(i).attribute11           := p_steps_mig(i).attribute11;
778       x_steps(i).attribute12           := p_steps_mig(i).attribute12;
779       x_steps(i).attribute13           := p_steps_mig(i).attribute13;
780       x_steps(i).attribute14           := p_steps_mig(i).attribute14;
781       x_steps(i).attribute15           := p_steps_mig(i).attribute15;
782       x_steps(i).attribute16           := p_steps_mig(i).attribute16;
783       x_steps(i).attribute17           := p_steps_mig(i).attribute17;
784       x_steps(i).attribute18           := p_steps_mig(i).attribute18;
785       x_steps(i).attribute19           := p_steps_mig(i).attribute19;
786       x_steps(i).attribute20           := p_steps_mig(i).attribute20;
787       x_steps(i).attribute21           := p_steps_mig(i).attribute21;
788       x_steps(i).attribute22           := p_steps_mig(i).attribute22;
789       x_steps(i).attribute23           := p_steps_mig(i).attribute23;
790       x_steps(i).attribute24           := p_steps_mig(i).attribute24;
791       x_steps(i).attribute25           := p_steps_mig(i).attribute25;
792       x_steps(i).attribute26           := p_steps_mig(i).attribute26;
793       x_steps(i).attribute27           := p_steps_mig(i).attribute27;
794       x_steps(i).attribute28           := p_steps_mig(i).attribute28;
795       x_steps(i).attribute29           := p_steps_mig(i).attribute29;
796       x_steps(i).attribute30           := p_steps_mig(i).attribute30;
797       x_steps(i).quality_status        := p_steps_mig(i).quality_status;
798       x_steps(i).minimum_transfer_qty  := p_steps_mig(i).minimum_transfer_qty;
799       x_steps(i).terminated_ind        := p_steps_mig(i).terminated_ind;
800       x_steps(i).mass_ref_um           := p_steps_mig(i).mass_ref_um;
801       x_steps(i).max_step_capacity_um  := p_steps_mig(i).max_step_capacity_um;
802       x_steps(i).step_qty_um           := p_steps_mig(i).step_qty_um;
803       x_steps(i).volume_ref_um         := p_steps_mig(i).volume_ref_um;
804     END LOOP;
805   END build_steps;
806 
807   PROCEDURE build_activities(p_activities_mig IN gme_post_migration.activ_mig_tab,
808                              x_activities     IN OUT NOCOPY gme_common_pvt.activities_tab) IS
809     l_cnt   NUMBER := 0;
810   BEGIN
811     l_cnt := x_activities.count;
812     FOR i IN 1..p_activities_mig.count LOOP
813       l_cnt := l_cnt + 1;
814       x_activities(l_cnt).batch_id               := p_activities_mig(i).batch_id;
815       x_activities(l_cnt).activity               := p_activities_mig(i).activity;
816       x_activities(l_cnt).batchstep_id           := p_activities_mig(i).batchstep_id;
817       x_activities(l_cnt).batchstep_activity_id  := p_activities_mig(i).batchstep_activity_id;
818       x_activities(l_cnt).oprn_line_id           := p_activities_mig(i).oprn_line_id;
819       x_activities(l_cnt).offset_interval        := p_activities_mig(i).offset_interval;
820       x_activities(l_cnt).plan_start_date        := p_activities_mig(i).plan_start_date;
821       x_activities(l_cnt).actual_start_date      := p_activities_mig(i).actual_start_date;
822       x_activities(l_cnt).plan_cmplt_date        := p_activities_mig(i).plan_cmplt_date;
823       x_activities(l_cnt).actual_cmplt_date      := p_activities_mig(i).actual_cmplt_date;
824       x_activities(l_cnt).plan_activity_factor   := p_activities_mig(i).plan_activity_factor;
825       x_activities(l_cnt).actual_activity_factor := p_activities_mig(i).actual_activity_factor;
826       x_activities(l_cnt).delete_mark            := p_activities_mig(i).delete_mark;
827       x_activities(l_cnt).attribute_category     := p_activities_mig(i).attribute_category;
828       x_activities(l_cnt).attribute1             := p_activities_mig(i).attribute1;
829       x_activities(l_cnt).attribute2             := p_activities_mig(i).attribute2;
830       x_activities(l_cnt).attribute3             := p_activities_mig(i).attribute3;
831       x_activities(l_cnt).attribute4             := p_activities_mig(i).attribute4;
832       x_activities(l_cnt).attribute5             := p_activities_mig(i).attribute5;
833       x_activities(l_cnt).attribute6             := p_activities_mig(i).attribute6;
834       x_activities(l_cnt).attribute7             := p_activities_mig(i).attribute7;
835       x_activities(l_cnt).attribute8             := p_activities_mig(i).attribute8;
836       x_activities(l_cnt).attribute9             := p_activities_mig(i).attribute9;
837       x_activities(l_cnt).attribute10            := p_activities_mig(i).attribute10;
838       x_activities(l_cnt).attribute11            := p_activities_mig(i).attribute11;
839       x_activities(l_cnt).attribute12            := p_activities_mig(i).attribute12;
840       x_activities(l_cnt).attribute13            := p_activities_mig(i).attribute13;
841       x_activities(l_cnt).attribute14            := p_activities_mig(i).attribute14;
842       x_activities(l_cnt).attribute15            := p_activities_mig(i).attribute15;
843       x_activities(l_cnt).attribute16            := p_activities_mig(i).attribute16;
844       x_activities(l_cnt).attribute17            := p_activities_mig(i).attribute17;
845       x_activities(l_cnt).attribute18            := p_activities_mig(i).attribute18;
846       x_activities(l_cnt).attribute19            := p_activities_mig(i).attribute19;
847       x_activities(l_cnt).attribute20            := p_activities_mig(i).attribute20;
848       x_activities(l_cnt).attribute21            := p_activities_mig(i).attribute21;
849       x_activities(l_cnt).attribute22            := p_activities_mig(i).attribute22;
850       x_activities(l_cnt).attribute23            := p_activities_mig(i).attribute23;
851       x_activities(l_cnt).attribute24            := p_activities_mig(i).attribute24;
852       x_activities(l_cnt).attribute25            := p_activities_mig(i).attribute25;
853       x_activities(l_cnt).attribute26            := p_activities_mig(i).attribute26;
854       x_activities(l_cnt).attribute27            := p_activities_mig(i).attribute27;
855       x_activities(l_cnt).attribute28            := p_activities_mig(i).attribute28;
856       x_activities(l_cnt).attribute29            := p_activities_mig(i).attribute29;
857       x_activities(l_cnt).attribute30            := p_activities_mig(i).attribute30;
858       x_activities(l_cnt).creation_date          := p_activities_mig(i).creation_date;
859       x_activities(l_cnt).created_by             := p_activities_mig(i).created_by;
860       x_activities(l_cnt).last_update_date       := p_activities_mig(i).last_update_date;
861       x_activities(l_cnt).last_updated_by        := p_activities_mig(i).last_updated_by;
862       x_activities(l_cnt).last_update_login      := p_activities_mig(i).last_update_login;
863       x_activities(l_cnt).text_code              := p_activities_mig(i).text_code;
864       x_activities(l_cnt).sequence_dependent_ind := p_activities_mig(i).sequence_dependent_ind;
865       x_activities(l_cnt).max_break              := p_activities_mig(i).max_break;
866       x_activities(l_cnt).break_ind              := p_activities_mig(i).break_ind;
867       x_activities(l_cnt).material_ind           := p_activities_mig(i).material_ind;
868     END LOOP;
869   END build_activities;
870 
871   PROCEDURE build_resources(p_resources_mig IN gme_post_migration.rsrc_mig_tab,
872                             x_resources     IN OUT NOCOPY gme_common_pvt.resources_tab) IS
873     l_cnt   NUMBER := 0;
874   BEGIN
875     l_cnt := x_resources.count;
876     FOR i IN 1..p_resources_mig.count LOOP
877       l_cnt := l_cnt + 1;
878       x_resources(l_cnt).batchstep_resource_id    := p_resources_mig(i).batchstep_resource_id;
879       x_resources(l_cnt).batchstep_activity_id    := p_resources_mig(i).batchstep_activity_id;
880       x_resources(l_cnt).resources                := p_resources_mig(i).resources;
881       x_resources(l_cnt).batchstep_id             := p_resources_mig(i).batchstep_id;
882       x_resources(l_cnt).batch_id                 := p_resources_mig(i).batch_id;
883       x_resources(l_cnt).cost_analysis_code       := p_resources_mig(i).cost_analysis_code;
884       x_resources(l_cnt).cost_cmpntcls_id         := p_resources_mig(i).cost_cmpntcls_id;
885       x_resources(l_cnt).prim_rsrc_ind            := p_resources_mig(i).prim_rsrc_ind;
886       x_resources(l_cnt).scale_type               := p_resources_mig(i).scale_type;
887       x_resources(l_cnt).plan_rsrc_count          := p_resources_mig(i).plan_rsrc_count;
888       x_resources(l_cnt).actual_rsrc_count        := p_resources_mig(i).actual_rsrc_count;
889       x_resources(l_cnt).resource_qty_uom         := p_resources_mig(i).resource_qty_uom;
890       x_resources(l_cnt).capacity_uom             := p_resources_mig(i).capacity_uom;
891       x_resources(l_cnt).plan_rsrc_usage          := p_resources_mig(i).plan_rsrc_usage;
892       x_resources(l_cnt).actual_rsrc_usage        := p_resources_mig(i).actual_rsrc_usage;
893       x_resources(l_cnt).plan_rsrc_qty            := p_resources_mig(i).plan_rsrc_qty;
894       x_resources(l_cnt).actual_rsrc_qty          := p_resources_mig(i).actual_rsrc_qty;
895       x_resources(l_cnt).usage_uom                := p_resources_mig(i).usage_uom;
896       x_resources(l_cnt).plan_start_date          := p_resources_mig(i).plan_start_date;
897       x_resources(l_cnt).actual_start_date        := p_resources_mig(i).actual_start_date;
898       x_resources(l_cnt).plan_cmplt_date          := p_resources_mig(i).plan_cmplt_date;
899       x_resources(l_cnt).actual_cmplt_date        := p_resources_mig(i).actual_cmplt_date;
900       x_resources(l_cnt).offset_interval          := p_resources_mig(i).offset_interval;
901       x_resources(l_cnt).min_capacity             := p_resources_mig(i).min_capacity;
902       x_resources(l_cnt).max_capacity             := p_resources_mig(i).max_capacity;
903       x_resources(l_cnt).calculate_charges        := p_resources_mig(i).calculate_charges;
904       x_resources(l_cnt).process_parameter_1      := p_resources_mig(i).process_parameter_1;
905       x_resources(l_cnt).process_parameter_2      := p_resources_mig(i).process_parameter_2;
906       x_resources(l_cnt).process_parameter_3      := p_resources_mig(i).process_parameter_3;
907       x_resources(l_cnt).process_parameter_4      := p_resources_mig(i).process_parameter_4;
908       x_resources(l_cnt).process_parameter_5      := p_resources_mig(i).process_parameter_5;
909       x_resources(l_cnt).attribute_category       := p_resources_mig(i).attribute_category;
910       x_resources(l_cnt).attribute1               := p_resources_mig(i).attribute1;
911       x_resources(l_cnt).attribute2               := p_resources_mig(i).attribute2;
912       x_resources(l_cnt).attribute3               := p_resources_mig(i).attribute3;
913       x_resources(l_cnt).attribute4               := p_resources_mig(i).attribute4;
914       x_resources(l_cnt).attribute5               := p_resources_mig(i).attribute5;
915       x_resources(l_cnt).attribute6               := p_resources_mig(i).attribute6;
916       x_resources(l_cnt).attribute7               := p_resources_mig(i).attribute7;
917       x_resources(l_cnt).attribute8               := p_resources_mig(i).attribute8;
918       x_resources(l_cnt).attribute9               := p_resources_mig(i).attribute9;
919       x_resources(l_cnt).attribute10              := p_resources_mig(i).attribute10;
920       x_resources(l_cnt).attribute11              := p_resources_mig(i).attribute11;
921       x_resources(l_cnt).attribute12              := p_resources_mig(i).attribute12;
922       x_resources(l_cnt).attribute13              := p_resources_mig(i).attribute13;
923       x_resources(l_cnt).attribute14              := p_resources_mig(i).attribute14;
924       x_resources(l_cnt).attribute15              := p_resources_mig(i).attribute15;
925       x_resources(l_cnt).attribute16              := p_resources_mig(i).attribute16;
926       x_resources(l_cnt).attribute17              := p_resources_mig(i).attribute17;
927       x_resources(l_cnt).attribute18              := p_resources_mig(i).attribute18;
928       x_resources(l_cnt).attribute19              := p_resources_mig(i).attribute19;
929       x_resources(l_cnt).attribute20              := p_resources_mig(i).attribute20;
930       x_resources(l_cnt).attribute21              := p_resources_mig(i).attribute21;
931       x_resources(l_cnt).attribute22              := p_resources_mig(i).attribute22;
932       x_resources(l_cnt).attribute23              := p_resources_mig(i).attribute23;
933       x_resources(l_cnt).attribute24              := p_resources_mig(i).attribute24;
934       x_resources(l_cnt).attribute25              := p_resources_mig(i).attribute25;
935       x_resources(l_cnt).attribute26              := p_resources_mig(i).attribute26;
936       x_resources(l_cnt).attribute27              := p_resources_mig(i).attribute27;
937       x_resources(l_cnt).attribute28              := p_resources_mig(i).attribute28;
938       x_resources(l_cnt).attribute29              := p_resources_mig(i).attribute29;
939       x_resources(l_cnt).attribute30              := p_resources_mig(i).attribute30;
940       x_resources(l_cnt).last_update_login        := p_resources_mig(i).last_update_login;
941       x_resources(l_cnt).last_update_date         := p_resources_mig(i).last_update_date;
942       x_resources(l_cnt).last_updated_by          := p_resources_mig(i).last_updated_by;
943       x_resources(l_cnt).created_by               := p_resources_mig(i).created_by;
944       x_resources(l_cnt).creation_date            := p_resources_mig(i).creation_date;
945       x_resources(l_cnt).text_code                := p_resources_mig(i).text_code;
946       x_resources(l_cnt).capacity_tolerance       := p_resources_mig(i).capacity_tolerance;
947       x_resources(l_cnt).original_rsrc_qty        := p_resources_mig(i).original_rsrc_qty;
948       x_resources(l_cnt).original_rsrc_usage      := p_resources_mig(i).original_rsrc_usage;
949       x_resources(l_cnt).sequence_dependent_id    := p_resources_mig(i).sequence_dependent_id;
950       x_resources(l_cnt).sequence_dependent_usage := p_resources_mig(i).sequence_dependent_usage;
951       x_resources(l_cnt).firm_type                := p_resources_mig(i).firm_type;
952       x_resources(l_cnt).group_sequence_id        := p_resources_mig(i).group_sequence_id;
953       x_resources(l_cnt).group_sequence_number    := p_resources_mig(i).group_sequence_number;
954       x_resources(l_cnt).capacity_um              := p_resources_mig(i).capacity_um;
955       x_resources(l_cnt).organization_id          := p_resources_mig(i).organization_id;
956       x_resources(l_cnt).resource_qty_um          := p_resources_mig(i).resource_qty_um;
957       x_resources(l_cnt).usage_um                 := p_resources_mig(i).usage_um;
958     END LOOP;
959   END build_resources;
960 
961   PROCEDURE build_parameters(p_parameters_mig IN gme_post_migration.process_param_mig_tab,
962                              x_parameters     IN OUT NOCOPY gme_post_migration.process_param_tab) IS
963     l_cnt   NUMBER := 0;
964   BEGIN
965     l_cnt := x_parameters.count;
966     FOR i IN 1..p_parameters_mig.count LOOP
967       l_cnt := l_cnt + 1;
968       x_parameters(l_cnt).process_param_id      := p_parameters_mig(i).process_param_id;
969       x_parameters(l_cnt).batch_id              := p_parameters_mig(i).batch_id;
970       x_parameters(l_cnt).batchstep_id          := p_parameters_mig(i).batchstep_id;
971       x_parameters(l_cnt).batchstep_activity_id := p_parameters_mig(i).batchstep_activity_id;
972       x_parameters(l_cnt).batchstep_resource_id := p_parameters_mig(i).batchstep_resource_id;
973       x_parameters(l_cnt).resources             := p_parameters_mig(i).resources;
974       x_parameters(l_cnt).parameter_id          := p_parameters_mig(i).parameter_id;
975       x_parameters(l_cnt).target_value          := p_parameters_mig(i).target_value;
976       x_parameters(l_cnt).minimum_value         := p_parameters_mig(i).minimum_value;
977       x_parameters(l_cnt).maximum_value         := p_parameters_mig(i).maximum_value;
978       x_parameters(l_cnt).parameter_uom         := p_parameters_mig(i).parameter_uom;
979       x_parameters(l_cnt).attribute_category    := p_parameters_mig(i).attribute_category;
980       x_parameters(l_cnt).attribute1            := p_parameters_mig(i).attribute1;
981       x_parameters(l_cnt).attribute2            := p_parameters_mig(i).attribute2;
982       x_parameters(l_cnt).attribute3            := p_parameters_mig(i).attribute3;
983       x_parameters(l_cnt).attribute4            := p_parameters_mig(i).attribute4;
984       x_parameters(l_cnt).attribute5            := p_parameters_mig(i).attribute5;
985       x_parameters(l_cnt).attribute6            := p_parameters_mig(i).attribute6;
986       x_parameters(l_cnt).attribute7            := p_parameters_mig(i).attribute7;
987       x_parameters(l_cnt).attribute8            := p_parameters_mig(i).attribute8;
988       x_parameters(l_cnt).attribute9            := p_parameters_mig(i).attribute9;
989       x_parameters(l_cnt).attribute10           := p_parameters_mig(i).attribute10;
990       x_parameters(l_cnt).attribute11           := p_parameters_mig(i).attribute11;
991       x_parameters(l_cnt).attribute12           := p_parameters_mig(i).attribute12;
992       x_parameters(l_cnt).attribute13           := p_parameters_mig(i).attribute13;
993       x_parameters(l_cnt).attribute14           := p_parameters_mig(i).attribute14;
994       x_parameters(l_cnt).attribute15           := p_parameters_mig(i).attribute15;
995       x_parameters(l_cnt).attribute16           := p_parameters_mig(i).attribute16;
996       x_parameters(l_cnt).attribute17           := p_parameters_mig(i).attribute17;
997       x_parameters(l_cnt).attribute18           := p_parameters_mig(i).attribute18;
998       x_parameters(l_cnt).attribute19           := p_parameters_mig(i).attribute19;
999       x_parameters(l_cnt).attribute20           := p_parameters_mig(i).attribute20;
1000       x_parameters(l_cnt).attribute21           := p_parameters_mig(i).attribute21;
1001       x_parameters(l_cnt).attribute22           := p_parameters_mig(i).attribute22;
1002       x_parameters(l_cnt).attribute23           := p_parameters_mig(i).attribute23;
1003       x_parameters(l_cnt).attribute24           := p_parameters_mig(i).attribute24;
1004       x_parameters(l_cnt).attribute25           := p_parameters_mig(i).attribute25;
1005       x_parameters(l_cnt).attribute26           := p_parameters_mig(i).attribute26;
1006       x_parameters(l_cnt).attribute27           := p_parameters_mig(i).attribute27;
1007       x_parameters(l_cnt).attribute28           := p_parameters_mig(i).attribute28;
1008       x_parameters(l_cnt).attribute29           := p_parameters_mig(i).attribute29;
1009       x_parameters(l_cnt).attribute30           := p_parameters_mig(i).attribute30;
1010       x_parameters(l_cnt).created_by            := p_parameters_mig(i).created_by;
1011       x_parameters(l_cnt).creation_date         := p_parameters_mig(i).creation_date;
1012       x_parameters(l_cnt).last_updated_by       := p_parameters_mig(i).last_updated_by;
1013       x_parameters(l_cnt).last_update_login     := p_parameters_mig(i).last_update_login;
1014       x_parameters(l_cnt).last_update_date      := p_parameters_mig(i).last_update_date;
1015       x_parameters(l_cnt).actual_value          := p_parameters_mig(i).actual_value;
1016       x_parameters(l_cnt).device_id             := p_parameters_mig(i).device_id;
1017       x_parameters(l_cnt).parameter_uom         := p_parameters_mig(i).parameter_uom;
1018     END LOOP;
1019   END build_parameters;
1020 
1021   PROCEDURE build_rsrc_txns(p_rsrc_txns_mig IN gme_post_migration.rsrc_txns_mig_tab,
1022                             x_rsrc_txns     IN OUT NOCOPY gme_post_migration.rsrc_txns_tab) IS
1023     l_cnt   NUMBER := 0;
1024   BEGIN
1025     l_cnt := x_rsrc_txns.count;
1026     FOR i IN 1..p_rsrc_txns_mig.count LOOP
1027       l_cnt := l_cnt + 1;
1028       x_rsrc_txns(l_cnt).poc_trans_id            := p_rsrc_txns_mig(i).poc_trans_id;
1029       x_rsrc_txns(l_cnt).orgn_code               := p_rsrc_txns_mig(i).orgn_code;
1030       x_rsrc_txns(l_cnt).doc_type                := p_rsrc_txns_mig(i).doc_type;
1031       x_rsrc_txns(l_cnt).doc_id                  := p_rsrc_txns_mig(i).doc_id;
1032       x_rsrc_txns(l_cnt).line_type               := p_rsrc_txns_mig(i).line_type;
1033       x_rsrc_txns(l_cnt).line_id                 := p_rsrc_txns_mig(i).line_id;
1034       x_rsrc_txns(l_cnt).resources               := p_rsrc_txns_mig(i).resources;
1035       x_rsrc_txns(l_cnt).resource_usage          := p_rsrc_txns_mig(i).resource_usage;
1036       x_rsrc_txns(l_cnt).trans_um                := p_rsrc_txns_mig(i).trans_um;
1037       x_rsrc_txns(l_cnt).trans_date              := p_rsrc_txns_mig(i).trans_date;
1038       x_rsrc_txns(l_cnt).completed_ind           := p_rsrc_txns_mig(i).completed_ind;
1039       x_rsrc_txns(l_cnt).event_id                := p_rsrc_txns_mig(i).event_id;
1040       x_rsrc_txns(l_cnt).posted_ind              := p_rsrc_txns_mig(i).posted_ind;
1041       x_rsrc_txns(l_cnt).overrided_protected_ind := p_rsrc_txns_mig(i).overrided_protected_ind;
1042       x_rsrc_txns(l_cnt).reason_code             := p_rsrc_txns_mig(i).reason_code;
1043       x_rsrc_txns(l_cnt).start_date              := p_rsrc_txns_mig(i).start_date;
1044       x_rsrc_txns(l_cnt).end_date                := p_rsrc_txns_mig(i).end_date;
1045       x_rsrc_txns(l_cnt).creation_date           := p_rsrc_txns_mig(i).creation_date;
1046       x_rsrc_txns(l_cnt).last_update_date        := p_rsrc_txns_mig(i).last_update_date;
1047       x_rsrc_txns(l_cnt).created_by              := p_rsrc_txns_mig(i).created_by;
1048       x_rsrc_txns(l_cnt).last_updated_by         := p_rsrc_txns_mig(i).last_updated_by;
1049       x_rsrc_txns(l_cnt).last_update_login       := p_rsrc_txns_mig(i).last_update_login;
1050       x_rsrc_txns(l_cnt).delete_mark             := p_rsrc_txns_mig(i).delete_mark;
1051       x_rsrc_txns(l_cnt).text_code               := p_rsrc_txns_mig(i).text_code;
1052       x_rsrc_txns(l_cnt).attribute1              := p_rsrc_txns_mig(i).attribute1;
1053       x_rsrc_txns(l_cnt).attribute2              := p_rsrc_txns_mig(i).attribute2;
1054       x_rsrc_txns(l_cnt).attribute3              := p_rsrc_txns_mig(i).attribute3;
1055       x_rsrc_txns(l_cnt).attribute4              := p_rsrc_txns_mig(i).attribute4;
1056       x_rsrc_txns(l_cnt).attribute5              := p_rsrc_txns_mig(i).attribute5;
1057       x_rsrc_txns(l_cnt).attribute6              := p_rsrc_txns_mig(i).attribute6;
1058       x_rsrc_txns(l_cnt).attribute7              := p_rsrc_txns_mig(i).attribute7;
1059       x_rsrc_txns(l_cnt).attribute8              := p_rsrc_txns_mig(i).attribute8;
1060       x_rsrc_txns(l_cnt).attribute9              := p_rsrc_txns_mig(i).attribute9;
1061       x_rsrc_txns(l_cnt).attribute10             := p_rsrc_txns_mig(i).attribute10;
1062       x_rsrc_txns(l_cnt).attribute11             := p_rsrc_txns_mig(i).attribute11;
1063       x_rsrc_txns(l_cnt).attribute12             := p_rsrc_txns_mig(i).attribute12;
1064       x_rsrc_txns(l_cnt).attribute13             := p_rsrc_txns_mig(i).attribute13;
1065       x_rsrc_txns(l_cnt).attribute14             := p_rsrc_txns_mig(i).attribute14;
1066       x_rsrc_txns(l_cnt).attribute15             := p_rsrc_txns_mig(i).attribute15;
1067       x_rsrc_txns(l_cnt).attribute16             := p_rsrc_txns_mig(i).attribute16;
1068       x_rsrc_txns(l_cnt).attribute17             := p_rsrc_txns_mig(i).attribute17;
1069       x_rsrc_txns(l_cnt).attribute18             := p_rsrc_txns_mig(i).attribute18;
1070       x_rsrc_txns(l_cnt).attribute19             := p_rsrc_txns_mig(i).attribute19;
1071       x_rsrc_txns(l_cnt).attribute20             := p_rsrc_txns_mig(i).attribute20;
1072       x_rsrc_txns(l_cnt).attribute21             := p_rsrc_txns_mig(i).attribute21;
1073       x_rsrc_txns(l_cnt).attribute22             := p_rsrc_txns_mig(i).attribute22;
1074       x_rsrc_txns(l_cnt).attribute23             := p_rsrc_txns_mig(i).attribute23;
1075       x_rsrc_txns(l_cnt).attribute24             := p_rsrc_txns_mig(i).attribute24;
1076       x_rsrc_txns(l_cnt).attribute25             := p_rsrc_txns_mig(i).attribute25;
1077       x_rsrc_txns(l_cnt).attribute26             := p_rsrc_txns_mig(i).attribute26;
1078       x_rsrc_txns(l_cnt).attribute27             := p_rsrc_txns_mig(i).attribute27;
1079       x_rsrc_txns(l_cnt).attribute28             := p_rsrc_txns_mig(i).attribute28;
1080       x_rsrc_txns(l_cnt).attribute29             := p_rsrc_txns_mig(i).attribute29;
1081       x_rsrc_txns(l_cnt).attribute30             := p_rsrc_txns_mig(i).attribute30;
1082       x_rsrc_txns(l_cnt).attribute_category      := p_rsrc_txns_mig(i).attribute_category;
1083       x_rsrc_txns(l_cnt).program_id              := p_rsrc_txns_mig(i).program_id;
1084       x_rsrc_txns(l_cnt).program_application_id  := p_rsrc_txns_mig(i).program_application_id;
1085       x_rsrc_txns(l_cnt).request_id              := p_rsrc_txns_mig(i).request_id;
1086       x_rsrc_txns(l_cnt).program_update_date     := p_rsrc_txns_mig(i).program_update_date;
1087       x_rsrc_txns(l_cnt).instance_id             := p_rsrc_txns_mig(i).instance_id;
1088       x_rsrc_txns(l_cnt).sequence_dependent_ind  := p_rsrc_txns_mig(i).sequence_dependent_ind;
1089       x_rsrc_txns(l_cnt).reverse_id              := p_rsrc_txns_mig(i).reverse_id;
1090       x_rsrc_txns(l_cnt).organization_id         := p_rsrc_txns_mig(i).organization_id;
1091       x_rsrc_txns(l_cnt).trans_qty_um            := p_rsrc_txns_mig(i).trans_qty_um;
1092       x_rsrc_txns(l_cnt).reason_id               := p_rsrc_txns_mig(i).reason_id;
1093     END LOOP;
1094   END build_rsrc_txns;
1095 
1096   FUNCTION get_new_step_id(p_old_step_id   IN NUMBER,
1097                            p_new_batch_id  IN NUMBER) RETURN NUMBER IS
1098     CURSOR Cur_get_step IS
1099       SELECT s.batchstep_id
1100       FROM   gme_batch_steps_mig m, gme_batch_steps s
1101       WHERE  m.batchstep_id = p_old_step_id
1102              AND s.batch_id = p_new_batch_id
1103              AND s.batchstep_no = m.batchstep_no;
1104     l_batchstep_id   NUMBER;
1105   BEGIN
1106     OPEN Cur_get_step;
1107     FETCH Cur_get_step INTO l_batchstep_id;
1108     CLOSE Cur_get_step;
1109     RETURN l_batchstep_id;
1110   END get_new_step_id;
1111 
1112   FUNCTION get_new_mat_id(p_old_mat_id   IN NUMBER,
1113                           p_new_batch_id IN NUMBER) RETURN NUMBER IS
1114     CURSOR Cur_get_mat IS
1115       SELECT d.material_detail_id
1116       FROM   gme_material_details_mig m, gme_material_details d
1117       WHERE  m.material_detail_id = p_old_mat_id
1118              AND d.batch_id = p_new_batch_id
1119              AND d.line_type = m.line_type
1120              AND d.line_no = m.line_no;
1121     l_material_detail_id   NUMBER;
1122   BEGIN
1123     OPEN Cur_get_mat;
1124     FETCH Cur_get_mat INTO l_material_detail_id;
1125     CLOSE Cur_get_mat;
1126     RETURN l_material_detail_id;
1127   END get_new_mat_id;
1128 
1129   PROCEDURE create_step_dependencies(p_old_batch_id IN NUMBER,
1130                                      p_new_batch_id IN NUMBER) IS
1131     CURSOR Cur_get_deps(v_batch_id NUMBER) IS
1132       SELECT *
1133       FROM   gme_batch_step_dep_mig
1134       WHERE  batch_id = v_batch_id;
1135     TYPE step_dep_mig_tab IS TABLE OF gme_batch_step_dep_mig%ROWTYPE INDEX BY BINARY_INTEGER;
1136     l_step_dep_mig_tbl step_dep_mig_tab;
1137     TYPE step_dep_tab IS TABLE OF gme_batch_step_dependencies%ROWTYPE INDEX BY BINARY_INTEGER;
1138     l_step_dep_tbl step_dep_tab;
1139     l_api_name VARCHAR2(30) := 'create_step_dependencies';
1140   BEGIN
1141     IF (g_debug <= gme_debug.g_log_procedure) THEN
1142       gme_debug.put_line('Start procedure '||l_api_name);
1143     END IF;
1144     OPEN Cur_get_deps(p_old_batch_id);
1145     FETCH Cur_get_deps BULK COLLECT INTO l_step_dep_mig_tbl;
1146     CLOSE Cur_get_deps;
1147     FOR i IN 1..l_step_dep_mig_tbl.count LOOP
1148       l_step_dep_tbl(i).batch_id           := p_new_batch_id;
1149       l_step_dep_tbl(i).batchstep_id       := get_new_step_id(p_old_step_id => l_step_dep_mig_tbl(i).batchstep_id, p_new_batch_id => p_new_batch_id);
1150       l_step_dep_tbl(i).dep_type           := l_step_dep_mig_tbl(i).dep_type;
1151       l_step_dep_tbl(i).dep_step_id        := get_new_step_id(p_old_step_id => l_step_dep_mig_tbl(i).dep_step_id, p_new_batch_id => p_new_batch_id);
1152       l_step_dep_tbl(i).rework_code        := l_step_dep_mig_tbl(i).rework_code;
1153       l_step_dep_tbl(i).standard_delay     := l_step_dep_mig_tbl(i).standard_delay;
1154       l_step_dep_tbl(i).min_delay          := l_step_dep_mig_tbl(i).min_delay;
1155       l_step_dep_tbl(i).max_delay          := l_step_dep_mig_tbl(i).max_delay;
1156       l_step_dep_tbl(i).transfer_qty       := l_step_dep_mig_tbl(i).transfer_qty;
1157       l_step_dep_tbl(i).transfer_um        := l_step_dep_mig_tbl(i).transfer_um;
1158       l_step_dep_tbl(i).text_code          := l_step_dep_mig_tbl(i).text_code;
1159       l_step_dep_tbl(i).last_update_login  := l_step_dep_mig_tbl(i).last_update_login;
1160       l_step_dep_tbl(i).last_updated_by    := l_step_dep_mig_tbl(i).last_updated_by;
1161       l_step_dep_tbl(i).created_by         := l_step_dep_mig_tbl(i).created_by;
1162       l_step_dep_tbl(i).creation_date      := l_step_dep_mig_tbl(i).creation_date;
1163       l_step_dep_tbl(i).last_update_date   := l_step_dep_mig_tbl(i).last_update_date;
1164       l_step_dep_tbl(i).transfer_percent   := l_step_dep_mig_tbl(i).transfer_percent;
1165       l_step_dep_tbl(i).attribute1         := l_step_dep_mig_tbl(i).attribute1;
1166       l_step_dep_tbl(i).attribute2         := l_step_dep_mig_tbl(i).attribute2;
1167       l_step_dep_tbl(i).attribute3         := l_step_dep_mig_tbl(i).attribute3;
1168       l_step_dep_tbl(i).attribute4         := l_step_dep_mig_tbl(i).attribute4;
1169       l_step_dep_tbl(i).attribute5         := l_step_dep_mig_tbl(i).attribute5;
1170       l_step_dep_tbl(i).attribute6         := l_step_dep_mig_tbl(i).attribute6;
1171       l_step_dep_tbl(i).attribute7         := l_step_dep_mig_tbl(i).attribute7;
1172       l_step_dep_tbl(i).attribute8         := l_step_dep_mig_tbl(i).attribute8;
1173       l_step_dep_tbl(i).attribute9         := l_step_dep_mig_tbl(i).attribute9;
1174       l_step_dep_tbl(i).attribute10        := l_step_dep_mig_tbl(i).attribute10;
1175       l_step_dep_tbl(i).attribute11        := l_step_dep_mig_tbl(i).attribute11;
1176       l_step_dep_tbl(i).attribute12        := l_step_dep_mig_tbl(i).attribute12;
1177       l_step_dep_tbl(i).attribute13        := l_step_dep_mig_tbl(i).attribute13;
1178       l_step_dep_tbl(i).attribute14        := l_step_dep_mig_tbl(i).attribute14;
1179       l_step_dep_tbl(i).attribute15        := l_step_dep_mig_tbl(i).attribute15;
1180       l_step_dep_tbl(i).attribute16        := l_step_dep_mig_tbl(i).attribute16;
1181       l_step_dep_tbl(i).attribute17        := l_step_dep_mig_tbl(i).attribute17;
1182       l_step_dep_tbl(i).attribute18        := l_step_dep_mig_tbl(i).attribute18;
1183       l_step_dep_tbl(i).attribute19        := l_step_dep_mig_tbl(i).attribute19;
1184       l_step_dep_tbl(i).attribute20        := l_step_dep_mig_tbl(i).attribute20;
1185       l_step_dep_tbl(i).attribute21        := l_step_dep_mig_tbl(i).attribute21;
1186       l_step_dep_tbl(i).attribute22        := l_step_dep_mig_tbl(i).attribute22;
1187       l_step_dep_tbl(i).attribute23        := l_step_dep_mig_tbl(i).attribute23;
1188       l_step_dep_tbl(i).attribute24        := l_step_dep_mig_tbl(i).attribute24;
1189       l_step_dep_tbl(i).attribute25        := l_step_dep_mig_tbl(i).attribute25;
1190       l_step_dep_tbl(i).attribute26        := l_step_dep_mig_tbl(i).attribute26;
1191       l_step_dep_tbl(i).attribute27        := l_step_dep_mig_tbl(i).attribute27;
1192       l_step_dep_tbl(i).attribute28        := l_step_dep_mig_tbl(i).attribute28;
1193       l_step_dep_tbl(i).attribute29        := l_step_dep_mig_tbl(i).attribute29;
1194       l_step_dep_tbl(i).attribute30        := l_step_dep_mig_tbl(i).attribute30;
1195       l_step_dep_tbl(i).attribute_category := l_step_dep_mig_tbl(i).attribute_category;
1196       l_step_dep_tbl(i).chargeable_ind     := l_step_dep_mig_tbl(i).chargeable_ind;
1197     END LOOP;
1198     FORALL a IN 1..l_step_dep_tbl.count
1199       INSERT INTO gme_batch_step_dependencies VALUES l_step_dep_tbl(a);
1200     IF (g_debug <= gme_debug.g_log_procedure) THEN
1201       gme_debug.put_line('End procedure '||l_api_name);
1202     END IF;
1203   END create_step_dependencies;
1204 
1205   PROCEDURE create_item_step_assoc(p_old_batch_id IN NUMBER,
1206                                    p_new_batch_id IN NUMBER) IS
1207     CURSOR Cur_item_assocs IS
1208       SELECT *
1209       FROM   gme_batch_step_items_mig
1210       WHERE  batch_id = p_old_batch_id;
1211     TYPE item_step_mig_tab IS TABLE OF gme_batch_step_items_mig%ROWTYPE INDEX BY BINARY_INTEGER;
1212     l_item_step_mig_tbl   item_step_mig_tab;
1213     TYPE item_step_tab IS TABLE OF gme_batch_step_items%ROWTYPE INDEX BY BINARY_INTEGER;
1214     l_item_step_tbl   item_step_tab;
1215     l_api_name VARCHAR2(30) := 'create_item_step_assoc';
1216   BEGIN
1217     IF (g_debug <= gme_debug.g_log_procedure) THEN
1218       gme_debug.put_line('Start procedure '||l_api_name);
1219     END IF;
1220     OPEN Cur_item_assocs;
1221     FETCH Cur_item_assocs BULK COLLECT INTO l_item_step_mig_tbl;
1222     CLOSE Cur_item_assocs;
1223     FOR i IN 1..l_item_step_mig_tbl.count LOOP
1224       l_item_step_tbl(i).material_detail_id   := get_new_mat_id(p_old_mat_id => l_item_step_mig_tbl(i).material_detail_id, p_new_batch_id => p_new_batch_id);
1225       l_item_step_tbl(i).batch_id             := p_new_batch_id;
1226       l_item_step_tbl(i).batchstep_id         := get_new_step_id(p_old_step_id => l_item_step_mig_tbl(i).batchstep_id, p_new_batch_id => p_new_batch_id);
1227       l_item_step_tbl(i).text_code            := l_item_step_mig_tbl(i).text_code;
1228       l_item_step_tbl(i).last_update_login    := l_item_step_mig_tbl(i).last_update_login;
1229       l_item_step_tbl(i).last_update_date     := l_item_step_mig_tbl(i).last_update_date;
1230       l_item_step_tbl(i).last_updated_by      := l_item_step_mig_tbl(i).last_updated_by;
1231       l_item_step_tbl(i).creation_date        := l_item_step_mig_tbl(i).creation_date;
1232       l_item_step_tbl(i).created_by           := l_item_step_mig_tbl(i).created_by;
1233       l_item_step_tbl(i).maximum_delay        := l_item_step_mig_tbl(i).maximum_delay;
1234       l_item_step_tbl(i).minimum_delay        := l_item_step_mig_tbl(i).minimum_delay;
1235       l_item_step_tbl(i).minimum_transfer_qty := l_item_step_mig_tbl(i).minimum_transfer_qty;
1236     END LOOP;
1237     FORALL a IN 1..l_item_step_tbl.count
1238       INSERT INTO gme_batch_step_items VALUES l_item_step_tbl(a);
1239     IF (g_debug <= gme_debug.g_log_procedure) THEN
1240       gme_debug.put_line('End procedure '||l_api_name);
1241     END IF;
1242   END create_item_step_assoc;
1243 
1244   PROCEDURE create_batch_step_charges(p_old_batch_id IN NUMBER,
1245                                       p_new_batch_id IN NUMBER) IS
1246     CURSOR Cur_step_charges IS
1247       SELECT *
1248       FROM   gme_batch_step_charges_mig
1249       WHERE  batch_id = p_old_batch_id;
1250     TYPE step_chrg_mig_tab IS TABLE OF gme_batch_step_charges_mig%ROWTYPE INDEX BY BINARY_INTEGER;
1251     l_step_chrg_mig_tbl  step_chrg_mig_tab;
1252     TYPE step_chrg_tab IS TABLE OF gme_batch_step_charges%ROWTYPE INDEX BY BINARY_INTEGER;
1253     l_step_chrg_tbl  step_chrg_tab;
1254     l_api_name VARCHAR2(30) := 'create_batch_step_charges';
1255   BEGIN
1256     IF (g_debug <= gme_debug.g_log_procedure) THEN
1257       gme_debug.put_line('Start procedure '||l_api_name);
1258     END IF;
1259     OPEN Cur_step_charges;
1260     FETCH Cur_step_charges BULK COLLECT INTO l_step_chrg_mig_tbl;
1261     CLOSE Cur_step_charges;
1262     FOR i IN 1..l_step_chrg_mig_tbl.count LOOP
1263       l_step_chrg_tbl(i).batch_id                 := p_new_batch_id;
1264       l_step_chrg_tbl(i).batchstep_id             := get_new_step_id(p_old_step_id => l_step_chrg_mig_tbl(i).batchstep_id, p_new_batch_id => p_new_batch_id);
1265       l_step_chrg_tbl(i).resources                := l_step_chrg_mig_tbl(i).resources;
1266       l_step_chrg_tbl(i).activity_sequence_number := l_step_chrg_mig_tbl(i).activity_sequence_number;
1267       l_step_chrg_tbl(i).charge_number            := l_step_chrg_mig_tbl(i).charge_number;
1268       l_step_chrg_tbl(i).charge_quantity          := l_step_chrg_mig_tbl(i).charge_quantity;
1269       l_step_chrg_tbl(i).plan_start_date          := l_step_chrg_mig_tbl(i).plan_start_date;
1270       l_step_chrg_tbl(i).plan_cmplt_date          := l_step_chrg_mig_tbl(i).plan_cmplt_date;
1271       l_step_chrg_tbl(i).created_by               := l_step_chrg_mig_tbl(i).created_by;
1272       l_step_chrg_tbl(i).creation_date            := l_step_chrg_mig_tbl(i).creation_date;
1273       l_step_chrg_tbl(i).last_updated_by          := l_step_chrg_mig_tbl(i).last_updated_by;
1274       l_step_chrg_tbl(i).last_update_login        := l_step_chrg_mig_tbl(i).last_update_login;
1275       l_step_chrg_tbl(i).last_update_date         := l_step_chrg_mig_tbl(i).last_update_date;
1276     END LOOP;
1277     FORALL a IN 1..l_step_chrg_tbl.count
1278       INSERT INTO gme_batch_step_charges VALUES l_step_chrg_tbl(a);
1279     IF (g_debug <= gme_debug.g_log_procedure) THEN
1280       gme_debug.put_line('End procedure '||l_api_name);
1281     END IF;
1282   END create_batch_step_charges;
1283 
1284   PROCEDURE create_batch_step_transfers(p_old_batch_id IN NUMBER,
1285                                         p_new_batch_id IN NUMBER) IS
1286     CURSOR Cur_step_txfrs IS
1287       SELECT *
1288       FROM   gme_batch_step_transfers_mig
1289       WHERE  batch_id = p_old_batch_id;
1290     TYPE step_txfrs_mig_tab IS TABLE OF gme_batch_step_transfers_mig%ROWTYPE INDEX BY BINARY_INTEGER;
1291     l_step_txfrs_mig_tbl  step_txfrs_mig_tab;
1292     TYPE step_txfrs_tab IS TABLE OF gme_batch_step_transfers%ROWTYPE INDEX BY BINARY_INTEGER;
1293     l_step_txfrs_tbl  step_txfrs_tab;
1294     l_api_name VARCHAR2(30) := 'create_batch_step_transfers';
1295   BEGIN
1296     IF (g_debug <= gme_debug.g_log_procedure) THEN
1297       gme_debug.put_line('Start procedure '||l_api_name);
1298     END IF;
1299     OPEN Cur_step_txfrs;
1300     FETCH Cur_step_txfrs BULK COLLECT INTO l_step_txfrs_mig_tbl;
1301     CLOSE Cur_step_txfrs;
1302     FOR i IN 1..l_step_txfrs_mig_tbl.count LOOP
1303       SELECT gem5_wip_trans_id_s.NEXTVAL INTO l_step_txfrs_tbl(i).wip_trans_id FROM DUAL;
1304       l_step_txfrs_tbl(i).batch_id           := p_new_batch_id;
1305       l_step_txfrs_tbl(i).batchstep_no       := l_step_txfrs_mig_tbl(i).batchstep_no;
1306       l_step_txfrs_tbl(i).transfer_step_no   := l_step_txfrs_mig_tbl(i).transfer_step_no;
1307       l_step_txfrs_tbl(i).line_type          := l_step_txfrs_mig_tbl(i).line_type;
1308       l_step_txfrs_tbl(i).trans_qty          := l_step_txfrs_mig_tbl(i).trans_qty;
1309       l_step_txfrs_tbl(i).trans_um           := l_step_txfrs_mig_tbl(i).trans_um;
1310       l_step_txfrs_tbl(i).trans_date         := l_step_txfrs_mig_tbl(i).trans_date;
1311       l_step_txfrs_tbl(i).last_updated_by    := l_step_txfrs_mig_tbl(i).last_updated_by;
1312       l_step_txfrs_tbl(i).last_update_date   := l_step_txfrs_mig_tbl(i).last_update_date;
1313       l_step_txfrs_tbl(i).last_update_login  := l_step_txfrs_mig_tbl(i).last_update_login;
1314       l_step_txfrs_tbl(i).creation_date      := l_step_txfrs_mig_tbl(i).creation_date;
1315       l_step_txfrs_tbl(i).created_by         := l_step_txfrs_mig_tbl(i).created_by;
1316       l_step_txfrs_tbl(i).delete_mark        := l_step_txfrs_mig_tbl(i).delete_mark;
1317       l_step_txfrs_tbl(i).text_code          := l_step_txfrs_mig_tbl(i).text_code;
1318       l_step_txfrs_tbl(i).attribute1         := l_step_txfrs_mig_tbl(i).attribute1;
1319       l_step_txfrs_tbl(i).attribute2         := l_step_txfrs_mig_tbl(i).attribute2;
1320       l_step_txfrs_tbl(i).attribute3         := l_step_txfrs_mig_tbl(i).attribute3;
1321       l_step_txfrs_tbl(i).attribute4         := l_step_txfrs_mig_tbl(i).attribute4;
1322       l_step_txfrs_tbl(i).attribute5         := l_step_txfrs_mig_tbl(i).attribute5;
1323       l_step_txfrs_tbl(i).attribute6         := l_step_txfrs_mig_tbl(i).attribute6;
1324       l_step_txfrs_tbl(i).attribute7         := l_step_txfrs_mig_tbl(i).attribute7;
1325       l_step_txfrs_tbl(i).attribute8         := l_step_txfrs_mig_tbl(i).attribute8;
1326       l_step_txfrs_tbl(i).attribute9         := l_step_txfrs_mig_tbl(i).attribute9;
1327       l_step_txfrs_tbl(i).attribute10        := l_step_txfrs_mig_tbl(i).attribute10;
1328       l_step_txfrs_tbl(i).attribute11        := l_step_txfrs_mig_tbl(i).attribute11;
1329       l_step_txfrs_tbl(i).attribute12        := l_step_txfrs_mig_tbl(i).attribute12;
1330       l_step_txfrs_tbl(i).attribute13        := l_step_txfrs_mig_tbl(i).attribute13;
1331       l_step_txfrs_tbl(i).attribute14        := l_step_txfrs_mig_tbl(i).attribute14;
1332       l_step_txfrs_tbl(i).attribute15        := l_step_txfrs_mig_tbl(i).attribute15;
1333       l_step_txfrs_tbl(i).attribute16        := l_step_txfrs_mig_tbl(i).attribute16;
1334       l_step_txfrs_tbl(i).attribute17        := l_step_txfrs_mig_tbl(i).attribute17;
1335       l_step_txfrs_tbl(i).attribute18        := l_step_txfrs_mig_tbl(i).attribute18;
1336       l_step_txfrs_tbl(i).attribute19        := l_step_txfrs_mig_tbl(i).attribute19;
1337       l_step_txfrs_tbl(i).attribute20        := l_step_txfrs_mig_tbl(i).attribute20;
1338       l_step_txfrs_tbl(i).attribute21        := l_step_txfrs_mig_tbl(i).attribute21;
1339       l_step_txfrs_tbl(i).attribute22        := l_step_txfrs_mig_tbl(i).attribute22;
1340       l_step_txfrs_tbl(i).attribute23        := l_step_txfrs_mig_tbl(i).attribute23;
1341       l_step_txfrs_tbl(i).attribute24        := l_step_txfrs_mig_tbl(i).attribute24;
1342       l_step_txfrs_tbl(i).attribute25        := l_step_txfrs_mig_tbl(i).attribute25;
1343       l_step_txfrs_tbl(i).attribute26        := l_step_txfrs_mig_tbl(i).attribute26;
1344       l_step_txfrs_tbl(i).attribute27        := l_step_txfrs_mig_tbl(i).attribute27;
1345       l_step_txfrs_tbl(i).attribute28        := l_step_txfrs_mig_tbl(i).attribute28;
1346       l_step_txfrs_tbl(i).attribute29        := l_step_txfrs_mig_tbl(i).attribute29;
1347       l_step_txfrs_tbl(i).attribute30        := l_step_txfrs_mig_tbl(i).attribute30;
1348       l_step_txfrs_tbl(i).attribute_category := l_step_txfrs_mig_tbl(i).attribute_category;
1349       l_step_txfrs_tbl(i).trans_qty_um       := l_step_txfrs_mig_tbl(i).trans_qty_um;
1350     END LOOP;
1351     FORALL a IN 1..l_step_txfrs_tbl.count
1352       INSERT INTO gme_batch_step_transfers VALUES l_step_txfrs_tbl(a);
1353     IF (g_debug <= gme_debug.g_log_procedure) THEN
1354       gme_debug.put_line('End procedure '||l_api_name);
1355     END IF;
1356   END create_batch_step_transfers;
1357 
1358   PROCEDURE create_batch_mapping(p_batch_header_mig IN gme_batch_header_mig%ROWTYPE,
1359                                  p_batch_header     IN gme_batch_header%ROWTYPE) IS
1360   BEGIN
1361     INSERT INTO gme_batch_mapping_mig(plant_code,
1362                                       old_batch_id,
1363                                       old_batch_no,
1364                                       organization_id,
1365                                       new_batch_id,
1366                                       new_batch_no,
1367                                       created_by,
1368                                       creation_date,
1369                                       last_updated_by,
1370                                       last_update_date)
1371     VALUES                           (p_batch_header_mig.plant_code,
1372                                       p_batch_header_mig.batch_id,
1373                                       SUBSTR(p_batch_header_mig.batch_no,1,30)||'-M',
1374                                       p_batch_header.organization_id,
1375                                       p_batch_header.batch_id,
1376                                       p_batch_header.batch_no,
1377                                       gme_common_pvt.g_user_ident,
1378                                       gme_common_pvt.g_timestamp,
1379                                       gme_common_pvt.g_user_ident,
1380                                       gme_common_pvt.g_timestamp);
1381   END create_batch_mapping;
1382 
1383   PROCEDURE create_phantom_links IS
1384     CURSOR Cur_get_phantoms IS
1385       SELECT d.material_detail_id new_ing_line_id, d.phantom_id old_phantom_id, d.inventory_item_id,
1386              m.plant_code, m.new_batch_no
1387       FROM   gme_material_details d, gme_batch_mapping_mig m
1388       WHERE  d.batch_id = m.new_batch_id
1389              AND d.line_type = -1
1390              AND d.phantom_id > 0
1391              AND d.phantom_id NOT IN (SELECT new_batch_id FROM gme_batch_mapping_mig);
1392     CURSOR Cur_new_phant_batch(v_batch_id NUMBER) IS
1393       SELECT new_batch_id
1394       FROM   gme_batch_mapping_mig
1395       WHERE  old_batch_id = v_batch_id;
1396     CURSOR Cur_new_phant_prod(v_batch_id NUMBER, v_inventory_item_id NUMBER) IS
1397       SELECT material_detail_id
1398       FROM   gme_material_details
1399       WHERE  batch_id = v_batch_id
1400              AND line_type = gme_common_pvt.g_line_type_prod
1401              AND inventory_item_id = v_inventory_item_id
1402       ORDER BY line_no;
1403     l_api_name VARCHAR2(30) := 'create_phantom_links';
1404     l_new_phantom_id           NUMBER;
1405     l_new_prod_line_id         NUMBER;
1406     new_phant_batch_not_found  EXCEPTION;
1407     new_phant_prod_not_found   EXCEPTION;
1408   BEGIN
1409     IF (g_debug <= gme_debug.g_log_procedure) THEN
1410       gme_debug.put_line('Start procedure '||l_api_name);
1411     END IF;
1412     FOR get_phantoms IN Cur_get_phantoms LOOP
1413       BEGIN
1414       	/* Get new phantom batch ID */
1415         OPEN Cur_new_phant_batch(get_phantoms.old_phantom_id);
1416         FETCH Cur_new_phant_batch INTO l_new_phantom_id;
1417         IF (Cur_new_phant_batch%NOTFOUND) THEN
1418           CLOSE Cur_new_phant_batch;
1419           RAISE new_phant_batch_not_found;
1420         END IF;
1421         CLOSE Cur_new_phant_batch;
1422         /* Get new phantom product ID */
1423         OPEN Cur_new_phant_prod(l_new_phantom_id, get_phantoms.inventory_item_id);
1424         FETCH Cur_new_phant_prod INTO l_new_prod_line_id;
1425         IF (Cur_new_phant_prod%NOTFOUND) THEN
1426           CLOSE Cur_new_phant_prod;
1427           RAISE new_phant_prod_not_found;
1428         END IF;
1429         CLOSE Cur_new_phant_prod;
1430         /* Update Phantom ing */
1431         UPDATE gme_material_details
1432         SET phantom_id = l_new_phantom_id,
1433             phantom_line_id = l_new_prod_line_id
1434         WHERE material_detail_id = get_phantoms.new_ing_line_id;
1435         /* Update phantom batch hdr */
1436         UPDATE gme_batch_header
1437         SET parentline_id = get_phantoms.new_ing_line_id
1438         WHERE batch_id = l_new_phantom_id;
1439         /* Update phantom product */
1440         UPDATE gme_material_details
1441         SET phantom_line_id = get_phantoms.new_ing_line_id
1442         WHERE material_detail_id = l_new_prod_line_id;
1443       EXCEPTION
1444         WHEN new_phant_batch_not_found THEN
1445           ROLLBACK;
1446           gma_common_logging.gma_migration_central_log
1447                      (p_run_id              => g_migration_run_id,
1448                       p_log_level           => fnd_log.level_error,
1449                       p_message_token       => 'GME_PHANT_BATCH_NOT_FOUND',
1450                       p_table_name          => 'GME_BATCH_HEADER',
1451                       p_context             => 'RECREATE_OPEN_BATCHES',
1452                       p_app_short_name      => 'GME',
1453                       p_token1              => 'BATCH_NO',
1454                       p_param1              => get_phantoms.plant_code||'-'||get_phantoms.new_batch_no);
1455       	WHEN new_phant_prod_not_found THEN
1456       	  ROLLBACK;
1457           gma_common_logging.gma_migration_central_log
1458                      (p_run_id              => g_migration_run_id,
1459                       p_log_level           => fnd_log.level_error,
1460                       p_message_token       => 'GME_PHANTOM_PROD_NOT_FOUND',
1461                       p_table_name          => 'GME_BATCH_HEADER',
1462                       p_context             => 'RECREATE_OPEN_BATCHES',
1463                       p_app_short_name      => 'GME',
1464                       p_token1              => 'BATCH_NO',
1465                       p_param1              => get_phantoms.plant_code||'-'||get_phantoms.new_batch_no);
1466         WHEN OTHERS THEN
1467           IF (g_debug <= gme_debug.g_log_unexpected) THEN
1468             gme_debug.put_line('When others in '||l_api_name||' '||SQLERRM);
1469           END IF;
1470           ROLLBACK;
1471           gma_common_logging.gma_migration_central_log
1472                      (p_run_id              => g_migration_run_id,
1473                       p_log_level           => fnd_log.level_error,
1474                       p_message_token       => 'GME_PHANT_BATCH_UNEXPECTED',
1475                       p_table_name          => 'GME_BATCH_HEADER',
1476                       p_context             => 'RECREATE_OPEN_BATCHES',
1477                       p_app_short_name      => 'GME',
1478                       p_token1              => 'BATCH_NO',
1479                       p_param1              => get_phantoms.plant_code||'-'||get_phantoms.new_batch_no,
1480                       p_token2              => 'MSG',
1481                       p_param2              => SQLERRM);
1482       END;
1483       COMMIT;
1484     END LOOP;
1485     IF (g_debug <= gme_debug.g_log_procedure) THEN
1486       gme_debug.put_line('End procedure '||l_api_name);
1487     END IF;
1488   END create_phantom_links;
1489 
1490   PROCEDURE release_batches IS
1491     CURSOR Cur_wip_batches IS
1492       SELECT m.*, o.actual_start_date
1493       FROM   gme_batch_header_mig o, gme_batch_mapping_mig m
1494       WHERE  o.batch_status = gme_common_pvt.g_batch_wip
1495              AND m.old_batch_id = o.batch_id
1496              AND o.parentline_id IS NULL
1497              AND m.new_batch_id NOT IN (SELECT batch_id
1498                                         FROM   gme_batch_header
1499                                         WHERE  batch_id = m.new_batch_id
1500                                                AND batch_status = gme_common_pvt.g_batch_wip)
1501       ORDER BY m.organization_id, m.new_batch_no;
1502     CURSOR Cur_get_steps(v_old_batch_id NUMBER, v_new_batch_id NUMBER) IS
1503       SELECT s.*, m.step_status old_step_status, m.actual_start_date old_actual_start_date,
1504              m.actual_cmplt_date old_actual_cmplt_date
1505       FROM   gme_batch_steps_mig m, gme_batch_steps s
1506       WHERE  m.batch_id = v_old_batch_id
1507              AND s.batch_id = v_new_batch_id
1508              AND m.step_status > gme_common_pvt.g_step_pending
1509              AND s.batchstep_no = m.batchstep_no
1510              AND NOT(s.step_status = m.step_status)
1511       ORDER BY s.batchstep_no;
1512     CURSOR Cur_verify_phantoms(v_batch_id NUMBER) IS
1513       SELECT 1
1514       FROM DUAL
1515       WHERE EXISTS (SELECT batch_id
1516                     FROM   gme_material_details
1517                     WHERE  batch_id = v_batch_id
1518                            AND phantom_type > 0
1519                            AND phantom_id NOT IN (SELECT new_batch_id FROM gme_batch_mapping_mig));
1520     l_date             DATE;
1521     l_temp             NUMBER;
1522     l_msg_cnt          NUMBER;
1523     l_current_org_id   NUMBER;
1524     l_msg_data         VARCHAR2(2000);
1525     l_return_status    VARCHAR2(1);
1526     l_api_name VARCHAR2(30) := 'release_batches';
1527     l_batch_header     gme_batch_header%ROWTYPE;
1528     l_batch_header_out gme_batch_header%ROWTYPE;
1529     l_step_rec         gme_batch_steps%ROWTYPE;
1530     l_step_rec_out     gme_batch_steps%ROWTYPE;
1531     l_exception_tbl    gme_common_pvt.exceptions_tab;
1532     no_open_period_err EXCEPTION;
1533     step_release_err   EXCEPTION;
1534     step_cmplt_err     EXCEPTION;
1535     release_batch_err  EXCEPTION;
1536     inv_phantoms_found EXCEPTION;
1537   BEGIN
1538     IF (g_debug <= gme_debug.g_log_procedure) THEN
1539       gme_debug.put_line('Start procedure '||l_api_name);
1540     END IF;
1541     gme_release_batch_pvt.g_bypass_txn_creation := 1;
1542     FOR get_wip_batches IN Cur_wip_batches LOOP
1543       BEGIN
1544       	/* Make sure phantom batches have been created before releasing main batch */
1545       	OPEN Cur_verify_phantoms(get_wip_batches.new_batch_id);
1546       	FETCH Cur_verify_phantoms INTO l_temp;
1547       	IF (Cur_verify_phantoms%FOUND) THEN
1548       	  CLOSE Cur_verify_phantoms;
1549       	  RAISE inv_phantoms_found;
1550       	END IF;
1551       	CLOSE Cur_verify_phantoms;
1552         l_batch_header.batch_id          := get_wip_batches.new_batch_id;
1553         l_batch_header.organization_id   := get_wip_batches.organization_id;
1554         l_batch_header.actual_start_date := get_wip_batches.actual_start_date;
1555         check_date(p_organization_id => l_batch_header.organization_id,
1556                    p_date            => l_batch_header.actual_start_date,
1557                    x_date            => l_date,
1558                    x_return_status   => l_return_status);
1559         IF (l_return_status <> fnd_api.g_ret_sts_success) THEN
1560           RAISE no_open_period_err;
1561         ELSE
1562           l_batch_header.actual_start_date := l_date;
1563         END IF;
1564         gme_api_pub.release_batch(p_api_version              => 2.0,
1565                                   p_validation_level         => gme_common_pvt.g_max_errors,
1566                                   p_init_msg_list            => fnd_api.g_false,
1567                                   p_commit                   => fnd_api.g_true,
1568                                   x_message_count            => l_msg_cnt,
1569                                   x_message_list             => l_msg_data,
1570                                   x_return_status            => l_return_status,
1571                                   p_batch_header_rec         => l_batch_header,
1572                                   p_org_code                 => NULL,
1573                                   p_ignore_exception         => fnd_api.g_false,
1574                                   p_validate_flexfields      => fnd_api.g_false,
1575                                   x_batch_header_rec         => l_batch_header_out,
1576                                   x_exception_material_tbl   => l_exception_tbl);
1577         IF (l_return_status <> fnd_api.g_ret_sts_success) THEN
1578           RAISE release_batch_err;
1579         END IF;
1580         FOR get_steps IN Cur_get_steps(get_wip_batches.old_batch_id, l_batch_header.batch_id) LOOP
1581           BEGIN
1582             check_date(p_organization_id => l_batch_header.organization_id,
1583                        p_date            => get_steps.old_actual_start_date,
1584                        x_date            => l_date,
1585                        x_return_status   => l_return_status);
1586             IF (l_return_status <> fnd_api.g_ret_sts_success) THEN
1587               RAISE no_open_period_err;
1588             ELSE
1589               get_steps.actual_start_date := l_date;
1590             END IF;
1591             l_step_rec.batchstep_id      := get_steps.batchstep_id;
1592             l_step_rec.batch_id          := get_steps.batch_id;
1593             l_step_rec.actual_start_date := get_steps.old_actual_start_date;
1594             l_step_rec.actual_cmplt_date := get_steps.old_actual_cmplt_date;
1595             IF (get_steps.old_step_status IN (gme_common_pvt.g_step_completed, gme_common_pvt.g_step_closed)) THEN
1596               gme_api_pub.complete_step(p_api_version            => 2.0,
1597                                         p_validation_level       => gme_common_pvt.g_max_errors,
1598                                         p_init_msg_list          => fnd_api.g_false,
1599                                         p_commit                 => fnd_api.g_true,
1600                                         x_message_count          => l_msg_cnt,
1601                                         x_message_list           => l_msg_data,
1602                                         x_return_status          => l_return_status,
1603                                         p_batch_step_rec         => l_step_rec,
1604                                         p_batch_no               => NULL,
1605                                         p_org_code               => NULL,
1606                                         p_ignore_exception       => fnd_api.g_false,
1607                                         p_override_quality       => fnd_api.g_false,
1608                                         p_validate_flexfields    => fnd_api.g_false,
1609                                         x_batch_step_rec         => l_step_rec_out,
1610                                         x_exception_material_tbl => l_exception_tbl);
1611               IF (l_return_status <> fnd_api.g_ret_sts_success) THEN
1612                 RAISE step_cmplt_err;
1613               END IF;
1614             ELSE
1615               gme_api_pub.release_step(p_api_version            => 2.0,
1616                                        p_validation_level       => gme_common_pvt.g_max_errors,
1617                                        p_init_msg_list          => fnd_api.g_false,
1618                                        p_commit                 => fnd_api.g_true,
1619                                        x_message_count          => l_msg_cnt,
1620                                        x_message_list           => l_msg_data,
1621                                        x_return_status          => l_return_status,
1622                                        p_batch_step_rec         => l_step_rec,
1623                                        p_batch_no               => NULL,
1624                                        p_org_code               => NULL,
1625                                        p_ignore_exception       => fnd_api.g_false,
1626                                        p_validate_flexfields    => fnd_api.g_false,
1627                                        x_batch_step_rec         => l_step_rec_out,
1628                                        x_exception_material_tbl => l_exception_tbl);
1629               IF (l_return_status <> fnd_api.g_ret_sts_success) THEN
1630                 RAISE step_release_err;
1631               END IF;
1632             END IF;
1633           EXCEPTION
1634             WHEN inv_phantoms_found THEN
1635               NULL;
1636             WHEN no_open_period_err THEN
1637               gma_common_logging.gma_migration_central_log
1638                      (p_run_id              => g_migration_run_id,
1639                       p_log_level           => fnd_log.level_error,
1640                       p_message_token       => 'GME_NO_OPEN_PERIODS_STEP',
1641                       p_table_name          => 'GME_BATCH_HEADER',
1642                       p_context             => 'RECREATE_OPEN_BATCHES',
1643                       p_app_short_name      => 'GME',
1644                       p_token1              => 'BATCH_NO',
1645                       p_param1              => get_wip_batches.plant_code||'-'||get_wip_batches.new_batch_no,
1646                       p_token2              => 'STEP_NO',
1647                       p_param2              => get_steps.batchstep_no);
1648             WHEN step_cmplt_err THEN
1649               gma_common_logging.gma_migration_central_log
1650                      (p_run_id              => g_migration_run_id,
1651                       p_log_level           => fnd_log.level_error,
1652                       p_message_token       => 'GME_STEP_CMPLT_ERR',
1653                       p_table_name          => 'GME_BATCH_HEADER',
1654                       p_context             => 'RECREATE_OPEN_BATCHES',
1655                       p_app_short_name      => 'GME',
1656                       p_token1              => 'BATCH_NO',
1657                       p_param1              => get_wip_batches.plant_code||'-'||get_wip_batches.new_batch_no,
1658                       p_token2              => 'STEP_NO',
1659                       p_param2              => get_steps.batchstep_no,
1660                       p_token3              => 'MSG',
1661                       p_param3              => l_msg_data);
1662             WHEN step_release_err THEN
1663               gma_common_logging.gma_migration_central_log
1664                      (p_run_id              => g_migration_run_id,
1665                       p_log_level           => fnd_log.level_error,
1666                       p_message_token       => 'GME_STEP_RELEASE_ERR',
1667                       p_table_name          => 'GME_BATCH_HEADER',
1668                       p_context             => 'RECREATE_OPEN_BATCHES',
1669                       p_app_short_name      => 'GME',
1670                       p_token1              => 'BATCH_NO',
1671                       p_param1              => get_wip_batches.plant_code||'-'||get_wip_batches.new_batch_no,
1672                       p_token2              => 'STEP_NO',
1673                       p_param2              => get_steps.batchstep_no,
1674                       p_token3              => 'MSG',
1675                       p_param3              => l_msg_data);
1676             WHEN OTHERS THEN
1677               IF (g_debug <= gme_debug.g_log_unexpected) THEN
1678                 gme_debug.put_line('When others in '||l_api_name||' '||SQLERRM);
1679               END IF;
1680               gma_common_logging.gma_migration_central_log
1681                          (p_run_id              => g_migration_run_id,
1682                           p_log_level           => fnd_log.level_error,
1683                           p_message_token       => 'GME_STEP_PROCESS_UNEXP',
1684                           p_table_name          => 'GME_BATCH_HEADER',
1685                           p_context             => 'RECREATE_OPEN_BATCHES',
1686                           p_app_short_name      => 'GME',
1687                           p_token1              => 'BATCH_NO',
1688                           p_param1              => get_wip_batches.plant_code||'-'||get_wip_batches.new_batch_no,
1689                           p_token2              => 'STEP_NO',
1690                           p_param2              => get_steps.batchstep_no,
1691                           p_token3              => 'MSG',
1692                           p_param3              => SQLERRM);
1693           END;
1694         END LOOP;
1695       EXCEPTION
1696         WHEN no_open_period_err THEN
1697           gma_common_logging.gma_migration_central_log
1698                    (p_run_id              => g_migration_run_id,
1699                     p_log_level           => fnd_log.level_error,
1700                     p_message_token       => 'GME_NO_OPEN_PERIODS_BATCH',
1701                     p_table_name          => 'GME_BATCH_HEADER',
1702                     p_context             => 'RECREATE_OPEN_BATCHES',
1703                     p_app_short_name      => 'GME',
1704                     p_token1              => 'BATCH_NO',
1705                     p_param1              => get_wip_batches.plant_code||'-'||get_wip_batches.new_batch_no);
1706         WHEN release_batch_err THEN
1707           gme_common_pvt.count_and_get(x_count  => l_msg_cnt
1708                                       ,x_data   => l_msg_data);
1709           gma_common_logging.gma_migration_central_log
1710                          (p_run_id              => g_migration_run_id,
1711                           p_log_level           => fnd_log.level_error,
1712                           p_message_token       => 'GME_BATCH_RELEASE_ERR',
1713                           p_table_name          => 'GME_BATCH_HEADER',
1714                           p_context             => 'RECREATE_OPEN_BATCHES',
1715                           p_app_short_name      => 'GME',
1716                           p_token1              => 'BATCH_NO',
1717                           p_param1              => get_wip_batches.plant_code||'-'||get_wip_batches.new_batch_no,
1718                           p_token2              => 'MSG',
1719                           p_param2              => l_msg_data);
1720         WHEN OTHERS THEN
1721           IF (g_debug <= gme_debug.g_log_unexpected) THEN
1722             gme_debug.put_line('When others in '||l_api_name||' '||SQLERRM);
1723           END IF;
1724           gma_common_logging.gma_migration_central_log
1725                    (p_run_id              => g_migration_run_id,
1726                     p_log_level           => fnd_log.level_error,
1727                     p_message_token       => 'GME_BATCH_PROCESS_UNEXP',
1728                     p_table_name          => 'GME_BATCH_HEADER',
1729                     p_context             => 'RECREATE_OPEN_BATCHES',
1730                     p_app_short_name      => 'GME',
1731                     p_token1              => 'BATCH_NO',
1732                     p_param1              => get_wip_batches.plant_code||'-'||get_wip_batches.new_batch_no,
1733                     p_token2              => 'MSG',
1734                     p_param2              => SQLERRM);
1735       END;
1736     END LOOP;
1737     IF (g_debug <= gme_debug.g_log_procedure) THEN
1738       gme_debug.put_line('End procedure '||l_api_name);
1739     END IF;
1740   END release_batches;
1741 
1742   PROCEDURE check_date(p_organization_id IN NUMBER,
1743                        p_date            IN DATE,
1744                        x_date            OUT NOCOPY DATE,
1745                        x_return_status   OUT NOCOPY VARCHAR2) IS
1746     l_period_id      NUMBER;
1747     l_open_period    BOOLEAN;
1748     no_open_periods  EXCEPTION;
1749   BEGIN
1750     x_return_status := fnd_api.g_ret_sts_success;
1751     invttmtx.tdatechk(org_id           => p_organization_id,
1752 		      transaction_date => p_date,
1753 		      period_id        => l_period_id,
1754  		      open_past_period => l_open_period);
1755     IF (l_period_id <= 0) THEN
1756       invttmtx.tdatechk(org_id           => p_organization_id,
1757 	  	        transaction_date => gme_common_pvt.g_timestamp,
1758 		        period_id        => l_period_id,
1759  		        open_past_period => l_open_period);
1760       IF (l_period_id <= 0) THEN
1761       	RAISE no_open_periods;
1762       ELSE
1763       	x_date := gme_common_pvt.g_timestamp;
1764       END IF;
1765     ELSE
1766       x_date := p_date;
1767     END IF;
1768   EXCEPTION
1769     WHEN no_open_periods THEN
1770       x_return_status := fnd_api.g_ret_sts_error;
1771   END check_date;
1772 
1773   PROCEDURE get_subinventory(p_whse_code       IN VARCHAR2,
1774                              x_subinventory    OUT NOCOPY VARCHAR2,
1775                              x_organization_id OUT NOCOPY NUMBER) IS
1776     CURSOR Cur_whse_mst(v_whse_code VARCHAR2) IS
1777       SELECT subinventory_ind_flag
1778       FROM   ic_whse_mst
1779       WHERE  whse_code = v_whse_code;
1780     CURSOR Cur_subinv_details(v_whse_code VARCHAR2) IS
1781       SELECT secondary_inventory_name, organization_id
1782       FROM   mtl_secondary_inventories
1783       WHERE  secondary_inventory_name = v_whse_code;
1784     CURSOR Cur_subinv_from_whse(v_whse_code VARCHAR2) IS
1785       SELECT s.secondary_inventory_name, s.organization_id
1786       FROM   mtl_secondary_inventories s, ic_whse_mst w
1787       WHERE  secondary_inventory_name = v_whse_code
1788              AND w.whse_code = s.secondary_inventory_name
1789              AND s.organization_id = w.mtl_organization_id;
1790     l_subinv_ind   VARCHAR2(1);
1791     l_api_name VARCHAR2(30) := 'get_subinventory';
1792   BEGIN
1793     IF (p_whse_code IS NOT NULL) THEN
1794       BEGIN
1795       	/* If already exists in PL/SQL table take it */
1796       	x_subinventory    := p_subinv_tbl(p_whse_code).subinventory;
1797       	x_organization_id := p_subinv_tbl(p_whse_code).organization_id;
1798       	RETURN;
1799       EXCEPTION
1800         WHEN NO_DATA_FOUND THEN
1801           NULL;
1802       END;
1803     ELSE
1804       RETURN;
1805     END IF;
1806     OPEN Cur_whse_mst(p_whse_code);
1807     FETCH Cur_whse_mst INTO l_subinv_ind;
1808     CLOSE Cur_whse_mst;
1809     IF NVL(l_subinv_ind, 'N') = 'Y' THEN
1810       OPEN Cur_subinv_details(p_whse_code);
1811       FETCH Cur_subinv_details INTO x_subinventory, x_organization_id;
1812       CLOSE Cur_subinv_details;
1813     ELSE
1814       OPEN Cur_subinv_from_whse(p_whse_code);
1815       FETCH Cur_subinv_from_whse INTO x_subinventory, x_organization_id;
1816       CLOSE Cur_subinv_from_whse;
1817     END IF;
1818     /* Add to PL/SQL table so next time this whse is used values can be taken from PL/SQL table */
1819     p_subinv_tbl(p_whse_code).subinventory    := x_subinventory;
1820     p_subinv_tbl(p_whse_code).organization_id := x_organization_id;
1821   END get_subinventory;
1822 
1823   PROCEDURE get_locator(p_location        IN VARCHAR2,
1824                         p_whse_code       IN VARCHAR2,
1825                         x_organization_id OUT NOCOPY NUMBER,
1826                         x_locator_id      OUT NOCOPY NUMBER,
1827                         x_subinventory    OUT NOCOPY VARCHAR2) IS
1828     CURSOR Cur_ic_loct_mst IS
1829       SELECT i.locator_id, m.organization_id, m.subinventory_code
1830       FROM   ic_loct_mst i, mtl_item_locations m
1831       WHERE  i.location = p_location
1832              AND i.whse_code = p_whse_code
1833              AND m.inventory_location_id = i.locator_id;
1834     CURSOR Cur_mtl_locs IS
1835       SELECT m.inventory_location_id locator_id, m.organization_id, m.subinventory_code
1836       FROM   mtl_item_locations m
1837       WHERE  m.segment1 = p_location
1838              AND m.subinventory_code = x_subinventory;
1839     l_api_name VARCHAR2(30) := 'get_locator';
1840   BEGIN
1841     BEGIN
1842       x_locator_id      := p_locator_tbl(p_whse_code||'**'||p_location).locator_id;
1843       x_organization_id := p_locator_tbl(p_whse_code||'**'||p_location).organization_id;
1844       x_subinventory    := p_locator_tbl(p_whse_code||'**'||p_location).subinventory;
1845       RETURN;
1846     EXCEPTION
1847       WHEN NO_DATA_FOUND THEN
1848         NULL;
1849     END;
1850     OPEN Cur_ic_loct_mst;
1851     FETCH Cur_ic_loct_mst INTO x_locator_id, x_organization_id, x_subinventory;
1852     IF (Cur_ic_loct_mst%NOTFOUND) THEN
1853       get_subinventory(p_whse_code       => p_whse_code,
1854                        x_subinventory    => x_subinventory,
1855                        x_organization_id => x_organization_id);
1856       OPEN Cur_mtl_locs;
1857       FETCH Cur_mtl_locs INTO x_locator_id, x_organization_id, x_subinventory;
1858       CLOSE Cur_mtl_locs;
1859     END IF;
1860     CLOSE Cur_ic_loct_mst;
1861     p_locator_tbl(p_whse_code||'**'||p_location).locator_id      := x_locator_id;
1862     p_locator_tbl(p_whse_code||'**'||p_location).organization_id := x_organization_id;
1863     p_locator_tbl(p_whse_code||'**'||p_location).subinventory    := x_subinventory;
1864   END get_locator;
1865 
1866   FUNCTION get_latest_revision(p_organization_id   IN NUMBER,
1867                                p_inventory_item_id IN NUMBER) RETURN VARCHAR2 IS
1868     CURSOR Cur_get_revision IS
1869       SELECT revision
1870       FROM   mtl_item_revisions
1871       WHERE  organization_id = p_organization_id
1872              AND inventory_item_id = p_inventory_item_id
1873              AND effectivity_date <= gme_common_pvt.g_timestamp
1874       ORDER BY effectivity_date DESC;
1875     l_revision  VARCHAR2(3);
1876   BEGIN
1877     OPEN Cur_get_revision;
1878     FETCH Cur_get_revision INTO l_revision;
1879     CLOSE Cur_get_revision;
1880     RETURN l_revision;
1881   END get_latest_revision;
1882 
1883   FUNCTION get_reason(p_reason_code IN VARCHAR2) RETURN NUMBER IS
1884     CURSOR Cur_get_reason IS
1885       SELECT reason_id
1886       FROM   sy_reas_cds_b
1887       WHERE  reason_code = p_reason_code;
1888     l_reason_id  NUMBER;
1889   BEGIN
1890     OPEN Cur_get_reason;
1891     FETCH Cur_get_reason INTO l_reason_id;
1892     CLOSE Cur_get_reason;
1893     RETURN l_reason_id;
1894   END get_reason;
1895 
1896   PROCEDURE create_locator(p_location		IN  VARCHAR2,
1897                            p_organization_id	IN  NUMBER,
1898                            p_subinventory_code	IN  VARCHAR2,
1899                            x_location_id	OUT NOCOPY NUMBER,
1900                            x_failure_count	OUT NOCOPY NUMBER) IS
1901     CURSOR Cur_loc_details IS
1902       SELECT *
1903       FROM   ic_loct_mst
1904       WHERE  location = p_location;
1905     l_loc_rec  ic_loct_mst%ROWTYPE;
1906     l_api_name VARCHAR2(30) := 'create_locator';
1907   BEGIN
1908     IF (g_debug <= gme_debug.g_log_procedure) THEN
1909       gme_debug.put_line('Start procedure '||l_api_name);
1910     END IF;
1911     IF (g_debug <= gme_debug.g_log_statement) THEN
1912       gme_debug.put_line('creating locator '||p_location||'->'||p_organization_id||'-'||p_subinventory_code);
1913     END IF;
1914     OPEN Cur_loc_details;
1915     FETCH Cur_loc_details INTO l_loc_rec;
1916     CLOSE Cur_loc_details;
1917     inv_migrate_process_org.create_location (p_migration_run_id	 => g_migration_run_id,
1918 		                             p_organization_id	 => p_organization_id,
1919 		                             p_subinventory_code => p_subinventory_code,
1920 		                             p_location		 => p_location,
1921 			                     p_loct_desc	 => l_loc_rec.loct_desc,
1922 			                     p_start_date_active => l_loc_rec.creation_date,
1923                                              p_commit		 => fnd_api.g_true,
1924 			                     x_location_id	 => x_location_id,
1925                                              x_failure_count	 => x_failure_count,
1926                                              p_disable_date      => NULL,
1927                                              p_segment2          => NULL,
1928                                              p_segment3          => NULL,
1929                                              p_segment4          => NULL,
1930                                              p_segment5          => NULL,
1931                                              p_segment6          => NULL,
1932                                              p_segment7          => NULL,
1933                                              p_segment8          => NULL,
1934                                              p_segment9          => NULL,
1935                                              p_segment10         => NULL,
1936                                              p_segment11         => NULL,
1937                                              p_segment12         => NULL,
1938                                              p_segment13         => NULL,
1939                                              p_segment14         => NULL,
1940                                              p_segment15         => NULL,
1941                                              p_segment16         => NULL,
1942                                              p_segment17         => NULL,
1943                                              p_segment18         => NULL,
1944                                              p_segment19         => NULL,
1945                                              p_segment20         => NULL);
1946     IF (g_debug <= gme_debug.g_log_procedure) THEN
1947       gme_debug.put_line('End procedure '||l_api_name);
1948     END IF;
1949   END create_locator;
1950 
1951   PROCEDURE get_subinv_locator_type(p_subinventory IN VARCHAR2,
1952                                     p_organization_id IN NUMBER,
1953                                     x_locator_type OUT NOCOPY NUMBER) IS
1954     CURSOR Cur_sub_control(v_org_id NUMBER, v_subinventory VARCHAR2) IS
1955       SELECT locator_type
1956       FROM   mtl_secondary_inventories
1957       WHERE  organization_id = v_org_id
1958              AND secondary_inventory_name = v_subinventory;
1959   BEGIN
1960     BEGIN
1961       x_locator_type := p_subinv_loctype_tbl(p_subinventory).locator_type;
1962       RETURN;
1963     EXCEPTION
1964       WHEN NO_DATA_FOUND THEN
1965         NULL;
1966     END;
1967     OPEN cur_sub_control (p_organization_id, p_subinventory);
1968     FETCH cur_sub_control INTO x_locator_type;
1969     CLOSE cur_sub_control;
1970     p_subinv_loctype_tbl(p_subinventory).locator_type := x_locator_type;
1971   END get_subinv_locator_type;
1972 
1973   PROCEDURE get_distribution_account(p_subinventory  IN VARCHAR2,
1974                                      p_org_id        IN NUMBER,
1975                                      x_dist_acct_id  OUT NOCOPY NUMBER) IS
1976     CURSOR Cur_get_acct IS
1977       SELECT NVL(NVL(s.expense_account, s.material_account),NVL(m.expense_account, m.material_account))
1978       FROM   mtl_secondary_inventories s, mtl_parameters m
1979       WHERE  s.secondary_inventory_name = p_subinventory
1980              AND m.organization_id = p_org_id;
1981   BEGIN
1982     OPEN Cur_get_acct;
1983     FETCH Cur_get_acct INTO x_dist_acct_id;
1984     CLOSE Cur_get_acct;
1985   END get_distribution_account;
1986   /* Bug 5620671 Added param completed ind */
1987   PROCEDURE create_txns_reservations(p_completed_ind IN NUMBER) IS
1988     TYPE txns_tab IS TABLE OF Cur_get_txns%ROWTYPE INDEX BY BINARY_INTEGER;
1989     l_txns_tbl        txns_tab;
1990     l_date            DATE;
1991     l_count           NUMBER;
1992     l_msg_cnt         NUMBER;
1993     l_mat_detail_id   NUMBER;
1994     l_curr_detail_id  NUMBER;
1995     l_curr_batch_id   NUMBER := 0;
1996     l_org_id          NUMBER;
1997     l_curr_org_id     NUMBER := 0;
1998     l_locator_id      NUMBER;
1999     l_sub_loc_type    NUMBER;
2000     l_eff_loc_control NUMBER;
2001     l_failure_count   NUMBER;
2002     l_api_name VARCHAR2(30) := 'create_txns_reservations';
2003     l_return_status   VARCHAR2(1);
2004     l_subinventory    VARCHAR2(10);
2005     l_in_subinventory VARCHAR2(10);
2006     l_msg_name        VARCHAR2(32);
2007     l_lot_no          VARCHAR2(32);
2008     l_sublot_no       VARCHAR2(32);
2009     l_lot_number      VARCHAR2(80);
2010     l_parent_lot_no   VARCHAR2(80);
2011     l_def_location    VARCHAR2(100) := FND_PROFILE.VALUE('IC$DEFAULT_LOCT');
2012     l_msg_data        VARCHAR2(2000);
2013     l_txn_data        VARCHAR2(2000);
2014     l_new_data        VARCHAR2(2000);
2015 
2016     CURSOR Cur_mtl_dtl(v_material_detail_id NUMBER) IS
2017       SELECT d.*, i.mtl_transactions_enabled_flag, i.reservable_type, i.segment1, i.lot_control_code,
2018              i.revision_qty_control_code, i.primary_uom_code, i.secondary_uom_code, i.restrict_subinventories_code,
2019              NVL(i.location_control_code,1) location_control_code, i.restrict_locators_code, i.segment1 item_no
2020       FROM   gme_material_details d, mtl_system_items_b i
2021       WHERE  d.material_detail_id = v_material_detail_id
2022              AND i.organization_id = d.organization_id
2023              AND i.inventory_item_id = d.inventory_item_id;
2024     CURSOR Cur_lot_mst(v_lot_id NUMBER) IS
2025       SELECT lot_no,sublot_no
2026       FROM   ic_lots_mst
2027       WHERE  lot_id = v_lot_id;
2028     l_batch_hdr       gme_batch_header%ROWTYPE;
2029     l_mtl_rec         Cur_mtl_dtl%ROWTYPE;
2030     l_mmti_rec        mtl_transactions_interface%ROWTYPE;
2031     l_mmli_tbl        gme_common_pvt.mtl_trans_lots_inter_tbl;
2032     l_mtl_dtl_rec     gme_material_details%ROWTYPE;
2033     l_plot_out_rec    gme_pending_product_lots%ROWTYPE;
2034     l_plot_in_rec     gme_pending_product_lots%ROWTYPE;
2035     l_mmt_rec         mtl_material_transactions%ROWTYPE;
2036     l_mmln_rec        gme_common_pvt.mtl_trans_lots_num_tbl;
2037     uom_conversion_fail     EXCEPTION;
2038     setup_failed            EXCEPTION;
2039     create_txn_rsv_pp_err   EXCEPTION;
2040     batch_fetch_err         EXCEPTION;
2041     expected_error          EXCEPTION;
2042     defined_error           EXCEPTION;
2043   BEGIN
2044     IF (g_debug <= gme_debug.g_log_procedure) THEN
2045       gme_debug.put_line('Start procedure '||l_api_name);
2046     END IF;
2047     /* Bug 5620671 Added param completed ind */
2048     OPEN Cur_get_txns(p_completed_ind);
2049     FETCH Cur_get_txns BULK COLLECT INTO l_txns_tbl;
2050     CLOSE Cur_get_txns;
2051     l_count := l_txns_tbl.count;
2052     IF (g_debug <= gme_debug.g_log_statement) THEN
2053       gme_debug.put_line('No. of txns = '||l_count);
2054     END IF;
2055     FOR i IN 1..l_count LOOP
2056       BEGIN
2057         IF (g_debug <= gme_debug.g_log_statement) THEN
2058           gme_debug.put_line('Processing trans_id = '||l_txns_tbl(i).trans_id);
2059           gme_debug.put_line('l_curr_org_id = '||l_curr_org_id||' l_txns_tbl(i).organization_id = '||l_txns_tbl(i).organization_id);
2060         END IF;
2061         gme_common_pvt.g_transaction_header_id := NULL;
2062       	l_lot_number   := NULL;
2063       	l_subinventory := NULL;
2064       	l_locator_id   := NULL;
2065       	l_org_id       := NULL;
2066       	l_mmti_rec     := NULL;
2067       	l_txn_data     := NULL;
2068       	l_new_data     := NULL;
2069       	l_mmli_tbl.delete;
2070       	IF (l_curr_org_id <> l_txns_tbl(i).organization_id) THEN
2071       	  IF NOT (gme_common_pvt.setup(p_org_id => l_txns_tbl(i).organization_id)) THEN
2072       	    RAISE setup_failed;
2073       	  END IF;
2074       	  l_curr_org_id := l_txns_tbl(i).organization_id;
2075           IF (g_debug <= gme_debug.g_log_statement) THEN
2076             gme_debug.put_line('gme_common_pvt.g_organization_id = '||gme_common_pvt.g_organization_id||' gme_common_pvt.g_organization_code = '||gme_common_pvt.g_organization_code);
2077           END IF;
2078       	END IF;
2079       	IF (l_curr_batch_id <> l_txns_tbl(i).new_batch_id) THEN
2080       	  l_batch_hdr.batch_id := l_txns_tbl(i).new_batch_id;
2081       	  IF NOT(gme_batch_header_dbl.fetch_row(p_batch_header => l_batch_hdr,
2082       	                                        x_batch_header => l_batch_hdr)) THEN
2083       	    RAISE batch_fetch_err;
2084       	  END IF;
2085       	  l_curr_batch_id := l_txns_tbl(i).new_batch_id;
2086       	END IF;
2087       	IF (NVL(l_curr_detail_id,0) <> NVL(l_txns_tbl(i).line_id, -1)) THEN
2088       	  l_mat_detail_id  := get_new_mat_id(p_old_mat_id => l_txns_tbl(i).line_id, p_new_batch_id => l_txns_tbl(i).new_batch_id);
2089       	  l_curr_detail_id := l_txns_tbl(i).line_id;
2090       	  OPEN Cur_mtl_dtl(l_mat_detail_id);
2091       	  FETCH Cur_mtl_dtl INTO l_mtl_rec;
2092       	  CLOSE Cur_mtl_dtl;
2093       	END IF;
2094         IF (g_debug <= gme_debug.g_log_statement) THEN
2095           gme_debug.put_line('Processing transaction for Batch = '||gme_common_pvt.g_organization_code||'-'||l_batch_hdr.batch_no||' Line Type = '||l_mtl_rec.line_type||' Line No = '||l_mtl_rec.line_no||' Phantom_type = '||l_mtl_rec.phantom_type);
2096         END IF;
2097       	/* Do not create phantom ing txns these will be created by phantom prod txns */
2098       	IF NOT(l_mtl_rec.line_type = gme_common_pvt.g_line_type_ing AND l_mtl_rec.phantom_type IN (gme_common_pvt.g_auto_phantom, gme_common_pvt.g_manual_phantom)) THEN
2099           IF (g_debug <= gme_debug.g_log_statement) THEN
2100             gme_debug.put_line('Not a phantom ing txn');
2101           END IF;
2102       	  IF (l_txns_tbl(i).completed_ind = 1) THEN
2103             IF (g_debug <= gme_debug.g_log_statement) THEN
2104               gme_debug.put_line('This is a completed txn');
2105             END IF;
2106             IF (l_batch_hdr.batch_status <= 1) THEN
2107               l_msg_name := 'GME_MIG_BATCH_INVALID_FOR_TXN';
2108               RAISE defined_error;
2109             END IF;
2110       	    IF (l_mtl_rec.mtl_transactions_enabled_flag <> 'Y') THEN
2111       	      l_msg_name := 'GME_MIG_ITEM_NOT_TXNS_ENABLED';
2112       	      RAISE defined_error;
2113       	    END IF;
2114             SELECT mtl_material_transactions_s.NEXTVAL INTO gme_common_pvt.g_transaction_header_id FROM DUAL;
2115             IF (g_debug <= gme_debug.g_log_statement) THEN
2116               gme_debug.put_line('Transaction header ID = '||gme_common_pvt.g_transaction_header_id);
2117             END IF;
2118             l_mmti_rec.transaction_source_id := l_mtl_rec.batch_id;
2119             l_mmti_rec.trx_source_line_id    := l_mtl_rec.material_detail_id;
2120             l_mmti_rec.inventory_item_id     := l_mtl_rec.inventory_item_id;
2121             l_mmti_rec.organization_id       := l_mtl_rec.organization_id;
2122             IF (l_mtl_rec.revision_qty_control_code = 2) THEN
2123               l_mmti_rec.revision := get_latest_revision(p_organization_id => l_mtl_rec.organization_id, p_inventory_item_id => l_mtl_rec.inventory_item_id);
2124               IF (l_mmti_rec.revision IS NULL) THEN
2125               	l_msg_name := 'GME_MIG_REVISION_NOT_FOUND';
2126               	RAISE defined_error;
2127               END IF;
2128             ELSE
2129               l_mmti_rec.revision := NULL;
2130             END IF;
2131             IF (g_debug <= gme_debug.g_log_statement) THEN
2132               gme_debug.put_line('After revision before check date');
2133             END IF;
2134             check_date(p_organization_id => l_mtl_rec.organization_id,
2135                        p_date            => l_txns_tbl(i).trans_date,
2136                        x_date            => l_date,
2137                        x_return_status   => l_return_status);
2138             IF (l_return_status <> fnd_api.g_ret_sts_success) THEN
2139               l_msg_name := 'GME_NO_OPEN_PERIODS_TXN';
2140               RAISE defined_error;
2141             END IF;
2142             l_mmti_rec.transaction_date := l_date;
2143             IF (l_mtl_rec.line_type = gme_common_pvt.g_line_type_ing) THEN
2144               l_mmti_rec.transaction_type_id   := gme_common_pvt.g_ing_issue;
2145               l_mmti_rec.transaction_action_id := gme_common_pvt.g_ing_issue_txn_action;
2146             ELSIF (l_mtl_rec.line_type = gme_common_pvt.g_line_type_prod) THEN
2147               l_mmti_rec.transaction_type_id   := gme_common_pvt.g_prod_completion;
2148               l_mmti_rec.transaction_action_id := gme_common_pvt.g_prod_comp_txn_action;
2149             ELSIF (l_mtl_rec.line_type = gme_common_pvt.g_line_type_byprod) THEN
2150               l_mmti_rec.transaction_type_id   := gme_common_pvt.g_byprod_completion;
2151               l_mmti_rec.transaction_action_id := gme_common_pvt.g_byprod_comp_txn_action;
2152             END IF;
2153             l_mmti_rec.primary_quantity               := ROUND(ABS(l_txns_tbl(i).trans_qty),5);
2154             l_mmti_rec.secondary_transaction_quantity := ROUND(ABS(l_txns_tbl(i).trans_qty2),5);
2155             l_mmti_rec.secondary_uom_code             := l_mtl_rec.secondary_uom_code;
2156             l_mmti_rec.transaction_uom                := l_mtl_rec.dtl_um;
2157             l_mmti_rec.transaction_source_type_id     := gme_common_pvt.g_txn_source_type;
2158             l_mmti_rec.wip_entity_type                := gme_common_pvt.g_wip_entity_type_batch;
2159             l_mmti_rec.reason_id                      := get_reason(l_txns_tbl(i).reason_code);
2160             IF (l_txns_tbl(i).reason_code IS NOT NULL AND l_mmti_rec.reason_id IS NULL) THEN
2161       	      l_txn_data := l_mtl_rec.item_no||'->'||l_txns_tbl(i).whse_code||'->'||l_txns_tbl(i).location||'->'||
2162       	      l_txns_tbl(i).lot_id||'->'||l_txns_tbl(i).trans_qty||'->'||l_mtl_rec.primary_uom_code||'->'||to_char(l_txns_tbl(i).trans_date, 'DD-MON-YYYY HH24:MI:SS');
2163               gma_common_logging.gma_migration_central_log
2164                      (p_run_id              => g_migration_run_id,
2165                       p_log_level           => fnd_log.level_error,
2166                       p_message_token       => 'GME_MIG_REASON_NOT_FOUND',
2167                       p_table_name          => 'GME_BATCH_HEADER',
2168                       p_context             => 'RECREATE_OPEN_BATCHES',
2169                       p_app_short_name      => 'GME',
2170                       p_token1              => 'BATCH_NO',
2171                       p_param1              => l_txns_tbl(i).plant_code||'-'||l_txns_tbl(i).new_batch_no,
2172                       p_token2              => 'TRANS_ID',
2173                       p_param2              => l_txns_tbl(i).trans_id,
2174                       p_token3              => 'TXN_DATA',
2175                       p_param3              => l_txn_data,
2176                       p_token4              => 'REASON_CODE',
2177                       p_param4              => l_txns_tbl(i).reason_code);
2178             END IF;
2179             IF (g_debug <= gme_debug.g_log_statement) THEN
2180               gme_debug.put_line('After putting all values in l_mmti_rec');
2181             END IF;
2182             /* If item is location controlled then get locator/sub/org otherwise get sub/org */
2183             IF (NVL(l_txns_tbl(i).location, l_def_location) <> l_def_location) THEN
2184               get_locator(p_location        => l_txns_tbl(i).location,
2185                           p_whse_code       => l_txns_tbl(i).whse_code,
2186                           x_organization_id => l_org_id,
2187                           x_locator_id      => l_locator_id,
2188                           x_subinventory    => l_subinventory);
2189             END IF;
2190             IF (g_debug <= gme_debug.g_log_statement) THEN
2191               gme_debug.put_line('One l_org_id = '||l_org_id||' l_subinventory = '||l_subinventory||' l_locator_id = '||l_locator_id );
2192             END IF;
2193 
2194             /* If we have sub it means locator exists otherwise get sub */
2195             IF (l_subinventory IS NULL) THEN
2196               get_subinventory(p_whse_code       => l_txns_tbl(i).whse_code,
2197                                x_subinventory    => l_subinventory,
2198                                x_organization_id => l_org_id);
2199               IF (l_subinventory IS NULL) THEN
2200               	l_msg_name := 'GME_MIG_SUBINV_NOT_FOUND';
2201                 RAISE defined_error;
2202               END IF;
2203             END IF;
2204             IF (g_debug <= gme_debug.g_log_statement) THEN
2205               gme_debug.put_line('Two l_org_id = '||l_org_id||' l_subinventory = '||l_subinventory||' l_locator_id = '||l_locator_id );
2206               gme_debug.put_line('l_org_id = '||l_org_id||' l_mmti_rec.organization_id = '||l_mmti_rec.organization_id);
2207             END IF;
2208             /* If subinventory is in same org as batch then it is fine or we have to do issue/receipt */
2209             IF (l_org_id <> l_mmti_rec.organization_id) THEN
2210               /* Create a misc issue in l_org_id and a receipt in l_mmti_rec.organization_id */
2211               IF (g_debug <= gme_debug.g_log_statement) THEN
2212                 gme_debug.put_line('creating issue/receipt from org = '||l_org_id||' to org = '||l_mmti_rec.organization_id);
2213               END IF;
2214               create_issue_receipt(p_curr_org_id       => l_org_id,
2215                                    p_inventory_item_id => l_mtl_rec.inventory_item_id,
2216                                    p_txn_rec           => l_txns_tbl(i),
2217                                    p_mmti_rec          => l_mmti_rec,
2218                                    p_item_no           => l_mtl_rec.item_no,
2219                                    p_subinventory      => l_subinventory,
2220                                    p_locator_id        => l_locator_id,
2221                                    p_batch_org_id      => l_mmti_rec.organization_id,
2222                                    x_subinventory      => l_mmti_rec.subinventory_code,
2223                                    x_locator_id        => l_mmti_rec.locator_id,
2224                                    x_lot_number        => l_lot_number,
2225                                    x_return_status     => l_return_status);
2226               IF (l_return_status <> FND_API.G_RET_STS_SUCCESS) THEN
2227                 RAISE expected_error;
2228               END IF;
2229             ELSE
2230               IF (g_debug <= gme_debug.g_log_statement) THEN
2231                 gme_debug.put_line('All in same org');
2232               END IF;
2233               IF NOT (gme_common_pvt.check_subinventory(p_organization_id   => l_mtl_rec.organization_id
2234                                                        ,p_subinventory      => l_subinventory
2235                                                        ,p_inventory_item_id => l_mtl_rec.inventory_item_id
2236                                                        ,p_restrict_subinv   => l_mtl_rec.restrict_subinventories_code)) THEN
2237                 l_subinventory := NULL;
2238                 l_locator_id   := NULL;
2239                 l_msg_name := 'GME_MIG_SUBINV_NOT_FOUND';
2240                 RAISE defined_error;
2241               END IF;
2242               get_subinv_locator_type(p_subinventory     => l_subinventory,
2243                                       p_organization_id  => l_mtl_rec.organization_id,
2244                                       x_locator_type     => l_sub_loc_type);
2245               l_eff_loc_control := gme_common_pvt.eff_locator_control(p_organization_id   => l_mtl_rec.organization_id,
2246                                                                       p_subinventory      => l_subinventory,
2247                                                                       p_inventory_item_id => l_mtl_rec.inventory_item_id,
2248                                                                       p_org_control       => gme_common_pvt.g_org_locator_control,
2249                                                                       p_sub_control       => l_sub_loc_type,
2250                                                                       p_item_control      => NVL(l_mtl_rec.location_control_code,1),
2251                                                                       p_item_loc_restrict => l_mtl_rec.restrict_locators_code,
2252                                                                       p_org_neg_allowed   => gme_common_pvt.g_allow_neg_inv,
2253                                                                       p_action            => l_mmti_rec.transaction_action_id);
2254               IF (l_eff_loc_control = 1) THEN
2255                 l_locator_id := NULL;
2256               ELSE
2257                 IF (l_locator_id IS NULL AND NVL(l_txns_tbl(i).location, l_def_location) <> l_def_location) THEN
2258                   create_locator(p_location	     => l_txns_tbl(i).location,
2259                                  p_organization_id   => l_mtl_rec.organization_id,
2260                                  p_subinventory_code => l_subinventory,
2261                                  x_location_id       => l_locator_id,
2262                                  x_failure_count     => l_failure_count);
2263                 END IF;
2264               END IF;
2265               IF (l_locator_id IS NOT NULL) THEN
2266                 IF NOT (Gme_Common_Pvt.check_locator
2267                             (p_organization_id        => l_mtl_rec.organization_id
2268                             ,p_locator_id             => l_locator_id
2269                             ,p_subinventory           => l_subinventory
2270                             ,p_inventory_item_id      => l_mtl_rec.inventory_item_id
2271                             ,p_org_control            => Gme_Common_Pvt.g_org_locator_control
2272                             ,p_sub_control            => l_sub_loc_type
2273                             ,p_item_control           => NVL(l_mtl_rec.location_control_code,1)
2274                             ,p_item_loc_restrict      => l_mtl_rec.restrict_locators_code
2275                             ,p_org_neg_allowed        => Gme_Common_Pvt.g_allow_neg_inv
2276                             ,p_txn_action_id          => l_mmti_rec.transaction_action_id)) THEN
2277                    l_locator_id := NULL;
2278                    l_msg_name := 'GME_MIG_LOCATOR_NOT_FOUND';
2279                    RAISE defined_error;
2280                 END IF;
2281               END IF;
2282               l_mmti_rec.subinventory_code := l_subinventory;
2283               l_mmti_rec.locator_id        := l_locator_id;
2284             END IF;
2285             IF (g_debug <= gme_debug.g_log_statement) THEN
2286               gme_debug.put_line('Lot control code is '||l_mtl_rec.lot_control_code);
2287             END IF;
2288             IF (l_mtl_rec.lot_control_code = 2) THEN
2289               IF (l_lot_number IS NULL) THEN
2290                 inv_opm_lot_migration.get_odm_lot(p_migration_run_id  => g_migration_run_id,
2291                                                   p_item_id           => l_txns_tbl(i).item_id,
2292                                                   p_lot_id	      => l_txns_tbl(i).lot_id,
2293                                                   p_whse_code	      => l_txns_tbl(i).whse_code,
2294                                                   p_orgn_code	      => NULL,
2295                                                   p_location	      => l_txns_tbl(i).location,
2296                                                   p_commit	      => fnd_api.g_true,
2297                                                   x_lot_number	      => l_lot_number,
2298                                                   x_parent_lot_number => l_parent_lot_no,
2299                                                   x_failure_count     => l_failure_count);
2300                 IF (l_failure_count > 0 OR l_lot_number IS NULL) THEN
2301                   l_msg_name := 'GME_MIG_LOT_NOT_FOUND';
2302                   RAISE defined_error;
2303                 END IF;
2304               END IF;
2305               l_mmli_tbl(1).lot_number := l_lot_number;
2306             END IF;
2307             IF (g_debug <= gme_debug.g_log_statement) THEN
2308               gme_debug.put_line('After Lot processing lot is '||l_lot_number);
2309             END IF;
2310             IF (l_mtl_rec.dtl_um <> l_mtl_rec.primary_uom_code) THEN
2311               l_mmti_rec.transaction_quantity := inv_convert.inv_um_convert(item_id         => l_mtl_rec.inventory_item_id
2312                                                                            ,lot_number      => l_lot_number
2313                                                                            ,organization_id => l_mtl_rec.organization_id
2314                                                                            ,PRECISION       => gme_common_pvt.g_precision
2315                                                                            ,from_quantity   => ABS(l_txns_tbl(i).trans_qty)
2316                                                                            ,from_unit       => l_mtl_rec.primary_uom_code
2317                                                                            ,to_unit         => l_mtl_rec.dtl_um
2318                                                                            ,from_name       => NULL
2319                                                                            ,to_name         => NULL);
2320               IF (l_mmti_rec.transaction_quantity < 0) THEN
2321               	RAISE uom_conversion_fail;
2322               END IF;
2323             ELSE
2324               l_mmti_rec.transaction_quantity := ROUND(ABS(l_txns_tbl(i).trans_qty),5);
2325             END IF;
2326             IF (l_mmli_tbl.count > 0) THEN
2327               l_mmli_tbl(1).transaction_quantity           := l_mmti_rec.transaction_quantity;
2328               l_mmli_tbl(1).secondary_transaction_quantity := l_mmti_rec.secondary_transaction_quantity;
2329             END IF;
2330             l_new_data := gme_common_pvt.g_organization_code||'->'||l_mtl_rec.item_no||'->'||l_mmti_rec.revision||'->'||
2331             l_mmti_rec.subinventory_code||'->'||l_mmti_rec.locator_id||'->'||l_lot_number||'->'||l_mmti_rec.transaction_quantity||'->'||l_mmti_rec.transaction_uom||'->'||TO_CHAR(l_mmti_rec.transaction_date, 'DD-MON-YYYY HH24:MI:SS');
2332             IF (g_debug <= gme_debug.g_log_statement) THEN
2333               gme_debug.put_line('Creating TXN with '||l_new_data);
2334             END IF;
2335       	    gme_api_pub.create_material_txn(p_api_version         => 2.0,
2336                                             p_validation_level    => gme_common_pvt.g_max_errors,
2337                                             p_init_msg_list       => fnd_api.g_false,
2338                                             p_commit              => fnd_api.g_false,
2339                                             x_message_count       => l_msg_cnt,
2340                                             x_message_list        => l_msg_data,
2341                                             x_return_status       => l_return_status,
2342                                             p_org_code            => NULL,
2343                                             p_mmti_rec            => l_mmti_rec,
2344                                             p_mmli_tbl            => l_mmli_tbl,
2345                                             p_batch_no            => NULL,
2346                                             p_line_no             => NULL,
2347                                             p_line_type           => NULL,
2348                                             p_create_lot          => NULL,
2349                                             p_generate_lot        => NULL,
2350                                             p_generate_parent_lot => NULL,
2351                                             x_mmt_rec             => l_mmt_rec,
2352                                             x_mmln_tbl            => l_mmln_rec);
2353             IF (l_return_status <> fnd_api.g_ret_sts_success) THEN
2354               l_msg_name := 'GME_CREATE_TXN_FAIL';
2355               RAISE create_txn_rsv_pp_err;
2356             END IF;
2357           ELSE /* IF (l_txns_tbl(i).completed_ind = 1) THEN */
2358             IF (g_debug <= gme_debug.g_log_statement) THEN
2359               gme_debug.put_line('This is a pending txn');
2360             END IF;
2361             l_mmti_rec.transaction_source_id := l_mtl_rec.batch_id;
2362             l_mmti_rec.trx_source_line_id    := l_mtl_rec.material_detail_id;
2363             l_mmti_rec.inventory_item_id     := l_mtl_rec.inventory_item_id;
2364             l_mmti_rec.organization_id       := l_mtl_rec.organization_id;
2365             IF (l_mtl_rec.line_type = gme_common_pvt.g_line_type_ing) THEN
2366               IF (g_debug <= gme_debug.g_log_statement) THEN
2367                 gme_debug.put_line('Ing so we will create a reservation');
2368               END IF;
2369               IF (l_mtl_rec.reservable_type <> 1) THEN
2370               	l_msg_name := 'GME_MIG_ITEM_NOT_RESV_ENABLED';
2371         	RAISE defined_error;
2372       	      END IF;
2373               IF (l_mtl_rec.phantom_type = 0) THEN
2374                 l_mtl_dtl_rec.material_detail_id        := l_mtl_rec.material_detail_id;
2375                 l_mtl_dtl_rec.batch_id                  := l_mtl_rec.batch_id;
2376                 l_mtl_dtl_rec.formulaline_id            := l_mtl_rec.formulaline_id;
2377                 l_mtl_dtl_rec.line_no                   := l_mtl_rec.line_no;
2378                 l_mtl_dtl_rec.item_id                   := l_mtl_rec.item_id;
2379                 l_mtl_dtl_rec.line_type                 := l_mtl_rec.line_type;
2380                 l_mtl_dtl_rec.plan_qty                  := l_mtl_rec.plan_qty;
2381                 l_mtl_dtl_rec.item_um                   := l_mtl_rec.item_um;
2382                 l_mtl_dtl_rec.item_um2                  := l_mtl_rec.item_um2;
2383                 l_mtl_dtl_rec.actual_qty                := l_mtl_rec.actual_qty;
2384                 l_mtl_dtl_rec.release_type              := l_mtl_rec.release_type;
2385                 l_mtl_dtl_rec.scrap_factor              := l_mtl_rec.scrap_factor;
2386                 l_mtl_dtl_rec.scale_type                := l_mtl_rec.scale_type;
2387                 l_mtl_dtl_rec.phantom_type              := l_mtl_rec.phantom_type;
2388                 l_mtl_dtl_rec.cost_alloc                := l_mtl_rec.cost_alloc;
2389                 l_mtl_dtl_rec.alloc_ind                 := l_mtl_rec.alloc_ind;
2390                 l_mtl_dtl_rec.cost                      := l_mtl_rec.cost;
2391                 l_mtl_dtl_rec.text_code                 := l_mtl_rec.text_code;
2392                 l_mtl_dtl_rec.phantom_id                := l_mtl_rec.phantom_id;
2393                 l_mtl_dtl_rec.rounding_direction        := l_mtl_rec.rounding_direction;
2394                 l_mtl_dtl_rec.creation_date             := l_mtl_rec.creation_date;
2395                 l_mtl_dtl_rec.created_by                := l_mtl_rec.created_by;
2396                 l_mtl_dtl_rec.last_update_date          := l_mtl_rec.last_update_date;
2397                 l_mtl_dtl_rec.last_updated_by           := l_mtl_rec.last_updated_by;
2398                 l_mtl_dtl_rec.last_update_login         := l_mtl_rec.last_update_login;
2399                 l_mtl_dtl_rec.scale_rounding_variance   := l_mtl_rec.scale_rounding_variance;
2400                 l_mtl_dtl_rec.scale_multiple            := l_mtl_rec.scale_multiple;
2401                 l_mtl_dtl_rec.contribute_yield_ind      := l_mtl_rec.contribute_yield_ind;
2402                 l_mtl_dtl_rec.contribute_step_qty_ind   := l_mtl_rec.contribute_step_qty_ind;
2403                 l_mtl_dtl_rec.wip_plan_qty              := l_mtl_rec.wip_plan_qty;
2404                 l_mtl_dtl_rec.original_qty              := l_mtl_rec.original_qty;
2405                 l_mtl_dtl_rec.by_product_type           := l_mtl_rec.by_product_type;
2406                 l_mtl_dtl_rec.backordered_qty           := l_mtl_rec.backordered_qty;
2407                 l_mtl_dtl_rec.dispense_ind              := l_mtl_rec.dispense_ind;
2408                 l_mtl_dtl_rec.dtl_um                    := l_mtl_rec.dtl_um;
2409                 l_mtl_dtl_rec.inventory_item_id         := l_mtl_rec.inventory_item_id;
2410                 l_mtl_dtl_rec.locator_id                := l_mtl_rec.locator_id;
2411                 l_mtl_dtl_rec.material_requirement_date := l_mtl_rec.material_requirement_date;
2412                 l_mtl_dtl_rec.move_order_line_id        := l_mtl_rec.move_order_line_id;
2413                 l_mtl_dtl_rec.organization_id           := l_mtl_rec.organization_id;
2414                 l_mtl_dtl_rec.original_primary_qty      := l_mtl_rec.original_primary_qty;
2415                 l_mtl_dtl_rec.phantom_line_id           := l_mtl_rec.phantom_line_id;
2416                 l_mtl_dtl_rec.revision                  := l_mtl_rec.revision;
2417                 l_mtl_dtl_rec.subinventory              := l_mtl_rec.subinventory;
2418                 IF (l_mtl_rec.revision_qty_control_code = 2) THEN
2419                   l_mtl_dtl_rec.revision := get_latest_revision(p_organization_id => l_mtl_rec.organization_id, p_inventory_item_id => l_mtl_rec.inventory_item_id);
2420                   IF (l_mtl_dtl_rec.revision IS NULL) THEN
2421                     l_msg_name := 'GME_MIG_REVISION_NOT_FOUND';
2422               	    RAISE defined_error;
2423                   END IF;
2424                 ELSE
2425                   l_mtl_dtl_rec.revision := NULL;
2426                 END IF;
2427                 IF (g_debug <= gme_debug.g_log_statement) THEN
2428                   gme_debug.put_line('After defaulting ing');
2429                 END IF;
2430                 IF (NVL(l_txns_tbl(i).location, l_def_location) <> l_def_location) THEN
2431                   get_locator(p_location        => l_txns_tbl(i).location,
2432                               p_whse_code       => l_txns_tbl(i).whse_code,
2433                               x_organization_id => l_org_id,
2434                               x_locator_id      => l_locator_id,
2435                               x_subinventory    => l_subinventory);
2436                 END IF;
2437                 IF (g_debug <= gme_debug.g_log_statement) THEN
2438                   gme_debug.put_line('Three locator_id = '||l_locator_id||' subinventory = '||l_subinventory||' org_id = '||l_org_id);
2439                 END IF;
2440                 IF (l_subinventory IS NULL) THEN
2441                   get_subinventory(p_whse_code       => l_txns_tbl(i).whse_code,
2442                                    x_subinventory    => l_subinventory,
2443                                    x_organization_id => l_org_id);
2444                 END IF;
2445                 /* If this txn is in a different org than the batch org then do a issue and receipt */
2446                 IF (g_debug <= gme_debug.g_log_statement) THEN
2447                   gme_debug.put_line('Four l_subinventory = '||l_subinventory||' l_org_id = '||l_org_id||' l_mmti_rec.organization_id = '||l_mmti_rec.organization_id);
2448                   gme_debug.put_line('creating issue/receipt from org = '||l_org_id||' to org = '||l_mmti_rec.organization_id);
2449                 END IF;
2450                 IF (l_org_id <> l_mmti_rec.organization_id) THEN
2451                   /* Create a misc issue in l_org_id and a receipt in l_mmti_rec.organization_id */
2452                   l_mmti_rec.primary_quantity               := ROUND(ABS(l_txns_tbl(i).trans_qty),5);
2453                   l_mmti_rec.reason_id                      := get_reason(l_txns_tbl(i).reason_code);
2454                   l_mmti_rec.secondary_transaction_quantity := ROUND(ABS(l_txns_tbl(i).trans_qty2),5);
2455                   l_mmti_rec.secondary_uom_code             := l_mtl_rec.secondary_uom_code;
2456                   IF (l_mtl_rec.revision_qty_control_code = 2) THEN
2457                     l_mmti_rec.revision := get_latest_revision(p_organization_id => l_mtl_rec.organization_id, p_inventory_item_id => l_mtl_rec.inventory_item_id);
2458                     IF (l_mmti_rec.revision IS NULL) THEN
2459               	      l_msg_name := 'GME_MIG_REVISION_NOT_FOUND';
2460               	      RAISE defined_error;
2461                     END IF;
2462                   ELSE
2463                     l_mmti_rec.revision := NULL;
2464                   END IF;
2465                   check_date(p_organization_id => l_mtl_rec.organization_id,
2466                              p_date            => l_txns_tbl(i).trans_date,
2467                              x_date            => l_date,
2468                              x_return_status   => l_return_status);
2469                   IF (l_return_status <> fnd_api.g_ret_sts_success) THEN
2470                     l_msg_name := 'GME_NO_OPEN_PERIODS_TXN';
2471                     RAISE defined_error;
2472                   END IF;
2473                   l_mmti_rec.transaction_date := l_date;
2474                   SELECT mtl_material_transactions_s.NEXTVAL INTO gme_common_pvt.g_transaction_header_id FROM DUAL;
2475                   IF (g_debug <= gme_debug.g_log_statement) THEN
2476                     gme_debug.put_line('Transaction header ID for reservation is '||gme_common_pvt.g_transaction_header_id);
2477                   END IF;
2478                   l_in_subinventory := l_subinventory;
2479                   create_issue_receipt(p_curr_org_id       => l_org_id,
2480                                        p_inventory_item_id => l_mtl_rec.inventory_item_id,
2481                                        p_txn_rec           => l_txns_tbl(i),
2482                                        p_mmti_rec          => l_mmti_rec,
2483                                        p_item_no           => l_mtl_rec.item_no,
2484                                        p_subinventory      => l_in_subinventory,
2485                                        p_locator_id        => l_locator_id,
2486                                        p_batch_org_id      => l_mmti_rec.organization_id,
2487                                        x_subinventory      => l_subinventory,
2488                                        x_locator_id        => l_locator_id,
2489                                        x_lot_number        => l_lot_number,
2490                                        x_return_status     => l_return_status);
2491                   IF (l_return_status <> FND_API.G_RET_STS_SUCCESS) THEN
2492                     RAISE expected_error;
2493                   END IF;
2494                   gme_api_pub.save_batch(p_header_id    => gme_common_pvt.g_transaction_header_id,
2495                                          p_table        => gme_common_pvt.g_interface_table,
2496                                          p_commit       => FND_API.G_FALSE,
2497                                          x_return_status => l_return_status);
2498                   IF (l_return_status <> fnd_api.g_ret_sts_success) THEN
2499                     l_msg_name := 'GME_MIG_INV_TRANSFER_FAIL';
2500                     RAISE create_txn_rsv_pp_err;
2501                   END IF;
2502                 ELSE
2503                   IF (g_debug <= gme_debug.g_log_statement) THEN
2504                     gme_debug.put_line('No transfer for this reservation needed');
2505                   END IF;
2506                   IF (l_subinventory IS NOT NULL) THEN
2507                     IF NOT (gme_common_pvt.check_subinventory(p_organization_id   => l_mtl_rec.organization_id
2508                                                              ,p_subinventory      => l_subinventory
2509                                                              ,p_inventory_item_id => l_mtl_rec.inventory_item_id
2510                                                              ,p_restrict_subinv   => l_mtl_rec.restrict_subinventories_code)) THEN
2511                       l_subinventory := NULL;
2512                       l_locator_id   := NULL;
2513                       l_msg_name := 'GME_MIG_SUBINV_NOT_FOUND';
2514                       RAISE defined_error;
2515                     END IF;
2516                     get_subinv_locator_type(p_subinventory     => l_subinventory,
2517                                             p_organization_id  => l_mtl_rec.organization_id,
2518                                             x_locator_type     => l_sub_loc_type);
2519                   ELSE
2520                     l_msg_name := 'GME_MIG_SUBINV_NOT_FOUND';
2521                     RAISE defined_error;
2522                   END IF;
2523                   l_eff_loc_control := gme_common_pvt.eff_locator_control(p_organization_id   => l_mtl_rec.organization_id,
2524                                                                           p_subinventory      => l_subinventory,
2525                                                                           p_inventory_item_id => l_mtl_rec.inventory_item_id,
2526                                                                           p_org_control       => gme_common_pvt.g_org_locator_control,
2527                                                                           p_sub_control       => l_sub_loc_type,
2528                                                                           p_item_control      => NVL(l_mtl_rec.location_control_code,1),
2529                                                                           p_item_loc_restrict => l_mtl_rec.restrict_locators_code,
2530                                                                           p_org_neg_allowed   => gme_common_pvt.g_allow_neg_inv,
2531                                                                           p_action            => 1);
2532                   IF (l_eff_loc_control = 1) THEN
2533                     l_locator_id := NULL;
2534                   ELSE
2535                     IF (l_locator_id IS NULL AND NVL(l_txns_tbl(i).location, l_def_location) <> l_def_location) THEN
2536                       create_locator(p_location	       => l_txns_tbl(i).location,
2537                                      p_organization_id   => l_mtl_rec.organization_id,
2538                                      p_subinventory_code => l_subinventory,
2539                                      x_location_id       => l_locator_id,
2540                                      x_failure_count     => l_failure_count);
2541                     END IF;
2542                   END IF;
2543                   IF (l_locator_id IS NOT NULL) THEN
2544                     IF NOT (Gme_Common_Pvt.check_locator
2545                                 (p_organization_id        => l_mtl_rec.organization_id
2546                                 ,p_locator_id             => l_locator_id
2547                                 ,p_subinventory           => l_subinventory
2548                                 ,p_inventory_item_id      => l_mtl_rec.inventory_item_id
2549                                 ,p_org_control            => Gme_Common_Pvt.g_org_locator_control
2550                                 ,p_sub_control            => l_sub_loc_type
2551                                 ,p_item_control           => NVL(l_mtl_rec.location_control_code,1)
2552                                 ,p_item_loc_restrict      => l_mtl_rec.restrict_locators_code
2553                                 ,p_org_neg_allowed        => Gme_Common_Pvt.g_allow_neg_inv
2554                                 ,p_txn_action_id          => 1)) THEN
2555                        l_locator_id := NULL;
2556                        l_msg_name := 'GME_MIG_LOCATOR_NOT_FOUND';
2557                        RAISE defined_error;
2558                     END IF;
2559                   END IF;
2560                   IF (l_mtl_rec.lot_control_code <> 2) THEN
2561                     IF (NVL(l_txns_tbl(i).lot_id,0) > 0) THEN
2562                       l_msg_name := 'GME_MIG_ITEM_NOT_LOT_ENABLED';
2563           	      RAISE defined_error;
2564                     END IF;
2565                   ELSE
2566                     IF NVL(l_txns_tbl(i).lot_id, 0) = 0 THEN
2567                       l_msg_name := 'GME_MIG_ITEM_LOT_ENABLED';
2568                       RAISE defined_error;
2569                     END IF;
2570                   END IF;
2571                   IF (g_debug <= gme_debug.g_log_statement) THEN
2572                     gme_debug.put_line('Lot control is for this reservation = '||l_mtl_rec.lot_control_code);
2573                   END IF;
2574                   IF (l_mtl_rec.lot_control_code = 2) THEN
2575                     inv_opm_lot_migration.get_odm_lot(p_migration_run_id  => g_migration_run_id,
2576                                                       p_item_id           => l_txns_tbl(i).item_id,
2577                                                       p_lot_id	          => l_txns_tbl(i).lot_id,
2578                                                       p_whse_code	  => l_txns_tbl(i).whse_code,
2579                                                       p_orgn_code	  => NULL,
2580                                                       p_location	  => l_txns_tbl(i).location,
2581                                                       p_commit	          => fnd_api.g_true,
2582                                                       x_lot_number	  => l_lot_number,
2583                                                       x_parent_lot_number => l_parent_lot_no,
2584                                                       x_failure_count	  => l_failure_count);
2585                     IF (l_failure_count > 0 OR l_lot_number IS NULL) THEN
2586                       l_msg_name := 'GME_MIG_LOT_NOT_FOUND';
2587                       RAISE defined_error;
2588                     END IF;
2589                   END IF;
2590                 END IF;
2591                 IF (g_debug <= gme_debug.g_log_statement) THEN
2592                   gme_debug.put_line('Lot is '||l_lot_number);
2593                 END IF;
2594                 l_mtl_dtl_rec.revision := l_mmti_rec.revision;
2595                 l_new_data := gme_common_pvt.g_organization_code||'->'||l_mtl_rec.item_no||'->'||l_mmti_rec.revision||'->'||l_subinventory||'->'||l_locator_id||'->'||l_lot_number||'->'||ABS(l_txns_tbl(i).trans_qty)||'->'||l_mtl_rec.primary_uom_code;
2596                 IF (g_debug <= gme_debug.g_log_statement) THEN
2597                   gme_debug.put_line('Creating reservation with '||l_new_data);
2598                 END IF;
2599                 gme_reservations_pvt.create_material_reservation(p_matl_dtl_rec  => l_mtl_dtl_rec,
2600                                                                  p_resv_qty      => ABS(l_txns_tbl(i).trans_qty),
2601                                                                  p_sec_resv_qty  => ABS(l_txns_tbl(i).trans_qty2),
2602                                                                  p_resv_um       => l_mtl_rec.primary_uom_code,
2603                                                                  p_subinventory  => l_subinventory,
2604                                                                  p_locator_id    => l_locator_id,
2605                                                                  p_lot_number    => l_lot_number,
2606                                                                  x_return_status => l_return_status);
2607                 IF (l_return_status <> fnd_api.g_ret_sts_success) THEN
2608                   l_msg_name := 'GME_CREATE_RESV_FAIL';
2609                   RAISE create_txn_rsv_pp_err;
2610                 END IF;
2611               END IF;
2612             ELSE /* products and byproducts create pending product lots */
2613               IF (g_debug <= gme_debug.g_log_statement) THEN
2614                 gme_debug.put_line('Creating pending product lot');
2615               END IF;
2616               l_mtl_dtl_rec.material_requirement_date := l_mtl_rec.material_requirement_date;
2617               l_mtl_dtl_rec.organization_id           := l_mtl_rec.organization_id;
2618               l_mtl_dtl_rec.inventory_item_id         := l_mtl_rec.inventory_item_id;
2619               l_mtl_dtl_rec.batch_id                  := l_mtl_rec.batch_id;
2620               l_mtl_dtl_rec.material_detail_id        := l_mtl_rec.material_detail_id;
2621               l_mtl_dtl_rec.dtl_um                    := l_mtl_rec.dtl_um;
2622               l_mtl_dtl_rec.plan_qty                  := l_mtl_rec.plan_qty;
2623               IF (l_mtl_rec.lot_control_code <> 2) THEN
2624               	l_msg_name := 'GME_MIG_ITEM_NOT_LOT_ENABLED';
2625         	RAISE defined_error;
2626               ELSE
2627               	IF (NVL(l_txns_tbl(i).lot_id, 0) = 0) THEN
2628               	  l_msg_name := 'GME_MIG_ITEM_LOT_ENABLED';
2629         	  RAISE defined_error;
2630               	END IF;
2631       	      END IF;
2632               -- create pend prod lots
2633               IF (l_mtl_rec.revision_qty_control_code = 2) THEN
2634                 l_plot_in_rec.revision := get_latest_revision(p_organization_id => l_mtl_rec.organization_id, p_inventory_item_id => l_mtl_rec.inventory_item_id);
2635               ELSE
2636                 l_plot_in_rec.revision := NULL;
2637               END IF;
2638               OPEN Cur_lot_mst(l_txns_tbl(i).lot_id);
2639               FETCH Cur_lot_mst INTO l_lot_no, l_sublot_no;
2640               CLOSE Cur_lot_mst;
2641               inv_opm_lot_migration.get_odm_lot(p_migration_run_id  => g_migration_run_id,
2642                                                 p_inventory_item_id => l_mtl_dtl_rec.inventory_item_id,
2643                                                 p_lot_no	    => l_lot_no,
2644                                                 p_sublot_no         => l_sublot_no,
2645                                                 p_organization_id   => l_mtl_dtl_rec.organization_id,
2646                                                 p_locator_id	    => NULL,
2647                                                 p_commit	    => fnd_api.g_true,
2648                                                 x_lot_number	    => l_lot_number,
2649                                                 x_parent_lot_number => l_parent_lot_no,
2650                                                 x_failure_count	    => l_failure_count);
2651               IF (l_failure_count > 0 OR l_lot_number IS NULL) THEN
2652                 l_msg_name := 'GME_MIG_LOT_NOT_FOUND';
2653                 RAISE defined_error;
2654               END IF;
2655               l_plot_in_rec.lot_number := l_lot_number;
2656               IF (l_mtl_rec.primary_uom_code <> l_mtl_rec.dtl_um) THEN
2657                 l_plot_in_rec.quantity := inv_convert.inv_um_convert(item_id         => l_mtl_rec.inventory_item_id
2658                                                                     ,lot_number      => l_plot_in_rec.lot_number
2659                                                                     ,organization_id => l_mtl_rec.organization_id
2660                                                                     ,PRECISION       => gme_common_pvt.g_precision
2661                                                                     ,from_quantity   => ABS(l_txns_tbl(i).trans_qty)
2662                                                                     ,from_unit       => l_mtl_rec.primary_uom_code
2663                                                                     ,to_unit         => l_mtl_rec.dtl_um
2664                                                                     ,from_name       => NULL
2665                                                                     ,to_name         => NULL);
2666                 IF (l_plot_in_rec.quantity < 0) THEN
2667                   RAISE uom_conversion_fail;
2668                 END IF;
2669               ELSE
2670                 l_plot_in_rec.quantity := ABS(l_txns_tbl(i).trans_qty);
2671               END IF;
2672               l_plot_in_rec.secondary_quantity := l_txns_tbl(i).trans_qty2;
2673               l_plot_in_rec.reason_id          := get_reason(l_txns_tbl(i).reason_code);
2674               l_plot_in_rec.sequence           := NULL;
2675               l_new_data := gme_common_pvt.g_organization_code||'->'||l_mtl_rec.item_no||'->'||l_plot_in_rec.revision||'->'||l_plot_in_rec.lot_number||'->'||l_plot_in_rec.quantity||'->'||l_mtl_dtl_rec.dtl_um;
2676               IF (g_debug <= gme_debug.g_log_statement) THEN
2677                 gme_debug.put_line('Creating pending product lot with '||l_new_data);
2678               END IF;
2679               gme_api_pub.create_pending_product_lot(p_api_version               => 2.0,
2680                                                      p_validation_level          => gme_common_pvt.g_max_errors,
2681                                                      p_init_msg_list            => fnd_api.g_false,
2682                                                      p_commit                   => fnd_api.g_false,
2683                                                      x_message_count            => l_msg_cnt,
2684                                                      x_message_list             => l_msg_data,
2685                                                      x_return_status            => l_return_status,
2686                                                      p_batch_header_rec         => l_batch_hdr,
2687                                                      p_org_code                 => gme_common_pvt.g_organization_code,
2688                                                      p_create_lot               => fnd_api.g_false,
2689                                                      p_generate_lot             => fnd_api.g_false,
2690                                                      p_generate_parent_lot      => fnd_api.g_false,
2691                                                      p_material_detail_rec      => l_mtl_dtl_rec,
2692                                                      p_expiration_date          => NULL,
2693                                                      p_pending_product_lots_rec => l_plot_in_rec,
2694                                                      x_pending_product_lots_rec => l_plot_out_rec);
2695               IF (l_return_status <> fnd_api.g_ret_sts_success) THEN
2696               	l_msg_name := 'GME_CREATE_PPLOT_FAIL';
2697                 RAISE create_txn_rsv_pp_err;
2698               END IF;
2699       	    END IF;
2700 	  END IF;
2701 	END IF; /* IF NOT(l_mtl_rec.line_type = gme_common_pvt.g_line_type_ing AND l_mtl_rec.phantom_type IN (gme_common_pvt.g_auto_phantom, gme_common_pvt.g_manual_phantom)) THEN */
2702         UPDATE gme_batch_txns_mig
2703         SET migrated_ind = 1
2704         WHERE trans_id = l_txns_tbl(i).trans_id;
2705         IF (g_debug <= gme_debug.g_log_statement) THEN
2706           gme_debug.put_line('Done transaction');
2707         END IF;
2708         COMMIT;
2709       EXCEPTION
2710         WHEN setup_failed OR batch_fetch_err THEN
2711           gme_common_pvt.count_and_get(x_count  => l_msg_cnt
2712                                       ,x_data   => l_msg_data);
2713           gma_common_logging.gma_migration_central_log
2714                      (p_run_id              => g_migration_run_id,
2715                       p_log_level           => fnd_log.level_error,
2716                       p_message_token       => 'GME_TXNS_MIG_FAILED',
2717                       p_table_name          => 'GME_BATCH_HEADER',
2718                       p_context             => 'RECREATE_OPEN_BATCHES',
2719                       p_app_short_name      => 'GME',
2720                       p_token1              => 'BATCH_NO',
2721                       p_param1              => l_txns_tbl(i).plant_code||'-'||l_txns_tbl(i).new_batch_no,
2722                       p_token2              => 'MSG',
2723                       p_param2              => l_msg_data);
2724           ROLLBACK;
2725         WHEN expected_error THEN
2726           l_txn_data := l_mtl_rec.item_no||'->'||l_txns_tbl(i).whse_code||'->'||l_txns_tbl(i).location||'->'||
2727           l_txns_tbl(i).lot_id||'->'||l_txns_tbl(i).trans_qty||'->'||l_mtl_rec.primary_uom_code||'->'||to_char(l_txns_tbl(i).trans_date, 'DD-MON-YYYY HH24:MI:SS');
2728           gme_common_pvt.count_and_get(x_count  => l_msg_cnt
2729                                       ,x_data   => l_msg_data);
2730           gma_common_logging.gma_migration_central_log
2731                      (p_run_id              => g_migration_run_id,
2732                       p_log_level           => fnd_log.level_error,
2733                       p_message_token       => 'GME_GENERAL_TXN_FAIL',
2734                       p_table_name          => 'GME_BATCH_HEADER',
2735                       p_context             => 'RECREATE_OPEN_BATCHES',
2736                       p_app_short_name      => 'GME',
2737                       p_token1              => 'BATCH_NO',
2738                       p_param1              => l_txns_tbl(i).plant_code||'-'||l_txns_tbl(i).new_batch_no,
2739                       p_token2              => 'MSG',
2740                       p_param2              => l_msg_data,
2741                       p_token3              => 'TXN_DATA',
2742                       p_param3              => l_txn_data);
2743           ROLLBACK;
2744       	WHEN defined_error THEN
2745       	  l_txn_data := l_mtl_rec.item_no||'->'||l_txns_tbl(i).whse_code||'->'||l_txns_tbl(i).location||'->'||
2746       	  l_txns_tbl(i).lot_id||'->'||l_txns_tbl(i).trans_qty||'->'||l_mtl_rec.primary_uom_code||'->'||to_char(l_txns_tbl(i).trans_date, 'DD-MON-YYYY HH24:MI:SS');
2747           gma_common_logging.gma_migration_central_log
2748                      (p_run_id              => g_migration_run_id,
2749                       p_log_level           => fnd_log.level_error,
2750                       p_message_token       => l_msg_name,
2751                       p_table_name          => 'GME_BATCH_HEADER',
2752                       p_context             => 'RECREATE_OPEN_BATCHES',
2753                       p_app_short_name      => 'GME',
2754                       p_token1              => 'BATCH_NO',
2755                       p_param1              => l_txns_tbl(i).plant_code||'-'||l_txns_tbl(i).new_batch_no,
2756                       p_token2              => 'TRANS_ID',
2757                       p_param2              => l_txns_tbl(i).trans_id,
2758                       p_token3              => 'TXN_DATA',
2759                       p_param3              => l_txn_data);
2760           ROLLBACK;
2761         WHEN uom_conversion_fail THEN
2762       	  l_txn_data := l_mtl_rec.item_no||'->'||l_txns_tbl(i).whse_code||'->'||l_txns_tbl(i).location||'->'||
2763       	  l_txns_tbl(i).lot_id||'->'||l_txns_tbl(i).trans_qty||'->'||l_mtl_rec.primary_uom_code||'->'||TO_CHAR(l_txns_tbl(i).trans_date, 'DD-MON-YYYY HH24:MI:SS');
2764           gma_common_logging.gma_migration_central_log
2765                      (p_run_id              => g_migration_run_id,
2766                       p_log_level           => fnd_log.level_error,
2767                       p_message_token       => 'GME_MIG_UOM_CONV_FAIL',
2768                       p_table_name          => 'GME_BATCH_HEADER',
2769                       p_context             => 'RECREATE_OPEN_BATCHES',
2770                       p_app_short_name      => 'GME',
2771                       p_token1              => 'BATCH_NO',
2772                       p_param1              => l_txns_tbl(i).plant_code||'-'||l_txns_tbl(i).new_batch_no,
2773                       p_token2              => 'TRANS_ID',
2774                       p_param2              => l_txns_tbl(i).trans_id,
2775                       p_token3              => 'TXN_DATA',
2776                       p_param3              => l_txn_data,
2777                       p_token4              => 'FROM_UOM',
2778                       p_param4              => l_mtl_rec.primary_uom_code,
2779                       p_token5              => 'TO_UOM',
2780                       p_param5              => l_mtl_rec.dtl_um);
2781           ROLLBACK;
2782         WHEN create_txn_rsv_pp_err THEN
2783           gme_common_pvt.count_and_get(p_encoded => FND_API.G_FALSE
2784                                       ,x_count  => l_msg_cnt
2785                                       ,x_data   => l_msg_data);
2786       	  l_txn_data := l_mtl_rec.item_no||'->'||l_txns_tbl(i).whse_code||'->'||l_txns_tbl(i).location||'->'||
2787       	  l_txns_tbl(i).lot_id||'->'||l_txns_tbl(i).trans_qty||'->'||l_mtl_rec.primary_uom_code||'->'||TO_CHAR(l_txns_tbl(i).trans_date, 'DD-MON-YYYY HH24:MI:SS');
2788           gma_common_logging.gma_migration_central_log
2789                      (p_run_id              => g_migration_run_id,
2790                       p_log_level           => fnd_log.level_error,
2791                       p_message_token       => l_msg_name,
2792                       p_table_name          => 'GME_BATCH_HEADER',
2793                       p_context             => 'RECREATE_OPEN_BATCHES',
2794                       p_app_short_name      => 'GME',
2795                       p_token1              => 'BATCH_NO',
2796                       p_param1              => l_txns_tbl(i).plant_code||'-'||l_txns_tbl(i).new_batch_no,
2797                       p_token2              => 'TRANS_ID',
2798                       p_param2              => l_txns_tbl(i).trans_id,
2799                       p_token3              => 'TXN_DATA',
2800                       p_param3              => l_txn_data,
2801                       p_token4              => 'MSG',
2802                       p_param4              => l_msg_data,
2803                       p_token5              => 'NEW_DATA',
2804                       p_param5              => l_new_data);
2805           ROLLBACK;
2806         WHEN OTHERS THEN
2807           IF (g_debug <= gme_debug.g_log_unexpected) THEN
2808             gme_debug.put_line('When others in '||l_api_name||' '||SQLERRM);
2809           END IF;
2810           l_txn_data := l_mtl_rec.item_no||'->'||l_txns_tbl(i).whse_code||'->'||l_txns_tbl(i).location||'->'||
2811           l_txns_tbl(i).lot_id||'->'||l_txns_tbl(i).trans_qty||'->'||l_mtl_rec.primary_uom_code||'->'||TO_CHAR(l_txns_tbl(i).trans_date, 'DD-MON-YYYY HH24:MI:SS');
2812           gma_common_logging.gma_migration_central_log
2813                      (p_run_id              => g_migration_run_id,
2814                       p_log_level           => fnd_log.level_error,
2815                       p_message_token       => 'GME_GENERAL_TXN_FAIL',
2816                       p_table_name          => 'GME_BATCH_HEADER',
2817                       p_context             => 'RECREATE_OPEN_BATCHES',
2818                       p_app_short_name      => 'GME',
2819                       p_token1              => 'BATCH_NO',
2820                       p_param1              => l_txns_tbl(i).plant_code||'-'||l_txns_tbl(i).new_batch_no,
2821                       p_token2              => 'MSG',
2822                       p_param2              => SQLERRM,
2823                       p_token3              => 'TXN_DATA',
2824                       p_param3              => l_txn_data);
2825           ROLLBACK;
2826       END;
2827     END LOOP;
2828     IF (g_debug <= gme_debug.g_log_procedure) THEN
2829       gme_debug.put_line('End procedure '||l_api_name);
2830     END IF;
2831   END create_txns_reservations;
2832 
2833   PROCEDURE create_issue_receipt(p_curr_org_id       IN NUMBER,
2834                                  p_inventory_item_id IN NUMBER,
2835                                  p_txn_rec           IN Cur_get_txns%ROWTYPE,
2836                                  p_mmti_rec          IN mtl_transactions_interface%ROWTYPE,
2837                                  p_item_no           IN VARCHAR2,
2838                                  p_subinventory      IN VARCHAR2,
2839                                  p_locator_id        IN NUMBER,
2840                                  p_batch_org_id      IN NUMBER,
2841                                  x_subinventory      OUT NOCOPY VARCHAR2,
2842                                  x_locator_id        OUT NOCOPY NUMBER,
2843                                  x_lot_number        OUT NOCOPY VARCHAR2,
2844                                  x_return_status     OUT NOCOPY VARCHAR2) IS
2845     l_api_name            VARCHAR2(30) := 'create_issue_receipt';
2846     l_organization_code   VARCHAR2(3);
2847     l_org                 VARCHAR2(3);
2848     l_return_status       VARCHAR2(1);
2849     l_def_location        VARCHAR2(100) := FND_PROFILE.VALUE('IC$DEFAULT_LOCT');
2850     l_lot_number          VARCHAR2(80);
2851     l_parent_lot_no       VARCHAR2(80);
2852     l_msg_name            VARCHAR2(32);
2853     l_msg_data            VARCHAR2(2000);
2854     l_txn_data            VARCHAR2(2000);
2855     l_msg_cnt             NUMBER;
2856     l_allow_neg_inv       NUMBER;
2857     l_org_loc_control     NUMBER;
2858     l_eff_loc_control     NUMBER;
2859     l_sub_loc_type        NUMBER;
2860     l_locator_id          NUMBER;
2861     l_failure_count       NUMBER;
2862     l_date                DATE;
2863     CURSOR Cur_item_dtl(v_organization_id NUMBER, v_inventory_item_id NUMBER) IS
2864       SELECT i.mtl_transactions_enabled_flag, i.reservable_type, i.segment1, i.lot_control_code,
2865              i.revision_qty_control_code, i.primary_uom_code, i.secondary_uom_code, i.restrict_subinventories_code,
2866              NVL(i.location_control_code,1) location_control_code, i.restrict_locators_code, i.segment1 item_no
2867       FROM   mtl_system_items_b i
2868       WHERE  i.organization_id = v_organization_id
2869              AND i.inventory_item_id = v_inventory_item_id;
2870     CURSOR Cur_new_loc(v_organization_id NUMBER, v_subinventory VARCHAR2, v_location VARCHAR2) IS
2871       SELECT m.inventory_location_id locator_id
2872       FROM   mtl_item_locations m
2873       WHERE  m.segment1 = v_location
2874              AND m.organization_id = v_organization_id
2875              AND m.subinventory_code = v_subinventory;
2876     CURSOR Cur_get_org_params(v_org_id NUMBER) IS
2877       SELECT negative_inv_receipt_code, stock_locator_control_code, organization_code
2878       FROM   mtl_parameters
2879       WHERE organization_id = v_org_id;
2880     l_item_rec        Cur_item_dtl%ROWTYPE;
2881     l_issue_rec       mtl_transactions_interface%ROWTYPE;
2882     l_issue_lot_rec   mtl_transaction_lots_interface%ROWTYPE;
2883     l_receipt_rec     mtl_transactions_interface%ROWTYPE;
2884     l_receipt_lot_rec mtl_transaction_lots_interface%ROWTYPE;
2885     defined_error      EXCEPTION;
2886     expected_error     EXCEPTION;
2887     item_not_defined   EXCEPTION;
2888     no_open_period_err EXCEPTION;
2889   BEGIN
2890     IF (g_debug <= gme_debug.g_log_procedure) THEN
2891       gme_debug.put_line('Start procedure '||l_api_name);
2892     END IF;
2893     IF (g_debug <= gme_debug.g_log_statement) THEN
2894       gme_debug.put_line('Moving from org = '||p_curr_org_id||' to org = '||p_batch_org_id);
2895     END IF;
2896     x_return_status := FND_API.G_RET_STS_SUCCESS;
2897     OPEN Cur_get_org_params(p_curr_org_id);
2898     FETCH Cur_get_org_params INTO l_allow_neg_inv, l_org_loc_control, l_organization_code;
2899     CLOSE Cur_get_org_params;
2900     l_txn_data := p_item_no||'->'||p_txn_rec.whse_code||'->'||p_txn_rec.location||'->'||p_txn_rec.lot_id||'->'||p_txn_rec.trans_qty||'->'||p_txn_rec.trans_um||'->'||to_char(p_txn_rec.trans_date, 'DD-MON-YYYY HH24:MI:SS');
2901     IF (g_debug <= gme_debug.g_log_statement) THEN
2902       gme_debug.put_line('TXN Data = '||l_txn_data);
2903     END IF;
2904     gma_common_logging.gma_migration_central_log
2905                  (p_run_id              => g_migration_run_id,
2906                   p_log_level           => fnd_log.level_error,
2907                   p_message_token       => 'GME_MIG_INV_TRANSFER',
2908                   p_table_name          => 'GME_BATCH_HEADER',
2909                   p_context             => 'RECREATE_OPEN_BATCHES',
2910                   p_app_short_name      => 'GME',
2911                   p_token1              => 'BATCH_NO',
2912                   p_param1              => p_txn_rec.plant_code||'-'||p_txn_rec.new_batch_no,
2913                   p_token2              => 'TRANS_ID',
2914                   p_param2              => p_txn_rec.trans_id,
2915                   p_token3              => 'TXN_DATA',
2916                   p_param3              => l_txn_data,
2917                   p_token4              => 'ORG',
2918                   p_param4              => l_organization_code);
2919     OPEN Cur_item_dtl(p_curr_org_id, p_inventory_item_id);
2920     FETCH Cur_item_dtl INTO l_item_rec;
2921     IF (Cur_item_dtl%NOTFOUND) THEN
2922       CLOSE Cur_item_dtl;
2923       l_org := l_organization_code;
2924       RAISE item_not_defined;
2925     END IF;
2926     CLOSE Cur_item_dtl;
2927     IF (l_item_rec.mtl_transactions_enabled_flag <> 'Y') THEN
2928       l_msg_name := 'GME_MIG_ITEM_NOT_TXNS_ENABLED';
2929       RAISE defined_error;
2930     END IF;
2931     IF (l_item_rec.lot_control_code <> 2) THEN
2932       IF (NVL(p_txn_rec.lot_id,0) > 0) THEN
2933         l_msg_name := 'GME_MIG_ITEM_NOT_LOT_ENABLED';
2934         RAISE defined_error;
2935       END IF;
2936     ELSE
2937       IF NVL(p_txn_rec.lot_id, 0) = 0 THEN
2938         l_msg_name := 'GME_MIG_ITEM_LOT_ENABLED';
2939         RAISE defined_error;
2940       END IF;
2941     END IF;
2942     IF (g_debug <= gme_debug.g_log_statement) THEN
2943       gme_debug.put_line('Before subinventory');
2944     END IF;
2945     /* Validate if sub found is valid in this org */
2946     IF NOT (gme_common_pvt.check_subinventory(p_organization_id   => p_curr_org_id
2947                                              ,p_subinventory      => p_subinventory
2948                                              ,p_inventory_item_id => p_inventory_item_id
2949                                              ,p_restrict_subinv   => l_item_rec.restrict_subinventories_code)) THEN
2950       l_msg_name := 'GME_MIG_SUBINV_NOT_FOUND';
2951       RAISE defined_error;
2952     END IF;
2953     get_subinv_locator_type(p_subinventory     => p_subinventory,
2954                             p_organization_id  => p_curr_org_id,
2955                             x_locator_type     => l_sub_loc_type);
2956     l_eff_loc_control := gme_common_pvt.eff_locator_control(p_organization_id   => p_curr_org_id,
2957                                                             p_subinventory      => p_subinventory,
2958                                                             p_inventory_item_id => p_inventory_item_id,
2959                                                             p_org_control       => l_org_loc_control,
2960                                                             p_sub_control       => l_sub_loc_type,
2961                                                             p_item_control      => NVL(l_item_rec.location_control_code,1),
2962                                                             p_item_loc_restrict => l_item_rec.restrict_locators_code,
2963                                                             p_org_neg_allowed   => l_allow_neg_inv,
2964                                                             p_action            => 1);
2965     IF (l_eff_loc_control = 1) THEN
2966       l_locator_id := NULL;
2967     ELSE
2968       IF (p_locator_id IS NULL AND NVL(p_txn_rec.location, l_def_location) <> l_def_location) THEN
2969         create_locator(p_location	   => p_txn_rec.location,
2970                        p_organization_id   => p_curr_org_id,
2971                        p_subinventory_code => p_subinventory,
2972                        x_location_id       => l_locator_id,
2973                        x_failure_count     => l_failure_count);
2974       ELSE
2975       	l_locator_id := p_locator_id;
2976       END IF;
2977     END IF;
2978     IF (l_locator_id IS NOT NULL) THEN
2979       IF NOT (Gme_Common_Pvt.check_locator
2980                     (p_organization_id        => p_curr_org_id
2981                     ,p_locator_id             => l_locator_id
2982                     ,p_subinventory           => p_subinventory
2983                     ,p_inventory_item_id      => p_inventory_item_id
2984                     ,p_org_control            => l_org_loc_control
2985                     ,p_sub_control            => l_sub_loc_type
2986                     ,p_item_control           => NVL(l_item_rec.location_control_code,1)
2987                     ,p_item_loc_restrict      => l_item_rec.restrict_locators_code
2988                     ,p_org_neg_allowed        => l_allow_neg_inv
2989                     ,p_txn_action_id          => 1)) THEN
2990         l_locator_id := NULL;
2991         l_msg_name := 'GME_MIG_LOCATOR_NOT_FOUND';
2992         RAISE defined_error;
2993       END IF;
2994     END IF;
2995     IF (l_item_rec.lot_control_code = 2) THEN
2996       inv_opm_lot_migration.get_odm_lot(p_migration_run_id    => g_migration_run_id,
2997                                         p_item_id             => p_txn_rec.item_id,
2998                                         p_lot_id	      => p_txn_rec.lot_id,
2999                                         p_whse_code	      => p_txn_rec.whse_code,
3000                                         p_orgn_code	      => NULL,
3001                                         p_location	      => p_txn_rec.location,
3002                                         p_commit	      => fnd_api.g_true,
3003                                         x_lot_number	      => l_lot_number,
3004                                         x_parent_lot_number   => l_parent_lot_no,
3005                                         x_failure_count       => l_failure_count);
3006       IF (l_failure_count > 0 OR l_lot_number IS NULL) THEN
3007       	l_msg_name := 'GME_MIG_LOT_NOT_FOUND';
3008         RAISE defined_error;
3009       END IF;
3010     END IF;
3011     get_distribution_account(p_subinventory  => p_subinventory,
3012                              p_org_id        => p_curr_org_id,
3013                              x_dist_acct_id  => l_issue_rec.distribution_account_id);
3014     check_date(p_organization_id => p_curr_org_id,
3015                p_date            => p_mmti_rec.transaction_date,
3016                x_date            => l_date,
3017                x_return_status   => l_return_status);
3018     IF (l_return_status <> fnd_api.g_ret_sts_success) THEN
3019       l_txn_data := l_organization_code||'->'||p_item_no||'->'||p_txn_rec.whse_code||'->'||p_txn_rec.location||'->'||p_txn_rec.lot_id||'->'||
3020       p_txn_rec.trans_qty||'->'||l_item_rec.primary_uom_code||'->'||to_char(p_txn_rec.trans_date, 'DD-MON-YYYY HH24:MI:SS');
3021       gme_common_pvt.log_message(p_product_code => 'INV', p_message_code => 'INV_NO_OPEN_PERIOD');
3022       RAISE no_open_period_err;
3023     ELSE
3024       l_issue_rec.transaction_date := l_date;
3025     END IF;
3026     /* Create a misc issue in original org/sub/loc and then a reciept in final org/sub/loc */
3027     SELECT mtl_material_transactions_s.NEXTVAL INTO
3028     l_issue_rec.transaction_interface_id FROM DUAL;
3029     l_issue_rec.transaction_header_id          := gme_common_pvt.g_transaction_header_id;
3030     l_issue_rec.source_code                    := 'OPM_GME_MIGRATION';
3031     l_issue_rec.source_line_id                 := p_txn_rec.trans_id;
3032     l_issue_rec.source_header_id               := p_txn_rec.doc_id;
3033     l_issue_rec.inventory_item_id              := p_inventory_item_id;
3034     l_issue_rec.organization_id                := p_curr_org_id;
3035     l_issue_rec.subinventory_code              := p_subinventory;
3036     l_issue_rec.locator_id                     := l_locator_id;
3037     l_issue_rec.transaction_type_id            := 32; --Misc. Issue
3038     l_issue_rec.transaction_action_id          := 1;
3039     l_issue_rec.transaction_source_type_id     := 13;
3040     l_issue_rec.transaction_source_id          := p_txn_rec.trans_id;
3041     l_issue_rec.transaction_source_name        := 'GME Transaction Migration';
3042     l_issue_rec.transaction_quantity           := -1 * ABS(p_mmti_rec.primary_quantity);
3043     l_issue_rec.transaction_uom                := l_item_rec.primary_uom_code;
3044     l_issue_rec.reason_id                      := p_mmti_rec.reason_id;
3045     l_issue_rec.secondary_transaction_quantity := -1 * ABS(p_mmti_rec.secondary_transaction_quantity);
3046     l_issue_rec.secondary_uom_code             := p_mmti_rec.secondary_uom_code;
3047     l_issue_rec.process_flag                   := 1;
3048     l_issue_rec.transaction_mode               := 2;
3049     l_issue_rec.transaction_batch_id           := gme_common_pvt.g_transaction_header_id;
3050     l_issue_rec.transaction_batch_seq          := 0;
3051     l_issue_rec.last_update_date               := p_txn_rec.last_update_date;
3052     l_issue_rec.last_updated_by                := p_txn_rec.last_updated_by;
3053     l_issue_rec.creation_date                  := p_txn_rec.creation_date;
3054     l_issue_rec.created_by                     := p_txn_rec.created_by;
3055     l_issue_rec.revision                       := p_mmti_rec.revision;
3056     IF (l_item_rec.lot_control_code = 2) THEN
3057       l_issue_lot_rec.transaction_interface_id       := l_issue_rec.transaction_interface_id;
3058       l_issue_lot_rec.last_update_date               := p_txn_rec.last_update_date;
3059       l_issue_lot_rec.last_updated_by                := p_txn_rec.last_updated_by;
3060       l_issue_lot_rec.creation_date                  := p_txn_rec.creation_date;
3061       l_issue_lot_rec.created_by                     := p_txn_rec.created_by;
3062       l_issue_lot_rec.lot_number                     := l_lot_number;
3063       l_issue_lot_rec.transaction_quantity           := -1 * ABS(p_mmti_rec.primary_quantity);
3064       l_issue_lot_rec.secondary_transaction_quantity := -1 * ABS(p_mmti_rec.secondary_transaction_quantity);
3065     END IF;
3066     IF (g_debug <= gme_debug.g_log_statement) THEN
3067       gme_debug.put_line('Issue record '||l_issue_rec.organization_id||'->'||p_item_no||'->'||l_issue_rec.subinventory_code||'->'||
3068       l_issue_rec.locator_id||'->'||l_lot_number||'->'||l_issue_rec.transaction_quantity||'->'||l_issue_rec.transaction_uom||'->'||to_char(l_issue_rec.transaction_date, 'DD-MON-YYYY HH24:MI:SS'));
3069     END IF;
3070     insert_interface_recs(p_mti_rec       => l_issue_rec,
3071                           p_mtli_rec      => l_issue_lot_rec,
3072                           x_return_status => l_return_status);
3073     IF (l_return_status <> FND_API.G_RET_STS_SUCCESS) THEN
3074     	RAISE expected_error;
3075     END IF;
3076     /* Now start the receipt in the batch org */
3077     OPEN Cur_item_dtl(p_batch_org_id, p_inventory_item_id);
3078     FETCH Cur_item_dtl INTO l_item_rec;
3079     IF (Cur_item_dtl%NOTFOUND) THEN
3080       CLOSE Cur_item_dtl;
3081       l_org := gme_common_pvt.g_organization_code;
3082       RAISE item_not_defined;
3083     END IF;
3084     CLOSE Cur_item_dtl;
3085     IF (l_item_rec.mtl_transactions_enabled_flag <> 'Y') THEN
3086       l_msg_name := 'GME_MIG_ITEM_NOT_TXNS_ENABLED';
3087       RAISE defined_error;
3088     END IF;
3089     IF (l_item_rec.lot_control_code <> 2) THEN
3090       IF (NVL(p_txn_rec.lot_id, 0) > 0) THEN
3091         l_msg_name := 'GME_MIG_ITEM_NOT_LOT_ENABLED';
3092         RAISE defined_error;
3093       END IF;
3094     ELSE
3095       IF NVL(p_txn_rec.lot_id, 0) = 0 THEN
3096         l_msg_name := 'GME_MIG_ITEM_LOT_ENABLED';
3097         RAISE defined_error;
3098       END IF;
3099     END IF;
3100     l_receipt_rec := l_issue_rec;
3101     check_date(p_organization_id => p_batch_org_id,
3102                p_date            => l_receipt_rec.transaction_date,
3103                x_date            => l_date,
3104                x_return_status   => l_return_status);
3105     IF (l_return_status <> fnd_api.g_ret_sts_success) THEN
3106       l_txn_data := gme_common_pvt.g_organization_code||'->'||p_item_no||'->'||p_txn_rec.whse_code||'->'||p_txn_rec.location||'->'||p_txn_rec.lot_id||'->'||
3107       p_txn_rec.trans_qty||'->'||l_item_rec.primary_uom_code||'->'||to_char(p_txn_rec.trans_date, 'DD-MON-YYYY HH24:MI:SS');
3108       gme_common_pvt.log_message(p_product_code => 'INV', p_message_code => 'INV_NO_OPEN_PERIOD');
3109       RAISE no_open_period_err;
3110     ELSE
3111       l_receipt_rec.transaction_date := l_date;
3112     END IF;
3113     SELECT mtl_material_transactions_s.NEXTVAL INTO
3114     l_receipt_rec.transaction_interface_id FROM DUAL;
3115     l_receipt_rec.organization_id                := p_batch_org_id;
3116     /* We are creating a receipt txn in a sub which has the same name as org. This will always exist */
3117     BEGIN
3118       SELECT whse_code
3119       INTO   l_receipt_rec.subinventory_code
3120       FROM   ic_whse_mst
3121       WHERE  mtl_organization_id = p_batch_org_id;
3122     EXCEPTION
3123       WHEN OTHERS THEN
3124         l_receipt_rec.subinventory_code := gme_common_pvt.g_organization_code;
3125     END;
3126     get_distribution_account(p_subinventory  => l_receipt_rec.subinventory_code,
3127                              p_org_id        => p_batch_org_id,
3128                              x_dist_acct_id  => l_receipt_rec.distribution_account_id);
3129     l_receipt_rec.transaction_type_id            := 42; --Misc Receipt
3130     l_receipt_rec.transaction_action_id          := 27;
3131     l_receipt_rec.transaction_quantity           := -1 * l_receipt_rec.transaction_quantity;
3132     l_receipt_rec.secondary_transaction_quantity := -1 * l_receipt_rec.secondary_transaction_quantity;
3133     get_subinv_locator_type(p_subinventory     => gme_common_pvt.g_organization_code,
3134                             p_organization_id  => p_batch_org_id,
3135                             x_locator_type     => l_sub_loc_type);
3136     /* Check for the eff locator control of this org */
3137     l_eff_loc_control := gme_common_pvt.eff_locator_control(p_organization_id   => p_batch_org_id,
3138                                                             p_subinventory      => l_receipt_rec.subinventory_code,
3139                                                             p_inventory_item_id => p_inventory_item_id,
3140                                                             p_org_control       => gme_common_pvt.g_org_locator_control,
3141                                                             p_sub_control       => l_sub_loc_type,
3142                                                             p_item_control      => NVL(l_item_rec.location_control_code,1),
3143                                                             p_item_loc_restrict => l_item_rec.restrict_locators_code,
3144                                                             p_org_neg_allowed   => gme_common_pvt.g_allow_neg_inv,
3145                                                             p_action            => 27);
3146     IF (l_eff_loc_control = 1) THEN
3147       l_locator_id := NULL;
3148     ELSE
3149       IF (NVL(p_txn_rec.location, l_def_location) <> l_def_location) THEN
3150         OPEN Cur_new_loc(p_batch_org_id, l_receipt_rec.subinventory_code, p_txn_rec.location);
3151         FETCH Cur_new_loc INTO l_receipt_rec.locator_id;
3152         IF (Cur_new_loc%NOTFOUND) THEN
3153           create_locator(p_location	     => p_txn_rec.location,
3154                          p_organization_id   => p_batch_org_id,
3155                          p_subinventory_code => l_receipt_rec.subinventory_code,
3156                          x_location_id       => l_receipt_rec.locator_id,
3157                          x_failure_count     => l_failure_count);
3158         END IF;
3159         CLOSE Cur_new_loc;
3160       END IF;
3161     END IF;
3162     IF (l_item_rec.lot_control_code = 2) THEN
3163       l_receipt_lot_rec.transaction_interface_id       := l_receipt_rec.transaction_interface_id;
3164       l_receipt_lot_rec.last_update_date               := p_txn_rec.last_update_date;
3165       l_receipt_lot_rec.last_updated_by                := p_txn_rec.last_updated_by;
3166       l_receipt_lot_rec.creation_date                  := p_txn_rec.creation_date;
3167       l_receipt_lot_rec.created_by                     := p_txn_rec.created_by;
3168       l_receipt_lot_rec.lot_number                     := l_lot_number;
3169       l_receipt_lot_rec.transaction_quantity           := l_receipt_rec.transaction_quantity;
3170       l_receipt_lot_rec.secondary_transaction_quantity := l_receipt_rec.secondary_transaction_quantity;
3171     END IF;
3172     IF (g_debug <= gme_debug.g_log_statement) THEN
3173       gme_debug.put_line('Receipt record '||l_receipt_rec.organization_id||'->'||p_item_no||'->'||l_receipt_rec.subinventory_code||'->'||
3174       l_receipt_rec.locator_id||'->'||l_lot_number||'->'||l_receipt_rec.transaction_quantity||'->'||l_receipt_rec.transaction_uom||'->'||to_char(l_receipt_rec.transaction_date, 'DD-MON-YYYY HH24:MI:SS'));
3175     END IF;
3176     insert_interface_recs(p_mti_rec       => l_receipt_rec,
3177                           p_mtli_rec      => l_receipt_lot_rec,
3178                           x_return_status => l_return_status);
3179     IF (l_return_status <> FND_API.G_RET_STS_SUCCESS) THEN
3180       RAISE expected_error;
3181     END IF;
3182     x_subinventory := l_receipt_rec.subinventory_code;
3183     x_locator_id   := l_receipt_rec.locator_id;
3184     x_lot_number   := l_receipt_lot_rec.lot_number;
3185     IF (g_debug <= gme_debug.g_log_procedure) THEN
3186       gme_debug.put_line('End procedure '||l_api_name);
3187     END IF;
3188   EXCEPTION
3189     WHEN item_not_defined THEN
3190       gma_common_logging.gma_migration_central_log
3191                  (p_run_id              => g_migration_run_id,
3192                   p_log_level           => fnd_log.level_error,
3193                   p_message_token       => 'INV_IC_INVALID_ITEM_ORG',
3194                   p_table_name          => 'GME_BATCH_HEADER',
3195                   p_context             => 'RECREATE_OPEN_BATCHES',
3196                   p_app_short_name      => 'INV',
3197                   p_token1              => 'ORG',
3198                   p_param1              => l_org,
3199                   p_token2              => 'ITEM',
3200                   p_param2              => p_item_no);
3201       x_return_status := FND_API.G_RET_STS_ERROR;
3202     WHEN no_open_period_err THEN
3203       gme_common_pvt.count_and_get(p_encoded => FND_API.G_FALSE
3204                                   ,x_count   => l_msg_cnt
3205                                   ,x_data    => l_msg_data);
3206       gma_common_logging.gma_migration_central_log
3207                  (p_run_id              => g_migration_run_id,
3208                   p_log_level           => fnd_log.level_error,
3209                   p_message_token       => 'GME_GENERAL_TXN_FAIL',
3210                   p_table_name          => 'GME_BATCH_HEADER',
3211                   p_context             => 'RECREATE_OPEN_BATCHES',
3212                   p_app_short_name      => 'GME',
3213                   p_token1              => 'BATCH_NO',
3214                   p_param1              => p_txn_rec.plant_code||'-'||p_txn_rec.new_batch_no,
3215                   p_token2              => 'MSG',
3216                   p_param2              => l_msg_data,
3217                   p_token3              => 'TXN_DATA',
3218                   p_param3              => l_txn_data);
3219       x_return_status := l_return_status;
3220     WHEN expected_error THEN
3221       l_txn_data := p_item_no||'->'||p_txn_rec.whse_code||'->'||p_txn_rec.location||'->'||p_txn_rec.lot_id||'->'||
3222       p_txn_rec.trans_qty||'->'||l_item_rec.primary_uom_code||'->'||to_char(p_txn_rec.trans_date, 'DD-MON-YYYY HH24:MI:SS');
3223       gme_common_pvt.count_and_get(p_encoded => FND_API.G_FALSE
3224                                   ,x_count   => l_msg_cnt
3225                                   ,x_data    => l_msg_data);
3226       gma_common_logging.gma_migration_central_log
3227                  (p_run_id              => g_migration_run_id,
3228                   p_log_level           => fnd_log.level_error,
3229                   p_message_token       => 'GME_GENERAL_TXN_FAIL',
3230                   p_table_name          => 'GME_BATCH_HEADER',
3231                   p_context             => 'RECREATE_OPEN_BATCHES',
3232                   p_app_short_name      => 'GME',
3233                   p_token1              => 'BATCH_NO',
3234                   p_param1              => p_txn_rec.plant_code||'-'||p_txn_rec.new_batch_no,
3235                   p_token2              => 'MSG',
3236                   p_param2              => l_msg_data,
3237                   p_token3              => 'TXN_DATA',
3238                   p_param3              => l_txn_data);
3239       x_return_status := l_return_status;
3240     WHEN defined_error THEN
3241       l_txn_data := p_item_no||'->'||p_txn_rec.whse_code||'->'||p_txn_rec.location||'->'||p_txn_rec.lot_id||'->'||p_txn_rec.trans_qty||'->'||l_item_rec.primary_uom_code||'->'||to_char(p_txn_rec.trans_date, 'DD-MON-YYYY HH24:MI:SS');
3242       gma_common_logging.gma_migration_central_log
3243                  (p_run_id              => g_migration_run_id,
3244                   p_log_level           => fnd_log.level_error,
3245                   p_message_token       => l_msg_name,
3246                   p_table_name          => 'GME_BATCH_HEADER',
3247                   p_context             => 'RECREATE_OPEN_BATCHES',
3248                   p_app_short_name      => 'GME',
3249                   p_token1              => 'BATCH_NO',
3250                   p_param1              => p_txn_rec.plant_code||'-'||p_txn_rec.new_batch_no,
3251                   p_token2              => 'TRANS_ID',
3252                   p_param2              => p_txn_rec.trans_id,
3253                   p_token3              => 'TXN_DATA',
3254                   p_param3              => l_txn_data);
3255       x_return_status := FND_API.G_RET_STS_ERROR;
3256     WHEN OTHERS THEN
3257       IF (g_debug <= gme_debug.g_log_unexpected) THEN
3258         gme_debug.put_line('When others in '||l_api_name||' '||SQLERRM);
3259       END IF;
3260       l_txn_data := p_item_no||'->'||p_txn_rec.whse_code||'->'||p_txn_rec.location||'->'||p_txn_rec.lot_id||'->'||p_txn_rec.trans_qty||'->'||l_item_rec.primary_uom_code||'->'||to_char(p_txn_rec.trans_date, 'DD-MON-YYYY HH24:MI:SS');
3261       x_return_status := FND_API.G_RET_STS_UNEXP_ERROR;
3262       gma_common_logging.gma_migration_central_log
3263                  (p_run_id              => g_migration_run_id,
3264                   p_log_level           => fnd_log.level_error,
3265                   p_message_token       => 'GME_GENERAL_TXN_FAIL',
3266                   p_table_name          => 'GME_BATCH_HEADER',
3267                   p_context             => 'RECREATE_OPEN_BATCHES',
3268                   p_app_short_name      => 'GME',
3269                   p_token1              => 'BATCH_NO',
3270                   p_param1              => p_txn_rec.plant_code||'-'||p_txn_rec.new_batch_no,
3271                   p_token2              => 'MSG',
3272                   p_param2              => SQLERRM,
3273                   p_token3              => 'TXN_DATA',
3274                   p_param3              => l_txn_data);
3275   END create_issue_receipt;
3276 
3277   PROCEDURE insert_interface_recs(p_mti_rec  IN mtl_transactions_interface%ROWTYPE,
3278                                   p_mtli_rec IN mtl_transaction_lots_interface%ROWTYPE,
3279                                   x_return_status OUT NOCOPY VARCHAR2) IS
3280     l_mti_tbl   gme_common_pvt.mtl_tran_int_tbl;
3281     l_mtli_tbl  gme_common_pvt.mtl_trans_lots_inter_tbl;
3282     l_api_name  VARCHAR2(30) := 'insert_interface_recs';
3283   BEGIN
3284     IF (g_debug <= gme_debug.g_log_procedure) THEN
3285       gme_debug.put_line('Start procedure '||l_api_name);
3286     END IF;
3287     x_return_status := FND_API.G_RET_STS_SUCCESS;
3288     l_mti_tbl(1)  := p_mti_rec;
3289     IF (p_mtli_rec.lot_number IS NOT NULL) THEN
3290       l_mtli_tbl(1) := p_mtli_rec;
3291     END IF;
3292     FORALL a IN 1..l_mti_tbl.COUNT
3293       INSERT INTO mtl_transactions_interface VALUES l_mti_tbl(a);
3294     FORALL b IN 1..l_mtli_tbl.COUNT
3295       INSERT INTO mtl_transaction_lots_interface VALUES l_mtli_tbl(b);
3296     IF (g_debug <= gme_debug.g_log_procedure) THEN
3297       gme_debug.put_line('End procedure '||l_api_name);
3298     END IF;
3299   EXCEPTION
3300     WHEN OTHERS THEN
3301       IF (g_debug <= gme_debug.g_log_unexpected) THEN
3302         gme_debug.put_line('When others in '||l_api_name||' '||SQLERRM);
3303       END IF;
3304       x_return_status := FND_API.G_RET_STS_UNEXP_ERROR;
3305       gma_common_logging.gma_migration_central_log
3306                   (p_run_id              => g_migration_run_id,
3307                    p_log_level           => fnd_log.level_unexpected,
3308                    p_message_token       => 'GMA_MIGRATION_DB_ERROR',
3309                    p_table_name          => 'GME_BATCH_HEADER',
3310                    p_context             => 'RECREATE_OPEN_BATCHES',
3311                    p_db_error            => SQLERRM,
3312                    p_app_short_name      => 'GMA');
3313   END insert_interface_recs;
3314 
3315   PROCEDURE close_steps IS
3316     CURSOR Cur_get_steps IS
3317       SELECT s.batchstep_id, m.step_close_date, bm.new_batch_no, s.batchstep_no, bm.plant_code, bm.old_batch_id
3318       FROM   gme_batch_steps_mig m, gme_batch_steps s, gme_batch_mapping_mig bm
3319       WHERE  m.step_status = gme_common_pvt.g_step_closed
3320              AND bm.old_batch_id = m.batch_id
3321              AND s.batch_id = bm.new_batch_id
3322              AND s.batchstep_no = m.batchstep_no
3323              AND NOT(s.step_status = m.step_status)
3324              AND s.step_status = gme_common_pvt.g_step_completed
3325       ORDER BY s.batch_id, s.batchstep_no;
3326     CURSOR Cur_verify_txns(v_batchstep_id NUMBER, v_old_batch_id NUMBER) IS
3327       SELECT 1
3328       FROM gme_batch_step_items bsi, gme_material_details gmdn,
3329            gme_material_details gmdo, gme_batch_txns_mig txn, ic_tran_pnd itp
3330       WHERE bsi.batchstep_id = v_batchstep_id
3331       AND gmdn.material_detail_id = bsi.material_detail_id
3332       AND gmdo.batch_id = v_old_batch_id
3333       AND gmdo.line_type = gmdn.line_type
3334       AND gmdo.line_no = gmdn.line_no
3335       AND txn.batch_id = v_old_batch_id
3336       AND NVL(txn.migrated_ind, 0) = 0
3337       AND itp.trans_id = txn.trans_id
3338       AND itp.line_id = gmdo.material_detail_id;
3339     l_step_rec     gme_batch_steps%ROWTYPE;
3340     l_out_step_rec gme_batch_steps%ROWTYPE;
3341     l_msg_cnt       NUMBER;
3342     l_found         NUMBER;
3343     l_msg_data      VARCHAR2(2000);
3344     l_return_status VARCHAR2(1);
3345     l_api_name  VARCHAR2(30) := 'close_steps';
3346     step_close_fail EXCEPTION;
3347   BEGIN
3348     IF (g_debug <= gme_debug.g_log_procedure) THEN
3349       gme_debug.put_line('Start procedure '||l_api_name);
3350     END IF;
3351     FOR get_steps IN Cur_get_steps LOOP
3352       BEGIN
3353         l_step_rec.batchstep_id := get_steps.batchstep_id;
3354         OPEN Cur_verify_txns(get_steps.batchstep_id, get_steps.old_batch_id);
3355         FETCH Cur_verify_txns INTO l_found;
3356         IF (Cur_verify_txns%NOTFOUND) THEN
3357           CLOSE Cur_verify_txns;
3358           gme_api_pub.close_step (p_api_version      => 2,
3359                                   p_validation_level => gme_common_pvt.g_max_errors,
3360                                   p_init_msg_list    => fnd_api.g_true,
3361                                   p_commit           => fnd_api.g_true,
3362                                   x_message_count    => l_msg_cnt,
3363                                   x_message_list     => l_msg_data,
3364                                   x_return_status    => l_return_status,
3365                                   p_batch_step_rec   => l_step_rec,
3366                                   p_delete_pending   => fnd_api.g_false,
3367                                   p_org_code         => NULL,
3368                                   p_batch_no         => NULL,
3369                                   x_batch_step_rec   => l_out_step_rec);
3370           IF (l_return_status <> fnd_api.g_ret_sts_success) THEN
3371             RAISE step_close_fail;
3372           END IF;
3373         ELSE
3374           CLOSE Cur_verify_txns;
3375         END IF;
3376       EXCEPTION
3377         WHEN step_close_fail THEN
3378           gma_common_logging.gma_migration_central_log
3379                      (p_run_id              => g_migration_run_id,
3380                       p_log_level           => fnd_log.level_error,
3381                       p_message_token       => 'GME_STEP_CLOSE_ERR',
3382                       p_table_name          => 'GME_BATCH_HEADER',
3383                       p_context             => 'RECREATE_OPEN_BATCHES',
3384                       p_app_short_name      => 'GME',
3385                       p_token1              => 'BATCH_NO',
3386                       p_param1              => get_steps.plant_code||'-'||get_steps.new_batch_no,
3387                       p_token2              => 'STEP_NO',
3388                       p_param2              => get_steps.batchstep_no,
3389                       p_token3              => 'MSG',
3390                       p_param3              => l_msg_data);
3391         WHEN OTHERS THEN
3392           IF (g_debug <= gme_debug.g_log_unexpected) THEN
3393             gme_debug.put_line('When others in '||l_api_name||' '||SQLERRM);
3394           END IF;
3395           gma_common_logging.gma_migration_central_log
3396                      (p_run_id              => g_migration_run_id,
3397                       p_log_level           => fnd_log.level_error,
3398                       p_message_token       => 'GME_STEP_PROCESS_UNEXP',
3399                       p_table_name          => 'GME_BATCH_HEADER',
3400                       p_context             => 'RECREATE_OPEN_BATCHES',
3401                       p_app_short_name      => 'GME',
3402                       p_token1              => 'BATCH_NO',
3403                       p_param1              => get_steps.plant_code||'-'||get_steps.new_batch_no,
3404                       p_token2              => 'STEP_NO',
3405                       p_param2              => get_steps.batchstep_no,
3406                       p_token3              => 'MSG',
3407                       p_param3              => SQLERRM);
3408       END;
3409     END LOOP;
3410     IF (g_debug <= gme_debug.g_log_procedure) THEN
3411       gme_debug.put_line('End procedure '||l_api_name);
3412     END IF;
3413   END close_steps;
3414 
3415   PROCEDURE insert_lab_lots IS
3416     l_api_name  VARCHAR2(30) := 'insert_lab_lots';
3417     CURSOR Cur_lab_lots IS
3418       SELECT l.*, m.organization_id, m.new_batch_no,  m.new_batch_id, m.plant_code, l.rowid
3419       FROM   gme_batch_mapping_mig m, gme_lab_batch_lots l
3420       WHERE  m.old_batch_id = l.batch_id
3421              AND NVL(attribute27, 'A') <> 'M';
3422     CURSOR Cur_item_dtl(v_organization_id NUMBER, v_inventory_item_id NUMBER) IS
3423       SELECT i.segment1, i.lot_control_code
3424       FROM   mtl_system_items_b i
3425       WHERE  i.organization_id = v_organization_id
3426              AND i.inventory_item_id = v_inventory_item_id;
3427     CURSOR Cur_mtl_dtl(v_material_detail_id NUMBER) IS
3428       SELECT d.*
3429       FROM   gme_material_details d
3430       WHERE  d.material_detail_id = v_material_detail_id;
3431     l_curr_batch_id   NUMBER;
3432     l_curr_detail_id  NUMBER;
3433     l_mat_detail_id   NUMBER;
3434     l_failure_count   NUMBER;
3435     l_msg_cnt         NUMBER;
3436     l_return_status   VARCHAR2(1);
3437     l_lot_number      VARCHAR2(80);
3438     l_parent_lot_no   VARCHAR2(80);
3439     l_txn_data        VARCHAR2(500);
3440     l_new_data        VARCHAR2(500);
3441     l_msg_data        VARCHAR2(2000);
3442     l_item_rec        Cur_item_dtl%ROWTYPE;
3443     l_batch_hdr       gme_batch_header%ROWTYPE;
3444     l_mtl_rec         gme_material_details%ROWTYPE;
3445     l_plot_out_rec    gme_pending_product_lots%ROWTYPE;
3446     l_plot_in_rec     gme_pending_product_lots%ROWTYPE;
3447     batch_fetch_err   EXCEPTION;
3448     create_pp_lot_err EXCEPTION;
3449   BEGIN
3450     IF (g_debug <= gme_debug.g_log_procedure) THEN
3451       gme_debug.put_line('Start procedure '||l_api_name);
3452     END IF;
3453     FOR get_lots IN Cur_lab_lots LOOP
3454       BEGIN
3455       	l_lot_number := NULL;
3456         l_txn_data   := NULL;
3457       	IF (NVL(l_curr_batch_id,0) <> NVL(get_lots.new_batch_id, -1)) THEN
3458       	  l_batch_hdr.batch_id := get_lots.new_batch_id;
3459       	  IF NOT(gme_batch_header_dbl.fetch_row(p_batch_header => l_batch_hdr,
3460       	                                        x_batch_header => l_batch_hdr)) THEN
3461       	    RAISE batch_fetch_err;
3462       	  END IF;
3463       	  l_curr_batch_id := get_lots.new_batch_id;
3464       	END IF;
3465       	IF (NVL(l_curr_detail_id,0) <> NVL(get_lots.material_detail_id, -1)) THEN
3466       	  l_mat_detail_id  := get_new_mat_id(p_old_mat_id => get_lots.material_detail_id, p_new_batch_id => get_lots.new_batch_id);
3467       	  OPEN Cur_mtl_dtl(l_mat_detail_id);
3468       	  FETCH Cur_mtl_dtl INTO l_mtl_rec;
3469       	  CLOSE Cur_mtl_dtl;
3470       	  l_curr_detail_id := get_lots.material_detail_id;
3471       	  OPEN Cur_item_dtl(l_mtl_rec.organization_id, l_mtl_rec.inventory_item_id);
3472       	  FETCH Cur_item_dtl INTO l_item_rec;
3473       	  CLOSE Cur_item_dtl;
3474       	END IF;
3475       	IF (l_item_rec.lot_control_code = 2) THEN
3476           inv_opm_lot_migration.get_odm_lot(p_migration_run_id    => g_migration_run_id,
3477                                             p_item_id             => get_lots.item_id,
3478                                             p_lot_id	          => get_lots.lot_id,
3479                                             p_whse_code	          => NULL,
3480                                             p_orgn_code	          => get_lots.plant_code,
3481                                             p_location	          => NULL,
3482                                             p_commit	          => fnd_api.g_true,
3483                                             x_lot_number	  => l_lot_number,
3484                                             x_parent_lot_number   => l_parent_lot_no,
3485                                             x_failure_count       => l_failure_count);
3486           IF (l_lot_number IS NOT NULL) THEN
3487             l_plot_in_rec.quantity           := get_lots.qty;
3488             l_plot_in_rec.secondary_quantity := get_lots.qty2;
3489             l_plot_in_rec.lot_number         := l_lot_number;
3490             gme_api_pub.create_pending_product_lot(p_api_version              => 2.0,
3491                                                    p_validation_level         => gme_common_pvt.g_max_errors,
3492                                                    p_init_msg_list            => fnd_api.g_false,
3493                                                    p_commit                   => fnd_api.g_false,
3494                                                    x_message_count            => l_msg_cnt,
3495                                                    x_message_list             => l_msg_data,
3496                                                    x_return_status            => l_return_status,
3497                                                    p_batch_header_rec         => l_batch_hdr,
3498                                                    p_org_code                 => NULL,
3499                                                    p_create_lot               => fnd_api.g_false,
3500                                                    p_generate_lot             => fnd_api.g_false,
3501                                                    p_generate_parent_lot      => fnd_api.g_false,
3502                                                    p_material_detail_rec      => l_mtl_rec,
3503                                                    p_expiration_date          => NULL,
3504                                                    p_pending_product_lots_rec => l_plot_in_rec,
3505                                                    x_pending_product_lots_rec => l_plot_out_rec);
3506             IF (l_return_status <> fnd_api.g_ret_sts_success) THEN
3507               RAISE create_pp_lot_err;
3508             END IF;
3509             UPDATE gme_lab_batch_lots
3510             SET    attribute27 = 'M'
3511             WHERE  rowid = get_lots.rowid;
3512           END IF;
3513       	END IF;
3514       	COMMIT;
3515       EXCEPTION
3516         WHEN batch_fetch_err THEN
3517           gme_common_pvt.count_and_get(x_count  => l_msg_cnt
3518                                       ,x_data   => l_msg_data);
3519           gma_common_logging.gma_migration_central_log
3520                      (p_run_id              => g_migration_run_id,
3521                       p_log_level           => fnd_log.level_error,
3522                       p_message_token       => 'GME_TXNS_MIG_FAILED',
3523                       p_table_name          => 'GME_BATCH_HEADER',
3524                       p_context             => 'RECREATE_OPEN_BATCHES',
3525                       p_app_short_name      => 'GME',
3526                       p_token1              => 'BATCH_NO',
3527                       p_param1              => get_lots.plant_code||'-'||get_lots.new_batch_no,
3528                       p_token2              => 'MSG',
3529                       p_param2              => l_msg_data);
3530           ROLLBACK;
3531         WHEN create_pp_lot_err THEN
3532           gme_common_pvt.count_and_get(p_encoded => FND_API.G_FALSE
3533                                       ,x_count   => l_msg_cnt
3534                                       ,x_data    => l_msg_data);
3535       	  l_txn_data := l_item_rec.segment1||'->'||get_lots.lot_id||'->'||get_lots.qty||'->'||get_lots.qty2;
3536       	  l_new_data := l_item_rec.segment1||'->'||l_lot_number||'->'||get_lots.qty||'->'||get_lots.qty2;
3537           gma_common_logging.gma_migration_central_log
3538                      (p_run_id              => g_migration_run_id,
3539                       p_log_level           => fnd_log.level_error,
3540                       p_message_token       => 'GME_CREATE_PPLOT_FAIL',
3541                       p_table_name          => 'GME_BATCH_HEADER',
3542                       p_context             => 'RECREATE_OPEN_BATCHES',
3543                       p_app_short_name      => 'GME',
3544                       p_token1              => 'BATCH_NO',
3545                       p_param1              => get_lots.plant_code||'-'||get_lots.new_batch_no,
3546                       p_token2              => 'TRANS_ID',
3547                       p_param2              => l_mtl_rec.material_detail_id,
3548                       p_token3              => 'TXN_DATA',
3549                       p_param3              => l_txn_data,
3550                       p_token4              => 'MSG',
3551                       p_param4              => l_msg_data,
3552                       p_token5              => 'NEW_DATA',
3553                       p_param5              => l_new_data);
3554           ROLLBACK;
3555         WHEN OTHERS THEN
3556           IF (g_debug <= gme_debug.g_log_unexpected) THEN
3557             gme_debug.put_line('When others in '||l_api_name||' '||SQLERRM);
3558           END IF;
3559       	  l_txn_data := l_item_rec.segment1||'->'||get_lots.lot_id||'->'||get_lots.qty||'->'||get_lots.qty2;
3560           gma_common_logging.gma_migration_central_log
3561                      (p_run_id              => g_migration_run_id,
3562                       p_log_level           => fnd_log.level_error,
3563                       p_message_token       => 'GME_TXNS_MIG_FAILED',
3564                       p_table_name          => 'GME_BATCH_HEADER',
3565                       p_context             => 'RECREATE_OPEN_BATCHES',
3566                       p_app_short_name      => 'GME',
3567                       p_token1              => 'BATCH_NO',
3568                       p_param1              => get_lots.plant_code||'->'||get_lots.new_batch_no||'->'||l_mtl_rec.line_type||'->'||
3569                                                l_mtl_rec.line_no||'->'||l_item_rec.segment1||'->'||get_lots.lot_id||'->'||get_lots.qty,
3570                       p_token2              => 'MSG',
3571                       p_param2              => SQLERRM);
3572           ROLLBACK;
3573       END;
3574     END LOOP;
3575     IF (g_debug <= gme_debug.g_log_procedure) THEN
3576       gme_debug.put_line('End procedure '||l_api_name);
3577     END IF;
3578   END insert_lab_lots;
3579 END gme_post_migration;