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.8.12020000.2 2012/08/08 01:15:11 qzeng ship $ */
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   --QZENG Bug 14197174 Added condition BASE_UOM_FLAG = 'Y' to fetch the base uom
839   CURSOR Cur_get_std_um (V_uom_class VARCHAR2) IS
840     SELECT uom_code
841     FROM   mtl_units_of_measure
842     WHERE  uom_class = V_uom_class
843     AND BASE_UOM_FLAG = 'Y';
844 BEGIN
845   -- Initialize the global variable to fix the bug 10161595
846   G_OTHER_UM_TYPE_EXISTS := FALSE;
847   X_num_rows := P_step_tbl.COUNT;
848   FOR i IN 1..X_num_rows LOOP
849 
850     OPEN Cur_get_um_type(P_step_tbl(i).step_qty_uom);
851     FETCH Cur_get_um_type INTO X_um_type;
852     CLOSE Cur_get_um_type;
853 
854     /* Check if the um type fr the current and new step are the same */
855     /* Bug#3431385 - Thomas Daniel */
856     /* Changed the following code to consider the Mass and Volume UOM profiles */
857     /* being NULL */
858     IF (G_profile_mass_um_type IS NULL OR X_um_type <> G_profile_mass_um_type) AND
859        (G_profile_volume_um_type IS NULL OR X_um_type <> G_profile_volume_um_type) THEN
860       IF (X_um_type = l_previous_um_type) THEN
861         l_other_type_cnt := l_other_type_cnt + 1;
862       END IF;
863       l_previous_um_type := X_um_type;
864     END IF;
865 
866   END LOOP;
867 
868   /* If all steps are of the same um type (and not MASS or VOLUME) then it is ok */
869   IF (l_previous_um_type IS NOT NULL) THEN -- there is a other um type
870     IF (l_other_type_cnt = X_num_rows) THEN -- if all step um type are of the same type
871       /* set this as a global profile um type */
872       G_PROFILE_OTHER_UM_TYPE := l_previous_um_type;
873       /* Get the std um for the other um type */
874       OPEN Cur_get_std_um (G_profile_other_um_type);
875       FETCH Cur_get_std_um INTO G_OTHER_STD_UM;
876       CLOSE Cur_get_std_um;
877       /* set this Global variable - it would be used in other procs */
878       G_OTHER_UM_TYPE_EXISTS := TRUE;
879     ELSE -- mixed um type is not allowed
880       -- i.e if there is a other type - all steps should of this um type
881       RETURN (FALSE);
882     END IF;
883   ELSE -- its either mass or volume type um
884     /* Populate the global mass and volume std um variables. */
885     OPEN Cur_get_std_um (G_profile_mass_um_type);
886     FETCH Cur_get_std_um INTO G_mass_std_um;
887     CLOSE Cur_get_std_um;
888 
889     OPEN Cur_get_std_um (G_profile_volume_um_type);
890     FETCH Cur_get_std_um INTO G_vol_std_um;
891     CLOSE Cur_get_std_um;
892   END IF;
893 
894   RETURN (TRUE);
895 END step_uom_mass_volume;
896 
897 /*======================================================================
898 --  PROCEDURE :
899 --    get_step_material_lines
900 --
901 --  DESCRIPTION:
902 --    This PL/SQL procedure  is responsible for fetching the material
903 --    lines associated with the steps.
904 --
905 --  REQUIREMENTS
906 --    p_work_step_tbl  non null value.
907 --  SYNOPSIS:
908 --    get_step_material_lines (426, 100, 0, X_step_tbl, X_work_step_tbl,
909 --                             X_return_status);
910 --
911 --  This procedure calls GMICUOM.uom_conversion
912 --
913 --  HISTORY
914 --  25Jul2001  L.R.Jackson  Changed cursor to use id instead of step_no.
915 --                          Use ic_item_mst_b instead of ic_item_mst
916 --  08FEB2002  Shikha Nagar Changed Cur_get_batch_lines to take scrap_factor
917                             into account.
918 --  08Mar2002  Shrikant Nene Changed the scrap factor calculation
919 --  05Apr2002  Shikha Nagar B2304515 Changed Cur_get_batch_lines to fetch
920                             both planned and actual qty.
921                             Also populating actual_mass_qty and actual_vol_qty
922                             of x_work_step_tbl.
923 --===================================================================== */
924 
925  PROCEDURE get_step_material_lines (P_parent_id		IN NUMBER,
926                                    P_routing_id		IN NUMBER,
927                                    P_called_from_batch	IN NUMBER,
928                                    P_step_tbl		IN step_rec_tbl,
929                                    P_work_step_tbl 	IN OUT NOCOPY work_step_rec_tbl,
930                                    P_return_status 	OUT NOCOPY VARCHAR2,
931                                    p_ignore_mass_conv   IN BOOLEAN DEFAULT FALSE,
932                                    p_ignore_vol_conv    IN BOOLEAN DEFAULT FALSE,
933                                    p_process_loss	IN NUMBER DEFAULT 0) IS
934   /* Local variables.
935   ==================*/
936   X_num_rows	NUMBER;
937   X_cur_rec	NUMBER DEFAULT 0;
938   X_line_qty	NUMBER;
939   X_temp_qty	NUMBER;
940   X_item_id	NUMBER;
941   X_from_uom	mtl_units_of_measure.uom_code%TYPE;
942   X_to_uom      mtl_units_of_measure.uom_code%TYPE;
943   X_item_no	mtl_system_items_kfv.concatenated_segments%TYPE;
944 
945   /* Cursor Definitions.
946   =====================*/
947   CURSOR Cur_get_material_lines (V_step_id NUMBER) IS
948     -- NPD Conv. Use inventory_iem_id and detail_uom instead of item_id and item_um
949     SELECT s.formulaline_id, d.line_type, d.qty, d.detail_uom, d.inventory_item_id, d.scale_type
950     FROM   gmd_recipe_step_materials s,
951            fm_matl_dtl d
952     WHERE  s.recipe_id = P_parent_id
953     AND    s.formulaline_id = d.formulaline_id
954     AND    s.routingstep_id = V_step_id
955     AND    NVL (d.contribute_step_qty_ind, 'Y') = 'Y'
956     ORDER BY d.line_type;
957 
958 -- Bug 9870402  in R12 the plan_qty also includes scrap qty so step qty calc,
959 -- remove it - hence changed the plan_qty to  d.plan_qty/(1+scrap_factor)
960   CURSOR Cur_get_batch_lines (V_step_id NUMBER) IS
961     SELECT b.material_detail_id batchline_id, d.line_type,
962            (d.plan_qty/(1+nvl(scrap_factor,0) ) )  plan_qty,
963            (d.actual_qty/(1+scrap_factor)) actual_qty,
964            d.dtl_um, d.inventory_item_id
965     FROM   gme_batch_step_items b,
966            gme_material_details d,
967            gme_batch_steps r
968     WHERE  b.batch_id = P_parent_id
969     AND    b.batchstep_id = r.batchstep_id
970     AND    b.material_detail_id = d.material_detail_id
971     AND    b.batchstep_id = V_step_id
972     AND    NVL (d.contribute_step_qty_ind, 'Y') = 'Y'
973     ORDER BY d.line_type;
974 
975   -- NPD Conv.
976   CURSOR Cur_get_item IS
977     SELECT concatenated_segments
978     FROM   mtl_system_items_kfv
979     WHERE  inventory_item_id = X_item_id;
980 
981   /* Cursor records.
982   =====================*/
983   -- none.  Cursor FOR loops used.
984 
985   /* Exceptions.
986   =====================*/
987   UOM_CONVERSION_ERROR		EXCEPTION;
988   NO_MATERIAL_STEP_ASSOC	EXCEPTION;
989 
990 BEGIN
991   P_work_step_tbl.DELETE;
992   P_return_status := FND_API.G_RET_STS_SUCCESS;
993   X_num_rows := P_step_tbl.COUNT;
994   FOR i IN 1..X_num_rows LOOP
995 
996     /* If called from GMD */
997     IF P_called_from_batch = 0 THEN
998       FOR X_material_rec IN Cur_get_material_lines (P_step_tbl(i).step_id) LOOP
999         X_cur_rec := X_cur_rec + 1;
1000         P_work_step_tbl(X_cur_rec).step_id := P_step_tbl(i).step_id;
1001         P_work_step_tbl(X_cur_rec).step_no := P_step_tbl(i).step_no;
1002         P_work_step_tbl(X_cur_rec).line_id := X_material_rec.formulaline_id;
1003         P_work_step_tbl(X_cur_rec).line_type := X_material_rec.line_type;
1004 
1005         /* If all steps of OTHER um type then you dont have to bother
1006            about converting line qtys to MASS and VOLUME type um */
1007         IF NOT (G_OTHER_UM_TYPE_EXISTS) THEN
1008           X_temp_qty := INV_CONVERT.inv_um_convert(item_id         => X_material_rec.inventory_item_id
1009                                                    ,precision      => 5
1010                                                    ,from_quantity  => X_material_rec.qty
1011                                                    ,from_unit      => X_material_rec.detail_uom
1012                                                    ,to_unit        => G_mass_std_um
1013                                                    ,from_name      => NULL
1014                                                    ,to_name	   => NULL);
1015 
1016           IF X_temp_qty < 0 THEN
1017             X_item_id := X_material_rec.inventory_item_id;
1018             X_from_uom := X_material_rec.detail_uom;
1019             X_to_uom := G_mass_std_um;
1020             IF (p_ignore_mass_conv = FALSE) THEN
1021               RAISE UOM_CONVERSION_ERROR;
1022             ELSE
1023               P_work_step_tbl(X_cur_rec).line_mass_qty := 0;
1024             END IF;
1025           ELSE
1026               P_work_step_tbl(X_cur_rec).line_mass_qty := X_temp_qty;
1027               /* Bug 1683702 - Thomas Daniel */
1028               /* Apply the process loss to the qty for the calculation of the step qty */
1029               IF X_material_rec.line_type = -1 AND
1030                  X_material_rec.scale_type = 1 AND
1031                  p_process_loss > 0 THEN
1032                 P_work_step_tbl(X_cur_rec).line_mass_qty := P_work_step_tbl(X_cur_rec).line_mass_qty *
1033                                                             100 / (100 - p_process_loss);
1034               END IF;
1035           END IF;
1036 
1037           /*Bug#3599182 - Thomas Daniel */
1038           /*Commented the following IF as we need to proceed with the volume conversion though the mass */
1039           /*conversion has failed as there is a possibility of all the routing steps and the formula lines */
1040           /*belong to the same UOM type */
1041           -- IF (X_temp_qty > 0) THEN
1042             X_temp_qty := INV_CONVERT.inv_um_convert(item_id       => X_material_rec.inventory_item_id
1043                                                    ,precision      => 5
1044                                                    ,from_quantity  => X_material_rec.qty
1045                                                    ,from_unit      => X_material_rec.detail_uom
1046                                                    ,to_unit        => G_vol_std_um
1047                                                    ,from_name      => NULL
1048                                                    ,to_name	   => NULL);
1049             IF X_temp_qty < 0 THEN
1050               X_item_id := X_material_rec.inventory_item_id;
1051               X_from_uom := X_material_rec.detail_uom;
1052               X_to_uom := G_vol_std_um;
1053               IF (p_ignore_vol_conv = FALSE) THEN
1054                 RAISE UOM_CONVERSION_ERROR;
1055               ELSE
1056                 P_work_step_tbl(X_cur_rec).line_vol_qty := 0;
1057               END IF;
1058             ELSE
1059               P_work_step_tbl(X_cur_rec).line_vol_qty := X_temp_qty;
1060               /* Bug 1683702 - Thomas Daniel */
1061               /* Apply the process loss to the qty for the calculation of the step qty */
1062               IF X_material_rec.line_type = -1 AND
1063                  X_material_rec.scale_type = 1 AND
1064                  p_process_loss > 0 THEN
1065                 P_work_step_tbl(X_cur_rec).line_vol_qty := P_work_step_tbl(X_cur_rec).line_vol_qty *
1066                                                             100 / (100 - p_process_loss);
1067               END IF;
1068             END IF;
1069           /*Bug#3599182 - Thomas Daniel */
1070           /*Commented the END IF following IF */
1071           -- END IF;
1072         ELSE  /* When only other um type exists */
1073           /* Added by Shyam - To capture the line qty in the other um types std um */
1074           X_temp_qty := INV_CONVERT.inv_um_convert(item_id       => X_material_rec.inventory_item_id
1075                                                    ,precision      => 5
1076                                                    ,from_quantity  => X_material_rec.qty
1077                                                    ,from_unit      => X_material_rec.detail_uom
1078                                                    ,to_unit        => G_other_std_um
1079                                                    ,from_name      => NULL
1080                                                    ,to_name	   => NULL);
1081           IF X_temp_qty < 0 THEN
1082             X_item_id := X_material_rec.inventory_item_id;
1083             X_from_uom := X_material_rec.detail_uom;
1084             X_to_uom := G_other_std_um;
1085             IF (p_ignore_mass_conv = FALSE) THEN
1086               RAISE UOM_CONVERSION_ERROR;
1087             ELSE
1088               P_work_step_tbl(X_cur_rec).line_other_qty := 0;
1089             END IF;
1090           ELSE
1091             P_work_step_tbl(X_cur_rec).line_other_qty := X_temp_qty;
1092             /* Bug 1683702 - Thomas Daniel */
1093             /* Apply the process loss to the qty for the calculation of the step qty */
1094             IF X_material_rec.line_type = -1 AND
1095                X_material_rec.scale_type = 1 AND
1096                p_process_loss > 0 THEN
1097               P_work_step_tbl(X_cur_rec).line_other_qty := P_work_step_tbl(X_cur_rec).line_other_qty *
1098                                                          100 / (100 - p_process_loss);
1099             END IF;
1100           END IF;
1101         END IF; /* Condition that tests if other um type exists */
1102 
1103       END LOOP; /*WHILE Cur_get_material_lines%FOUND*/
1104 
1105     ELSE /*IF P_called_from_batch = 0.  This section used if called from batch */
1106       FOR X_batch_rec IN Cur_get_batch_lines (P_step_tbl(i).step_id) LOOP
1107         X_cur_rec := X_cur_rec + 1;
1108         P_work_step_tbl(X_cur_rec).step_id := P_step_tbl(i).step_id;
1109         P_work_step_tbl(X_cur_rec).step_no := P_step_tbl(i).step_no;
1110         P_work_step_tbl(X_cur_rec).line_id := X_batch_rec.batchline_id;
1111         P_work_step_tbl(X_cur_rec).line_type := X_batch_rec.line_type;
1112 
1113         /* If all steps of OTHER um type then you dont have to bother
1114            about converting line qtys to MASS and VOLUME type um */
1115         IF NOT (G_OTHER_UM_TYPE_EXISTS) THEN
1116           X_temp_qty := INV_CONVERT.inv_um_convert(item_id         => X_batch_rec.inventory_item_id
1117                                                    ,precision      => 5
1118                                                    ,from_quantity  => X_batch_rec.plan_qty
1119                                                    ,from_unit      => X_batch_rec.dtl_um
1120                                                    ,to_unit        => G_mass_std_um
1121                                                    ,from_name      => NULL
1122                                                    ,to_name	   => NULL);
1123 
1124           IF X_temp_qty < 0 THEN
1125             X_item_id := X_batch_rec.inventory_item_id;
1126             X_from_uom := X_batch_rec.dtl_um;
1127             X_to_uom := G_mass_std_um;
1128             IF(p_ignore_mass_conv = FALSE) THEN
1129               RAISE UOM_CONVERSION_ERROR;
1130             ELSE
1131               P_work_step_tbl(X_cur_rec).line_mass_qty := 0;
1132             END IF;
1133           ELSE
1134             P_work_step_tbl(X_cur_rec).line_mass_qty := X_temp_qty;
1135           END IF;
1136           -- Shikha Nagar B2304515
1137           X_temp_qty := INV_CONVERT.inv_um_convert(item_id         => X_batch_rec.inventory_item_id
1138                                                    ,precision      => 5
1139                                                    ,from_quantity  => X_batch_rec.actual_qty
1140                                                    ,from_unit      => X_batch_rec.dtl_um
1141                                                    ,to_unit        => G_mass_std_um
1142                                                    ,from_name      => NULL
1143                                                    ,to_name	   => NULL);
1144           IF X_temp_qty < 0 THEN
1145             X_item_id := X_batch_rec.inventory_item_id;
1146             X_from_uom := X_batch_rec.dtl_um;
1147             X_to_uom := G_mass_std_um;
1148             IF(p_ignore_mass_conv = FALSE) THEN
1149               RAISE UOM_CONVERSION_ERROR;
1150             ELSE
1151               P_work_step_tbl(X_cur_rec).actual_mass_qty := 0;
1152             END IF;
1153           ELSE
1154             P_work_step_tbl(X_cur_rec).actual_mass_qty := X_temp_qty;
1155           END IF;
1156 
1157           X_temp_qty := INV_CONVERT.inv_um_convert(item_id         => X_batch_rec.inventory_item_id
1158                                                    ,precision      => 5
1159                                                    ,from_quantity  => X_batch_rec.plan_qty
1160                                                    ,from_unit      => X_batch_rec.dtl_um
1161                                                    ,to_unit        => G_vol_std_um
1162                                                    ,from_name      => NULL
1163                                                    ,to_name	   => NULL);
1164           IF X_temp_qty < 0 THEN
1165             X_item_id := X_batch_rec.inventory_item_id;
1166             X_from_uom := X_batch_rec.dtl_um;
1167             X_to_uom := G_vol_std_um;
1168             IF (p_ignore_vol_conv = FALSE) THEN
1169               RAISE UOM_CONVERSION_ERROR;
1170             ELSE
1171               P_work_step_tbl(X_cur_rec).line_vol_qty := 0;
1172             END IF;
1173           ELSE
1174               P_work_step_tbl(X_cur_rec).line_vol_qty := X_temp_qty;
1175           END IF;
1176 
1177           -- Shikha Nagar B2304515
1178           X_temp_qty := INV_CONVERT.inv_um_convert(item_id         => X_batch_rec.inventory_item_id
1179                                                    ,precision      => 5
1180                                                    ,from_quantity  => X_batch_rec.actual_qty
1181                                                    ,from_unit      => X_batch_rec.dtl_um
1182                                                    ,to_unit        => G_vol_std_um
1183                                                    ,from_name      => NULL
1184                                                    ,to_name	   => NULL);
1185           IF X_temp_qty < 0 THEN
1186             X_item_id := X_batch_rec.inventory_item_id;
1187             X_from_uom := X_batch_rec.dtl_um;
1188             X_to_uom := G_vol_std_um;
1189             IF (p_ignore_vol_conv = FALSE) THEN
1190               RAISE UOM_CONVERSION_ERROR;
1191             ELSE
1192               P_work_step_tbl(X_cur_rec).actual_vol_qty := 0;
1193             END IF;
1194           ELSE
1195              P_work_step_tbl(X_cur_rec).actual_vol_qty := X_temp_qty;
1196           END IF;
1197 
1198          ELSE /* Condition that checks for other type um */
1199            X_temp_qty := INV_CONVERT.inv_um_convert(item_id         => X_batch_rec.inventory_item_id
1200                                                    ,precision      => 5
1201                                                    ,from_quantity  => X_batch_rec.plan_qty
1202                                                    ,from_unit      => X_batch_rec.dtl_um
1203                                                    ,to_unit        => G_other_std_um
1204                                                    ,from_name      => NULL
1205                                                    ,to_name	   => NULL);
1206 
1207           IF X_temp_qty < 0 THEN
1208             X_item_id := X_batch_rec.inventory_item_id;
1209             X_from_uom := X_batch_rec.dtl_um;
1210             X_to_uom := G_other_std_um;
1211             IF(p_ignore_mass_conv = FALSE) THEN
1212               RAISE UOM_CONVERSION_ERROR;
1213             ELSE
1214               P_work_step_tbl(X_cur_rec).line_other_qty := 0;
1215             END IF;
1216           ELSE
1217             P_work_step_tbl(X_cur_rec).line_other_qty := X_temp_qty;
1218           END IF;
1219           -- Shikha Nagar B2304515
1220           X_temp_qty := INV_CONVERT.inv_um_convert(item_id         => X_batch_rec.inventory_item_id
1221                                                    ,precision      => 5
1222                                                    ,from_quantity  => X_batch_rec.actual_qty
1223                                                    ,from_unit      => X_batch_rec.dtl_um
1224                                                    ,to_unit        => G_other_std_um
1225                                                    ,from_name      => NULL
1226                                                    ,to_name	   => NULL);
1227 
1228           IF X_temp_qty < 0 THEN
1229             X_item_id := X_batch_rec.inventory_item_id;
1230             X_from_uom := X_batch_rec.dtl_um;
1231             X_to_uom := G_other_std_um;
1232             IF(p_ignore_mass_conv = FALSE) THEN
1233               RAISE UOM_CONVERSION_ERROR;
1234             ELSE
1235               P_work_step_tbl(X_cur_rec).actual_other_qty := 0;
1236             END IF;
1237           ELSE
1238             P_work_step_tbl(X_cur_rec).actual_other_qty := X_temp_qty;
1239           END IF;
1240         END IF; /* condition for other type um */
1241       END LOOP; /*WHILE Cur_get_batch_lines%FOUND*/
1242 
1243     END IF; /*IF P_called_from_batch = 0*/
1244   END LOOP; /* FOR i IN 1..X_num_rows */
1245   IF X_cur_rec = 0 THEN
1246     RAISE NO_MATERIAL_STEP_ASSOC;
1247   END IF;
1248 
1249 EXCEPTION
1250   WHEN UOM_CONVERSION_ERROR THEN
1251     P_return_status := FND_API.G_RET_STS_ERROR;
1252     OPEN Cur_get_item;
1253     FETCH Cur_get_item INTO X_item_no;
1254     CLOSE Cur_get_item;
1255     FND_MESSAGE.SET_NAME('GMI', 'IC_API_UOM_CONVERSION_ERROR');
1256     FND_MESSAGE.SET_TOKEN('ITEM_NO', X_item_no);
1257     FND_MESSAGE.SET_TOKEN('FROM_UOM', X_from_uom);
1258     FND_MESSAGE.SET_TOKEN('TO_UOM', X_to_uom);
1259     FND_MSG_PUB.ADD;
1260   WHEN NO_MATERIAL_STEP_ASSOC THEN
1261     P_return_status := FND_API.G_RET_STS_ERROR;
1262     FND_MESSAGE.SET_NAME('GMD', 'GMD_MISSING_MATL_STEP_ASSOC');
1263     FND_MSG_PUB.ADD;
1264   WHEN OTHERS THEN
1265     P_return_status := FND_API.G_RET_STS_UNEXP_ERROR;
1266     FND_MSG_PUB.ADD;
1267 END get_step_material_lines;
1268 
1269 
1270 /* Added by Shyam for GMF */
1271 /*======================================================================
1272 --  PROCEDURE : Overloaded
1273 --    get_step_material_lines
1274 --
1275 --  DESCRIPTION:
1276 --    This PL/SQL overloaded procedure is responsible for fetching the sclaed material
1277 --    lines associated with the steps.
1278 --
1279 --  REQUIREMENTS
1280 --    p_work_step_tbl  non null value.
1281 --    p_scale_factor   not null value.
1282 --  SYNOPSIS:
1283 --    get_step_material_lines (426, 100, 0, X_step_tbl,P_scale_factor, X_work_step_tbl,
1284 --                             X_return_status);
1285 --
1286 --  This procedure calls GMICUOM.uom_conversion
1287 --
1288 --  HISTORY
1289 --  Shyam   05/10/2002  Initial Implementation
1290 ======================================================================== */
1291 
1292 PROCEDURE get_step_material_lines (P_parent_id		IN NUMBER,
1293                                    P_routing_id		IN NUMBER,
1294                                    P_called_from_batch	IN NUMBER,
1295                                    P_step_tbl		IN step_rec_tbl,
1296                                    P_scale_factor       IN NUMBER ,
1297                                    P_work_step_tbl 	IN OUT NOCOPY work_step_rec_tbl,
1298                                    P_return_status 	OUT NOCOPY VARCHAR2,
1299                                    p_ignore_mass_conv   IN BOOLEAN DEFAULT FALSE,
1300                                    p_ignore_vol_conv    IN BOOLEAN DEFAULT FALSE,
1301                                    p_process_loss	IN NUMBER DEFAULT 0) IS
1302 
1303   /* Local variables.
1304   ==================*/
1305   X_num_rows	NUMBER;
1306   X_cur_rec	NUMBER DEFAULT 0;
1307   X_line_qty	NUMBER;
1308   X_temp_qty	NUMBER;
1309   X_item_id	NUMBER;
1310   X_from_uom	mtl_units_of_measure.uom_code%TYPE;
1311   X_to_uom      mtl_units_of_measure.uom_code%TYPE;
1312   X_item_no	mtl_system_items_kfv.concatenated_segments%TYPE;
1313 
1314 
1315   /* Scaling realted variables */
1316   k                    NUMBER  := 0;
1317   x_cost_row_cnt       NUMBER  := 0;
1318   x_cost_return_status VARCHAR2(1);
1319   p_cost_scale_tab     GMD_COMMON_SCALE.scale_tab;
1320   x_cost_scale_tab     GMD_COMMON_SCALE.scale_tab;
1321 
1322   /* This table associates the formulaline with the - scaled qtys in x_cost_scale_tab */
1323   P_formulaline_scale_tab  formulaline_scale_tab;
1324 
1325   /* Cursor Definitions.
1326   =====================*/
1327   CURSOR Cur_get_material_lines (V_step_id NUMBER) IS
1328     -- NPD Conv. Use inventory_item_id and detail_uom instead of item_id and item_um from fm_matl_dtl
1329     SELECT s.formulaline_id, d.line_type, d.qty, d.detail_uom, d.inventory_item_id, d.scale_type
1330     FROM   gmd_recipe_step_materials s,
1331            fm_matl_dtl d
1332     WHERE  s.recipe_id = P_parent_id
1333     AND    s.formulaline_id = d.formulaline_id
1334     AND    s.routingstep_id = V_step_id
1335     AND    NVL (d.contribute_step_qty_ind, 'Y') = 'Y'
1336     ORDER BY d.line_type;
1337 
1338   -- NPD Conv.
1339   CURSOR Cur_get_item IS
1340     SELECT concatenated_segments
1341     FROM   mtl_system_items_kfv
1342     WHERE  inventory_item_id = X_item_id;
1343 
1344   /* Get all formulaline information */
1345   CURSOR Cur_get_formulaline_info  IS
1346     SELECT d.*
1347     FROM  fm_matl_dtl d ,
1348           gmd_recipes_b r
1349     WHERE r.recipe_id = P_parent_id
1350       AND r.formula_id = d.formula_id
1351     ORDER BY d.line_type, d.line_no;
1352 
1353   -- NPD Conv. Get the formula owner orgn id
1354   CURSOR get_formula_owner_orgn_id IS
1355     SELECT f.owner_organization_id
1356     FROM   fm_form_mst f, gmd_recipes r
1357     WHERE  r.recipe_id = P_parent_id
1358     AND    f.formula_id = r.formula_id;
1359 
1360  l_orgn_id NUMBER;
1361 
1362   /* Exceptions.
1363   =====================*/
1364   UOM_CONVERSION_ERROR		EXCEPTION;
1365   NO_MATERIAL_STEP_ASSOC	EXCEPTION;
1366   COST_SCALING_ERROR            EXCEPTION;
1367 
1368 BEGIN
1369   P_work_step_tbl.DELETE;
1370   P_return_status := FND_API.G_RET_STS_SUCCESS;
1371 
1372   /* Perform the formula scaling first */
1373   /* Scale the formula using the scale factor */
1374 
1375   /* p_cost_scale_tab holds all formula scaled qtys */
1376   /* p_formulaline_scale_tab holds all formulaline and its scaled qtys */
1377 
1378   /* Initialize all tables */
1379   x_cost_scale_tab.DELETE;
1380   p_cost_scale_tab.DELETE;
1381   p_formulaline_scale_tab.DELETE;
1382 
1383   FOR X_formulaline_rec IN Cur_get_formulaline_info LOOP
1384 
1385     X_cost_row_cnt := X_cost_row_cnt + 1;
1386     -- NPD Conv. Use inventory_item_id and detail_uom instead of item_id and item_um
1387     p_cost_scale_tab(X_cost_row_cnt).line_no                 := X_formulaline_rec.line_no                ;
1388     p_cost_scale_tab(X_cost_row_cnt).line_type               := X_formulaline_rec.line_type              ;
1389     p_cost_scale_tab(X_cost_row_cnt).inventory_item_id       := X_formulaline_rec.inventory_item_id                ;
1390     p_cost_scale_tab(X_cost_row_cnt).qty                     := X_formulaline_rec.qty                    ;
1391     p_cost_scale_tab(X_cost_row_cnt).detail_uom              := X_formulaline_rec.detail_uom             ;
1392     p_cost_scale_tab(X_cost_row_cnt).scale_type              := X_formulaline_rec.scale_type             ;
1393     p_cost_scale_tab(X_cost_row_cnt).contribute_yield_ind    := X_formulaline_rec.contribute_yield_ind   ;
1394     p_cost_scale_tab(X_cost_row_cnt).scale_multiple          := X_formulaline_rec.scale_multiple         ;
1395     p_cost_scale_tab(X_cost_row_cnt).scale_rounding_variance := X_formulaline_rec.scale_rounding_variance;
1396     p_cost_scale_tab(X_cost_row_cnt).rounding_direction      := X_formulaline_rec.rounding_direction     ;
1397     p_formulaline_scale_tab(X_cost_row_cnt).formulaline_id   := X_formulaline_rec.formulaline_id         ;
1398   END LOOP;
1399 
1400   -- NPD Conv.
1401   OPEN get_formula_owner_orgn_id;
1402   FETCH get_formula_owner_orgn_id INTO l_orgn_id;
1403   CLOSE get_formula_owner_orgn_id;
1404 
1405   /* Calling the scaling API  */
1406   gmd_common_scale.scale( p_scale_tab      => p_cost_scale_tab
1407                           ,p_orgn_id       => l_orgn_id
1408                           ,p_scale_factor  => P_scale_factor
1409                           ,p_primaries     => 'OUTPUTS'
1410                           ,x_scale_tab     => x_cost_scale_tab
1411                           ,x_return_status => x_cost_return_status
1412                          );
1413 
1414   IF (x_cost_return_status <> 'S') THEN
1415      RAISE COST_SCALING_ERROR;
1416   END IF;
1417 
1418   /* Associate formulaline id with scaled values  */
1419   FOR i IN 1 .. x_cost_scale_tab.count LOOP
1420     p_formulaline_scale_tab(i).line_no                 :=  x_cost_scale_tab(i).line_no                ;
1421     p_formulaline_scale_tab(i).line_type               :=  x_cost_scale_tab(i).line_type              ;
1422     p_formulaline_scale_tab(i).inventory_item_id       :=  x_cost_scale_tab(i).inventory_item_id      ;
1423     p_formulaline_scale_tab(i).qty                     :=  x_cost_scale_tab(i).qty                    ;
1424     p_formulaline_scale_tab(i).detail_uom              :=  x_cost_scale_tab(i).detail_uom                ;
1425     p_formulaline_scale_tab(i).scale_type              :=  x_cost_scale_tab(i).scale_type             ;
1426     p_formulaline_scale_tab(i).contribute_yield_ind    :=  x_cost_scale_tab(i).contribute_yield_ind   ;
1427     p_formulaline_scale_tab(i).scale_multiple          :=  x_cost_scale_tab(i).scale_multiple         ;
1428     p_formulaline_scale_tab(i).scale_rounding_variance :=  x_cost_scale_tab(i).scale_rounding_variance;
1429     p_formulaline_scale_tab(i).rounding_direction      :=  x_cost_scale_tab(i).rounding_direction     ;
1430   END LOOP;
1431 
1432   X_num_rows := P_step_tbl.COUNT;
1433   FOR i IN 1..X_num_rows LOOP
1434 
1435     /* If called from GMF */
1436     IF (P_called_from_batch = 0) THEN
1437 
1438       FOR X_material_rec IN Cur_get_material_lines (P_step_tbl(i).step_id) LOOP
1439         X_cur_rec := X_cur_rec + 1;
1440         P_work_step_tbl(X_cur_rec).step_id := P_step_tbl(i).step_id;
1441         P_work_step_tbl(X_cur_rec).step_no := P_step_tbl(i).step_no;
1442         P_work_step_tbl(X_cur_rec).line_id := X_material_rec.formulaline_id;
1443         P_work_step_tbl(X_cur_rec).line_type := X_material_rec.line_type;
1444 
1445         FOR k in 1 .. x_cost_scale_tab.count LOOP
1446           IF (X_material_rec.formulaline_id = p_formulaline_scale_tab(k).formulaline_id) THEN
1447             /* If all steps of OTHER um type then you dont have to bother
1448                about converting line qtys to MASS and VOLUME type um */
1449             IF NOT (G_OTHER_UM_TYPE_EXISTS) THEN
1450               X_temp_qty := INV_CONVERT.inv_um_convert(item_id     => X_material_rec.inventory_item_id
1451                                                    ,precision      => 5
1452                                                    ,from_quantity  => p_formulaline_scale_tab(k).qty
1453                                                    ,from_unit      => p_formulaline_scale_tab(k).detail_uom
1454                                                    ,to_unit        => G_mass_std_um
1455                                                    ,from_name      => NULL
1456                                                    ,to_name	   => NULL);
1457 
1458               IF X_temp_qty < 0 THEN
1459                 X_item_id := X_material_rec.inventory_item_id;  -- NPD Conv.
1460                 X_from_uom := X_material_rec.detail_uom;  -- NPD Conv.
1461                 X_to_uom := G_mass_std_um;
1462                 IF (p_ignore_mass_conv = FALSE) THEN
1463                   RAISE UOM_CONVERSION_ERROR;
1464                 ELSE
1465                   P_work_step_tbl(X_cur_rec).line_mass_qty := 0;
1466                 END IF;
1467               ELSE
1468                 P_work_step_tbl(X_cur_rec).line_mass_qty := X_temp_qty;
1469                 /* Bug 1683702 - Thomas Daniel */
1470                 /* Apply the process loss to the qty for the calculation of the step qty */
1471                 IF X_material_rec.line_type = -1 AND
1472                    X_material_rec.scale_type = 1 AND
1473                    p_process_loss > 0 THEN
1474                   P_work_step_tbl(X_cur_rec).line_mass_qty := P_work_step_tbl(X_cur_rec).line_mass_qty *
1475                                                             100 / (100 - p_process_loss);
1476                 END IF;
1477               END IF;  /* x_temp_qty > 0 condition */
1478 
1479               /*Bug#3599182 - Thomas Daniel */
1480               /*Commented the following IF as we need to proceed with the volume conversion though the mass */
1481               /*conversion has failed as there is a possibility of all the routing steps and the formula lines */
1482               /*belong to the same UOM type */
1483               -- IF (X_temp_qty > 0) THEN
1484                 X_temp_qty := INV_CONVERT.inv_um_convert(item_id   => X_material_rec.inventory_item_id
1485                                                    ,precision      => 5
1486                                                    ,from_quantity  => p_formulaline_scale_tab(k).qty
1487                                                    ,from_unit      => p_formulaline_scale_tab(k).detail_uom
1488                                                    ,to_unit        => G_vol_std_um
1489                                                    ,from_name      => NULL
1490                                                    ,to_name	   => NULL);
1491                 IF X_temp_qty < 0 THEN
1492                   X_item_id := X_material_rec.inventory_item_id;
1493                   X_from_uom := X_material_rec.detail_uom;
1494                   X_to_uom := G_vol_std_um;
1495                   IF (p_ignore_vol_conv = FALSE) THEN
1496                     RAISE UOM_CONVERSION_ERROR;
1497                   ELSE
1498                     P_work_step_tbl(X_cur_rec).line_vol_qty := 0;
1499                   END IF;
1500                 ELSE
1501                   P_work_step_tbl(X_cur_rec).line_vol_qty := X_temp_qty;
1502                   /* Bug 1683702 - Thomas Daniel */
1503                   /* Apply the process loss to the qty for the calculation of the step qty */
1504                   IF X_material_rec.line_type = -1 AND
1505                     X_material_rec.scale_type = 1 AND
1506                     p_process_loss > 0 THEN
1507                     P_work_step_tbl(X_cur_rec).line_vol_qty := P_work_step_tbl(X_cur_rec).line_vol_qty *
1508                                                                100 / (100 - p_process_loss);
1509                   END IF;
1510                 END IF;
1511               /*Bug#3599182 - Thomas Daniel */
1512               /*Commented the ENDIF following IF */
1513               -- END IF;  /* x_temp_qty > 0 condition */
1514 
1515             ELSE /* When only other um type exists */
1516               /* Added by Shyam - To capture the line qty in the other um types std um */
1517               X_temp_qty := INV_CONVERT.inv_um_convert(item_id     => X_material_rec.inventory_item_id
1518                                                    ,precision      => 5
1519                                                    ,from_quantity  => p_formulaline_scale_tab(k).qty
1520                                                    ,from_unit      => p_formulaline_scale_tab(k).detail_uom
1521                                                    ,to_unit        => G_other_std_um
1522                                                    ,from_name      => NULL
1523                                                    ,to_name	   => NULL);
1524               IF X_temp_qty < 0 THEN
1525                  X_item_id := X_material_rec.inventory_item_id;
1526                  X_from_uom := X_material_rec.detail_uom;
1527                  X_to_uom := G_other_std_um;
1528                  IF (p_ignore_mass_conv = FALSE) THEN
1529                    RAISE UOM_CONVERSION_ERROR;
1530                  ELSE
1531                    P_work_step_tbl(X_cur_rec).line_other_qty := 0;
1532                  END IF;
1533               ELSE
1534                 P_work_step_tbl(X_cur_rec).line_other_qty := X_temp_qty;
1535                 /* Bug 1683702 - Thomas Daniel */
1536                 /* Apply the process loss to the qty for the calculation of the step qty */
1537                 IF X_material_rec.line_type = -1 AND
1538                    X_material_rec.scale_type = 1 AND
1539                    p_process_loss > 0 THEN
1540                   P_work_step_tbl(X_cur_rec).line_other_qty := P_work_step_tbl(X_cur_rec).line_other_qty *
1541                                                               100 / (100 - p_process_loss);
1542                 END IF;
1543               END IF;
1544             END IF; /* Condition that tests if other um type exists */
1545 
1546             EXIT; /* because the match in formulaline btw cursor and table type has occured */
1547          END IF; /* Condition when the formulaine in material_rec is same as that in
1548                     x_formulaline_scale_tab */
1549        END LOOP ; /* for the FOR formulaline in x_formulaline_scale_tab */
1550 
1551        /* K needs to be reset to zero */
1552        k := 0;
1553 
1554      END LOOP; /*For Cur_get_material_lines%FOUND*/
1555     END IF; /* if p_batch .. condition */
1556   END LOOP; /* FOR i IN 1..X_num_rows */
1557 
1558   IF X_cur_rec = 0 THEN
1559     RAISE NO_MATERIAL_STEP_ASSOC;
1560   END IF;
1561 
1562 EXCEPTION
1563   WHEN UOM_CONVERSION_ERROR THEN
1564     P_return_status := FND_API.G_RET_STS_ERROR;
1565     OPEN Cur_get_item;
1566     FETCH Cur_get_item INTO X_item_no;
1567     CLOSE Cur_get_item;
1568     FND_MESSAGE.SET_NAME('GMI', 'IC_API_UOM_CONVERSION_ERROR');
1569     FND_MESSAGE.SET_TOKEN('ITEM_NO', X_item_no);
1570     FND_MESSAGE.SET_TOKEN('FROM_UOM', X_from_uom);
1571     FND_MESSAGE.SET_TOKEN('TO_UOM', X_to_uom);
1572     FND_MSG_PUB.ADD;
1573   WHEN NO_MATERIAL_STEP_ASSOC THEN
1574     P_return_status := FND_API.G_RET_STS_ERROR;
1575     FND_MESSAGE.SET_NAME('GMD', 'GMD_MISSING_MATL_STEP_ASSOC');
1576     FND_MSG_PUB.ADD;
1577   WHEN COST_SCALING_ERROR THEN
1578     P_return_status := FND_API.G_RET_STS_ERROR;
1579   WHEN OTHERS THEN
1580     P_return_status := FND_API.G_RET_STS_UNEXP_ERROR;
1581     FND_MSG_PUB.ADD;
1582 END get_step_material_lines;
1583 
1584 
1585 /*======================================================================
1586 --  FUNCTION :
1587 --    get_step_rec
1588 --
1589 --  DESCRIPTION:
1590 --    This PL/SQL procedure  is responsible for returning the row number
1591 --    associated with the step.
1592 --  REQUIREMENTS
1593 --    p_step_tbl  non null value.
1594 --  SYNOPSIS:
1595 --    X_rec := get_step_rec (<routingstep_no>, X_step_tbl);
1596 --
1597 --  25Jul2001  L.R.Jackson  Reworked to have only one RETURN, and to
1598 --               use WHILE instead of FOR.
1599 --===================================================================== */
1600 
1601 FUNCTION get_step_rec (P_step_no	IN NUMBER,
1602                        P_step_tbl	IN step_rec_tbl)
1603          RETURN NUMBER IS
1604 
1605   /* Local variables.
1606   ==================*/
1607   X_cur_rec	    NUMBER  := 1;
1608   X_num_rows    NUMBER  := 0;
1609   X_done        BOOLEAN := FALSE;
1610 
1611 BEGIN
1612   WHILE (X_cur_rec <= P_step_tbl.COUNT) AND NOT X_done LOOP
1613     IF P_step_tbl(X_cur_rec).step_no = P_step_no THEN
1614       X_done := TRUE;
1615       X_num_rows := X_cur_rec;
1616     END IF;
1617     X_cur_rec := X_cur_rec + 1;
1618   END LOOP;
1619   RETURN (X_num_rows);
1620 END get_step_rec;
1621 
1622 
1623 /*======================================================================
1624 --  PROCEDURE :
1625 --    sort_step_lines
1626 --
1627 --  DESCRIPTION:
1628 --    This PL/SQL procedure  is responsible for sorting the step table
1629 --    based on the step no
1630 --  REQUIREMENTS
1631 --    p_step_tbl  non null value.
1632 --  SYNOPSIS:
1633 --    sort_step_lines (X_step_tbl);
1634 --
1635 -- 25Jul2001  L.R.Jackson  Added step_id to list of columns to move.
1636 --              Moved this procedure up with others called by calc_step_qty
1637 --===================================================================== */
1638 
1639 PROCEDURE sort_step_lines (P_step_tbl	IN OUT NOCOPY step_rec_tbl,
1640                            P_return_status OUT NOCOPY VARCHAR2) IS
1641   /* Local variables.
1642   ==================*/
1643   X_step_id		NUMBER;
1644   X_step_no             NUMBER;
1645   X_step_qty            NUMBER;
1646   X_step_qty_uom        sy_uoms_mst.um_code%TYPE;
1647   X_step_mass_qty       NUMBER;
1648   X_step_vol_qty        NUMBER;
1649   X_step_other_qty       NUMBER;
1650   X_count               NUMBER;
1651 BEGIN
1652   P_return_status := FND_API.G_RET_STS_SUCCESS;
1653   X_count := P_step_tbl.COUNT;
1654   FOR i IN 1..X_count LOOP
1655     FOR j IN i+1..X_count LOOP
1656       IF P_step_tbl(i).step_no > P_step_tbl(j).step_no THEN
1657         X_step_id       := P_step_tbl(i).step_id;
1658         X_step_no       := P_step_tbl(i).step_no;
1659         X_step_qty      := P_step_tbl(i).step_qty;
1660         X_step_qty_uom  := P_step_tbl(i).step_qty_uom;
1661         X_step_mass_qty := P_step_tbl(i).step_mass_qty;
1662         X_step_vol_qty  := P_step_tbl(i).step_vol_qty;
1663         X_step_other_qty  := P_step_tbl(i).step_other_qty;
1664 
1665         P_step_tbl(i).step_id       := P_step_tbl(j).step_id;
1666         P_step_tbl(i).step_no       := P_step_tbl(j).step_no;
1667         P_step_tbl(i).step_qty      := P_step_tbl(j).step_qty;
1668         P_step_tbl(i).step_qty_uom  := P_step_tbl(j).step_qty_uom;
1669         P_step_tbl(i).step_mass_qty := P_step_tbl(j).step_mass_qty;
1670         P_step_tbl(i).step_vol_qty  := P_step_tbl(j).step_vol_qty;
1671         P_step_tbl(i).step_other_qty  := P_step_tbl(j).step_other_qty;
1672 
1673         P_step_tbl(j).step_id       := X_step_id;
1674         P_step_tbl(j).step_no       := X_step_no;
1675         P_step_tbl(j).step_qty      := X_step_qty;
1676         P_step_tbl(j).step_qty_uom  := X_step_qty_uom;
1677         P_step_tbl(j).step_mass_qty := X_step_mass_qty;
1678         P_step_tbl(j).step_vol_qty  := X_step_vol_qty;
1679         P_step_tbl(j).step_other_qty  := X_step_other_qty;
1680 
1681       END IF;
1682     END LOOP; /* FOR j IN 1..X_count */
1683   END LOOP; /* FOR i IN 1..X_count */
1684 EXCEPTION
1685   WHEN OTHERS THEN
1686      P_return_status := FND_API.G_RET_STS_UNEXP_ERROR;
1687      FND_MSG_PUB.ADD;
1688 END sort_step_lines;
1689 
1690 
1691 /*======================================================================
1692 --  PROCEDURE :
1693 --    check_step_qty_calculatable
1694 --
1695 --  DESCRIPTION:
1696 --    This PL/SQL procedure  is responsible for checking whether the
1697 --    automatic step quantity calculation can be performed.
1698 --
1699 --  REQUIREMENTS
1700 --    p_parent_id  non null value.
1701 --  SYNOPSIS:
1702 --    check_step_qty_calculatable (426, X_msg_count, X_msg_stack,
1703 --                             X_return_status);
1704 --
1705 --  This procedure calls GMICUOM.uom_conversion
1706 --
1707 --
1708 --===================================================================== */
1709 
1710 PROCEDURE check_step_qty_calculatable (P_check            IN  calculatable_rec_type,
1711     	                               P_msg_count        OUT NOCOPY NUMBER,
1712                                        P_msg_stack        OUT NOCOPY VARCHAR2,
1713                                        P_return_status    OUT NOCOPY VARCHAR2,
1714                                        P_ignore_mass_conv OUT NOCOPY BOOLEAN,
1715                                        P_ignore_vol_conv  OUT NOCOPY BOOLEAN,
1716 				       P_organization_id  IN  NUMBER) IS
1717   /* Local variables.
1718   ==================*/
1719   X_exists	NUMBER(5);
1720   X_temp_qty	NUMBER;
1721   X_item_id	NUMBER;
1722   X_from_uom	mtl_units_of_measure.uom_code%TYPE;
1723   X_to_uom      mtl_units_of_measure.uom_code%TYPE;
1724   X_item_no	mtl_system_items_kfv.concatenated_segments%TYPE;
1725 
1726   /* Cursor Definitions.
1727   =====================*/
1728   CURSOR Cur_get_recipe_details IS
1729     SELECT formula_id, routing_id
1730     FROM   gmd_recipes_b
1731     WHERE  recipe_id = P_check.parent_id;
1732 
1733   CURSOR Cur_get_rout_details (V_routing_id NUMBER) IS
1734     SELECT 1
1735     FROM   sys.dual
1736     WHERE EXISTS (SELECT 1
1737                   FROM   fm_rout_dtl
1738                   WHERE  routing_id = V_routing_id);
1739 
1740   -- p_formulaline_id would have a value if this procedure is called
1741   -- from cascade_del_to_step_mat.  From the formula details form, the delete of
1742   -- the formula line would not be committed yet.  Process the rest of
1743   -- the lines, not the line which is being deleted.
1744   CURSOR Cur_check_matl_lines_assoc (V_formula_id NUMBER) IS
1745     SELECT 1
1746     FROM   fm_matl_dtl
1747     WHERE  formula_id = V_formula_id
1748     AND    NVL(contribute_step_qty_ind, 'Y') = 'Y'
1749     AND    formulaline_id NOT IN (SELECT formulaline_id
1750                                   FROM   gmd_recipe_step_materials
1751                                   WHERE  recipe_id = P_check.parent_id)
1752     AND (P_check.formulaline_id IS NULL OR
1753                formulaline_id <> P_check.formulaline_id)
1754     ;
1755 
1756   CURSOR Cur_get_material_lines (V_formula_id NUMBER) IS
1757     SELECT d.qty, d.detail_uom, d.inventory_item_id
1758     FROM   fm_matl_dtl d
1759     WHERE  d.formula_id = V_formula_id
1760       AND    NVL(d.contribute_step_qty_ind, 'Y')  = 'Y'
1761       AND (P_check.formulaline_id IS NULL OR
1762                    formulaline_id <> P_check.formulaline_id)
1763     ;
1764 
1765   CURSOR Cur_get_item IS
1766     SELECT concatenated_segments
1767     FROM   mtl_system_items_kfv
1768     WHERE  inventory_item_id = X_item_id;
1769 
1770   --QZENG Bug 14197174 Added condition BASE_UOM_FLAG = 'Y' to fetch the base uom
1771   CURSOR Cur_get_std_um (V_uom_class VARCHAR2) IS
1772     SELECT uom_code
1773     FROM   mtl_units_of_measure
1774     WHERE  uom_class = V_uom_class
1775     AND BASE_UOM_FLAG = 'Y';
1776 
1777   CURSOR Cur_chk_matrl_umtype(pformula_id NUMBER) IS
1778     SELECT COUNT(distinct uom_class)
1779      FROM  fm_matl_dtl d ,mtl_units_of_measure m
1780      WHERE d.detail_uom = m.uom_code
1781          AND d.formula_id = pformula_id
1782          AND NVL(d.contribute_step_qty_ind, 'Y')  = 'Y'
1783          AND (P_check.formulaline_id IS NULL OR
1784                    formulaline_id <> P_check.formulaline_id);
1785 
1786   CURSOR Cur_get_mtl_umtype(pformula_id NUMBER) IS
1787     SELECT distinct m.uom_class
1788      FROM  fm_matl_dtl d ,mtl_units_of_measure m
1789      WHERE d.detail_uom = m.uom_code
1790          AND d.formula_id = pformula_id
1791          AND NVL(d.contribute_step_qty_ind, 'Y')  = 'Y'
1792          AND (P_check.formulaline_id IS NULL OR
1793               formulaline_id <> P_check.formulaline_id);
1794 
1795   CURSOR Cur_check_depstps (prouting_id NUMBER) IS
1796     SELECT count(*)
1797     FROM  fm_rout_dtl h,fm_rout_dep d
1798     WHERE h.routing_id = prouting_id AND
1799           h.routing_id = d.routing_id;
1800 
1801   CURSOR Cur_get_umtyp_cnt(prouting_id NUMBER) IS
1802     SELECT count(distinct u.uom_class)
1803     FROM   fm_rout_dtl d,
1804            gmd_operations_b o,
1805            mtl_units_of_measure u
1806     WHERE  d.oprn_id = o.oprn_id
1807     AND    d.routing_id = prouting_id
1808     AND    o.process_qty_uom = u.uom_code;
1809 
1810 
1811   CURSOR Cur_get_process_umtyp(prouting_id NUMBER) IS
1812     SELECT distinct u.uom_class
1813     FROM   fm_rout_dtl d,
1814            gmd_operations_b o,
1815            mtl_units_of_measure u
1816     WHERE  d.oprn_id = o.oprn_id
1817     AND    d.routing_id = prouting_id
1818     AND    o.process_qty_uom = u.uom_code;
1819 
1820 
1821   /* Cursor records.
1822   =====================*/
1823   X_recipe_details_rec  Cur_get_recipe_details%ROWTYPE;
1824 --  X_material_rec	Cur_get_material_lines%ROWTYPE;
1825   X_um_type             mtl_units_of_measure.uom_class%TYPE;
1826   X_count               NUMBER := 0;
1827   l_return_status	VARCHAR2(10);
1828   /* Exceptions.
1829   =====================*/
1830   NO_MATERIAL_STEP_ASSOC	EXCEPTION;
1831   NO_ROUTING_ASSOCIATED		EXCEPTION;
1832   ROUTING_DETAILS_MISSING	EXCEPTION;
1833   ALL_MTL_LINES_NOT_ASSOC  	EXCEPTION;
1834   UOM_CONVERSION_ERROR		EXCEPTION;
1835 BEGIN
1836   P_return_status := FND_API.G_RET_STS_SUCCESS;
1837   FND_MSG_PUB.INITIALIZE;
1838 
1839   /* If recipe id is null it implies that the material
1840      step association has not been done */
1841   IF P_check.parent_id IS NULL THEN
1842     RAISE NO_MATERIAL_STEP_ASSOC;
1843   END IF;
1844 
1845   GMD_API_GRP.FETCH_PARM_VALUES (P_orgn_id      => p_organization_id	,
1846 				P_parm_name     => 'GMD_MASS_UM_TYPE'	,
1847 				P_parm_value    => gmd_auto_step_calc.G_PROFILE_MASS_UM_TYPE	,
1848 				X_return_status => l_return_status	);
1849 
1850   GMD_API_GRP.FETCH_PARM_VALUES (P_orgn_id      => p_organization_id	,
1851 				P_parm_name     => 'GMD_VOLUME_UM_TYPE'	,
1852 				P_parm_value    => gmd_auto_step_calc.G_PROFILE_VOLUME_UM_TYPE	,
1853 				X_return_status => l_return_status	);
1854 
1855   OPEN Cur_get_recipe_details;
1856   FETCH Cur_get_recipe_details INTO X_recipe_details_rec;
1857   CLOSE Cur_get_recipe_details;
1858 
1859   /* Check whether a routing is associated with the recipe */
1860   IF X_recipe_details_rec.routing_id IS NULL THEN
1861     RAISE NO_ROUTING_ASSOCIATED;
1862   END IF;
1863 
1864   /* Check whether the routing has steps associated */
1865   OPEN Cur_get_rout_details (X_recipe_details_rec.routing_id);
1866   FETCH Cur_get_rout_details INTO X_exists;
1867   IF Cur_get_rout_details%NOTFOUND THEN
1868     CLOSE Cur_get_rout_details;
1869     RAISE ROUTING_DETAILS_MISSING;
1870   END IF;
1871   CLOSE Cur_get_rout_details;
1872 
1873   /* Check whether all the material lines where contribute-step-qty_ind = Y
1874      have been attached to a step */
1875   OPEN Cur_check_matl_lines_assoc (X_recipe_details_rec.formula_id);
1876   FETCH Cur_check_matl_lines_assoc INTO X_exists;
1877   IF Cur_check_matl_lines_assoc%FOUND THEN
1878     CLOSE Cur_check_matl_lines_assoc;
1879     RAISE ALL_MTL_LINES_NOT_ASSOC;
1880   END IF;
1881   CLOSE Cur_check_matl_lines_assoc;
1882 
1883   /* Populate the global std um variables. */
1884   OPEN Cur_get_std_um (G_profile_mass_um_type);
1885   FETCH Cur_get_std_um INTO G_mass_std_um;
1886   CLOSE Cur_get_std_um;
1887 
1888   OPEN Cur_get_std_um (G_profile_volume_um_type);
1889   FETCH Cur_get_std_um INTO G_vol_std_um;
1890   CLOSE Cur_get_std_um;
1891 
1892 
1893   -- Check if material lines are define in mass uom or Vol uom.
1894   -- Bug   2130655
1895   -- Bug # 2362814 Added by Shyam
1896   -- If x_count = 1 it is ok.
1897   OPEN Cur_chk_matrl_umtype(x_recipe_details_rec.formula_id);
1898   FETCH Cur_chk_matrl_umtype INTO x_count;
1899   CLOSE Cur_chk_matrl_umtype;
1900 
1901   IF (x_count = 1) THEN
1902     OPEN Cur_get_mtl_umtype(x_recipe_details_rec.formula_id);
1903     FETCH Cur_get_mtl_umtype INTO x_um_type;
1904     CLOSE Cur_get_mtl_umtype;
1905 
1906     IF (x_um_type = G_profile_mass_um_type) THEN
1907       p_ignore_vol_conv := TRUE;
1908     ELSIF (x_um_type = G_profile_volume_um_type) THEN
1909       p_ignore_mass_conv := TRUE;
1910     END IF;
1911   ELSIF(x_count > 1) THEN
1912     p_ignore_mass_conv := FALSE;
1913     p_ignore_vol_conv  := FALSE;
1914   END IF;
1915 
1916  IF (x_recipe_details_rec.routing_id IS NOT NULL) THEN
1917    OPEN Cur_get_umtyp_cnt(x_recipe_details_rec.routing_id);
1918    FETCH Cur_get_umtyp_cnt INTO x_count;
1919    CLOSE Cur_get_umtyp_cnt;
1920 
1921    /* if x_count is 1 then it could be MASS or VOL or some OTHER type */
1922    IF (x_count = 1) THEN
1923      OPEN Cur_get_process_umtyp(x_recipe_details_rec.routing_id);
1924      FETCH Cur_get_process_umtyp INTO x_um_type;
1925      CLOSE Cur_get_process_umtyp;
1926      IF (x_um_type = G_profile_mass_um_type) THEN
1927        p_ignore_vol_conv := TRUE;
1928      ELSIF (x_um_type = G_profile_volume_um_type) THEN
1929        p_ignore_mass_conv := TRUE;
1930      ELSE
1931       /* Get the other UOM type */
1932        G_PROFILE_OTHER_UM_TYPE := x_um_type;
1933      END IF;
1934    ELSIF(x_count > 1) THEN
1935      p_ignore_mass_conv := FALSE;
1936      p_ignore_vol_conv  := FALSE;
1937    END IF;
1938  END IF;
1939 
1940    -- End Bug 2130655.
1941    IF (G_PROFILE_OTHER_UM_TYPE IS NOT NULL) THEN
1942      OPEN Cur_get_std_um (G_PROFILE_OTHER_UM_TYPE);
1943      FETCH Cur_get_std_um INTO G_other_std_um;
1944      CLOSE Cur_get_std_um;
1945    END IF;
1946 
1947    /* Check whether all the material lines checked to be contributing
1948      to the step qty are convertible to the mass and volume uom types */
1949    FOR x_material_rec IN Cur_get_material_lines (X_recipe_details_rec.formula_id) LOOP
1950 
1951      IF (G_PROFILE_OTHER_UM_TYPE IS NULL) THEN
1952        X_temp_qty := INV_CONVERT.inv_um_convert(item_id        => X_material_rec.inventory_item_id
1953                                                ,precision      => 5
1954                                                ,from_quantity  => X_material_rec.qty
1955                                                ,from_unit      => X_material_rec.detail_uom
1956                                                ,to_unit        => G_mass_std_um
1957                                                ,from_name      => NULL
1958                                                ,to_name	       => NULL);
1959        IF X_temp_qty < 0 THEN
1960          X_item_id := X_material_rec.inventory_item_id;
1961          X_from_uom := X_material_rec.detail_uom;
1962          X_to_uom := G_mass_std_um;
1963          IF (p_ignore_mass_conv = FALSE) THEN
1964            RAISE UOM_CONVERSION_ERROR;
1965          END IF;
1966        END IF;
1967        X_temp_qty := INV_CONVERT.inv_um_convert(item_id         => X_material_rec.inventory_item_id
1968                                                ,precision      => 5
1969                                                ,from_quantity  => X_material_rec.qty
1970                                                ,from_unit      => X_material_rec.detail_uom
1971                                                ,to_unit        => G_vol_std_um
1972                                                ,from_name      => NULL
1973                                                ,to_name	       => NULL);
1974 
1975        IF X_temp_qty < 0 THEN
1976          X_item_id := X_material_rec.inventory_item_id;
1977          X_from_uom := X_material_rec.detail_uom;
1978          X_to_uom := G_vol_std_um;
1979          IF (p_ignore_vol_conv = FALSE) THEN
1980            RAISE UOM_CONVERSION_ERROR;
1981          END IF;
1982        END IF;
1983      ELSE /* IF the um type is of other type */
1984        X_temp_qty := INV_CONVERT.inv_um_convert(item_id        => X_material_rec.inventory_item_id
1985                                                ,precision      => 5
1986                                                ,from_quantity  => X_material_rec.qty
1987                                                ,from_unit      => X_material_rec.detail_uom
1988                                                ,to_unit        => G_other_std_um
1989                                                ,from_name      => NULL
1990                                                ,to_name	       => NULL);
1991        IF X_temp_qty < 0 THEN
1992          X_item_id := X_material_rec.inventory_item_id;
1993          X_from_uom := X_material_rec.detail_uom;
1994          X_to_uom := G_other_std_um;
1995          RAISE UOM_CONVERSION_ERROR;
1996        END IF;
1997      END IF;
1998 
1999    END LOOP;
2000 EXCEPTION
2001   WHEN NO_ROUTING_ASSOCIATED THEN
2002     P_return_status := FND_API.G_RET_STS_ERROR;
2003     FND_MESSAGE.SET_NAME('GMD', 'GMD_AUTO_STEP_QTY_NEEDS_ROUT');
2004     FND_MSG_PUB.ADD;
2005     FND_MSG_PUB.COUNT_AND_GET (P_count => P_msg_count,
2006                                P_data  => P_msg_stack);
2007   WHEN ROUTING_DETAILS_MISSING THEN
2008     P_return_status := FND_API.G_RET_STS_ERROR;
2009     FND_MESSAGE.SET_NAME('GMD', 'FMROUTINGSTEPNOTFOUND');
2010     FND_MSG_PUB.ADD;
2011     FND_MSG_PUB.COUNT_AND_GET (P_count => P_msg_count,
2012                                P_data  => P_msg_stack);
2013   WHEN  NO_MATERIAL_STEP_ASSOC THEN
2014     P_return_status := FND_API.G_RET_STS_ERROR;
2015     --  debug line p_return_status := 'Z';
2016     FND_MESSAGE.SET_NAME('GMD', 'GMD_MISSING_MATL_STEP_ASSOC');
2017     FND_MSG_PUB.ADD;
2018     FND_MSG_PUB.COUNT_AND_GET (P_count => P_msg_count,
2019                                P_data  => P_msg_stack);
2020   WHEN ALL_MTL_LINES_NOT_ASSOC THEN
2021     P_return_status := FND_API.G_RET_STS_ERROR;
2022     --  debug line p_return_status := 'Y';
2023     FND_MESSAGE.SET_NAME('GMD', 'GMD_ALL_MATL_STEP_NOT_ASSOC');
2024     FND_MSG_PUB.ADD;
2025     FND_MSG_PUB.COUNT_AND_GET (P_count => P_msg_count,
2026                                P_data  => P_msg_stack);
2027   WHEN UOM_CONVERSION_ERROR THEN
2028     P_return_status := FND_API.G_RET_STS_ERROR;
2029     OPEN Cur_get_item;
2030     FETCH Cur_get_item INTO X_item_no;
2031     CLOSE Cur_get_item;
2032     FND_MESSAGE.SET_NAME('GMI', 'IC_API_UOM_CONVERSION_ERROR');
2033     FND_MESSAGE.SET_TOKEN('ITEM_NO', X_item_no);
2034     FND_MESSAGE.SET_TOKEN('FROM_UOM', X_from_uom);
2035     FND_MESSAGE.SET_TOKEN('TO_UOM', X_to_uom);
2036     FND_MSG_PUB.ADD;
2037     FND_MSG_PUB.COUNT_AND_GET (P_count => P_msg_count,
2038                                 P_data  => P_msg_stack);
2039   WHEN OTHERS THEN
2040      P_return_status := FND_API.G_RET_STS_UNEXP_ERROR;
2041      fnd_message.set_name('GMD',SQLERRM);
2042      fnd_msg_pub.add;
2043      FND_MSG_PUB.COUNT_AND_GET (P_count => P_msg_count,
2044                                 P_data  => P_msg_stack);
2045 END check_step_qty_calculatable;
2046 
2047 
2048 /*****************************************************
2049 --  PROCEDURE :
2050 --    check_del_from_step_mat
2051 --
2052 --  DESCRIPTION:
2053 --    This PL/SQL procedure accepts a formulaline_id or routingstep_id
2054 --    which is being deleted from the formula material table or routing detail
2055 --    table, respectively.  It returns the recipe id's affected by the deleted,
2056 --
2057 --    This procedure is called by the forms, to tell the user what the scope of
2058 --    their delete is, and to ask if they wish to continue.  If they answer YES,
2059 --    then cascade_del_to_step_mat procedure is called, which does the actual
2060 --    delete from the step/mat assoc table and recalc's step qty's if necessary.
2061 --
2062 --  REQUIREMENTS
2063 --    p_check record  non null value. (recipe, formulaline or routingstep, WHO)
2064 --
2065 --  SYNOPSIS:
2066 --    check_del_from_step_mat (p_check, X_return_status);
2067 --
2068 --  Procedures used:  none
2069 
2070 --
2071 --  HISTORY
2072 --  02Aug2001  L.R.Jackson  Bug 1856832.  Created
2073 
2074 ************************************************************************/
2075 PROCEDURE check_del_from_step_mat(P_check          IN calculatable_rec_type,
2076                                   P_recipe_tbl     OUT NOCOPY recipe_id_tbl,
2077                                   P_check_step_mat OUT NOCOPY check_step_mat_type,
2078                                   P_msg_count      OUT NOCOPY NUMBER,
2079                                   P_msg_stack      OUT NOCOPY VARCHAR2,
2080                                   P_return_status  OUT NOCOPY VARCHAR2
2081                                  )  IS
2082 
2083 CURSOR Cur_get_step_mat_recipes (p_formulaline_id NUMBER, p_routingstep_id NUMBER) IS
2084       SELECT m.recipe_id,
2085              r.recipe_status
2086       FROM   gmd_recipe_step_materials m,
2087              gmd_recipes_b r,
2088              gmd_status_b s
2089       WHERE  s.status_code    = r.recipe_status
2090         AND  r.recipe_id      = m.recipe_id
2091         AND  ((p_formulaline_id is not null and m.formulaline_id = P_formulaline_id)
2092                OR
2093                (p_routingstep_id is not null and m.routingstep_id = P_routingstep_id))
2094         AND  r.calculate_step_quantity > 0
2095         AND  s.status_type   <> 1000
2096         AND  r.delete_mark    = 0;
2097 
2098 x_recipe_cntr   NUMBER := 0;
2099 
2100 BEGIN
2101   P_return_status := FND_API.G_RET_STS_SUCCESS;
2102     -- 1. Get a list of recipes where this formulaline exists in step/mat association,
2103     --    and where calculate_step_qty flag IS set (ASQC=Yes)
2104     --    and where delete_mark is NOT set
2105     --    and the recipe is NOT marked obsolete.
2106     -- 2. Count the recipes in step/mat rows where this formulaline exists (regardless of ASQC flag).
2107 
2108   FOR get_recipe_id IN cur_get_step_mat_recipes (p_check.formulaline_id, p_check.routingstep_id)
2109           LOOP
2110     x_recipe_cntr := x_recipe_cntr + 1;
2111     p_recipe_tbl(x_recipe_cntr) := get_recipe_id.recipe_id;
2112   END LOOP;
2113 
2114   P_check_step_mat.ASQC_RECIPES  := x_recipe_cntr;
2115 
2116   SELECT COUNT(unique recipe_id) into P_check_step_mat.STEP_ASSOC_RECIPES
2117     FROM   gmd_recipe_step_materials
2118    WHERE  (P_check.formulaline_id is not null AND formulaline_id = P_check.formulaline_id)
2119              OR
2120           (p_check.routingstep_id is not null AND routingstep_id = P_check.routingstep_id) ;
2121 
2122 EXCEPTION
2123    WHEN OTHERS THEN
2124           -- It is OK if no rows are found in step/mat table.
2125           -- This exception is for database errors
2126         P_return_status := FND_API.G_RET_STS_UNEXP_ERROR;
2127         FND_MSG_PUB.COUNT_AND_GET (P_count => P_msg_count,
2128                                    P_data  => P_msg_stack);
2129 END check_del_from_step_mat;
2130 
2131 
2132 
2133 /*****************************************************
2134 --  PROCEDURE :
2135 --    cascade_del_to_step_mat
2136 --
2137 --  DESCRIPTION:
2138 --    This PL/SQL procedure accepts a formulaline_id or routingstep_id
2139 --    which is being deleted from the formula material table or routing detail
2140 --    table, respectively.  The formualine_id or routingstep_id is deleted from
2141 --    GMD_RECIPE_STEP_MATERIALS.  Then, if ASQC flag = yes, step qty's are
2142 --    recalculated.
2143 --
2144 --  REQUIREMENTS
2145 --    Calling program must first call check_del_from_step_mat.
2146 --    p_check record  non null value. (recipe, formulaline or routingstep, WHO)
2147 --    If formulaline_id is being deleted, routingstep_id parameter must be null
2148 --
2149 --  SYNOPSIS:
2150 --    cascade_del_to_step_mat (p_check, X_return_status);
2151 --
2152 --  Procedures used:  gmd_auto_step_calc.check_step_qty_calculatable
2153 --                    gmd_auto_step_calc.calc_step_qty
2154 --                    gmd_recipe_detail.recipe_routing_steps
2155 --
2156 --  HISTORY
2157 --  25Jul2001  L.R.Jackson  Bug 1856832.  Created
2158 --  Sukarna Reddy Dt 03/14/02. Bug 2130655. p_ignore_mass_conv
2159 --   and p_ignore_vol_conv will not be passed as parameter.
2160 ************************************************************/
2161 
2162 PROCEDURE cascade_del_to_step_mat(P_check          IN calculatable_rec_type,
2163                                   P_recipe_tbl     IN recipe_id_tbl,
2164                                   P_check_step_mat IN check_step_mat_type,
2165                                   P_msg_count      OUT NOCOPY NUMBER,
2166                                   P_msg_stack      OUT NOCOPY VARCHAR2,
2167                                   P_return_status  OUT NOCOPY VARCHAR2,
2168                                   P_organization_id IN NUMBER)  IS
2169 
2170 x_recipe_cntr       NUMBER := 0;
2171 x_step_cntr         NUMBER := 0;
2172 X_step_tbl	        gmd_auto_step_calc.step_rec_tbl;
2173 X_all_steps_tbl     gmd_recipe_detail.recipe_detail_tbl;
2174 x_flex              gmd_recipe_detail.recipe_flex;
2175 x_update_flex       gmd_recipe_detail.recipe_update_flex;
2176 x_check_out         gmd_auto_step_calc.calculatable_rec_type;
2177 debug_msg           EXCEPTION;    -- used in debugging
2178 x_ignore_mass_conv BOOLEAN;
2179 x_ignore_vol_conv  BOOLEAN;
2180 ALL_MTL_LINES_NOT_ASSOC  	EXCEPTION;
2181 
2182 BEGIN
2183   P_return_status := FND_API.G_RET_STS_SUCCESS;
2184     -- Calling program should delete from fm_matl_dtl.
2185     --    DELETE  FROM   fm_matl_dtl WHERE  formulaline_id = P_formulaline_id;
2186     -- 1. Use gmd_auto_step_calc.check_del_from_step_mat to get a list of recipes where
2187     --       this formulaline exists in step/mat association,
2188     --    and where calculate_step_qty flag IS set (ASQC=Yes)
2189     --    and where delete_mark is NOT set
2190     --    and the recipe is NOT marked obsolete.
2191     -- check_del_from_step_mat will also count if there are any step/mat associations which
2192     --    need to be deleted.
2193     -- 2. Delete the step/mat rows where this formulaline exists (regardless of ASQC flag).
2194     -- 3. Recalculate step qty's in the recipes in the list.
2195 
2196     -- debug dbms_output.put_line('Value of v_formulaline_id='||P_check_in.formulaline_id||' **********************************');
2197 
2198   -- If there are any step/mat lines using this formulaline or routingstep, delete them.
2199   -- Then, if any of the recipes involved need the step qty's re calculated (id's would be in
2200   --   p_recipe_tbl) then recalc.
2201   -- By definition, if a routingstep is being deleted and there were step associations, now
2202   --   there will be items with no association to a step (the step which is being deleted).
2203   -- ***********************************************************************************
2204   -- For the next version, check if formulaline's which would go away because a routing step
2205   -- is deleted actually ARE marked as contributing-to-step-qty.  If not, then asqc can be
2206   -- recalc'ed.
2207   IF P_check_step_mat.STEP_ASSOC_RECIPES > 0 THEN
2208     DELETE FROM   gmd_recipe_step_materials
2209      WHERE  (P_check.formulaline_id is not null AND formulaline_id = P_check.formulaline_id)
2210              OR
2211             (p_check.routingstep_id is not null AND routingstep_id = P_check.routingstep_id) ;
2212 
2213 
2214     /* Commented the code below by Shyam */
2215     /* We need not perform the ASQC recalculation and update the GMD Recipe
2216        step table because if the ASQC flag is ON then the values are not saved
2217        in the db or the GMD Recipe Steps table.  Each time the Recipes form
2218        open if the ASQC flag is ON then it performs the recalculation */
2219 
2220     IF p_check.routingstep_id is not null THEN
2221        -- save what has been done so far and go to end.  Put message on stack.
2222        IF (P_check_step_mat.ASQC_RECIPES > 0) THEN
2223            RAISE ALL_MTL_LINES_NOT_ASSOC;
2224        ELSE
2225            DELETE FROM gmd_recipe_routing_steps
2226            WHERE  (p_check.routingstep_id is not null
2227                    AND routingstep_id = P_check.routingstep_id);
2228        END IF;
2229     END IF;   -- end if routingstep is being deleted.
2230 
2231     /*
2232     FOR x_recipe_cntr in 1..P_recipe_tbl.COUNT LOOP
2233         -- debug dbms_output.put_line('call asqc to recalculate here. Give user a message. recipe_id '|| x_recipe_tbl(x_recipe_cntr) );
2234       x_check_out := p_check;
2235       x_check_out.parent_id := P_recipe_tbl(x_recipe_cntr);
2236       gmd_auto_step_calc.check_step_qty_calculatable
2237                                      (p_check         => x_check_out,
2238                                       p_msg_count     => P_msg_count,
2239                                       p_msg_stack     => P_msg_stack,
2240                                       p_return_status => P_return_status,
2241                                       P_ignore_mass_conv => x_ignore_mass_conv,
2242                                       P_ignore_vol_conv => x_ignore_vol_conv,
2243 				      P_organization_id => P_organization_id);
2244 
2245       -- debug dbms_output.put_line('status from calculatable is ' || p_return_status);
2246       IF p_return_status = 'S' THEN
2247         gmd_auto_step_calc.calc_step_qty(p_parent_id     => P_recipe_tbl(x_recipe_cntr),
2248                                          p_step_tbl      => X_step_tbl,
2249                                          p_msg_count     => P_msg_count,
2250                                          p_msg_stack     => P_msg_stack,
2251                                          p_return_status => p_return_status,
2252 					 P_organization_id => P_organization_id);
2253       END IF;
2254       -- Check_step_qty_calculatable and Calc_step_qty put their own messages on the stack.
2255 
2256       IF p_return_status = 'S' THEN
2257         -- debug  dbms_output.put_line('Value of X_step_tbl.COUNT='||X_step_tbl.COUNT);
2258         -- debug  dbms_output.put_line('After calc Value of p_return_status= *'||p_return_status ||'*');
2259 
2260       -- We are in a loop for every recipe where ASQC=Yes.  If ASQC was succussful,
2261       --   for each step returned in the step table, put the results in a holding table.
2262       --   This holding table will be sent to the recipe_details pkg for update (maybe insert)
2263       --   of the gmd_recipe_routing_steps table.
2264       -- Counter is only initialized at top of procedure.
2265         FOR asqc_cntr in 1..X_step_tbl.COUNT LOOP
2266           x_step_cntr := x_step_cntr + 1;
2267           X_all_steps_tbl(x_step_cntr).recipe_id         := P_recipe_tbl(x_recipe_cntr);
2268           X_all_steps_tbl(x_step_cntr).routingstep_id    := X_step_tbl(asqc_cntr).step_id;
2269           X_all_steps_tbl(x_step_cntr).step_qty          := X_step_tbl(asqc_cntr).step_qty;
2270           X_all_steps_tbl(x_step_cntr).mass_qty          := X_step_tbl(asqc_cntr).step_mass_qty;
2271           X_all_steps_tbl(x_step_cntr).mass_ref_uom      := X_step_tbl(asqc_cntr).step_mass_uom;
2272           X_all_steps_tbl(x_step_cntr).volume_qty        := X_step_tbl(asqc_cntr).step_vol_qty;
2273           X_all_steps_tbl(x_step_cntr).volume_ref_uom    := X_step_tbl(asqc_cntr).step_vol_uom;
2274           X_all_steps_tbl(x_step_cntr).creation_date     := P_check.creation_date;
2275           X_all_steps_tbl(x_step_cntr).created_by        := P_check.created_by;
2276           X_all_steps_tbl(x_step_cntr).last_update_date  := P_check.last_update_date;
2277           X_all_steps_tbl(x_step_cntr).last_updated_by   := P_check.last_updated_by;
2278           X_all_steps_tbl(x_step_cntr).last_update_login := P_check.last_update_login;
2279         END LOOP;
2280       END IF;    -- end if return status from calc_step_qty = S
2281     END LOOP;    -- end loop for each recipe which had the given formulaline or routing
2282                  --   in the step/material association
2283 
2284     -- After everything has been calculated, update step qty's in gmd_recipe_routing_steps.
2285     IF p_return_status = 'S' THEN
2286       gmd_recipe_detail.recipe_routing_steps
2287                                    (p_api_version        => 1.1,
2288                                     p_init_msg_list      => 'F',
2289                                     p_commit             => 'F',
2290                                     p_called_from_forms  => 'NO',
2291                                     x_return_status      => p_return_status,
2292                                     x_msg_count          => P_msg_count,
2293                                     x_msg_data           => P_msg_stack,
2294                                     p_recipe_detail_tbl  => X_all_steps_tbl,
2295                                     p_recipe_insert_flex => x_flex,
2296                                     p_recipe_update_flex => x_update_flex
2297                                    );
2298 
2299     END IF;  -- end if calc_step was successful
2300 
2301     */
2302   END IF;    -- end if there are any recipes affected by the formulaline or routingstep delete
2303 
2304   EXCEPTION
2305     WHEN debug_msg THEN
2306           FND_MSG_PUB.ADD;
2307           FND_MSG_PUB.COUNT_AND_GET (P_count => P_msg_count,
2308                                      P_data  => P_msg_stack);
2309           -- debug dbms_output.put_line ('in exception ' || p_return_status);
2310 
2311     WHEN ALL_MTL_LINES_NOT_ASSOC THEN
2312     P_return_status := FND_API.G_RET_STS_ERROR;
2313     FND_MESSAGE.SET_NAME('GMD', 'GMD_ALL_MATL_STEP_NOT_ASSOC');
2314     FND_MSG_PUB.ADD;
2315     FND_MSG_PUB.COUNT_AND_GET (P_count => P_msg_count,
2316                                P_data  => P_msg_stack);
2317     WHEN OTHERS THEN
2318           -- It is OK if no rows are found in step/mat table.
2319           -- The 3 procedures called have their own error handling.
2320         P_return_status := FND_API.G_RET_STS_UNEXP_ERROR;
2321         FND_MSG_PUB.COUNT_AND_GET (P_count => P_msg_count,
2322                                    P_data  => P_msg_stack);
2323   END cascade_del_to_step_mat;
2324 
2325 
2326 /*****************************************************
2327 --  PROCEDURE :
2328 --    check_Bch_stp_qty_calculatable
2329 --
2330 --  DESCRIPTION:
2331 --    Handles the UOM type conversion
2332 --
2333 --  HISTORY
2334 --  26-06-06  Kapil M  Created the procedure for bug# 5347857.
2335 --  08-08-06  Kapil M  Replaced sy_uoms_mst with mtl_units_of_measure
2336 **************************************************************/
2337 
2338 PROCEDURE check_Bch_stp_qty_calculatable (P_check            IN  calculatable_rec_type,
2339                                         P_ignore_mass_conv OUT NOCOPY BOOLEAN,
2340                                         P_ignore_vol_conv  OUT NOCOPY BOOLEAN) IS
2341 
2342   /* Cursor Definitions.
2343   =====================*/
2344   CURSOR Cur_get_recipe_details IS
2345     SELECT formula_id, routing_id
2346     FROM   GME_BATCH_HEADER
2347     WHERE  BATCH_ID = P_check.parent_id;
2348 
2349 
2350   CURSOR Cur_get_std_um (V_um_type VARCHAR2) IS
2351     SELECT UOM_CODE
2352     FROM   mtl_units_of_measure
2353     WHERE  uom_class = V_um_type
2354     AND BASE_UOM_FLAG = 'Y';
2355 
2356   CURSOR Cur_chk_matrl_umtype(pformula_id NUMBER) IS
2357     SELECT COUNT(distinct m.uom_class)
2358      FROM  fm_matl_dtl d ,mtl_units_of_measure m
2359      WHERE d.DETAIL_UOM = m.uom_code
2360          AND d.formula_id = pformula_id
2361          AND NVL(d.contribute_step_qty_ind, 'Y')  = 'Y'
2362          AND (P_check.formulaline_id IS NULL OR
2363                    formulaline_id <> P_check.formulaline_id);
2364 
2365   CURSOR Cur_get_mtl_umtype(pformula_id NUMBER) IS
2366     SELECT distinct m.uom_class
2367      FROM  fm_matl_dtl d ,mtl_units_of_measure m
2368      WHERE d.DETAIL_UOM= m.uom_code
2369          AND d.formula_id = pformula_id
2370          AND NVL(d.contribute_step_qty_ind, 'Y')  = 'Y'
2371          AND (P_check.formulaline_id IS NULL OR
2372               formulaline_id <> P_check.formulaline_id);
2373 
2374   CURSOR Cur_get_umtyp_cnt(prouting_id NUMBER) IS
2375     SELECT count(distinct u.uom_class)
2376     FROM   fm_rout_dtl d,
2377            gmd_operations_b o,
2378            mtl_units_of_measure u
2379     WHERE  d.oprn_id = o.oprn_id
2380     AND    d.routing_id = prouting_id
2381     AND    o.process_qty_uom = u.uom_code;
2382 
2383   CURSOR Cur_get_process_umtyp(prouting_id NUMBER) IS
2384     SELECT distinct u.uom_class
2385     FROM   fm_rout_dtl d,
2386            gmd_operations_b o,
2387            mtl_units_of_measure u
2388     WHERE  d.oprn_id = o.oprn_id
2389     AND    d.routing_id = prouting_id
2390     AND    o.process_qty_uom = u.uom_code;
2391 
2392 
2393   /* Cursor records.
2394   =====================*/
2395   X_recipe_details_rec  Cur_get_recipe_details%ROWTYPE;
2396   X_um_type             sy_uoms_typ.um_type%TYPE;
2397   X_count               NUMBER := 0;
2398   /* Exceptions.
2399   =====================*/
2400   NO_MATERIAL_STEP_ASSOC	EXCEPTION;
2401   NO_ROUTING_ASSOCIATED		EXCEPTION;
2402 BEGIN
2403 
2404   OPEN Cur_get_recipe_details;
2405   FETCH Cur_get_recipe_details INTO X_recipe_details_rec;
2406   CLOSE Cur_get_recipe_details;
2407 
2408   /* Check whether all the material lines where contribute-step-qty_ind = Y
2409      have been attached to a step */
2410 
2411   /* Populate the global std um variables. */
2412   OPEN Cur_get_std_um (G_profile_mass_um_type);
2413   FETCH Cur_get_std_um INTO G_mass_std_um;
2414   CLOSE Cur_get_std_um;
2415 
2416   OPEN Cur_get_std_um (G_profile_volume_um_type);
2417   FETCH Cur_get_std_um INTO G_vol_std_um;
2418   CLOSE Cur_get_std_um;
2419 
2420   -- Check if material lines are define in mass uom or Vol uom.
2421   -- Bug   2130655
2422   -- Bug # 2362814 Added by Shyam
2423   -- If x_count = 1 it is ok.
2424   OPEN Cur_chk_matrl_umtype(x_recipe_details_rec.formula_id);
2425   FETCH Cur_chk_matrl_umtype INTO x_count;
2426   CLOSE Cur_chk_matrl_umtype;
2427   IF (x_count = 1) THEN
2428     OPEN Cur_get_mtl_umtype(x_recipe_details_rec.formula_id);
2429     FETCH Cur_get_mtl_umtype INTO x_um_type;
2430     CLOSE Cur_get_mtl_umtype;
2431     IF (x_um_type = G_profile_mass_um_type) THEN
2432       p_ignore_vol_conv := TRUE;
2433     ELSIF (x_um_type = G_profile_volume_um_type) THEN
2434       p_ignore_mass_conv := TRUE;
2435     END IF;
2436   ELSIF(x_count > 1) THEN
2437     p_ignore_mass_conv := FALSE;
2438     p_ignore_vol_conv  := FALSE;
2439     return;
2440   END IF;
2441 
2442  IF (x_recipe_details_rec.routing_id IS NOT NULL) THEN
2443    OPEN Cur_get_umtyp_cnt(x_recipe_details_rec.routing_id);
2444    FETCH Cur_get_umtyp_cnt INTO x_count;
2445    CLOSE Cur_get_umtyp_cnt;
2446    /* if x_count is 1 then it could be MASS or VOL or some OTHER type */
2447    IF (x_count = 1) THEN
2448      OPEN Cur_get_process_umtyp(x_recipe_details_rec.routing_id);
2449      FETCH Cur_get_process_umtyp INTO x_um_type;
2450      CLOSE Cur_get_process_umtyp;
2451      IF (x_um_type = G_profile_mass_um_type) THEN
2452        p_ignore_vol_conv := TRUE;
2453      ELSIF (x_um_type = G_profile_volume_um_type) THEN
2454        p_ignore_mass_conv := TRUE;
2455      ELSE
2456       /* Get the other UOM type */
2457        G_PROFILE_OTHER_UM_TYPE := x_um_type;
2458      END IF;
2459    ELSIF(x_count > 1) THEN
2460      p_ignore_mass_conv := FALSE;
2461      p_ignore_vol_conv  := FALSE;
2462      return;
2463    END IF;
2464  END IF;
2465 
2466    -- End Bug 2130655.
2467    IF (G_PROFILE_OTHER_UM_TYPE IS NOT NULL) THEN
2468      OPEN Cur_get_std_um (G_PROFILE_OTHER_UM_TYPE);
2469      FETCH Cur_get_std_um INTO G_other_std_um;
2470      CLOSE Cur_get_std_um;
2471    END IF;
2472 
2473 
2474 EXCEPTION
2475   WHEN OTHERS THEN
2476      p_ignore_mass_conv := FALSE;
2477      p_ignore_vol_conv  := FALSE;
2478 END check_Bch_stp_qty_calculatable;
2479 
2480 
2481 END GMD_AUTO_STEP_CALC;