DBA Data[Home] [Help]

PACKAGE BODY: APPS.GME_POST_MIGRATION

Source


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