DBA Data[Home] [Help]

PACKAGE BODY: APPS.GMD_AUTO_STEP_CALC

Source


1 PACKAGE BODY GMD_AUTO_STEP_CALC AS
2 /* $Header: GMDSTEPB.pls 120.6 2006/08/09 05:39:28 kmotupal noship $ */
3 
4 /*======================================================================
5 --  PROCEDURE :
6 --   calc_step_qty
7 --
8 --  DESCRIPTION:
9 --    This PL/SQL procedure  is responsible for calculating step
10 --    quantities automatically.  It assumes that check_step_qty_calculatable
11 --    has already been successfully executed.
12 --
13 --  REQUIREMENTS
14 --    p_parent_id non null value.
15 --    p_step_tbl  non null value.
16 --  SYNOPSIS:
17 --    calc_step_qty (426, X_step_tbl, X_msg_count, X_msg_stack, X_return_status, 0, 0);
18 --
19 --  This procedure calls:  LOAD_STEPS
20 --                         GET_STEP_MATERIAL_LINES
21 --                         GET_STEP_REC
22 --                         SORT_STEP_LINES
23 --
24 --===================================================================== */
25 -- Forward declaration of procedure to determine whether the batch has entirely Mass or vol type..
26 PROCEDURE check_Bch_stp_qty_calculatable (P_check            IN  calculatable_rec_type,
27                                         P_ignore_mass_conv OUT NOCOPY BOOLEAN,
28                                         P_ignore_vol_conv  OUT NOCOPY BOOLEAN);
29 
30 PROCEDURE calc_step_qty (P_parent_id	     IN     NUMBER,
31                          P_step_tbl          OUT NOCOPY    step_rec_tbl,
32                          P_msg_count	     OUT NOCOPY    NUMBER,
33                          P_msg_stack	     OUT NOCOPY    VARCHAR2,
34                          P_return_status     OUT NOCOPY    VARCHAR2,
35                          P_called_from_batch IN     NUMBER DEFAULT 0,
36                          P_step_no	     IN	    NUMBER DEFAULT NULL,
37                          p_ignore_mass_conv  IN BOOLEAN DEFAULT FALSE,
38                          p_ignore_vol_conv   IN BOOLEAN DEFAULT FALSE,
39                          p_scale_factor      IN NUMBER DEFAULT NULL,
40                          p_process_loss	     IN NUMBER DEFAULT 0,
41 			 p_organization_id   IN NUMBER) IS
42   /* Local variables.
43   ==================*/
44   X_work_step_tbl		work_step_rec_tbl;
45   X_step_rows			NUMBER;
46   X_routing_id			NUMBER;
47   X_cur_rec		        NUMBER;
48   X_step_qty			NUMBER;
49   X_step_mass_qty		NUMBER;
50   X_step_vol_qty		NUMBER;
51   X_cur_mass_qty		NUMBER;
52   X_cur_vol_qty			NUMBER;
53   X_new_factor			NUMBER;
54   X_um_type			mtl_units_of_measure.uom_class%TYPE;
55   X_return_status 		VARCHAR2(1);
56   X_cur_step_status             NUMBER;
57 
58   X_plan_mass_qty		NUMBER;
59   X_plan_vol_qty		NUMBER;
60   X_actual_mass_qty		NUMBER;
61   X_actual_vol_qty		NUMBER;
62 
63   X_step_plan_mass_qty		NUMBER;
64   X_step_plan_vol_qty		NUMBER;
65   X_step_actual_mass_qty	NUMBER;
66   X_step_actual_vol_qty		NUMBER;
67 
68   /* Added by Shyam */
69   X_cur_other_qty              NUMBER := 0;
70   X_plan_other_qty             NUMBER := 0;
71   X_actual_other_qty           NUMBER := 0;
72   X_step_other_qty             NUMBER := 0;
73 
74   X_step_plan_other_qty		NUMBER := 0;
75   X_step_actual_other_qty	NUMBER := 0;
76 
77   X_work_step_qty_tbl		work_step_qty_tbl;
78   l_return_status		VARCHAR2(10);
79 
80   x_check  gmd_auto_step_calc.calculatable_rec_type;
81   x_ignore_mass_conv BOOLEAN DEFAULT FALSE;
82   x_ignore_vol_conv BOOLEAN DEFAULT FALSE;
83 
84   /* Cursor Definitions.
85   =====================*/
86   CURSOR Cur_get_fm_dep_steps (V_step NUMBER) IS
87     SELECT dep_routingstep_no, transfer_pct
88     FROM   fm_rout_dep
89     WHERE  routing_id = X_routing_id
90     AND    routingstep_no = V_step;
91 
92   CURSOR Cur_get_pm_dep_steps (V_step_id NUMBER) IS
93     SELECT batchstep_no, transfer_percent, step_status
94     FROM   gme_batch_step_dependencies d, gme_batch_steps s
95     WHERE  d.batch_id = P_parent_id
96     AND    d.batchstep_id = V_step_id
97     AND    s.batchstep_id = d.dep_step_id
98     AND    s.batch_id = d.batch_id;
99 
100   CURSOR Cur_get_std_factor (V_uom_code VARCHAR2) IS
101     SELECT a.conversion_rate, b.uom_class
102     FROM   mtl_uom_conversions a, mtl_units_of_measure b
103     WHERE  a.uom_code = b.uom_code
104            AND a.inventory_item_id = 0
105 	   AND b.uom_code = V_uom_code;
106 
107   CURSOR Cur_get_step_status (V_step_id NUMBER) IS
108     SELECT step_status
109     FROM   gme_batch_steps
110     WHERE  batchstep_id = V_step_id;
111 
112   /* Cursor Record.
113   =====================*/
114   -- None.  Cursor FOR loops are used.
115 
116   /* Exceptions.
117   ================*/
118   MISSING_PARENT_ID        		  EXCEPTION;
119   STEPS_UOM_NOT_MASS_VOLUME_TYPE          EXCEPTION;
120   LOAD_STEPS_FAILED			  EXCEPTION;
121   GET_STEP_MATERIAL_LINES_FAILED          EXCEPTION;
122   ERROR_SORTING_STEPS			  EXCEPTION;
123 
124 BEGIN
125   P_return_status := FND_API.G_RET_STS_SUCCESS;
126   IF P_parent_id IS NULL THEN
127     RAISE MISSING_PARENT_ID;
128   END IF;
129 
130   GMD_API_GRP.FETCH_PARM_VALUES (P_orgn_id      => p_organization_id	,
131 				P_parm_name     => 'GMD_MASS_UM_TYPE'	,
132 				P_parm_value    => gmd_auto_step_calc.G_PROFILE_MASS_UM_TYPE	,
133 				X_return_status => l_return_status	);
134 
135   GMD_API_GRP.FETCH_PARM_VALUES (P_orgn_id      => p_organization_id	,
136 				P_parm_name     => 'GMD_VOLUME_UM_TYPE'	,
137 				P_parm_value    => gmd_auto_step_calc.G_PROFILE_VOLUME_UM_TYPE	,
138 				X_return_status => l_return_status	);
139 
140   /* Load all steps into the PL/SQL table P_step_tbl */
141   /* Table is returned with step no filled in; qty and uom fields empty */
142   load_steps (P_parent_id, P_called_from_batch, P_step_no, P_step_tbl, X_routing_id, X_return_status);
143   IF X_return_status <> P_return_status THEN
144     RAISE LOAD_STEPS_FAILED;
145   END IF;
146 
147   /* Check that all the steps are defined in MASS or VOLUME uom type */
148   /* Additional logic added by Shyam */
149   /* If all steps are defined of the same type that is not Mass or Volume type then
150      that is OK.  */
151   /* So all steps can be 1) Either Mass or Volume type OR 2) some other type but the same
152      type for all */
153   IF NOT step_uom_mass_volume (P_step_tbl) THEN
154     RAISE STEPS_UOM_NOT_MASS_VOLUME_TYPE;
155   END IF;
156 
157 -- bug# 5347857
158 -- If called from batch see if all the step items have same UOM type of mass or vol ..the mass.
159    IF P_called_from_batch  = 1 THEN
160     x_check.Parent_id := P_parent_id;
161    check_Bch_stp_qty_calculatable (P_check  => x_check,
162                                         P_ignore_mass_conv => x_ignore_mass_conv,
163                                         P_ignore_vol_conv  => x_ignore_vol_conv
164 					);
165    ELSE
166      x_ignore_mass_conv := P_ignore_mass_conv;
167      x_ignore_vol_conv  :=  P_ignore_vol_conv;
168    END IF;
169 
170   /* Get all the material lines associated with the steps into the X_work_step_tbl   */
171   /* The procedure calls the GMI conversion routing, so the qty's in X_work_step_tbl */
172   /* will be converted to std mass and vol.                                          */
173 
174   /* Bug#3599182 - Thomas Daniel */
175   /* The overloaded step material lines for scaling should only be invoked if the scale factor is not */
176   /* equal to 1, changed the checking from NULL to equal to 1 as the recipe fetch pub is passing in   */
177   /* a default value of 1 for p_scale_factor */
178   IF NVL(P_scale_factor,1) = 1 THEN
179     get_step_material_lines (P_parent_id, X_routing_id, P_called_from_batch, P_step_tbl, X_work_step_tbl,
180                              X_return_status,x_ignore_mass_conv,x_ignore_vol_conv, p_process_loss);
181   ELSE
182     get_step_material_lines (P_parent_id, X_routing_id, P_called_from_batch, P_step_tbl, P_scale_factor,
183                              X_work_step_tbl, X_return_status,x_ignore_mass_conv,x_ignore_vol_conv, p_process_loss);
184   END IF;
185 
186   IF X_return_status <> P_return_status THEN
187     RAISE GET_STEP_MATERIAL_LINES_FAILED;
188   END IF;
189 
190   X_step_rows := P_step_tbl.COUNT;
191   /* Calculate the step quantities for all the rows in P_step_tbl */
192   FOR i IN 1..X_step_rows LOOP
193     X_cur_mass_qty := 0;
194     X_cur_vol_qty := 0;
195 
196     /*Bug 3431385 - Thomas Daniel */
197     /*Initialize the other qty variable */
198     X_cur_other_qty := 0;
199 
200     /* Bug 2314635 - Thomas Daniel */
201     /* Changed the following calculations of the step quantities to consider the */
202     /* plan and actual quantities for GME */
203     X_plan_mass_qty := 0;
204     X_plan_vol_qty := 0;
205     X_actual_mass_qty := 0;
206     X_actual_vol_qty := 0;
207 
208     /*Bug 3431385 - Thomas Daniel */
209     /*Initialize the other qty variables */
210     X_plan_other_qty := 0;
211     X_actual_other_qty := 0;
212 
213     /* If called from GMD */
214     IF P_called_from_batch = 0 THEN
215 
216       /* Calculate the quantities transferred from the prior steps */
217       FOR X_fm_dep_step_rec IN Cur_get_fm_dep_steps (P_step_tbl(i).step_no) LOOP
218         /*    Point X_cur_rec to the row(s) in P_Step_tbl which have data for    */
219         /*    previous, dependent step.  Ex. Step 20 flows to step 30.  I have */
220         /*    already calculated for step 20.  Now for step 30, pull step 20   */
221         /*    data, subtract any product coming out of 20, apply transfer %.   */
222         /*    This is the amount going in to step 30.                          */
223 
224         X_cur_rec := get_step_rec (X_fm_dep_step_rec.dep_routingstep_no, P_step_tbl);
225 
226         IF NOT (G_OTHER_UM_TYPE_EXISTS) THEN
227           X_step_mass_qty := P_step_tbl(X_cur_rec).step_mass_qty;
228           X_step_vol_qty := P_step_tbl(X_cur_rec).step_vol_qty;
229 
230           /* Deduct the products or byproduct quantities leaving the previous step */
231           FOR j IN 1..X_work_step_tbl.COUNT LOOP
232             IF (X_work_step_tbl(j).line_type <> -1) AND
233                (X_work_step_tbl(j).step_no = X_fm_dep_step_rec.dep_routingstep_no) THEN
234               X_step_mass_qty := X_step_mass_qty - X_work_step_tbl(j).line_mass_qty;
235               X_step_vol_qty := X_step_vol_qty - X_work_step_tbl(j).line_vol_qty;
236               IF X_step_mass_qty < 0 THEN
237                 X_step_mass_qty := 0;
238               END IF;
239               IF X_step_vol_qty < 0 THEN
240                 X_step_vol_qty := 0;
241               END IF;
242             END IF;
243           END LOOP; /* FOR j IN 1..X_work_step_tbl.COUNT*/
244           X_cur_mass_qty := X_cur_mass_qty +
245                              (X_step_mass_qty * X_fm_dep_step_rec.transfer_pct * 0.01);
246           X_cur_vol_qty  := X_cur_vol_qty +
247                              (X_step_vol_qty * X_fm_dep_step_rec.transfer_pct * 0.01);
248         ELSE /* when it is of other um type */
249           X_step_other_qty := P_step_tbl(X_cur_rec).step_other_qty;
250 
251           /* Deduct the products or byproduct quantities leaving the previous step */
252           FOR j IN 1..X_work_step_tbl.COUNT LOOP
253             IF (X_work_step_tbl(j).line_type <> -1) AND
254                (X_work_step_tbl(j).step_no = X_fm_dep_step_rec.dep_routingstep_no) THEN
255               X_step_other_qty := X_step_other_qty - X_work_step_tbl(j).line_other_qty;
256               IF X_step_other_qty < 0 THEN
257                 X_step_other_qty := 0;
258               END IF;
259             END IF;
260           END LOOP; /* FOR j IN 1..X_work_step_tbl.COUNT*/
261           X_cur_other_qty := X_cur_other_qty +
262                              (X_step_other_qty * X_fm_dep_step_rec.transfer_pct * 0.01);
263 
264         END IF; /* Condition that checks for other um type */
265       END LOOP; /* Cur_get_fm_dep_steps%FOUND*/
266 
267     ELSE /*IF P_called_from_batch = 0*/
268 
269       /* Calculate the quantities transferred from the prior steps */
270       FOR X_pm_dep_step_rec IN Cur_get_pm_dep_steps (P_step_tbl(i).step_id)LOOP
271 
272         X_step_plan_mass_qty := 0;
273         X_step_plan_vol_qty := 0;
274         X_step_actual_mass_qty := 0;
275         X_step_actual_vol_qty := 0;
276 
277         -- Added by Shyam
278         X_step_plan_other_qty := 0;
279         X_step_actual_other_qty := 0;
280 
281         IF NOT (G_OTHER_UM_TYPE_EXISTS) THEN
282           FOR k in 1..X_work_step_qty_tbl.COUNT LOOP
283             IF X_work_step_qty_tbl(k).step_no = X_pm_dep_step_rec.batchstep_no THEN
284               X_step_plan_mass_qty := X_work_step_qty_tbl(k).plan_mass_qty;
285               X_step_plan_vol_qty  := X_work_step_qty_tbl(k).plan_vol_qty;
286               X_step_actual_mass_qty := X_work_step_qty_tbl(k).actual_mass_qty;
287               X_step_actual_vol_qty  := X_work_step_qty_tbl(k).actual_vol_qty;
288               EXIT;
289             END IF;
290           END LOOP;
291 
292           /* Deduct the products or byproduct quantities leaving the previous step */
293           FOR j IN 1..X_work_step_tbl.COUNT LOOP
294             IF (X_work_step_tbl(j).step_no = X_pm_dep_step_rec.batchstep_no) THEN
295               IF X_work_step_tbl(j).line_type <> -1 THEN
296                 X_step_plan_mass_qty := X_step_plan_mass_qty - X_work_step_tbl(j).line_mass_qty;
297                 X_step_plan_vol_qty := X_step_plan_vol_qty - X_work_step_tbl(j).line_vol_qty;
298                 X_step_actual_mass_qty := X_step_actual_mass_qty - X_work_step_tbl(j).actual_mass_qty;
299                 X_step_actual_vol_qty := X_step_actual_vol_qty - X_work_step_tbl(j).actual_vol_qty;
300               END IF;
301             END IF;
302           END LOOP; /* FOR j IN 1..X_work_step_tbl.COUNT*/
303 
304           IF X_step_plan_mass_qty  > 0 THEN
305             X_plan_mass_qty := X_plan_mass_qty +
306                              (X_step_plan_mass_qty * X_pm_dep_step_rec.transfer_percent * 0.01);
307           END IF;
308           IF X_step_plan_vol_qty  > 0 THEN
309             X_plan_vol_qty := X_plan_vol_qty +
310                               (X_step_plan_vol_qty * X_pm_dep_step_rec.transfer_percent * 0.01);
311           END IF;
312 
313           /* B2335788 - Thomas Daniel */
314           /* Moved the following checking as the transfer quantities need not be calculated only */
315           /* for actuals if the parent step is in WIP status, still the planned transfers need to be calculated */
316           /* The transfer quantities should not be calculated for WIP step*/
317           /* Shikha Nagar B2304515 - reintroduced below code with WIP status         */
318           IF X_pm_dep_step_rec.step_status <> 2 THEN
319             IF X_step_actual_mass_qty  > 0 THEN
320               X_actual_mass_qty := X_actual_mass_qty +
321                                 (X_step_actual_mass_qty * X_pm_dep_step_rec.transfer_percent * 0.01);
322             END IF;
323             IF X_step_actual_vol_qty  > 0 THEN
324               X_actual_vol_qty := X_actual_vol_qty +
325                                 (X_step_actual_vol_qty * X_pm_dep_step_rec.transfer_percent * 0.01);
326             END IF;
327           END IF; /* IF X_pm_dep_step_rec.step_status <> 2 */
328         ELSE /* when the um of other um type */
329           FOR k in 1..X_work_step_qty_tbl.COUNT LOOP
330             IF X_work_step_qty_tbl(k).step_no = X_pm_dep_step_rec.batchstep_no THEN
331               X_step_plan_other_qty := X_work_step_qty_tbl(k).plan_other_qty;
332               X_step_actual_other_qty := X_work_step_qty_tbl(k).actual_other_qty;
333               EXIT;
334             END IF;
335           END LOOP;
336 
337           /* Deduct the products or byproduct quantities leaving the previous step */
338           FOR j IN 1..X_work_step_tbl.COUNT LOOP
339             IF (X_work_step_tbl(j).step_no = X_pm_dep_step_rec.batchstep_no) THEN
340               IF X_work_step_tbl(j).line_type <> -1 THEN
341                 X_step_plan_other_qty := X_step_plan_other_qty - X_work_step_tbl(j).line_other_qty;
342                 X_step_actual_other_qty := X_step_actual_other_qty - X_work_step_tbl(j).actual_other_qty;
343               END IF;
344             END IF;
345           END LOOP; /* FOR j IN 1..X_work_step_tbl.COUNT*/
346 
347           IF X_step_plan_other_qty  > 0 THEN
348             X_plan_other_qty := X_plan_other_qty +
349                              (X_step_plan_other_qty * X_pm_dep_step_rec.transfer_percent * 0.01);
350           END IF;
351 
352           /* B2335788 - Thomas Daniel */
353           /* Moved the following checking as the transfer quantities need not be calculated only */
354           /* for actuals if the parent step is in WIP status, still the planned transfers need to be calculated */
355           /* The transfer quantities should not be calculated for WIP step*/
356           /* Shikha Nagar B2304515 - reintroduced below code with WIP status         */
357           IF X_pm_dep_step_rec.step_status <> 2 THEN
358             IF X_step_actual_other_qty  > 0 THEN
359               X_actual_other_qty := X_actual_other_qty +
360                                 (X_step_actual_other_qty * X_pm_dep_step_rec.transfer_percent * 0.01);
361             END IF;
362           END IF; /* IF X_pm_dep_step_rec.step_status <> 2 */
363         END IF; /* end of other um typ econdition */
364       END LOOP; /* Cur_get_pm_dep_steps%FOUND */
365     END IF; /*IF P_called_from_batch = 0*/
366 
367     /* Add the ingredient quantities that go into the current step */
368     FOR j IN 1..X_work_step_tbl.COUNT LOOP
369       IF (X_work_step_tbl(j).line_type = -1) AND
370          (X_work_step_tbl(j).step_no = P_step_tbl(i).step_no) THEN
371         IF p_called_from_batch = 0 THEN
372           IF NOT G_OTHER_UM_TYPE_EXISTS THEN /* checking for other um type */
373             X_cur_mass_qty := X_cur_mass_qty + X_work_step_tbl(j).line_mass_qty;
374             X_cur_vol_qty := X_cur_vol_qty + X_work_step_tbl(j).line_vol_qty;
375           ELSE
376             X_cur_other_qty := X_cur_other_qty + X_work_step_tbl(j).line_other_qty;
377           END IF;
378         ELSE /* for batch */
379           IF NOT G_OTHER_UM_TYPE_EXISTS THEN /* checking for other um type */
380              X_plan_mass_qty := X_plan_mass_qty + X_work_step_tbl(j).line_mass_qty;
381              X_plan_vol_qty := X_plan_vol_qty + X_work_step_tbl(j).line_vol_qty;
382              X_actual_mass_qty := X_actual_mass_qty + X_work_step_tbl(j).actual_mass_qty;
383              X_actual_vol_qty := X_actual_vol_qty + X_work_step_tbl(j).actual_vol_qty;
384           ELSE
385              X_plan_other_qty := X_plan_other_qty + X_work_step_tbl(j).line_other_qty;
386              X_actual_other_qty := X_actual_other_qty + X_work_step_tbl(j).actual_other_qty;
387           END IF;
388         END IF;
389       END IF;
390     END LOOP; /* FOR j IN 1..X_work_step_tbl.COUNT*/
391 
392     -- Shikha Nagar B2304515 Added check to see batch step status to get
393     -- planned or actual qty
394     IF p_called_from_batch = 1 THEN
395       IF NOT G_OTHER_UM_TYPE_EXISTS THEN /* checking for other um type */
396         OPEN Cur_get_step_status(P_step_tbl(i).step_id);
397         FETCH Cur_get_step_status INTO X_cur_step_status;
398         CLOSE Cur_get_step_status ;
399 
400         IF X_cur_step_status > 1 THEN
401           X_cur_mass_qty := X_actual_mass_qty;
402           X_cur_vol_qty  := X_actual_vol_qty;
403         ELSE
404           X_cur_mass_qty := X_plan_mass_qty;
405           X_cur_vol_qty  := X_plan_vol_qty;
406         END IF;
407       ELSE /* when the um typ eis other um typ e*/
408         OPEN Cur_get_step_status(P_step_tbl(i).step_id);
409         FETCH Cur_get_step_status INTO X_cur_step_status;
410         CLOSE Cur_get_step_status ;
411 
412         IF X_cur_step_status > 1 THEN
413           X_cur_other_qty := X_actual_other_qty;
414         ELSE
415           X_cur_other_qty := X_plan_other_qty;
416         END IF;
417       END IF; /* condition for um type */
418     END IF;
419 
420     /* Get the std factor and UOM type for the step qty uom */
421     OPEN Cur_get_std_factor (P_step_tbl(i).step_qty_uom);
422     FETCH Cur_get_std_factor INTO X_new_factor, X_um_type;
423     CLOSE Cur_get_std_factor;
424 
425     IF (X_um_type = G_profile_mass_um_type) THEN
426       X_step_qty := X_cur_mass_qty * (1 / X_new_factor);
427     ELSIF (X_um_type = G_profile_volume_um_type) THEN
428       X_step_qty := X_cur_vol_qty * (1 / X_new_factor);
429     ELSIF (X_um_type = G_profile_other_um_type) THEN
430       X_step_qty := X_cur_other_qty * (1 / X_new_factor);
431     END IF; /* IF X_um_type = G_profile_mass_um_type */
432 
433     IF NOT G_OTHER_UM_TYPE_EXISTS THEN
434       P_step_tbl(i).step_qty      := X_step_qty;
435       P_step_tbl(i).step_mass_qty := X_cur_mass_qty;
436       P_step_tbl(i).step_mass_uom := G_mass_std_um;
437       P_step_tbl(i).step_vol_qty  := X_cur_vol_qty;
438       P_step_tbl(i).step_vol_uom  := G_vol_std_um;
439 
440       X_work_step_qty_tbl(i).step_no := p_step_tbl(i).step_no;
441       X_work_step_qty_tbl(i).plan_mass_qty := X_plan_mass_qty;
442       X_work_step_qty_tbl(i).plan_vol_qty := X_plan_vol_qty;
443       X_work_step_qty_tbl(i).actual_mass_qty := X_actual_mass_qty;
444       X_work_step_qty_tbl(i).actual_vol_qty := X_actual_vol_qty;
445     ELSE
446       P_step_tbl(i).step_qty      := X_step_qty;
447       P_step_tbl(i).step_other_qty := X_cur_other_qty;
448       P_step_tbl(i).step_other_uom := G_other_std_um;
449       X_work_step_qty_tbl(i).step_no := p_step_tbl(i).step_no;
450       X_work_step_qty_tbl(i).plan_other_qty := X_plan_other_qty;
451       X_work_step_qty_tbl(i).actual_other_qty := X_actual_other_qty;
452     END IF;
453 
454   END LOOP; /*FOR i IN 1..X_step_rows*/
455   /* Sort the step lines */
456   sort_step_lines (P_step_tbl, X_return_status);
457 
458   IF X_return_status <> P_return_status THEN
459     RAISE ERROR_SORTING_STEPS;
460   END IF;
461 
462 EXCEPTION
463   WHEN MISSING_PARENT_ID THEN
464      P_return_status := FND_API.G_RET_STS_ERROR;
465      FND_MESSAGE.SET_NAME('GMA', 'SY_KEYMISSING');
466      FND_MSG_PUB.ADD;
467      FND_MSG_PUB.COUNT_AND_GET (P_count => P_msg_count,
468                                 P_data  => P_msg_stack);
469   WHEN LOAD_STEPS_FAILED THEN
470      P_return_status := FND_API.G_RET_STS_ERROR;
471      FND_MSG_PUB.COUNT_AND_GET (P_count => P_msg_count,
472                                 P_data  => P_msg_stack);
473   WHEN STEPS_UOM_NOT_MASS_VOLUME_TYPE THEN
474      P_return_status := FND_API.G_RET_STS_ERROR;
475      FND_MESSAGE.SET_NAME('GMD', 'GMD_STEP_NOT_MASS_VOL_UOM');
476      FND_MSG_PUB.ADD;
477      FND_MSG_PUB.COUNT_AND_GET (P_count => P_msg_count,
478                                 P_data  => P_msg_stack);
479   WHEN GET_STEP_MATERIAL_LINES_FAILED THEN
480      P_return_status := FND_API.G_RET_STS_ERROR;
481      FND_MSG_PUB.COUNT_AND_GET (P_count => P_msg_count,
482                                 P_data  => P_msg_stack);
483   WHEN ERROR_SORTING_STEPS THEN
484      P_return_status := FND_API.G_RET_STS_ERROR;
485      FND_MSG_PUB.COUNT_AND_GET (P_count => P_msg_count,
486                                 P_data  => P_msg_stack);
487   WHEN OTHERS THEN
488      P_return_status := FND_API.G_RET_STS_UNEXP_ERROR;
489      FND_MSG_PUB.COUNT_AND_GET (P_count => P_msg_count,
490                                 P_data  => P_msg_stack);
491 END calc_step_qty;
492 
493 /*======================================================================
494 --  PROCEDURE :
495 --   load_steps
496 --
497 --  DESCRIPTION:
498 --    This PL/SQL procedure  is responsible for loading steps to the
499 --    PL/SQL table.
500 --
501 --  REQUIREMENTS
502 --    p_step_tbl  non null value.
503 --    P_parent_id non null value.
504 --  SYNOPSIS:
505 --    load_steps (426, 0, X_step_tbl, X_routing_id, X_return_status);
506 --
507 --  HISTORY
508 --  25Jul2001  L.R.Jackson   Added step_id to the load.  Changed some
509 --              explicit cursors to Cursor FOR loops.
510 --              Use _B tables where appropriate.
511 --  31oct2001  Raju  Added circular reference exception in the exceptions section
512 --             added message SQLERRM for when OTHERS exception.(bug2077203)
513 --  22jul2005  changed the step_qty_uom to step_qty_um in Cur_get_pm_process_uom cursor.
514 --===================================================================== */
515 
516 PROCEDURE load_steps (P_parent_id         IN NUMBER,
517                       P_called_from_batch IN NUMBER,
518                       P_step_no	          IN NUMBER,
519                       P_step_tbl         OUT NOCOPY step_rec_tbl,
520                       P_routing_id       OUT NOCOPY NUMBER,
521                       P_return_status    OUT NOCOPY VARCHAR2) IS
522   /* Local variables.
523   ==================*/
524 
525   X_return_status   	VARCHAR2(1);
526   X_step_no	        NUMBER;
527   X_step_id	        NUMBER;
528   X_num_steps	    	NUMBER := 0;
529   X_process_qty_um	mtl_units_of_measure.uom_code%TYPE;
530   /* Cursor Definitions.
531   =====================*/
532   CURSOR Cur_get_routing IS
533     SELECT routing_id
534     FROM   gmd_recipes_b
535     WHERE  recipe_id = P_parent_id;
536 
537   /* Gets all step no's that are dependent */
538   CURSOR Cur_get_steps IS
539     SELECT dep_routingstep_no, max(level)
540     FROM   fm_rout_dep
541     START WITH ((routing_id = P_routing_id) AND
542                 ((p_step_no IS NULL) OR (routingstep_no = p_step_no)))
543     CONNECT BY routing_id = prior routing_id
544     AND    routingstep_no = prior dep_routingstep_no
545     GROUP BY dep_routingstep_no
546     ORDER BY max(level) desc;
547 
548   /* Gets all step no's that are independent */
549   CURSOR cur_get_other_steps IS
550     SELECT routingstep_no
551     FROM   fm_rout_dtl
552     WHERE  routing_id = P_routing_id
553     AND    routingstep_no NOT IN
554            (SELECT dep_routingstep_no
555             FROM   fm_rout_dep
556             WHERE  routing_id = P_routing_id);
557 
558   CURSOR Cur_get_process_uom (V_routingstep_no NUMBER) IS
559     SELECT o.process_qty_uom, d.routingstep_id
560     FROM   fm_rout_dtl d,
561            gmd_operations_b o
562     WHERE  d.oprn_id = o.oprn_id
563     AND    d.routing_id = P_routing_id
564     AND    d.routingstep_no = V_routingstep_no;
565 
566   CURSOR Cur_get_pm_routing IS
567     SELECT routing_id
568     FROM   gme_batch_header
569     WHERE  batch_id = P_parent_id;
570 
571   CURSOR Cur_get_pm_steps (V_step_id NUMBER) IS
572     SELECT d.dep_step_id, max(level)
573     FROM   gme_batch_step_dependencies d
574     WHERE  d.batch_id = P_parent_id
575     START WITH ((d.batch_id = P_parent_id) AND
576                 ((v_step_id IS NULL) OR (batchstep_id = v_step_id)))
577     CONNECT BY d.batch_id = prior d.batch_id
578     AND    d.batchstep_id = prior d.dep_step_id
579     GROUP BY d.dep_step_id
580     ORDER BY max(level) desc;
581 
582   CURSOR Cur_get_pm_step_id (V_step_no NUMBER) IS
583     SELECT batchstep_id
584     FROM   gme_batch_steps
585     WHERE  batch_id = P_parent_id
586     AND    batchstep_no = V_step_no;
587 
588   CURSOR Cur_get_pm_step_no (V_step_id NUMBER) IS
589     SELECT batchstep_no
590     FROM   gme_batch_steps
591     WHERE  batch_id = P_parent_id
592     AND    batchstep_id = V_step_id;
593 
594   CURSOR Cur_get_pm_other_steps IS
595     SELECT batchstep_id, batchstep_no
596     FROM   gme_batch_steps s
597     WHERE  s.batch_id = P_parent_id
598     AND    s.batchstep_id NOT IN
599            (SELECT dep_step_id
600             FROM   gme_batch_step_dependencies
601             WHERE  batch_id = P_parent_id);
602 
603   CURSOR Cur_get_pm_process_uom (V_batchstep_no NUMBER) IS
604     SELECT STEP_QTY_UM
605     FROM   gme_batch_steps
606     WHERE  batch_id = P_parent_id
607     AND    batchstep_no = V_batchstep_no;
608 
609   /* Cursor records.
610   =====================*/
611   -- Cursor FOR loop used instead
612 
613   /* Exceptions.
614   =====================*/
615    --For bug 2077203
616   circular_reference EXCEPTION;
617   PRAGMA EXCEPTION_INIT(circular_reference, -01436);
618 
619   NO_ROUTING_ASSOCIATED		EXCEPTION;
620   ROUTING_DETAILS_MISSING	EXCEPTION;
621 BEGIN
622   P_return_status := FND_API.G_RET_STS_SUCCESS;
623   /* If called from GMD */
624   IF P_called_from_batch = 0 THEN
625     /* Fetch the routing for the recipe passed in from GMD */
626     OPEN Cur_get_routing;
627     FETCH Cur_get_routing INTO P_routing_id;
628     IF Cur_get_routing%NOTFOUND THEN
629       RAISE NO_ROUTING_ASSOCIATED;
630     END IF;
631     CLOSE Cur_get_routing;
632 
633     /* Get the routing steps from the dependency table */
634     /* Add the steps to the pl/sql table              */
635     FOR X_step_rec IN Cur_get_steps LOOP
636       X_num_steps := X_num_steps + 1;
637 
638       /* Get the step UOM */
639       OPEN Cur_get_process_uom (X_step_rec.dep_routingstep_no);
640       FETCH Cur_get_process_uom INTO X_process_qty_um, X_step_id;
641       CLOSE Cur_get_process_uom;
642 
643       P_step_tbl(X_num_steps).step_id       := X_step_id;
644       P_step_tbl(X_num_steps).step_no       := X_step_rec.dep_routingstep_no;
645       P_step_tbl(X_num_steps).step_qty_uom  := X_process_qty_um;
646       P_step_tbl(X_num_steps).step_qty      := 0;
647       P_step_tbl(X_num_steps).step_mass_qty := 0;
648       P_step_tbl(X_num_steps).step_vol_qty  := 0;
649       P_step_tbl(X_num_steps).step_other_qty  := 0;
650     END LOOP; /* Cur_get_steps%FOUND */
651 
652     /* No dependencies defined get the steps from the routing table */
653     /* or get the final steps for the dependent steps               */
654     /* If requested for a step then directly associate the table with the step */
655     IF P_step_no IS NOT NULL THEN
656       /* Get the step UOM */
657       OPEN Cur_get_process_uom (P_step_no);
658       FETCH Cur_get_process_uom INTO X_process_qty_um, X_step_id;
659       CLOSE Cur_get_process_uom;
660       X_num_steps := X_num_steps + 1;
661       P_step_tbl(X_num_steps).step_id       := X_step_id;
662       P_step_tbl(X_num_steps).step_no       := P_step_no;
663       P_step_tbl(X_num_steps).step_qty_uom  := X_process_qty_um;
664       P_step_tbl(X_num_steps).step_qty      := 0;
665       P_step_tbl(X_num_steps).step_mass_qty := 0;
666       P_step_tbl(X_num_steps).step_vol_qty  := 0;
667       P_step_tbl(X_num_steps).step_other_qty  := 0;
668     ELSE
669       -- Do not change this open/fetch/close cursor to Cursor FOR because
670       -- an exception needs to be raised if no rows are found.
671       -- We could get the id from the cur_get_other_steps cursor, but
672       -- the process uom cursor is already returning it, so not necessary
673       -- to select the value twice.
674       OPEN cur_get_other_steps;
675       FETCH cur_get_other_steps INTO X_step_no;
676       IF cur_get_other_steps%FOUND THEN
677         WHILE cur_get_other_steps%FOUND LOOP
678           X_num_steps := X_num_steps + 1;
679 
680           /* Get the step UOM */
681           OPEN Cur_get_process_uom (X_step_no);
682           FETCH Cur_get_process_uom INTO X_process_qty_um, X_step_id;
683           CLOSE Cur_get_process_uom;
684 
685           P_step_tbl(X_num_steps).step_id       := X_step_id;
686           P_step_tbl(X_num_steps).step_no       := X_step_no;
687           P_step_tbl(X_num_steps).step_qty_uom  := X_process_qty_um;
688           P_step_tbl(X_num_steps).step_qty      := 0;
689           P_step_tbl(X_num_steps).step_mass_qty := 0;
690           P_step_tbl(X_num_steps).step_vol_qty  := 0;
691           P_step_tbl(X_num_steps).step_other_qty  := 0;
692           FETCH cur_get_other_steps INTO X_step_no;
693         END LOOP; /*WHILE cur_get_other_steps%FOUND*/
694       ELSE
695         RAISE ROUTING_DETAILS_MISSING;
696       END IF; /*IF cur_get_other_steps%FOUND*/
697       CLOSE cur_get_other_steps;
698     END IF; /* IF P_step_no IS NOT NULL */
699 
700   -- *****************************  BATCH  *************************
701   ELSE
702     /* Fetch the routing for the BATCH passed in */
703     OPEN Cur_get_pm_routing;
704     FETCH Cur_get_pm_routing INTO P_routing_id;
705     IF Cur_get_pm_routing%NOTFOUND THEN
706       RAISE NO_ROUTING_ASSOCIATED;
707     END IF;
708     CLOSE Cur_get_pm_routing;
709 
710     /* Fetch the batchstep id for the step no passed in */
711     IF P_step_no IS NOT NULL THEN
712       OPEN Cur_get_pm_step_id (P_step_no);
713       FETCH Cur_get_pm_step_id INTO X_step_id;
714       CLOSE Cur_get_pm_step_id;
715     END IF;
716 
717     /* Get the routing steps from the PM dependency table */
718     /* Add the steps to the pl/sql table                  */
719     FOR X_pm_step_rec IN Cur_get_pm_steps (X_step_id) LOOP
720       X_num_steps := X_num_steps + 1;
721 
722       /* Get the step no */
723       OPEN Cur_get_pm_step_no (X_pm_step_rec.dep_step_id);
724       FETCH Cur_get_pm_step_no INTO X_step_no;
725       CLOSE Cur_get_pm_step_no;
726 
727       /* Get the step UOM */
728       OPEN Cur_get_pm_process_uom (X_step_no);
729       FETCH Cur_get_pm_process_uom INTO X_process_qty_um;
730       CLOSE Cur_get_pm_process_uom;
731 
732       P_step_tbl(X_num_steps).step_id := X_pm_step_rec.dep_step_id;
733       P_step_tbl(X_num_steps).step_no := X_step_no;
734       P_step_tbl(X_num_steps).step_qty_uom := X_process_qty_um;
735       P_step_tbl(X_num_steps).step_qty := 0;
736       P_step_tbl(X_num_steps).step_mass_qty := 0;
737       P_step_tbl(X_num_steps).step_vol_qty := 0;
738       P_step_tbl(X_num_steps).step_other_qty  := 0;
739     END LOOP; /* WHILE Cur_get_steps%FOUND */
740 
741     /* No dependencies defined get the steps from the routing table */
742     /* or get the final steps for the dependent steps               */
743     /* If requested for a step then directly associate the table with the step */
744     IF P_step_no IS NOT NULL THEN
745       /* Get the step UOM */
746       OPEN Cur_get_pm_process_uom (P_step_no);
747       FETCH Cur_get_pm_process_uom INTO X_process_qty_um;
748       CLOSE Cur_get_pm_process_uom;
749       X_num_steps := X_num_steps + 1;
750       P_step_tbl(X_num_steps).step_id := X_step_id;
751       P_step_tbl(X_num_steps).step_no := P_step_no;
752       P_step_tbl(X_num_steps).step_qty_uom := X_process_qty_um;
753       P_step_tbl(X_num_steps).step_qty := 0;
754       P_step_tbl(X_num_steps).step_mass_qty := 0;
755       P_step_tbl(X_num_steps).step_vol_qty := 0;
756       P_step_tbl(X_num_steps).step_other_qty  := 0;
757     ELSE
758       OPEN Cur_get_pm_other_steps;
759       FETCH Cur_get_pm_other_steps INTO X_step_id, X_step_no;
760       IF Cur_get_pm_other_steps%FOUND THEN
761         WHILE Cur_get_pm_other_steps%FOUND LOOP
762           X_num_steps := X_num_steps + 1;
763 
764           /* Get the step UOM */
765           OPEN Cur_get_pm_process_uom (X_step_no);
766           FETCH Cur_get_pm_process_uom INTO X_process_qty_um;
767           CLOSE Cur_get_pm_process_uom;
768 
769           P_step_tbl(X_num_steps).step_id := X_step_id;
770           P_step_tbl(X_num_steps).step_no := X_step_no;
771           P_step_tbl(X_num_steps).step_qty_uom := X_process_qty_um;
772           P_step_tbl(X_num_steps).step_qty := 0;
773           P_step_tbl(X_num_steps).step_mass_qty := 0;
774           P_step_tbl(X_num_steps).step_vol_qty := 0;
775           P_step_tbl(X_num_steps).step_other_qty  := 0;
776           FETCH Cur_get_pm_other_steps INTO X_step_id, X_step_no;
777         END LOOP; /*WHILE Cur_get_pm_other_steps%FOUND*/
778       ELSE
779         RAISE ROUTING_DETAILS_MISSING;
780       END IF; /*IF Cur_get_pm_other_steps%FOUND*/
781       CLOSE Cur_get_pm_other_steps;
782     END IF; /* IF P_step_no IS NOT NULL */
783   END IF; /* IF P_called_from_batch = 0 */
784 EXCEPTION
785   WHEN NO_ROUTING_ASSOCIATED THEN
786     P_return_status := FND_API.G_RET_STS_ERROR;
787     FND_MESSAGE.SET_NAME('GMD', 'GMD_AUTO_STEP_QTY_NEEDS_ROUT');
788     FND_MSG_PUB.ADD;
789   WHEN ROUTING_DETAILS_MISSING THEN
790     P_return_status := FND_API.G_RET_STS_ERROR;
791     FND_MESSAGE.SET_NAME('GMD', 'FMROUTINGSTEPNOTFOUND');
792     FND_MSG_PUB.ADD;
793     --Following messages added for bug 2077203
794   WHEN CIRCULAR_REFERENCE THEN
795     P_return_status := FND_API.G_RET_STS_ERROR;
796     FND_MESSAGE.SET_NAME('GMD', 'GMD_CIRCULAR_DEPEN_DETECT');
797     FND_MSG_PUB.ADD;
798   WHEN OTHERS THEN
799      P_return_status := FND_API.G_RET_STS_UNEXP_ERROR;
800      FND_MESSAGE.SET_NAME('GMD', 'GMD_UNEXPECTED_ERROR');
801      FND_MESSAGE.SET_TOKEN('ERROR', SQLERRM);
802      FND_MSG_PUB.ADD;
803 END load_steps;
804 
805 /*======================================================================
806 --  FUNCTION :
807 --    steps_uom_mass_volume
808 --
809 --  DESCRIPTION:
810 --    This PL/SQL procedure  is responsible for ensuring that every
811 --    step is defined in MASS or VOLUME.
812 --
813 --  REQUIREMENTS
814 --    p_step_tbl  non null value.
815 --  SYNOPSIS:
816 --    X_ret := step_uom_mass_volume (X_step_tbl);
817 --
818 --
819 --===================================================================== */
820 
821 FUNCTION step_uom_mass_volume (P_step_tbl IN step_rec_tbl)
822          RETURN BOOLEAN IS
823   /* Local variables.
824   ==================*/
825   X_um_type	        mtl_units_of_measure.uom_class%TYPE;
826   l_previous_um_type	mtl_units_of_measure.uom_class%TYPE;
827   X_num_rows	        NUMBER(10);
828 
829   l_other_type_cnt      NUMBER := 1;
830 
831   /* Cursor Definitions.
832   =====================*/
833   CURSOR Cur_get_um_type (V_uom_code VARCHAR2) IS
834     SELECT uom_class
835     FROM   mtl_units_of_measure
836     WHERE  uom_code = V_uom_code;
837 
838   CURSOR Cur_get_std_um (V_uom_class VARCHAR2) IS
839     SELECT uom_code
840     FROM   mtl_units_of_measure
841     WHERE  uom_class = V_uom_class;
842 BEGIN
843   X_num_rows := P_step_tbl.COUNT;
844   FOR i IN 1..X_num_rows LOOP
845 
846     OPEN Cur_get_um_type(P_step_tbl(i).step_qty_uom);
847     FETCH Cur_get_um_type INTO X_um_type;
848     CLOSE Cur_get_um_type;
849 
850     /* Check if the um type fr the current and new step are the same */
851     /* Bug#3431385 - Thomas Daniel */
852     /* Changed the following code to consider the Mass and Volume UOM profiles */
853     /* being NULL */
854     IF (G_profile_mass_um_type IS NULL OR X_um_type <> G_profile_mass_um_type) AND
855        (G_profile_volume_um_type IS NULL OR X_um_type <> G_profile_volume_um_type) THEN
856       IF (X_um_type = l_previous_um_type) THEN
857         l_other_type_cnt := l_other_type_cnt + 1;
858       END IF;
859       l_previous_um_type := X_um_type;
860     END IF;
861 
862   END LOOP;
863 
864   /* If all steps are of the same um type (and not MASS or VOLUME) then it is ok */
865   IF (l_previous_um_type IS NOT NULL) THEN -- there is a other um type
866     IF (l_other_type_cnt = X_num_rows) THEN -- if all step um type are of the same type
867       /* set this as a global profile um type */
868       G_PROFILE_OTHER_UM_TYPE := l_previous_um_type;
869       /* Get the std um for the other um type */
870       OPEN Cur_get_std_um (G_profile_other_um_type);
871       FETCH Cur_get_std_um INTO G_OTHER_STD_UM;
872       CLOSE Cur_get_std_um;
873       /* set this Global variable - it would be used in other procs */
874       G_OTHER_UM_TYPE_EXISTS := TRUE;
875     ELSE -- mixed um type is not allowed
876       -- i.e if there is a other type - all steps should of this um type
877       RETURN (FALSE);
878     END IF;
879   ELSE -- its either mass or volume type um
880     /* Populate the global mass and volume std um variables. */
881     OPEN Cur_get_std_um (G_profile_mass_um_type);
882     FETCH Cur_get_std_um INTO G_mass_std_um;
883     CLOSE Cur_get_std_um;
884 
885     OPEN Cur_get_std_um (G_profile_volume_um_type);
886     FETCH Cur_get_std_um INTO G_vol_std_um;
887     CLOSE Cur_get_std_um;
888   END IF;
889 
890   RETURN (TRUE);
891 END step_uom_mass_volume;
892 
893 /*======================================================================
894 --  PROCEDURE :
895 --    get_step_material_lines
896 --
897 --  DESCRIPTION:
898 --    This PL/SQL procedure  is responsible for fetching the material
899 --    lines associated with the steps.
900 --
901 --  REQUIREMENTS
902 --    p_work_step_tbl  non null value.
903 --  SYNOPSIS:
904 --    get_step_material_lines (426, 100, 0, X_step_tbl, X_work_step_tbl,
905 --                             X_return_status);
906 --
907 --  This procedure calls GMICUOM.uom_conversion
908 --
909 --  HISTORY
910 --  25Jul2001  L.R.Jackson  Changed cursor to use id instead of step_no.
911 --                          Use ic_item_mst_b instead of ic_item_mst
912 --  08FEB2002  Shikha Nagar Changed Cur_get_batch_lines to take scrap_factor
913                             into account.
914 --  08Mar2002  Shrikant Nene Changed the scrap factor calculation
915 --  05Apr2002  Shikha Nagar B2304515 Changed Cur_get_batch_lines to fetch
916                             both planned and actual qty.
917                             Also populating actual_mass_qty and actual_vol_qty
918                             of x_work_step_tbl.
919 --===================================================================== */
920 
921  PROCEDURE get_step_material_lines (P_parent_id		IN NUMBER,
922                                    P_routing_id		IN NUMBER,
923                                    P_called_from_batch	IN NUMBER,
924                                    P_step_tbl		IN step_rec_tbl,
925                                    P_work_step_tbl 	IN OUT NOCOPY work_step_rec_tbl,
926                                    P_return_status 	OUT NOCOPY VARCHAR2,
927                                    p_ignore_mass_conv   IN BOOLEAN DEFAULT FALSE,
928                                    p_ignore_vol_conv    IN BOOLEAN DEFAULT FALSE,
929                                    p_process_loss	IN NUMBER DEFAULT 0) IS
930   /* Local variables.
931   ==================*/
932   X_num_rows	NUMBER;
933   X_cur_rec	NUMBER DEFAULT 0;
934   X_line_qty	NUMBER;
935   X_temp_qty	NUMBER;
936   X_item_id	NUMBER;
937   X_from_uom	mtl_units_of_measure.uom_code%TYPE;
938   X_to_uom      mtl_units_of_measure.uom_code%TYPE;
939   X_item_no	mtl_system_items_kfv.concatenated_segments%TYPE;
940 
941   /* Cursor Definitions.
942   =====================*/
943   CURSOR Cur_get_material_lines (V_step_id NUMBER) IS
944     -- NPD Conv. Use inventory_iem_id and detail_uom instead of item_id and item_um
945     SELECT s.formulaline_id, d.line_type, d.qty, d.detail_uom, d.inventory_item_id, d.scale_type
946     FROM   gmd_recipe_step_materials s,
947            fm_matl_dtl d
948     WHERE  s.recipe_id = P_parent_id
949     AND    s.formulaline_id = d.formulaline_id
950     AND    s.routingstep_id = V_step_id
951     AND    NVL (d.contribute_step_qty_ind, 'Y') = 'Y'
952     ORDER BY d.line_type;
953 
954   CURSOR Cur_get_batch_lines (V_step_id NUMBER) IS
955     SELECT b.material_detail_id batchline_id, d.line_type,
956            d.plan_qty,
957            (d.actual_qty/(1+scrap_factor)) actual_qty,
958            d.dtl_um, d.inventory_item_id
959     FROM   gme_batch_step_items b,
960            gme_material_details d,
961            gme_batch_steps r
962     WHERE  b.batch_id = P_parent_id
963     AND    b.batchstep_id = r.batchstep_id
964     AND    b.material_detail_id = d.material_detail_id
965     AND    b.batchstep_id = V_step_id
966     AND    NVL (d.contribute_step_qty_ind, 'Y') = 'Y'
967     ORDER BY d.line_type;
968 
969   -- NPD Conv.
970   CURSOR Cur_get_item IS
971     SELECT concatenated_segments
972     FROM   mtl_system_items_kfv
973     WHERE  inventory_item_id = X_item_id;
974 
975   /* Cursor records.
976   =====================*/
977   -- none.  Cursor FOR loops used.
978 
979   /* Exceptions.
980   =====================*/
981   UOM_CONVERSION_ERROR		EXCEPTION;
982   NO_MATERIAL_STEP_ASSOC	EXCEPTION;
983 
984 BEGIN
985   P_work_step_tbl.DELETE;
986   P_return_status := FND_API.G_RET_STS_SUCCESS;
987   X_num_rows := P_step_tbl.COUNT;
988   FOR i IN 1..X_num_rows LOOP
989 
990     /* If called from GMD */
991     IF P_called_from_batch = 0 THEN
992       FOR X_material_rec IN Cur_get_material_lines (P_step_tbl(i).step_id) LOOP
993         X_cur_rec := X_cur_rec + 1;
994         P_work_step_tbl(X_cur_rec).step_id := P_step_tbl(i).step_id;
995         P_work_step_tbl(X_cur_rec).step_no := P_step_tbl(i).step_no;
996         P_work_step_tbl(X_cur_rec).line_id := X_material_rec.formulaline_id;
997         P_work_step_tbl(X_cur_rec).line_type := X_material_rec.line_type;
998 
999         /* If all steps of OTHER um type then you dont have to bother
1000            about converting line qtys to MASS and VOLUME type um */
1001         IF NOT (G_OTHER_UM_TYPE_EXISTS) THEN
1002           X_temp_qty := INV_CONVERT.inv_um_convert(item_id         => X_material_rec.inventory_item_id
1003                                                    ,precision      => 5
1004                                                    ,from_quantity  => X_material_rec.qty
1005                                                    ,from_unit      => X_material_rec.detail_uom
1006                                                    ,to_unit        => G_mass_std_um
1007                                                    ,from_name      => NULL
1008                                                    ,to_name	   => NULL);
1009 
1010           IF X_temp_qty < 0 THEN
1011             X_item_id := X_material_rec.inventory_item_id;
1012             X_from_uom := X_material_rec.detail_uom;
1013             X_to_uom := G_mass_std_um;
1014             IF (p_ignore_mass_conv = FALSE) THEN
1015               RAISE UOM_CONVERSION_ERROR;
1016             ELSE
1017               P_work_step_tbl(X_cur_rec).line_mass_qty := 0;
1018             END IF;
1019           ELSE
1020               P_work_step_tbl(X_cur_rec).line_mass_qty := X_temp_qty;
1021               /* Bug 1683702 - Thomas Daniel */
1022               /* Apply the process loss to the qty for the calculation of the step qty */
1023               IF X_material_rec.line_type = -1 AND
1024                  X_material_rec.scale_type = 1 AND
1025                  p_process_loss > 0 THEN
1026                 P_work_step_tbl(X_cur_rec).line_mass_qty := P_work_step_tbl(X_cur_rec).line_mass_qty *
1027                                                             100 / (100 - p_process_loss);
1028               END IF;
1029           END IF;
1030 
1031           /*Bug#3599182 - Thomas Daniel */
1032           /*Commented the following IF as we need to proceed with the volume conversion though the mass */
1033           /*conversion has failed as there is a possibility of all the routing steps and the formula lines */
1034           /*belong to the same UOM type */
1035           -- IF (X_temp_qty > 0) THEN
1036             X_temp_qty := INV_CONVERT.inv_um_convert(item_id       => X_material_rec.inventory_item_id
1037                                                    ,precision      => 5
1038                                                    ,from_quantity  => X_material_rec.qty
1039                                                    ,from_unit      => X_material_rec.detail_uom
1040                                                    ,to_unit        => G_vol_std_um
1041                                                    ,from_name      => NULL
1042                                                    ,to_name	   => NULL);
1043             IF X_temp_qty < 0 THEN
1044               X_item_id := X_material_rec.inventory_item_id;
1045               X_from_uom := X_material_rec.detail_uom;
1046               X_to_uom := G_vol_std_um;
1047               IF (p_ignore_vol_conv = FALSE) THEN
1048                 RAISE UOM_CONVERSION_ERROR;
1049               ELSE
1050                 P_work_step_tbl(X_cur_rec).line_vol_qty := 0;
1051               END IF;
1052             ELSE
1053               P_work_step_tbl(X_cur_rec).line_vol_qty := X_temp_qty;
1054               /* Bug 1683702 - Thomas Daniel */
1055               /* Apply the process loss to the qty for the calculation of the step qty */
1056               IF X_material_rec.line_type = -1 AND
1057                  X_material_rec.scale_type = 1 AND
1058                  p_process_loss > 0 THEN
1059                 P_work_step_tbl(X_cur_rec).line_vol_qty := P_work_step_tbl(X_cur_rec).line_vol_qty *
1060                                                             100 / (100 - p_process_loss);
1061               END IF;
1062             END IF;
1063           /*Bug#3599182 - Thomas Daniel */
1064           /*Commented the END IF following IF */
1065           -- END IF;
1066         ELSE  /* When only other um type exists */
1067           /* Added by Shyam - To capture the line qty in the other um types std um */
1068           X_temp_qty := INV_CONVERT.inv_um_convert(item_id       => X_material_rec.inventory_item_id
1069                                                    ,precision      => 5
1070                                                    ,from_quantity  => X_material_rec.qty
1071                                                    ,from_unit      => X_material_rec.detail_uom
1072                                                    ,to_unit        => G_other_std_um
1073                                                    ,from_name      => NULL
1074                                                    ,to_name	   => NULL);
1075           IF X_temp_qty < 0 THEN
1076             X_item_id := X_material_rec.inventory_item_id;
1077             X_from_uom := X_material_rec.detail_uom;
1078             X_to_uom := G_other_std_um;
1079             IF (p_ignore_mass_conv = FALSE) THEN
1080               RAISE UOM_CONVERSION_ERROR;
1081             ELSE
1082               P_work_step_tbl(X_cur_rec).line_other_qty := 0;
1083             END IF;
1084           ELSE
1085             P_work_step_tbl(X_cur_rec).line_other_qty := X_temp_qty;
1086             /* Bug 1683702 - Thomas Daniel */
1087             /* Apply the process loss to the qty for the calculation of the step qty */
1088             IF X_material_rec.line_type = -1 AND
1089                X_material_rec.scale_type = 1 AND
1090                p_process_loss > 0 THEN
1091               P_work_step_tbl(X_cur_rec).line_other_qty := P_work_step_tbl(X_cur_rec).line_other_qty *
1092                                                          100 / (100 - p_process_loss);
1093             END IF;
1094           END IF;
1095         END IF; /* Condition that tests if other um type exists */
1096 
1097       END LOOP; /*WHILE Cur_get_material_lines%FOUND*/
1098 
1099     ELSE /*IF P_called_from_batch = 0.  This section used if called from batch */
1100       FOR X_batch_rec IN Cur_get_batch_lines (P_step_tbl(i).step_id) LOOP
1101         X_cur_rec := X_cur_rec + 1;
1102         P_work_step_tbl(X_cur_rec).step_id := P_step_tbl(i).step_id;
1103         P_work_step_tbl(X_cur_rec).step_no := P_step_tbl(i).step_no;
1104         P_work_step_tbl(X_cur_rec).line_id := X_batch_rec.batchline_id;
1105         P_work_step_tbl(X_cur_rec).line_type := X_batch_rec.line_type;
1106 
1107         /* If all steps of OTHER um type then you dont have to bother
1108            about converting line qtys to MASS and VOLUME type um */
1109         IF NOT (G_OTHER_UM_TYPE_EXISTS) THEN
1110           X_temp_qty := INV_CONVERT.inv_um_convert(item_id         => X_batch_rec.inventory_item_id
1111                                                    ,precision      => 5
1112                                                    ,from_quantity  => X_batch_rec.plan_qty
1113                                                    ,from_unit      => X_batch_rec.dtl_um
1114                                                    ,to_unit        => G_mass_std_um
1115                                                    ,from_name      => NULL
1116                                                    ,to_name	   => NULL);
1117 
1118           IF X_temp_qty < 0 THEN
1119             X_item_id := X_batch_rec.inventory_item_id;
1120             X_from_uom := X_batch_rec.dtl_um;
1121             X_to_uom := G_mass_std_um;
1122             IF(p_ignore_mass_conv = FALSE) THEN
1123               RAISE UOM_CONVERSION_ERROR;
1124             ELSE
1125               P_work_step_tbl(X_cur_rec).line_mass_qty := 0;
1126             END IF;
1127           ELSE
1128             P_work_step_tbl(X_cur_rec).line_mass_qty := X_temp_qty;
1129           END IF;
1130           -- Shikha Nagar B2304515
1131           X_temp_qty := INV_CONVERT.inv_um_convert(item_id         => X_batch_rec.inventory_item_id
1132                                                    ,precision      => 5
1133                                                    ,from_quantity  => X_batch_rec.actual_qty
1134                                                    ,from_unit      => X_batch_rec.dtl_um
1135                                                    ,to_unit        => G_mass_std_um
1136                                                    ,from_name      => NULL
1137                                                    ,to_name	   => NULL);
1138           IF X_temp_qty < 0 THEN
1139             X_item_id := X_batch_rec.inventory_item_id;
1140             X_from_uom := X_batch_rec.dtl_um;
1141             X_to_uom := G_mass_std_um;
1142             IF(p_ignore_mass_conv = FALSE) THEN
1143               RAISE UOM_CONVERSION_ERROR;
1144             ELSE
1145               P_work_step_tbl(X_cur_rec).actual_mass_qty := 0;
1146             END IF;
1147           ELSE
1148             P_work_step_tbl(X_cur_rec).actual_mass_qty := X_temp_qty;
1149           END IF;
1150 
1151           X_temp_qty := INV_CONVERT.inv_um_convert(item_id         => X_batch_rec.inventory_item_id
1152                                                    ,precision      => 5
1153                                                    ,from_quantity  => X_batch_rec.plan_qty
1154                                                    ,from_unit      => X_batch_rec.dtl_um
1155                                                    ,to_unit        => G_vol_std_um
1156                                                    ,from_name      => NULL
1157                                                    ,to_name	   => NULL);
1158           IF X_temp_qty < 0 THEN
1159             X_item_id := X_batch_rec.inventory_item_id;
1160             X_from_uom := X_batch_rec.dtl_um;
1161             X_to_uom := G_vol_std_um;
1162             IF (p_ignore_vol_conv = FALSE) THEN
1163               RAISE UOM_CONVERSION_ERROR;
1164             ELSE
1165               P_work_step_tbl(X_cur_rec).line_vol_qty := 0;
1166             END IF;
1167           ELSE
1168               P_work_step_tbl(X_cur_rec).line_vol_qty := X_temp_qty;
1169           END IF;
1170 
1171           -- Shikha Nagar B2304515
1172           X_temp_qty := INV_CONVERT.inv_um_convert(item_id         => X_batch_rec.inventory_item_id
1173                                                    ,precision      => 5
1174                                                    ,from_quantity  => X_batch_rec.actual_qty
1175                                                    ,from_unit      => X_batch_rec.dtl_um
1176                                                    ,to_unit        => G_vol_std_um
1177                                                    ,from_name      => NULL
1178                                                    ,to_name	   => NULL);
1179           IF X_temp_qty < 0 THEN
1180             X_item_id := X_batch_rec.inventory_item_id;
1181             X_from_uom := X_batch_rec.dtl_um;
1182             X_to_uom := G_vol_std_um;
1183             IF (p_ignore_vol_conv = FALSE) THEN
1184               RAISE UOM_CONVERSION_ERROR;
1185             ELSE
1186               P_work_step_tbl(X_cur_rec).actual_vol_qty := 0;
1187             END IF;
1188           ELSE
1189              P_work_step_tbl(X_cur_rec).actual_vol_qty := X_temp_qty;
1190           END IF;
1191 
1192          ELSE /* Condition that checks for other type um */
1193            X_temp_qty := INV_CONVERT.inv_um_convert(item_id         => X_batch_rec.inventory_item_id
1194                                                    ,precision      => 5
1195                                                    ,from_quantity  => X_batch_rec.plan_qty
1196                                                    ,from_unit      => X_batch_rec.dtl_um
1197                                                    ,to_unit        => G_other_std_um
1198                                                    ,from_name      => NULL
1199                                                    ,to_name	   => NULL);
1200 
1201           IF X_temp_qty < 0 THEN
1202             X_item_id := X_batch_rec.inventory_item_id;
1203             X_from_uom := X_batch_rec.dtl_um;
1204             X_to_uom := G_other_std_um;
1205             IF(p_ignore_mass_conv = FALSE) THEN
1206               RAISE UOM_CONVERSION_ERROR;
1207             ELSE
1208               P_work_step_tbl(X_cur_rec).line_other_qty := 0;
1209             END IF;
1210           ELSE
1211             P_work_step_tbl(X_cur_rec).line_other_qty := X_temp_qty;
1212           END IF;
1213           -- Shikha Nagar B2304515
1214           X_temp_qty := INV_CONVERT.inv_um_convert(item_id         => X_batch_rec.inventory_item_id
1215                                                    ,precision      => 5
1216                                                    ,from_quantity  => X_batch_rec.actual_qty
1217                                                    ,from_unit      => X_batch_rec.dtl_um
1218                                                    ,to_unit        => G_other_std_um
1219                                                    ,from_name      => NULL
1220                                                    ,to_name	   => NULL);
1221 
1222           IF X_temp_qty < 0 THEN
1223             X_item_id := X_batch_rec.inventory_item_id;
1224             X_from_uom := X_batch_rec.dtl_um;
1225             X_to_uom := G_other_std_um;
1226             IF(p_ignore_mass_conv = FALSE) THEN
1227               RAISE UOM_CONVERSION_ERROR;
1228             ELSE
1229               P_work_step_tbl(X_cur_rec).actual_other_qty := 0;
1230             END IF;
1231           ELSE
1232             P_work_step_tbl(X_cur_rec).actual_other_qty := X_temp_qty;
1233           END IF;
1234         END IF; /* condition for other type um */
1235       END LOOP; /*WHILE Cur_get_batch_lines%FOUND*/
1236 
1237     END IF; /*IF P_called_from_batch = 0*/
1238   END LOOP; /* FOR i IN 1..X_num_rows */
1239   IF X_cur_rec = 0 THEN
1240     RAISE NO_MATERIAL_STEP_ASSOC;
1241   END IF;
1242 
1243 EXCEPTION
1244   WHEN UOM_CONVERSION_ERROR THEN
1245     P_return_status := FND_API.G_RET_STS_ERROR;
1246     OPEN Cur_get_item;
1247     FETCH Cur_get_item INTO X_item_no;
1248     CLOSE Cur_get_item;
1249     FND_MESSAGE.SET_NAME('GMI', 'IC_API_UOM_CONVERSION_ERROR');
1250     FND_MESSAGE.SET_TOKEN('ITEM_NO', X_item_no);
1251     FND_MESSAGE.SET_TOKEN('FROM_UOM', X_from_uom);
1252     FND_MESSAGE.SET_TOKEN('TO_UOM', X_to_uom);
1253     FND_MSG_PUB.ADD;
1254   WHEN NO_MATERIAL_STEP_ASSOC THEN
1255     P_return_status := FND_API.G_RET_STS_ERROR;
1256     FND_MESSAGE.SET_NAME('GMD', 'GMD_MISSING_MATL_STEP_ASSOC');
1257     FND_MSG_PUB.ADD;
1258   WHEN OTHERS THEN
1259     P_return_status := FND_API.G_RET_STS_UNEXP_ERROR;
1260     FND_MSG_PUB.ADD;
1261 END get_step_material_lines;
1262 
1263 
1264 /* Added by Shyam for GMF */
1265 /*======================================================================
1266 --  PROCEDURE : Overloaded
1267 --    get_step_material_lines
1268 --
1269 --  DESCRIPTION:
1270 --    This PL/SQL overloaded procedure is responsible for fetching the sclaed material
1271 --    lines associated with the steps.
1272 --
1273 --  REQUIREMENTS
1274 --    p_work_step_tbl  non null value.
1275 --    p_scale_factor   not null value.
1276 --  SYNOPSIS:
1277 --    get_step_material_lines (426, 100, 0, X_step_tbl,P_scale_factor, X_work_step_tbl,
1278 --                             X_return_status);
1279 --
1280 --  This procedure calls GMICUOM.uom_conversion
1281 --
1282 --  HISTORY
1283 --  Shyam   05/10/2002  Initial Implementation
1284 ======================================================================== */
1285 
1286 PROCEDURE get_step_material_lines (P_parent_id		IN NUMBER,
1287                                    P_routing_id		IN NUMBER,
1288                                    P_called_from_batch	IN NUMBER,
1289                                    P_step_tbl		IN step_rec_tbl,
1290                                    P_scale_factor       IN NUMBER ,
1291                                    P_work_step_tbl 	IN OUT NOCOPY work_step_rec_tbl,
1292                                    P_return_status 	OUT NOCOPY VARCHAR2,
1293                                    p_ignore_mass_conv   IN BOOLEAN DEFAULT FALSE,
1294                                    p_ignore_vol_conv    IN BOOLEAN DEFAULT FALSE,
1295                                    p_process_loss	IN NUMBER DEFAULT 0) IS
1296 
1297   /* Local variables.
1298   ==================*/
1299   X_num_rows	NUMBER;
1300   X_cur_rec	NUMBER DEFAULT 0;
1301   X_line_qty	NUMBER;
1302   X_temp_qty	NUMBER;
1303   X_item_id	NUMBER;
1304   X_from_uom	mtl_units_of_measure.uom_code%TYPE;
1305   X_to_uom      mtl_units_of_measure.uom_code%TYPE;
1306   X_item_no	mtl_system_items_kfv.concatenated_segments%TYPE;
1307 
1308 
1309   /* Scaling realted variables */
1310   k                    NUMBER  := 0;
1311   x_cost_row_cnt       NUMBER  := 0;
1312   x_cost_return_status VARCHAR2(1);
1313   p_cost_scale_tab     GMD_COMMON_SCALE.scale_tab;
1314   x_cost_scale_tab     GMD_COMMON_SCALE.scale_tab;
1315 
1316   /* This table associates the formulaline with the - scaled qtys in x_cost_scale_tab */
1317   P_formulaline_scale_tab  formulaline_scale_tab;
1318 
1319   /* Cursor Definitions.
1320   =====================*/
1321   CURSOR Cur_get_material_lines (V_step_id NUMBER) IS
1322     -- NPD Conv. Use inventory_item_id and detail_uom instead of item_id and item_um from fm_matl_dtl
1323     SELECT s.formulaline_id, d.line_type, d.qty, d.detail_uom, d.inventory_item_id, d.scale_type
1324     FROM   gmd_recipe_step_materials s,
1325            fm_matl_dtl d
1326     WHERE  s.recipe_id = P_parent_id
1327     AND    s.formulaline_id = d.formulaline_id
1328     AND    s.routingstep_id = V_step_id
1329     AND    NVL (d.contribute_step_qty_ind, 'Y') = 'Y'
1330     ORDER BY d.line_type;
1331 
1332   -- NPD Conv.
1333   CURSOR Cur_get_item IS
1334     SELECT concatenated_segments
1335     FROM   mtl_system_items_kfv
1336     WHERE  inventory_item_id = X_item_id;
1337 
1338   /* Get all formulaline information */
1339   CURSOR Cur_get_formulaline_info  IS
1340     SELECT d.*
1341     FROM  fm_matl_dtl d ,
1342           gmd_recipes_b r
1343     WHERE r.recipe_id = P_parent_id
1344       AND r.formula_id = d.formula_id
1345     ORDER BY d.line_type, d.line_no;
1346 
1347   -- NPD Conv. Get the formula owner orgn id
1348   CURSOR get_formula_owner_orgn_id IS
1349     SELECT f.owner_organization_id
1350     FROM   fm_form_mst f, gmd_recipes r
1351     WHERE  r.recipe_id = P_parent_id
1352     AND    f.formula_id = r.formula_id;
1353 
1354  l_orgn_id NUMBER;
1355 
1356   /* Exceptions.
1357   =====================*/
1358   UOM_CONVERSION_ERROR		EXCEPTION;
1359   NO_MATERIAL_STEP_ASSOC	EXCEPTION;
1360   COST_SCALING_ERROR            EXCEPTION;
1361 
1362 BEGIN
1363   P_work_step_tbl.DELETE;
1364   P_return_status := FND_API.G_RET_STS_SUCCESS;
1365 
1366   /* Perform the formula scaling first */
1367   /* Scale the formula using the scale factor */
1368 
1369   /* p_cost_scale_tab holds all formula scaled qtys */
1370   /* p_formulaline_scale_tab holds all formulaline and its scaled qtys */
1371 
1372   /* Initialize all tables */
1373   x_cost_scale_tab.DELETE;
1374   p_cost_scale_tab.DELETE;
1375   p_formulaline_scale_tab.DELETE;
1376 
1377   FOR X_formulaline_rec IN Cur_get_formulaline_info LOOP
1378 
1379     X_cost_row_cnt := X_cost_row_cnt + 1;
1380     -- NPD Conv. Use inventory_item_id and detail_uom instead of item_id and item_um
1381     p_cost_scale_tab(X_cost_row_cnt).line_no                 := X_formulaline_rec.line_no                ;
1382     p_cost_scale_tab(X_cost_row_cnt).line_type               := X_formulaline_rec.line_type              ;
1383     p_cost_scale_tab(X_cost_row_cnt).inventory_item_id       := X_formulaline_rec.inventory_item_id                ;
1384     p_cost_scale_tab(X_cost_row_cnt).qty                     := X_formulaline_rec.qty                    ;
1385     p_cost_scale_tab(X_cost_row_cnt).detail_uom              := X_formulaline_rec.detail_uom             ;
1386     p_cost_scale_tab(X_cost_row_cnt).scale_type              := X_formulaline_rec.scale_type             ;
1387     p_cost_scale_tab(X_cost_row_cnt).contribute_yield_ind    := X_formulaline_rec.contribute_yield_ind   ;
1388     p_cost_scale_tab(X_cost_row_cnt).scale_multiple          := X_formulaline_rec.scale_multiple         ;
1389     p_cost_scale_tab(X_cost_row_cnt).scale_rounding_variance := X_formulaline_rec.scale_rounding_variance;
1390     p_cost_scale_tab(X_cost_row_cnt).rounding_direction      := X_formulaline_rec.rounding_direction     ;
1391     p_formulaline_scale_tab(X_cost_row_cnt).formulaline_id   := X_formulaline_rec.formulaline_id         ;
1392   END LOOP;
1393 
1394   -- NPD Conv.
1395   OPEN get_formula_owner_orgn_id;
1396   FETCH get_formula_owner_orgn_id INTO l_orgn_id;
1397   CLOSE get_formula_owner_orgn_id;
1398 
1399   /* Calling the scaling API  */
1400   gmd_common_scale.scale( p_scale_tab      => p_cost_scale_tab
1401                           ,p_orgn_id       => l_orgn_id
1402                           ,p_scale_factor  => P_scale_factor
1403                           ,p_primaries     => 'OUTPUTS'
1404                           ,x_scale_tab     => x_cost_scale_tab
1405                           ,x_return_status => x_cost_return_status
1406                          );
1407 
1408   IF (x_cost_return_status <> 'S') THEN
1409      RAISE COST_SCALING_ERROR;
1410   END IF;
1411 
1412   /* Associate formulaline id with scaled values  */
1413   FOR i IN 1 .. x_cost_scale_tab.count LOOP
1414     p_formulaline_scale_tab(i).line_no                 :=  x_cost_scale_tab(i).line_no                ;
1415     p_formulaline_scale_tab(i).line_type               :=  x_cost_scale_tab(i).line_type              ;
1416     p_formulaline_scale_tab(i).inventory_item_id       :=  x_cost_scale_tab(i).inventory_item_id      ;
1417     p_formulaline_scale_tab(i).qty                     :=  x_cost_scale_tab(i).qty                    ;
1418     p_formulaline_scale_tab(i).detail_uom              :=  x_cost_scale_tab(i).detail_uom                ;
1419     p_formulaline_scale_tab(i).scale_type              :=  x_cost_scale_tab(i).scale_type             ;
1420     p_formulaline_scale_tab(i).contribute_yield_ind    :=  x_cost_scale_tab(i).contribute_yield_ind   ;
1421     p_formulaline_scale_tab(i).scale_multiple          :=  x_cost_scale_tab(i).scale_multiple         ;
1422     p_formulaline_scale_tab(i).scale_rounding_variance :=  x_cost_scale_tab(i).scale_rounding_variance;
1423     p_formulaline_scale_tab(i).rounding_direction      :=  x_cost_scale_tab(i).rounding_direction     ;
1424   END LOOP;
1425 
1426   X_num_rows := P_step_tbl.COUNT;
1427   FOR i IN 1..X_num_rows LOOP
1428 
1429     /* If called from GMF */
1430     IF (P_called_from_batch = 0) THEN
1431 
1432       FOR X_material_rec IN Cur_get_material_lines (P_step_tbl(i).step_id) LOOP
1433         X_cur_rec := X_cur_rec + 1;
1434         P_work_step_tbl(X_cur_rec).step_id := P_step_tbl(i).step_id;
1435         P_work_step_tbl(X_cur_rec).step_no := P_step_tbl(i).step_no;
1436         P_work_step_tbl(X_cur_rec).line_id := X_material_rec.formulaline_id;
1437         P_work_step_tbl(X_cur_rec).line_type := X_material_rec.line_type;
1438 
1439         FOR k in 1 .. x_cost_scale_tab.count LOOP
1440           IF (X_material_rec.formulaline_id = p_formulaline_scale_tab(k).formulaline_id) THEN
1441             /* If all steps of OTHER um type then you dont have to bother
1442                about converting line qtys to MASS and VOLUME type um */
1443             IF NOT (G_OTHER_UM_TYPE_EXISTS) THEN
1444               X_temp_qty := INV_CONVERT.inv_um_convert(item_id     => X_material_rec.inventory_item_id
1445                                                    ,precision      => 5
1446                                                    ,from_quantity  => p_formulaline_scale_tab(k).qty
1447                                                    ,from_unit      => p_formulaline_scale_tab(k).detail_uom
1448                                                    ,to_unit        => G_mass_std_um
1449                                                    ,from_name      => NULL
1450                                                    ,to_name	   => NULL);
1451 
1452               IF X_temp_qty < 0 THEN
1453                 X_item_id := X_material_rec.inventory_item_id;  -- NPD Conv.
1454                 X_from_uom := X_material_rec.detail_uom;  -- NPD Conv.
1455                 X_to_uom := G_mass_std_um;
1456                 IF (p_ignore_mass_conv = FALSE) THEN
1457                   RAISE UOM_CONVERSION_ERROR;
1458                 ELSE
1459                   P_work_step_tbl(X_cur_rec).line_mass_qty := 0;
1460                 END IF;
1461               ELSE
1462                 P_work_step_tbl(X_cur_rec).line_mass_qty := X_temp_qty;
1463                 /* Bug 1683702 - Thomas Daniel */
1464                 /* Apply the process loss to the qty for the calculation of the step qty */
1465                 IF X_material_rec.line_type = -1 AND
1466                    X_material_rec.scale_type = 1 AND
1467                    p_process_loss > 0 THEN
1468                   P_work_step_tbl(X_cur_rec).line_mass_qty := P_work_step_tbl(X_cur_rec).line_mass_qty *
1469                                                             100 / (100 - p_process_loss);
1470                 END IF;
1471               END IF;  /* x_temp_qty > 0 condition */
1472 
1473               /*Bug#3599182 - Thomas Daniel */
1474               /*Commented the following IF as we need to proceed with the volume conversion though the mass */
1475               /*conversion has failed as there is a possibility of all the routing steps and the formula lines */
1476               /*belong to the same UOM type */
1477               -- IF (X_temp_qty > 0) THEN
1478                 X_temp_qty := INV_CONVERT.inv_um_convert(item_id   => X_material_rec.inventory_item_id
1479                                                    ,precision      => 5
1480                                                    ,from_quantity  => p_formulaline_scale_tab(k).qty
1481                                                    ,from_unit      => p_formulaline_scale_tab(k).detail_uom
1482                                                    ,to_unit        => G_vol_std_um
1483                                                    ,from_name      => NULL
1484                                                    ,to_name	   => NULL);
1485                 IF X_temp_qty < 0 THEN
1486                   X_item_id := X_material_rec.inventory_item_id;
1487                   X_from_uom := X_material_rec.detail_uom;
1488                   X_to_uom := G_vol_std_um;
1489                   IF (p_ignore_vol_conv = FALSE) THEN
1490                     RAISE UOM_CONVERSION_ERROR;
1491                   ELSE
1492                     P_work_step_tbl(X_cur_rec).line_vol_qty := 0;
1493                   END IF;
1494                 ELSE
1495                   P_work_step_tbl(X_cur_rec).line_vol_qty := X_temp_qty;
1496                   /* Bug 1683702 - Thomas Daniel */
1497                   /* Apply the process loss to the qty for the calculation of the step qty */
1498                   IF X_material_rec.line_type = -1 AND
1499                     X_material_rec.scale_type = 1 AND
1500                     p_process_loss > 0 THEN
1501                     P_work_step_tbl(X_cur_rec).line_vol_qty := P_work_step_tbl(X_cur_rec).line_vol_qty *
1502                                                                100 / (100 - p_process_loss);
1503                   END IF;
1504                 END IF;
1505               /*Bug#3599182 - Thomas Daniel */
1506               /*Commented the ENDIF following IF */
1507               -- END IF;  /* x_temp_qty > 0 condition */
1508 
1509             ELSE /* When only other um type exists */
1510               /* Added by Shyam - To capture the line qty in the other um types std um */
1511               X_temp_qty := INV_CONVERT.inv_um_convert(item_id     => X_material_rec.inventory_item_id
1512                                                    ,precision      => 5
1513                                                    ,from_quantity  => p_formulaline_scale_tab(k).qty
1514                                                    ,from_unit      => p_formulaline_scale_tab(k).detail_uom
1515                                                    ,to_unit        => G_other_std_um
1516                                                    ,from_name      => NULL
1517                                                    ,to_name	   => NULL);
1518               IF X_temp_qty < 0 THEN
1519                  X_item_id := X_material_rec.inventory_item_id;
1520                  X_from_uom := X_material_rec.detail_uom;
1521                  X_to_uom := G_other_std_um;
1522                  IF (p_ignore_mass_conv = FALSE) THEN
1523                    RAISE UOM_CONVERSION_ERROR;
1524                  ELSE
1525                    P_work_step_tbl(X_cur_rec).line_other_qty := 0;
1526                  END IF;
1527               ELSE
1528                 P_work_step_tbl(X_cur_rec).line_other_qty := X_temp_qty;
1529                 /* Bug 1683702 - Thomas Daniel */
1530                 /* Apply the process loss to the qty for the calculation of the step qty */
1531                 IF X_material_rec.line_type = -1 AND
1532                    X_material_rec.scale_type = 1 AND
1533                    p_process_loss > 0 THEN
1534                   P_work_step_tbl(X_cur_rec).line_other_qty := P_work_step_tbl(X_cur_rec).line_other_qty *
1535                                                               100 / (100 - p_process_loss);
1536                 END IF;
1537               END IF;
1538             END IF; /* Condition that tests if other um type exists */
1539 
1540             EXIT; /* because the match in formulaline btw cursor and table type has occured */
1541          END IF; /* Condition when the formulaine in material_rec is same as that in
1542                     x_formulaline_scale_tab */
1543        END LOOP ; /* for the FOR formulaline in x_formulaline_scale_tab */
1544 
1545        /* K needs to be reset to zero */
1546        k := 0;
1547 
1548      END LOOP; /*For Cur_get_material_lines%FOUND*/
1549     END IF; /* if p_batch .. condition */
1550   END LOOP; /* FOR i IN 1..X_num_rows */
1551 
1552   IF X_cur_rec = 0 THEN
1553     RAISE NO_MATERIAL_STEP_ASSOC;
1554   END IF;
1555 
1556 EXCEPTION
1557   WHEN UOM_CONVERSION_ERROR THEN
1558     P_return_status := FND_API.G_RET_STS_ERROR;
1559     OPEN Cur_get_item;
1560     FETCH Cur_get_item INTO X_item_no;
1561     CLOSE Cur_get_item;
1562     FND_MESSAGE.SET_NAME('GMI', 'IC_API_UOM_CONVERSION_ERROR');
1563     FND_MESSAGE.SET_TOKEN('ITEM_NO', X_item_no);
1564     FND_MESSAGE.SET_TOKEN('FROM_UOM', X_from_uom);
1565     FND_MESSAGE.SET_TOKEN('TO_UOM', X_to_uom);
1566     FND_MSG_PUB.ADD;
1567   WHEN NO_MATERIAL_STEP_ASSOC THEN
1568     P_return_status := FND_API.G_RET_STS_ERROR;
1569     FND_MESSAGE.SET_NAME('GMD', 'GMD_MISSING_MATL_STEP_ASSOC');
1570     FND_MSG_PUB.ADD;
1571   WHEN COST_SCALING_ERROR THEN
1572     P_return_status := FND_API.G_RET_STS_ERROR;
1573   WHEN OTHERS THEN
1574     P_return_status := FND_API.G_RET_STS_UNEXP_ERROR;
1575     FND_MSG_PUB.ADD;
1576 END get_step_material_lines;
1577 
1578 
1579 /*======================================================================
1580 --  FUNCTION :
1581 --    get_step_rec
1582 --
1583 --  DESCRIPTION:
1584 --    This PL/SQL procedure  is responsible for returning the row number
1585 --    associated with the step.
1586 --  REQUIREMENTS
1587 --    p_step_tbl  non null value.
1588 --  SYNOPSIS:
1589 --    X_rec := get_step_rec (<routingstep_no>, X_step_tbl);
1590 --
1591 --  25Jul2001  L.R.Jackson  Reworked to have only one RETURN, and to
1592 --               use WHILE instead of FOR.
1593 --===================================================================== */
1594 
1595 FUNCTION get_step_rec (P_step_no	IN NUMBER,
1596                        P_step_tbl	IN step_rec_tbl)
1597          RETURN NUMBER IS
1598 
1599   /* Local variables.
1600   ==================*/
1601   X_cur_rec	    NUMBER  := 1;
1602   X_num_rows    NUMBER  := 0;
1603   X_done        BOOLEAN := FALSE;
1604 
1605 BEGIN
1606   WHILE (X_cur_rec <= P_step_tbl.COUNT) AND NOT X_done LOOP
1607     IF P_step_tbl(X_cur_rec).step_no = P_step_no THEN
1608       X_done := TRUE;
1609       X_num_rows := X_cur_rec;
1610     END IF;
1611     X_cur_rec := X_cur_rec + 1;
1612   END LOOP;
1613   RETURN (X_num_rows);
1614 END get_step_rec;
1615 
1616 
1617 /*======================================================================
1618 --  PROCEDURE :
1619 --    sort_step_lines
1620 --
1621 --  DESCRIPTION:
1622 --    This PL/SQL procedure  is responsible for sorting the step table
1623 --    based on the step no
1624 --  REQUIREMENTS
1625 --    p_step_tbl  non null value.
1626 --  SYNOPSIS:
1627 --    sort_step_lines (X_step_tbl);
1628 --
1629 -- 25Jul2001  L.R.Jackson  Added step_id to list of columns to move.
1630 --              Moved this procedure up with others called by calc_step_qty
1631 --===================================================================== */
1632 
1633 PROCEDURE sort_step_lines (P_step_tbl	IN OUT NOCOPY step_rec_tbl,
1634                            P_return_status OUT NOCOPY VARCHAR2) IS
1635   /* Local variables.
1636   ==================*/
1637   X_step_id		NUMBER;
1638   X_step_no             NUMBER;
1639   X_step_qty            NUMBER;
1640   X_step_qty_uom        sy_uoms_mst.um_code%TYPE;
1641   X_step_mass_qty       NUMBER;
1642   X_step_vol_qty        NUMBER;
1643   X_step_other_qty       NUMBER;
1644   X_count               NUMBER;
1645 BEGIN
1646   P_return_status := FND_API.G_RET_STS_SUCCESS;
1647   X_count := P_step_tbl.COUNT;
1648   FOR i IN 1..X_count LOOP
1649     FOR j IN i+1..X_count LOOP
1650       IF P_step_tbl(i).step_no > P_step_tbl(j).step_no THEN
1651         X_step_id       := P_step_tbl(i).step_id;
1652         X_step_no       := P_step_tbl(i).step_no;
1653         X_step_qty      := P_step_tbl(i).step_qty;
1654         X_step_qty_uom  := P_step_tbl(i).step_qty_uom;
1655         X_step_mass_qty := P_step_tbl(i).step_mass_qty;
1656         X_step_vol_qty  := P_step_tbl(i).step_vol_qty;
1657         X_step_other_qty  := P_step_tbl(i).step_other_qty;
1658 
1659         P_step_tbl(i).step_id       := P_step_tbl(j).step_id;
1660         P_step_tbl(i).step_no       := P_step_tbl(j).step_no;
1661         P_step_tbl(i).step_qty      := P_step_tbl(j).step_qty;
1662         P_step_tbl(i).step_qty_uom  := P_step_tbl(j).step_qty_uom;
1663         P_step_tbl(i).step_mass_qty := P_step_tbl(j).step_mass_qty;
1664         P_step_tbl(i).step_vol_qty  := P_step_tbl(j).step_vol_qty;
1665         P_step_tbl(i).step_other_qty  := P_step_tbl(j).step_other_qty;
1666 
1667         P_step_tbl(j).step_id       := X_step_id;
1668         P_step_tbl(j).step_no       := X_step_no;
1669         P_step_tbl(j).step_qty      := X_step_qty;
1670         P_step_tbl(j).step_qty_uom  := X_step_qty_uom;
1671         P_step_tbl(j).step_mass_qty := X_step_mass_qty;
1672         P_step_tbl(j).step_vol_qty  := X_step_vol_qty;
1673         P_step_tbl(j).step_other_qty  := X_step_other_qty;
1674 
1675       END IF;
1676     END LOOP; /* FOR j IN 1..X_count */
1677   END LOOP; /* FOR i IN 1..X_count */
1678 EXCEPTION
1679   WHEN OTHERS THEN
1680      P_return_status := FND_API.G_RET_STS_UNEXP_ERROR;
1681      FND_MSG_PUB.ADD;
1682 END sort_step_lines;
1683 
1684 
1685 /*======================================================================
1686 --  PROCEDURE :
1687 --    check_step_qty_calculatable
1688 --
1689 --  DESCRIPTION:
1690 --    This PL/SQL procedure  is responsible for checking whether the
1691 --    automatic step quantity calculation can be performed.
1692 --
1693 --  REQUIREMENTS
1694 --    p_parent_id  non null value.
1695 --  SYNOPSIS:
1696 --    check_step_qty_calculatable (426, X_msg_count, X_msg_stack,
1697 --                             X_return_status);
1698 --
1699 --  This procedure calls GMICUOM.uom_conversion
1700 --
1701 --
1702 --===================================================================== */
1703 
1704 PROCEDURE check_step_qty_calculatable (P_check            IN  calculatable_rec_type,
1705     	                               P_msg_count        OUT NOCOPY NUMBER,
1706                                        P_msg_stack        OUT NOCOPY VARCHAR2,
1707                                        P_return_status    OUT NOCOPY VARCHAR2,
1708                                        P_ignore_mass_conv OUT NOCOPY BOOLEAN,
1709                                        P_ignore_vol_conv  OUT NOCOPY BOOLEAN,
1710 				       P_organization_id  IN  NUMBER) IS
1711   /* Local variables.
1712   ==================*/
1713   X_exists	NUMBER(5);
1714   X_temp_qty	NUMBER;
1715   X_item_id	NUMBER;
1716   X_from_uom	mtl_units_of_measure.uom_code%TYPE;
1717   X_to_uom      mtl_units_of_measure.uom_code%TYPE;
1718   X_item_no	mtl_system_items_kfv.concatenated_segments%TYPE;
1719 
1720   /* Cursor Definitions.
1721   =====================*/
1722   CURSOR Cur_get_recipe_details IS
1723     SELECT formula_id, routing_id
1724     FROM   gmd_recipes_b
1725     WHERE  recipe_id = P_check.parent_id;
1726 
1727   CURSOR Cur_get_rout_details (V_routing_id NUMBER) IS
1728     SELECT 1
1729     FROM   sys.dual
1730     WHERE EXISTS (SELECT 1
1731                   FROM   fm_rout_dtl
1732                   WHERE  routing_id = V_routing_id);
1733 
1734   -- p_formulaline_id would have a value if this procedure is called
1735   -- from cascade_del_to_step_mat.  From the formula details form, the delete of
1736   -- the formula line would not be committed yet.  Process the rest of
1737   -- the lines, not the line which is being deleted.
1738   CURSOR Cur_check_matl_lines_assoc (V_formula_id NUMBER) IS
1739     SELECT 1
1740     FROM   fm_matl_dtl
1741     WHERE  formula_id = V_formula_id
1742     AND    NVL(contribute_step_qty_ind, 'Y') = 'Y'
1743     AND    formulaline_id NOT IN (SELECT formulaline_id
1744                                   FROM   gmd_recipe_step_materials
1745                                   WHERE  recipe_id = P_check.parent_id)
1746     AND (P_check.formulaline_id IS NULL OR
1747                formulaline_id <> P_check.formulaline_id)
1748     ;
1749 
1750   CURSOR Cur_get_material_lines (V_formula_id NUMBER) IS
1751     SELECT d.qty, d.detail_uom, d.inventory_item_id
1752     FROM   fm_matl_dtl d
1753     WHERE  d.formula_id = V_formula_id
1754       AND    NVL(d.contribute_step_qty_ind, 'Y')  = 'Y'
1755       AND (P_check.formulaline_id IS NULL OR
1756                    formulaline_id <> P_check.formulaline_id)
1757     ;
1758 
1759   CURSOR Cur_get_item IS
1760     SELECT concatenated_segments
1761     FROM   mtl_system_items_kfv
1762     WHERE  inventory_item_id = X_item_id;
1763 
1764   CURSOR Cur_get_std_um (V_uom_class VARCHAR2) IS
1765     SELECT uom_code
1766     FROM   mtl_units_of_measure
1767     WHERE  uom_class = V_uom_class;
1768 
1769   CURSOR Cur_chk_matrl_umtype(pformula_id NUMBER) IS
1770     SELECT COUNT(distinct uom_class)
1771      FROM  fm_matl_dtl d ,mtl_units_of_measure m
1772      WHERE d.detail_uom = m.uom_code
1773          AND d.formula_id = pformula_id
1774          AND NVL(d.contribute_step_qty_ind, 'Y')  = 'Y'
1775          AND (P_check.formulaline_id IS NULL OR
1776                    formulaline_id <> P_check.formulaline_id);
1777 
1778   CURSOR Cur_get_mtl_umtype(pformula_id NUMBER) IS
1779     SELECT distinct m.uom_class
1780      FROM  fm_matl_dtl d ,mtl_units_of_measure m
1781      WHERE d.detail_uom = m.uom_code
1782          AND d.formula_id = pformula_id
1783          AND NVL(d.contribute_step_qty_ind, 'Y')  = 'Y'
1784          AND (P_check.formulaline_id IS NULL OR
1785               formulaline_id <> P_check.formulaline_id);
1786 
1787   CURSOR Cur_check_depstps (prouting_id NUMBER) IS
1788     SELECT count(*)
1789     FROM  fm_rout_dtl h,fm_rout_dep d
1790     WHERE h.routing_id = prouting_id AND
1791           h.routing_id = d.routing_id;
1792 
1793   CURSOR Cur_get_umtyp_cnt(prouting_id NUMBER) IS
1794     SELECT count(distinct u.uom_class)
1795     FROM   fm_rout_dtl d,
1796            gmd_operations_b o,
1797            mtl_units_of_measure u
1798     WHERE  d.oprn_id = o.oprn_id
1799     AND    d.routing_id = prouting_id
1800     AND    o.process_qty_uom = u.uom_code;
1801 
1802 
1803   CURSOR Cur_get_process_umtyp(prouting_id NUMBER) IS
1804     SELECT distinct u.uom_class
1805     FROM   fm_rout_dtl d,
1806            gmd_operations_b o,
1807            mtl_units_of_measure u
1808     WHERE  d.oprn_id = o.oprn_id
1809     AND    d.routing_id = prouting_id
1810     AND    o.process_qty_uom = u.uom_code;
1811 
1812 
1813   /* Cursor records.
1814   =====================*/
1815   X_recipe_details_rec  Cur_get_recipe_details%ROWTYPE;
1816 --  X_material_rec	Cur_get_material_lines%ROWTYPE;
1817   X_um_type             mtl_units_of_measure.uom_class%TYPE;
1818   X_count               NUMBER := 0;
1819   l_return_status	VARCHAR2(10);
1820   /* Exceptions.
1821   =====================*/
1822   NO_MATERIAL_STEP_ASSOC	EXCEPTION;
1823   NO_ROUTING_ASSOCIATED		EXCEPTION;
1824   ROUTING_DETAILS_MISSING	EXCEPTION;
1825   ALL_MTL_LINES_NOT_ASSOC  	EXCEPTION;
1826   UOM_CONVERSION_ERROR		EXCEPTION;
1827 BEGIN
1828   P_return_status := FND_API.G_RET_STS_SUCCESS;
1829   FND_MSG_PUB.INITIALIZE;
1830 
1831   /* If recipe id is null it implies that the material
1832      step association has not been done */
1833   IF P_check.parent_id IS NULL THEN
1834     RAISE NO_MATERIAL_STEP_ASSOC;
1835   END IF;
1836 
1837   GMD_API_GRP.FETCH_PARM_VALUES (P_orgn_id      => p_organization_id	,
1838 				P_parm_name     => 'GMD_MASS_UM_TYPE'	,
1839 				P_parm_value    => gmd_auto_step_calc.G_PROFILE_MASS_UM_TYPE	,
1840 				X_return_status => l_return_status	);
1841 
1842   GMD_API_GRP.FETCH_PARM_VALUES (P_orgn_id      => p_organization_id	,
1843 				P_parm_name     => 'GMD_VOLUME_UM_TYPE'	,
1844 				P_parm_value    => gmd_auto_step_calc.G_PROFILE_VOLUME_UM_TYPE	,
1845 				X_return_status => l_return_status	);
1846 
1847   OPEN Cur_get_recipe_details;
1848   FETCH Cur_get_recipe_details INTO X_recipe_details_rec;
1849   CLOSE Cur_get_recipe_details;
1850 
1851   /* Check whether a routing is associated with the recipe */
1852   IF X_recipe_details_rec.routing_id IS NULL THEN
1853     RAISE NO_ROUTING_ASSOCIATED;
1854   END IF;
1855 
1856   /* Check whether the routing has steps associated */
1857   OPEN Cur_get_rout_details (X_recipe_details_rec.routing_id);
1858   FETCH Cur_get_rout_details INTO X_exists;
1859   IF Cur_get_rout_details%NOTFOUND THEN
1860     CLOSE Cur_get_rout_details;
1861     RAISE ROUTING_DETAILS_MISSING;
1862   END IF;
1863   CLOSE Cur_get_rout_details;
1864 
1865   /* Check whether all the material lines where contribute-step-qty_ind = Y
1866      have been attached to a step */
1867   OPEN Cur_check_matl_lines_assoc (X_recipe_details_rec.formula_id);
1868   FETCH Cur_check_matl_lines_assoc INTO X_exists;
1869   IF Cur_check_matl_lines_assoc%FOUND THEN
1870     CLOSE Cur_check_matl_lines_assoc;
1871     RAISE ALL_MTL_LINES_NOT_ASSOC;
1872   END IF;
1873   CLOSE Cur_check_matl_lines_assoc;
1874 
1875   /* Populate the global std um variables. */
1876   OPEN Cur_get_std_um (G_profile_mass_um_type);
1877   FETCH Cur_get_std_um INTO G_mass_std_um;
1878   CLOSE Cur_get_std_um;
1879 
1880   OPEN Cur_get_std_um (G_profile_volume_um_type);
1881   FETCH Cur_get_std_um INTO G_vol_std_um;
1882   CLOSE Cur_get_std_um;
1883 
1884 
1885   -- Check if material lines are define in mass uom or Vol uom.
1886   -- Bug   2130655
1887   -- Bug # 2362814 Added by Shyam
1888   -- If x_count = 1 it is ok.
1889   OPEN Cur_chk_matrl_umtype(x_recipe_details_rec.formula_id);
1890   FETCH Cur_chk_matrl_umtype INTO x_count;
1891   CLOSE Cur_chk_matrl_umtype;
1892 
1893   IF (x_count = 1) THEN
1894     OPEN Cur_get_mtl_umtype(x_recipe_details_rec.formula_id);
1895     FETCH Cur_get_mtl_umtype INTO x_um_type;
1896     CLOSE Cur_get_mtl_umtype;
1897 
1898     IF (x_um_type = G_profile_mass_um_type) THEN
1899       p_ignore_vol_conv := TRUE;
1900     ELSIF (x_um_type = G_profile_volume_um_type) THEN
1901       p_ignore_mass_conv := TRUE;
1902     END IF;
1903   ELSIF(x_count > 1) THEN
1904     p_ignore_mass_conv := FALSE;
1905     p_ignore_vol_conv  := FALSE;
1906   END IF;
1907 
1908  IF (x_recipe_details_rec.routing_id IS NOT NULL) THEN
1909    OPEN Cur_get_umtyp_cnt(x_recipe_details_rec.routing_id);
1910    FETCH Cur_get_umtyp_cnt INTO x_count;
1911    CLOSE Cur_get_umtyp_cnt;
1912 
1913    /* if x_count is 1 then it could be MASS or VOL or some OTHER type */
1914    IF (x_count = 1) THEN
1915      OPEN Cur_get_process_umtyp(x_recipe_details_rec.routing_id);
1916      FETCH Cur_get_process_umtyp INTO x_um_type;
1917      CLOSE Cur_get_process_umtyp;
1918      IF (x_um_type = G_profile_mass_um_type) THEN
1919        p_ignore_vol_conv := TRUE;
1920      ELSIF (x_um_type = G_profile_volume_um_type) THEN
1921        p_ignore_mass_conv := TRUE;
1922      ELSE
1923       /* Get the other UOM type */
1924        G_PROFILE_OTHER_UM_TYPE := x_um_type;
1925      END IF;
1926    ELSIF(x_count > 1) THEN
1927      p_ignore_mass_conv := FALSE;
1928      p_ignore_vol_conv  := FALSE;
1929    END IF;
1930  END IF;
1931 
1932    -- End Bug 2130655.
1933    IF (G_PROFILE_OTHER_UM_TYPE IS NOT NULL) THEN
1934      OPEN Cur_get_std_um (G_PROFILE_OTHER_UM_TYPE);
1935      FETCH Cur_get_std_um INTO G_other_std_um;
1936      CLOSE Cur_get_std_um;
1937    END IF;
1938 
1939    /* Check whether all the material lines checked to be contributing
1940      to the step qty are convertible to the mass and volume uom types */
1941    FOR x_material_rec IN Cur_get_material_lines (X_recipe_details_rec.formula_id) LOOP
1942 
1943      IF (G_PROFILE_OTHER_UM_TYPE IS NULL) THEN
1944        X_temp_qty := INV_CONVERT.inv_um_convert(item_id        => X_material_rec.inventory_item_id
1945                                                ,precision      => 5
1946                                                ,from_quantity  => X_material_rec.qty
1947                                                ,from_unit      => X_material_rec.detail_uom
1948                                                ,to_unit        => G_mass_std_um
1949                                                ,from_name      => NULL
1950                                                ,to_name	       => NULL);
1951        IF X_temp_qty < 0 THEN
1952          X_item_id := X_material_rec.inventory_item_id;
1953          X_from_uom := X_material_rec.detail_uom;
1954          X_to_uom := G_mass_std_um;
1955          IF (p_ignore_mass_conv = FALSE) THEN
1956            RAISE UOM_CONVERSION_ERROR;
1957          END IF;
1958        END IF;
1959        X_temp_qty := INV_CONVERT.inv_um_convert(item_id         => X_material_rec.inventory_item_id
1960                                                ,precision      => 5
1961                                                ,from_quantity  => X_material_rec.qty
1962                                                ,from_unit      => X_material_rec.detail_uom
1963                                                ,to_unit        => G_vol_std_um
1964                                                ,from_name      => NULL
1965                                                ,to_name	       => NULL);
1966 
1967        IF X_temp_qty < 0 THEN
1968          X_item_id := X_material_rec.inventory_item_id;
1969          X_from_uom := X_material_rec.detail_uom;
1970          X_to_uom := G_vol_std_um;
1971          IF (p_ignore_vol_conv = FALSE) THEN
1972            RAISE UOM_CONVERSION_ERROR;
1973          END IF;
1974        END IF;
1975      ELSE /* IF the um type is of other type */
1976        X_temp_qty := INV_CONVERT.inv_um_convert(item_id        => X_material_rec.inventory_item_id
1977                                                ,precision      => 5
1978                                                ,from_quantity  => X_material_rec.qty
1979                                                ,from_unit      => X_material_rec.detail_uom
1980                                                ,to_unit        => G_other_std_um
1981                                                ,from_name      => NULL
1982                                                ,to_name	       => NULL);
1983        IF X_temp_qty < 0 THEN
1984          X_item_id := X_material_rec.inventory_item_id;
1985          X_from_uom := X_material_rec.detail_uom;
1986          X_to_uom := G_other_std_um;
1987          RAISE UOM_CONVERSION_ERROR;
1988        END IF;
1989      END IF;
1990 
1991    END LOOP;
1992 EXCEPTION
1993   WHEN NO_ROUTING_ASSOCIATED THEN
1994     P_return_status := FND_API.G_RET_STS_ERROR;
1995     FND_MESSAGE.SET_NAME('GMD', 'GMD_AUTO_STEP_QTY_NEEDS_ROUT');
1996     FND_MSG_PUB.ADD;
1997     FND_MSG_PUB.COUNT_AND_GET (P_count => P_msg_count,
1998                                P_data  => P_msg_stack);
1999   WHEN ROUTING_DETAILS_MISSING THEN
2000     P_return_status := FND_API.G_RET_STS_ERROR;
2001     FND_MESSAGE.SET_NAME('GMD', 'FMROUTINGSTEPNOTFOUND');
2002     FND_MSG_PUB.ADD;
2003     FND_MSG_PUB.COUNT_AND_GET (P_count => P_msg_count,
2004                                P_data  => P_msg_stack);
2005   WHEN  NO_MATERIAL_STEP_ASSOC THEN
2006     P_return_status := FND_API.G_RET_STS_ERROR;
2007     --  debug line p_return_status := 'Z';
2008     FND_MESSAGE.SET_NAME('GMD', 'GMD_MISSING_MATL_STEP_ASSOC');
2009     FND_MSG_PUB.ADD;
2010     FND_MSG_PUB.COUNT_AND_GET (P_count => P_msg_count,
2011                                P_data  => P_msg_stack);
2012   WHEN ALL_MTL_LINES_NOT_ASSOC THEN
2013     P_return_status := FND_API.G_RET_STS_ERROR;
2014     --  debug line p_return_status := 'Y';
2015     FND_MESSAGE.SET_NAME('GMD', 'GMD_ALL_MATL_STEP_NOT_ASSOC');
2016     FND_MSG_PUB.ADD;
2017     FND_MSG_PUB.COUNT_AND_GET (P_count => P_msg_count,
2018                                P_data  => P_msg_stack);
2019   WHEN UOM_CONVERSION_ERROR THEN
2020     P_return_status := FND_API.G_RET_STS_ERROR;
2021     OPEN Cur_get_item;
2022     FETCH Cur_get_item INTO X_item_no;
2023     CLOSE Cur_get_item;
2024     FND_MESSAGE.SET_NAME('GMI', 'IC_API_UOM_CONVERSION_ERROR');
2025     FND_MESSAGE.SET_TOKEN('ITEM_NO', X_item_no);
2026     FND_MESSAGE.SET_TOKEN('FROM_UOM', X_from_uom);
2027     FND_MESSAGE.SET_TOKEN('TO_UOM', X_to_uom);
2028     FND_MSG_PUB.ADD;
2029     FND_MSG_PUB.COUNT_AND_GET (P_count => P_msg_count,
2030                                 P_data  => P_msg_stack);
2031   WHEN OTHERS THEN
2032      P_return_status := FND_API.G_RET_STS_UNEXP_ERROR;
2033      fnd_message.set_name('GMD',SQLERRM);
2034      fnd_msg_pub.add;
2035      FND_MSG_PUB.COUNT_AND_GET (P_count => P_msg_count,
2036                                 P_data  => P_msg_stack);
2037 END check_step_qty_calculatable;
2038 
2039 
2040 /*****************************************************
2041 --  PROCEDURE :
2042 --    check_del_from_step_mat
2043 --
2044 --  DESCRIPTION:
2045 --    This PL/SQL procedure accepts a formulaline_id or routingstep_id
2046 --    which is being deleted from the formula material table or routing detail
2047 --    table, respectively.  It returns the recipe id's affected by the deleted,
2048 --
2049 --    This procedure is called by the forms, to tell the user what the scope of
2050 --    their delete is, and to ask if they wish to continue.  If they answer YES,
2051 --    then cascade_del_to_step_mat procedure is called, which does the actual
2052 --    delete from the step/mat assoc table and recalc's step qty's if necessary.
2053 --
2054 --  REQUIREMENTS
2055 --    p_check record  non null value. (recipe, formulaline or routingstep, WHO)
2056 --
2057 --  SYNOPSIS:
2058 --    check_del_from_step_mat (p_check, X_return_status);
2059 --
2060 --  Procedures used:  none
2061 
2062 --
2063 --  HISTORY
2064 --  02Aug2001  L.R.Jackson  Bug 1856832.  Created
2065 
2066 ************************************************************************/
2067 PROCEDURE check_del_from_step_mat(P_check          IN calculatable_rec_type,
2068                                   P_recipe_tbl     OUT NOCOPY recipe_id_tbl,
2069                                   P_check_step_mat OUT NOCOPY check_step_mat_type,
2070                                   P_msg_count      OUT NOCOPY NUMBER,
2071                                   P_msg_stack      OUT NOCOPY VARCHAR2,
2072                                   P_return_status  OUT NOCOPY VARCHAR2
2073                                  )  IS
2074 
2075 CURSOR Cur_get_step_mat_recipes (p_formulaline_id NUMBER, p_routingstep_id NUMBER) IS
2076       SELECT m.recipe_id,
2077              r.recipe_status
2078       FROM   gmd_recipe_step_materials m,
2079              gmd_recipes_b r,
2080              gmd_status_b s
2081       WHERE  s.status_code    = r.recipe_status
2082         AND  r.recipe_id      = m.recipe_id
2083         AND  ((p_formulaline_id is not null and m.formulaline_id = P_formulaline_id)
2084                OR
2085                (p_routingstep_id is not null and m.routingstep_id = P_routingstep_id))
2086         AND  r.calculate_step_quantity > 0
2087         AND  s.status_type   <> 1000
2088         AND  r.delete_mark    = 0;
2089 
2090 x_recipe_cntr   NUMBER := 0;
2091 
2092 BEGIN
2093   P_return_status := FND_API.G_RET_STS_SUCCESS;
2094     -- 1. Get a list of recipes where this formulaline exists in step/mat association,
2095     --    and where calculate_step_qty flag IS set (ASQC=Yes)
2096     --    and where delete_mark is NOT set
2097     --    and the recipe is NOT marked obsolete.
2098     -- 2. Count the recipes in step/mat rows where this formulaline exists (regardless of ASQC flag).
2099 
2100   FOR get_recipe_id IN cur_get_step_mat_recipes (p_check.formulaline_id, p_check.routingstep_id)
2101           LOOP
2102     x_recipe_cntr := x_recipe_cntr + 1;
2103     p_recipe_tbl(x_recipe_cntr) := get_recipe_id.recipe_id;
2104   END LOOP;
2105 
2106   P_check_step_mat.ASQC_RECIPES  := x_recipe_cntr;
2107 
2108   SELECT COUNT(unique recipe_id) into P_check_step_mat.STEP_ASSOC_RECIPES
2109     FROM   gmd_recipe_step_materials
2110    WHERE  (P_check.formulaline_id is not null AND formulaline_id = P_check.formulaline_id)
2111              OR
2112           (p_check.routingstep_id is not null AND routingstep_id = P_check.routingstep_id) ;
2113 
2114 EXCEPTION
2115    WHEN OTHERS THEN
2116           -- It is OK if no rows are found in step/mat table.
2117           -- This exception is for database errors
2118         P_return_status := FND_API.G_RET_STS_UNEXP_ERROR;
2119         FND_MSG_PUB.COUNT_AND_GET (P_count => P_msg_count,
2120                                    P_data  => P_msg_stack);
2121 END check_del_from_step_mat;
2122 
2123 
2124 
2125 /*****************************************************
2126 --  PROCEDURE :
2127 --    cascade_del_to_step_mat
2128 --
2129 --  DESCRIPTION:
2130 --    This PL/SQL procedure accepts a formulaline_id or routingstep_id
2131 --    which is being deleted from the formula material table or routing detail
2132 --    table, respectively.  The formualine_id or routingstep_id is deleted from
2133 --    GMD_RECIPE_STEP_MATERIALS.  Then, if ASQC flag = yes, step qty's are
2134 --    recalculated.
2135 --
2136 --  REQUIREMENTS
2137 --    Calling program must first call check_del_from_step_mat.
2138 --    p_check record  non null value. (recipe, formulaline or routingstep, WHO)
2139 --    If formulaline_id is being deleted, routingstep_id parameter must be null
2140 --
2141 --  SYNOPSIS:
2142 --    cascade_del_to_step_mat (p_check, X_return_status);
2143 --
2144 --  Procedures used:  gmd_auto_step_calc.check_step_qty_calculatable
2145 --                    gmd_auto_step_calc.calc_step_qty
2146 --                    gmd_recipe_detail.recipe_routing_steps
2147 --
2148 --  HISTORY
2149 --  25Jul2001  L.R.Jackson  Bug 1856832.  Created
2150 --  Sukarna Reddy Dt 03/14/02. Bug 2130655. p_ignore_mass_conv
2151 --   and p_ignore_vol_conv will not be passed as parameter.
2152 ************************************************************/
2153 
2154 PROCEDURE cascade_del_to_step_mat(P_check          IN calculatable_rec_type,
2155                                   P_recipe_tbl     IN recipe_id_tbl,
2156                                   P_check_step_mat IN check_step_mat_type,
2157                                   P_msg_count      OUT NOCOPY NUMBER,
2158                                   P_msg_stack      OUT NOCOPY VARCHAR2,
2159                                   P_return_status  OUT NOCOPY VARCHAR2,
2160                                   P_organization_id IN NUMBER)  IS
2161 
2162 x_recipe_cntr       NUMBER := 0;
2163 x_step_cntr         NUMBER := 0;
2164 X_step_tbl	        gmd_auto_step_calc.step_rec_tbl;
2165 X_all_steps_tbl     gmd_recipe_detail.recipe_detail_tbl;
2166 x_flex              gmd_recipe_detail.recipe_flex;
2167 x_update_flex       gmd_recipe_detail.recipe_update_flex;
2168 x_check_out         gmd_auto_step_calc.calculatable_rec_type;
2169 debug_msg           EXCEPTION;    -- used in debugging
2170 x_ignore_mass_conv BOOLEAN;
2171 x_ignore_vol_conv  BOOLEAN;
2172 ALL_MTL_LINES_NOT_ASSOC  	EXCEPTION;
2173 
2174 BEGIN
2175   P_return_status := FND_API.G_RET_STS_SUCCESS;
2176     -- Calling program should delete from fm_matl_dtl.
2177     --    DELETE  FROM   fm_matl_dtl WHERE  formulaline_id = P_formulaline_id;
2178     -- 1. Use gmd_auto_step_calc.check_del_from_step_mat to get a list of recipes where
2179     --       this formulaline exists in step/mat association,
2180     --    and where calculate_step_qty flag IS set (ASQC=Yes)
2181     --    and where delete_mark is NOT set
2182     --    and the recipe is NOT marked obsolete.
2183     -- check_del_from_step_mat will also count if there are any step/mat associations which
2184     --    need to be deleted.
2185     -- 2. Delete the step/mat rows where this formulaline exists (regardless of ASQC flag).
2186     -- 3. Recalculate step qty's in the recipes in the list.
2187 
2188     -- debug dbms_output.put_line('Value of v_formulaline_id='||P_check_in.formulaline_id||' **********************************');
2189 
2190   -- If there are any step/mat lines using this formulaline or routingstep, delete them.
2191   -- Then, if any of the recipes involved need the step qty's re calculated (id's would be in
2192   --   p_recipe_tbl) then recalc.
2193   -- By definition, if a routingstep is being deleted and there were step associations, now
2194   --   there will be items with no association to a step (the step which is being deleted).
2195   -- ***********************************************************************************
2196   -- For the next version, check if formulaline's which would go away because a routing step
2197   -- is deleted actually ARE marked as contributing-to-step-qty.  If not, then asqc can be
2198   -- recalc'ed.
2199   IF P_check_step_mat.STEP_ASSOC_RECIPES > 0 THEN
2200     DELETE FROM   gmd_recipe_step_materials
2201      WHERE  (P_check.formulaline_id is not null AND formulaline_id = P_check.formulaline_id)
2202              OR
2203             (p_check.routingstep_id is not null AND routingstep_id = P_check.routingstep_id) ;
2204 
2205 
2206     /* Commented the code below by Shyam */
2207     /* We need not perform the ASQC recalculation and update the GMD Recipe
2208        step table because if the ASQC flag is ON then the values are not saved
2209        in the db or the GMD Recipe Steps table.  Each time the Recipes form
2210        open if the ASQC flag is ON then it performs the recalculation */
2211 
2212     IF p_check.routingstep_id is not null THEN
2213        -- save what has been done so far and go to end.  Put message on stack.
2214        IF (P_check_step_mat.ASQC_RECIPES > 0) THEN
2215            RAISE ALL_MTL_LINES_NOT_ASSOC;
2216        ELSE
2217            DELETE FROM gmd_recipe_routing_steps
2218            WHERE  (p_check.routingstep_id is not null
2219                    AND routingstep_id = P_check.routingstep_id);
2220        END IF;
2221     END IF;   -- end if routingstep is being deleted.
2222 
2223     /*
2224     FOR x_recipe_cntr in 1..P_recipe_tbl.COUNT LOOP
2225         -- debug dbms_output.put_line('call asqc to recalculate here. Give user a message. recipe_id '|| x_recipe_tbl(x_recipe_cntr) );
2226       x_check_out := p_check;
2227       x_check_out.parent_id := P_recipe_tbl(x_recipe_cntr);
2228       gmd_auto_step_calc.check_step_qty_calculatable
2229                                      (p_check         => x_check_out,
2230                                       p_msg_count     => P_msg_count,
2231                                       p_msg_stack     => P_msg_stack,
2232                                       p_return_status => P_return_status,
2233                                       P_ignore_mass_conv => x_ignore_mass_conv,
2234                                       P_ignore_vol_conv => x_ignore_vol_conv,
2235 				      P_organization_id => P_organization_id);
2236 
2237       -- debug dbms_output.put_line('status from calculatable is ' || p_return_status);
2238       IF p_return_status = 'S' THEN
2239         gmd_auto_step_calc.calc_step_qty(p_parent_id     => P_recipe_tbl(x_recipe_cntr),
2240                                          p_step_tbl      => X_step_tbl,
2241                                          p_msg_count     => P_msg_count,
2242                                          p_msg_stack     => P_msg_stack,
2243                                          p_return_status => p_return_status,
2244 					 P_organization_id => P_organization_id);
2245       END IF;
2246       -- Check_step_qty_calculatable and Calc_step_qty put their own messages on the stack.
2247 
2248       IF p_return_status = 'S' THEN
2249         -- debug  dbms_output.put_line('Value of X_step_tbl.COUNT='||X_step_tbl.COUNT);
2250         -- debug  dbms_output.put_line('After calc Value of p_return_status= *'||p_return_status ||'*');
2251 
2252       -- We are in a loop for every recipe where ASQC=Yes.  If ASQC was succussful,
2253       --   for each step returned in the step table, put the results in a holding table.
2254       --   This holding table will be sent to the recipe_details pkg for update (maybe insert)
2255       --   of the gmd_recipe_routing_steps table.
2256       -- Counter is only initialized at top of procedure.
2257         FOR asqc_cntr in 1..X_step_tbl.COUNT LOOP
2258           x_step_cntr := x_step_cntr + 1;
2259           X_all_steps_tbl(x_step_cntr).recipe_id         := P_recipe_tbl(x_recipe_cntr);
2260           X_all_steps_tbl(x_step_cntr).routingstep_id    := X_step_tbl(asqc_cntr).step_id;
2261           X_all_steps_tbl(x_step_cntr).step_qty          := X_step_tbl(asqc_cntr).step_qty;
2262           X_all_steps_tbl(x_step_cntr).mass_qty          := X_step_tbl(asqc_cntr).step_mass_qty;
2263           X_all_steps_tbl(x_step_cntr).mass_ref_uom      := X_step_tbl(asqc_cntr).step_mass_uom;
2264           X_all_steps_tbl(x_step_cntr).volume_qty        := X_step_tbl(asqc_cntr).step_vol_qty;
2265           X_all_steps_tbl(x_step_cntr).volume_ref_uom    := X_step_tbl(asqc_cntr).step_vol_uom;
2266           X_all_steps_tbl(x_step_cntr).creation_date     := P_check.creation_date;
2267           X_all_steps_tbl(x_step_cntr).created_by        := P_check.created_by;
2268           X_all_steps_tbl(x_step_cntr).last_update_date  := P_check.last_update_date;
2269           X_all_steps_tbl(x_step_cntr).last_updated_by   := P_check.last_updated_by;
2270           X_all_steps_tbl(x_step_cntr).last_update_login := P_check.last_update_login;
2271         END LOOP;
2272       END IF;    -- end if return status from calc_step_qty = S
2273     END LOOP;    -- end loop for each recipe which had the given formulaline or routing
2274                  --   in the step/material association
2275 
2276     -- After everything has been calculated, update step qty's in gmd_recipe_routing_steps.
2277     IF p_return_status = 'S' THEN
2278       gmd_recipe_detail.recipe_routing_steps
2279                                    (p_api_version        => 1.1,
2280                                     p_init_msg_list      => 'F',
2281                                     p_commit             => 'F',
2282                                     p_called_from_forms  => 'NO',
2283                                     x_return_status      => p_return_status,
2284                                     x_msg_count          => P_msg_count,
2285                                     x_msg_data           => P_msg_stack,
2286                                     p_recipe_detail_tbl  => X_all_steps_tbl,
2287                                     p_recipe_insert_flex => x_flex,
2288                                     p_recipe_update_flex => x_update_flex
2289                                    );
2290 
2291     END IF;  -- end if calc_step was successful
2292 
2293     */
2294   END IF;    -- end if there are any recipes affected by the formulaline or routingstep delete
2295 
2296   EXCEPTION
2297     WHEN debug_msg THEN
2298           FND_MSG_PUB.ADD;
2299           FND_MSG_PUB.COUNT_AND_GET (P_count => P_msg_count,
2300                                      P_data  => P_msg_stack);
2301           -- debug dbms_output.put_line ('in exception ' || p_return_status);
2302 
2303     WHEN ALL_MTL_LINES_NOT_ASSOC THEN
2304     P_return_status := FND_API.G_RET_STS_ERROR;
2305     FND_MESSAGE.SET_NAME('GMD', 'GMD_ALL_MATL_STEP_NOT_ASSOC');
2306     FND_MSG_PUB.ADD;
2307     FND_MSG_PUB.COUNT_AND_GET (P_count => P_msg_count,
2308                                P_data  => P_msg_stack);
2309     WHEN OTHERS THEN
2310           -- It is OK if no rows are found in step/mat table.
2311           -- The 3 procedures called have their own error handling.
2312         P_return_status := FND_API.G_RET_STS_UNEXP_ERROR;
2313         FND_MSG_PUB.COUNT_AND_GET (P_count => P_msg_count,
2314                                    P_data  => P_msg_stack);
2315   END cascade_del_to_step_mat;
2316 
2317 
2318 /*****************************************************
2319 --  PROCEDURE :
2320 --    check_Bch_stp_qty_calculatable
2321 --
2322 --  DESCRIPTION:
2323 --    Handles the UOM type conversion
2324 --
2325 --  HISTORY
2326 --  26-06-06  Kapil M  Created the procedure for bug# 5347857.
2327 --  08-08-06  Kapil M  Replaced sy_uoms_mst with mtl_units_of_measure
2328 **************************************************************/
2329 
2330 PROCEDURE check_Bch_stp_qty_calculatable (P_check            IN  calculatable_rec_type,
2331                                         P_ignore_mass_conv OUT NOCOPY BOOLEAN,
2332                                         P_ignore_vol_conv  OUT NOCOPY BOOLEAN) IS
2333 
2334   /* Cursor Definitions.
2335   =====================*/
2336   CURSOR Cur_get_recipe_details IS
2337     SELECT formula_id, routing_id
2338     FROM   GME_BATCH_HEADER
2339     WHERE  BATCH_ID = P_check.parent_id;
2340 
2341 
2342   CURSOR Cur_get_std_um (V_um_type VARCHAR2) IS
2343     SELECT UOM_CODE
2344     FROM   mtl_units_of_measure
2345     WHERE  uom_class = V_um_type
2346     AND BASE_UOM_FLAG = 'Y';
2347 
2348   CURSOR Cur_chk_matrl_umtype(pformula_id NUMBER) IS
2349     SELECT COUNT(distinct m.uom_class)
2350      FROM  fm_matl_dtl d ,mtl_units_of_measure m
2351      WHERE d.DETAIL_UOM = m.uom_code
2352          AND d.formula_id = pformula_id
2353          AND NVL(d.contribute_step_qty_ind, 'Y')  = 'Y'
2354          AND (P_check.formulaline_id IS NULL OR
2355                    formulaline_id <> P_check.formulaline_id);
2356 
2357   CURSOR Cur_get_mtl_umtype(pformula_id NUMBER) IS
2358     SELECT distinct m.uom_class
2359      FROM  fm_matl_dtl d ,mtl_units_of_measure m
2360      WHERE d.DETAIL_UOM= m.uom_code
2361          AND d.formula_id = pformula_id
2362          AND NVL(d.contribute_step_qty_ind, 'Y')  = 'Y'
2363          AND (P_check.formulaline_id IS NULL OR
2364               formulaline_id <> P_check.formulaline_id);
2365 
2366   CURSOR Cur_get_umtyp_cnt(prouting_id NUMBER) IS
2367     SELECT count(distinct u.uom_class)
2368     FROM   fm_rout_dtl d,
2369            gmd_operations_b o,
2370            mtl_units_of_measure u
2371     WHERE  d.oprn_id = o.oprn_id
2372     AND    d.routing_id = prouting_id
2373     AND    o.process_qty_uom = u.uom_code;
2374 
2375   CURSOR Cur_get_process_umtyp(prouting_id NUMBER) IS
2376     SELECT distinct u.uom_class
2377     FROM   fm_rout_dtl d,
2378            gmd_operations_b o,
2379            mtl_units_of_measure u
2380     WHERE  d.oprn_id = o.oprn_id
2381     AND    d.routing_id = prouting_id
2382     AND    o.process_qty_uom = u.uom_code;
2383 
2384 
2385   /* Cursor records.
2386   =====================*/
2387   X_recipe_details_rec  Cur_get_recipe_details%ROWTYPE;
2388   X_um_type             sy_uoms_typ.um_type%TYPE;
2389   X_count               NUMBER := 0;
2390   /* Exceptions.
2391   =====================*/
2392   NO_MATERIAL_STEP_ASSOC	EXCEPTION;
2393   NO_ROUTING_ASSOCIATED		EXCEPTION;
2394 BEGIN
2395 
2396   OPEN Cur_get_recipe_details;
2397   FETCH Cur_get_recipe_details INTO X_recipe_details_rec;
2398   CLOSE Cur_get_recipe_details;
2399 
2400   /* Check whether all the material lines where contribute-step-qty_ind = Y
2401      have been attached to a step */
2402 
2403   /* Populate the global std um variables. */
2404   OPEN Cur_get_std_um (G_profile_mass_um_type);
2405   FETCH Cur_get_std_um INTO G_mass_std_um;
2406   CLOSE Cur_get_std_um;
2407 
2408   OPEN Cur_get_std_um (G_profile_volume_um_type);
2409   FETCH Cur_get_std_um INTO G_vol_std_um;
2410   CLOSE Cur_get_std_um;
2411 
2412   -- Check if material lines are define in mass uom or Vol uom.
2413   -- Bug   2130655
2414   -- Bug # 2362814 Added by Shyam
2415   -- If x_count = 1 it is ok.
2416   OPEN Cur_chk_matrl_umtype(x_recipe_details_rec.formula_id);
2417   FETCH Cur_chk_matrl_umtype INTO x_count;
2418   CLOSE Cur_chk_matrl_umtype;
2419   IF (x_count = 1) THEN
2420     OPEN Cur_get_mtl_umtype(x_recipe_details_rec.formula_id);
2421     FETCH Cur_get_mtl_umtype INTO x_um_type;
2422     CLOSE Cur_get_mtl_umtype;
2423     IF (x_um_type = G_profile_mass_um_type) THEN
2424       p_ignore_vol_conv := TRUE;
2425     ELSIF (x_um_type = G_profile_volume_um_type) THEN
2426       p_ignore_mass_conv := TRUE;
2427     END IF;
2428   ELSIF(x_count > 1) THEN
2429     p_ignore_mass_conv := FALSE;
2430     p_ignore_vol_conv  := FALSE;
2431     return;
2432   END IF;
2433 
2434  IF (x_recipe_details_rec.routing_id IS NOT NULL) THEN
2435    OPEN Cur_get_umtyp_cnt(x_recipe_details_rec.routing_id);
2436    FETCH Cur_get_umtyp_cnt INTO x_count;
2437    CLOSE Cur_get_umtyp_cnt;
2438    /* if x_count is 1 then it could be MASS or VOL or some OTHER type */
2439    IF (x_count = 1) THEN
2440      OPEN Cur_get_process_umtyp(x_recipe_details_rec.routing_id);
2441      FETCH Cur_get_process_umtyp INTO x_um_type;
2442      CLOSE Cur_get_process_umtyp;
2443      IF (x_um_type = G_profile_mass_um_type) THEN
2444        p_ignore_vol_conv := TRUE;
2445      ELSIF (x_um_type = G_profile_volume_um_type) THEN
2446        p_ignore_mass_conv := TRUE;
2447      ELSE
2448       /* Get the other UOM type */
2449        G_PROFILE_OTHER_UM_TYPE := x_um_type;
2450      END IF;
2451    ELSIF(x_count > 1) THEN
2452      p_ignore_mass_conv := FALSE;
2453      p_ignore_vol_conv  := FALSE;
2454      return;
2455    END IF;
2456  END IF;
2457 
2458    -- End Bug 2130655.
2459    IF (G_PROFILE_OTHER_UM_TYPE IS NOT NULL) THEN
2460      OPEN Cur_get_std_um (G_PROFILE_OTHER_UM_TYPE);
2461      FETCH Cur_get_std_um INTO G_other_std_um;
2462      CLOSE Cur_get_std_um;
2463    END IF;
2464 
2465 
2466 EXCEPTION
2467   WHEN OTHERS THEN
2468      p_ignore_mass_conv := FALSE;
2469      p_ignore_vol_conv  := FALSE;
2470 END check_Bch_stp_qty_calculatable;
2471 
2472 
2473 END GMD_AUTO_STEP_CALC;