DBA Data[Home] [Help]

PACKAGE BODY: APPS.GMD_VALIDITY_RULES

Source


1 PACKAGE BODY GMD_VALIDITY_RULES AS
2 /* $Header: GMDPRVRB.pls 120.13.12000000.2 2007/09/26 09:08:11 kannavar ship $ */
3 
4 G_PKG_NAME VARCHAR2(32);
5 G_default_cost_mthd VARCHAR2(20);
6 G_cost_source_orgn_id NUMBER(15);
7 G_cost_source BINARY_INTEGER;
8 
9 /*======================================================================
10 --  PROCEDURE :
11 --   get_validity_rules
12 --
13 --  DESCRIPTION:
14 --    This PL/SQL procedure  is responsible for getting the
15 --    validity rules based on the input parameters.
16 --
17 --  REQUIREMENTS
18 --
19 --  SYNOPSIS:
20 --    get_validity_rules (1.0, X_init_msg_list, X_recipe_id, X_item_id,
21 --                        X_orgn_code, X_product_qty, X_uom, X_recipe_use,
22 --                        X_total_input, X_total_output, X_status,
23 --                        X_return_status, X_msg_count, X_msg_data,
24 --                        X_return_code, X_vr_table);
25 --
26 --
27 --===================================================================== */
28 
29 PROCEDURE get_validity_rules(p_api_version         IN  NUMBER                           ,
30                              p_init_msg_list       IN  VARCHAR2 := FND_API.G_FALSE      ,
31                              p_recipe_no           IN  VARCHAR2 := NULL                 ,
32                              p_recipe_version      IN  NUMBER   := NULL                 ,
33                              p_recipe_id           IN  NUMBER   := NULL                 ,
34                              p_total_input         IN  NUMBER   := NULL                 ,
35                              p_total_output        IN  NUMBER   := NULL                 ,
36                              p_formula_id          IN  NUMBER   := NULL                 ,
37                              p_item_id             IN  NUMBER   := NULL                 ,
38                              p_revision            IN  VARCHAR2 := NULL                 ,
39                              p_item_no             IN  VARCHAR2 := NULL                 ,
40                              p_product_qty         IN  NUMBER   := NULL                 ,
41                              p_uom                 IN  VARCHAR2 := NULL                 ,
42                              p_recipe_use          IN  VARCHAR2 := NULL                 ,
43                              p_orgn_code           IN  VARCHAR2 := NULL                 ,
44                              p_organization_id     IN  NUMBER   := NULL                	,
45      			     p_least_cost_validity IN  VARCHAR2 := 'F'			,
46                              p_start_date          IN  DATE     := NULL                 ,
47                              p_end_date            IN  DATE     := NULL                 ,
48                              p_status_type         IN  VARCHAR2 := NULL                 ,
49                              p_validity_rule_id    IN  NUMBER   := NULL                 ,
50                              x_return_status       OUT NOCOPY VARCHAR2                  ,
51                              x_msg_count           OUT NOCOPY NUMBER                    ,
52                              x_msg_data            OUT NOCOPY VARCHAR2                  ,
53                              x_return_code         OUT NOCOPY NUMBER                    ,
54                              X_recipe_validity_out OUT NOCOPY recipe_validity_tbl) IS
55 
56   --  local Variables
57   l_api_name           VARCHAR2(30) := 'get_validity_rules';
58   l_api_version        NUMBER       := 1.0;
59   i                    NUMBER       := 0;
60   l_uom                VARCHAR2(4);
61 
62   l_item_uom           VARCHAR2(4);
63   l_line_um            VARCHAR2(4);
64   l_quantity           NUMBER;
65   l_item_qty           NUMBER;
66   l_scale_type         NUMBER;
67   l_msg_count          NUMBER;
68   l_msg_data           VARCHAR2(100);
69   l_return_code        VARCHAR2(10);
70   l_yield_um           VARCHAR2(4);
71   l_formula_id         NUMBER;
72   l_formula_output     NUMBER;
73   l_formula_input      NUMBER;
74   l_total_output       NUMBER;
75   l_total_input        NUMBER;
76   l_output_ratio       NUMBER;
77   l_ingred_prod_ratio  NUMBER;
78   l_batchformula_ratio NUMBER;
79   l_contributing_qty   NUMBER;
80 
81    -- Bug 3818835
82    l_qty       NUMBER;
83    l_form_qty  NUMBER;
84    l_prod_id   NUMBER;
85    l_prod_uom  VARCHAR2(4);
86 
87    l_uom_class VARCHAR2(25);
88 
89   /* Cursor to get data based on recipe ID and input and output qty. */
90   CURSOR get_val IS
91     SELECT v.*
92     FROM   gmd_recipe_validity_rules v, gmd_recipes r, gmd_status s
93     WHERE   v.recipe_id = r.recipe_id
94            AND v.validity_rule_status = s.status_code
95            AND  v.recipe_id = NVL(P_RECIPE_ID, v.recipe_id)
96            AND ( r.recipe_no = NVL(p_recipe_no, r.recipe_no) AND r.recipe_version = nvl(p_recipe_version, r.recipe_version) )
97            AND r.formula_id = NVL(p_formula_id, r.formula_id)
98 	   AND ( (p_status_type IS NULL AND  s.status_type IN ( '700', '900'))
99 				OR (p_status_type IS  NOT NULL AND s.status_type = p_status_type) )
100            AND v.recipe_use IN (0,p_recipe_use)
101            AND ((v.organization_id = NVL(p_organization_id,v.organization_id))
102 	   OR (v.organization_id IS NULL) )
103            /* Bug 2690833 - Thomas Daniel */
104            /* Modified the following start and end date condtions to ensure that the date */
105            /* range validation is done properly */
106            AND ( (p_start_date IS NULL) or
107                  ((start_date) <= (p_start_date) AND
108                   (NVL(end_date, p_start_date)) >= (p_start_date)
109                  )
110                )
111            AND ( (p_end_date IS NULL) OR
112                   ((NVL(end_date,p_end_date)) >= (P_end_date) AND
113                    (start_date) <= (p_end_date))
114                 )
115            AND (p_validity_rule_id IS NULL OR
116                  (p_validity_rule_id IS NOT NULL AND v.recipe_validity_rule_id = p_validity_rule_id))
117            AND v.delete_mark = 0
118      ORDER BY orgn_code,preference, recipe_use, s.status_type ;
119 
120   /* Cursor to get data based on item. */
121   CURSOR get_val_item(l_quantity NUMBER) IS
122     SELECT v.*
123     FROM   gmd_recipe_validity_rules v, gmd_recipes_b r, gmd_status_b s,
124            mtl_system_items_kfv I, fm_matl_dtl d
125     WHERE  v.recipe_id = r.recipe_id
126            AND v.validity_rule_status = s.status_code
127            AND i.inventory_item_id = v.inventory_item_id
128            AND r.owner_organization_id = i.organization_id
129            AND (v.inventory_item_id = p_item_id or i.concatenated_segments = p_item_no)
130            AND (p_revision IS NULL OR (p_revision IS NOT NULL AND v.revision = p_revision))
131 	   AND (r.formula_id = NVL(p_formula_id, r.formula_id))
132            AND (inv_min_qty <= nvl(l_quantity,inv_min_qty) AND inv_max_qty >= 	nvl(l_quantity,inv_max_qty))
133            AND ((p_status_type is NULL)  AND  (s.status_type IN ( '700', '900'))
134 		OR ( p_status_type is  NOT NULL AND s.status_type = p_status_type))
135 	   AND v.recipe_use IN (0,p_recipe_use)
136 	   AND ((v.organization_id = NVL(p_organization_id,v.organization_id))
137 	        or (v.organization_id IS NULL) )
138            AND ( (p_start_date IS NULL) or
139 	       ((start_date) <= (p_start_date) AND
140 	       (NVL(end_date, p_start_date)) >= (p_start_date)
141 	       )
142 	       )
143 	   AND ( (p_end_date IS NULL) OR
144 	      ((NVL(end_date,p_end_date)) >= (P_end_date) AND
145 	       (start_date) <= (p_end_date))
146 	       )
147 	   AND (p_validity_rule_id IS NULL OR
148 	       (p_validity_rule_id IS NOT NULL AND v.recipe_validity_rule_id =
149         	p_validity_rule_id))
150 	   AND v.delete_mark = 0
151 	   AND d.formula_id = r.formula_id
152 	   AND v.inventory_item_id = d.inventory_item_id
153            AND (p_revision IS NULL OR (p_revision IS NOT NULL AND d.revision = p_revision))
154            AND d.line_type = 1
155     ORDER BY orgn_code,preference, recipe_use, s.status_type ;
156 
157   l_item_id  NUMBER;
158 
159   CURSOR get_item_id(p_item_no VARCHAR2) IS
160     SELECT inventory_item_id
161     FROM   mtl_system_items_kfv
162     WHERE  concatenated_segments = p_item_no;
163 
164   -- NPD Conv.
165   CURSOR cur_item_uom(p_item_id NUMBER) IS
166     SELECT primary_uom_code
167     FROM   mtl_system_items_b
168     WHERE  inventory_item_id = p_item_id;
169 
170   -- NPD Conv.
171   CURSOR Cur_std_um (p_uom_class VARCHAR2) IS
172     SELECT uom_code
173     FROM   mtl_units_of_measure
174     WHERE  uom_class = p_uom_class
175     AND    base_uom_flag = 'Y';
176 
177   -- NPD Conv.
178   CURSOR Cur_get_qty(V_item_id NUMBER) IS
179     SELECT qty, scale_type, detail_uom
180     FROM   fm_matl_dtl
181     WHERE  formula_id = l_formula_id
182            AND inventory_item_id = V_item_id
183            AND line_type = 1
184     ORDER BY line_no;
185 
186 
187   CURSOR Cur_get_recipe (V_recipe_no VARCHAR2, V_recipe_vers NUMBER) IS
188     SELECT recipe_id
189     FROM   gmd_recipes_b
190     WHERE  recipe_no = V_recipe_no
191     AND    recipe_version = V_recipe_vers;
192 
193   CURSOR Cur_get_orgn_code IS
194     SELECT organization_code
195       FROM mtl_parameters
196      WHERE organization_id = p_organization_id;
197 
198   CURSOR Cur_get_VR IS
199     SELECT *
200     FROM GMD_VAL_RULE_GTMP;
201 
202   CURSOR get_form_prod(l_formula_id NUMBER) IS
203     SELECT inventory_item_id, qty, detail_uom
204     FROM   fm_matl_dtl
205     WHERE  formula_id = l_formula_id
206            AND line_type = 1
207            AND line_no = 1;
208 
209   CURSOR Cur_get_formula (V_recipe_id NUMBER) IS
210     SELECT formula_id
211     FROM   gmd_recipes_b
212     WHERE  recipe_id = V_recipe_id;
213 
214 
215   /* Exceptions */
216   NO_YIELD_TYPE_UM           EXCEPTION;
217   GET_FORMULA_ERR            EXCEPTION;
218   GET_TOTAL_QTY_ERR          EXCEPTION;
219   GET_OUTPUT_RATIO_ERR       EXCEPTION;
220   GET_INGREDPROD_RATIO_ERR   EXCEPTION;
221   GET_BATCHFORMULA_RATIO_ERR EXCEPTION;
222   GET_CONTRIBUTING_QTY_ERR   EXCEPTION;
223   GET_INPUT_RATIO_ERR        EXCEPTION;
224   ITEM_UOM_CONV_ERR          EXCEPTION;
225   UOM_CONVERSION_ERROR       EXCEPTION;
226   ITEM_ORGN_MISSING          EXCEPTION;
227   ITEM_NOT_FOUND_ERROR       EXCEPTION;
228   GET_FORMULA_COST_ERR       EXCEPTION;
229 
230   l_recipe_id              NUMBER;
231   l_orgn_code		   VARCHAR2(3);
232   l_total_cost	   	   NUMBER;
233   l_unit_cost		   NUMBER;
234   l_return_status	   VARCHAR2(10);
235   l_form_id		   NUMBER;
236 
237 BEGIN
238   IF (NOT FND_API.Compatible_API_Call (l_api_version, p_api_version,
239                                        l_api_name, G_PKG_NAME)) THEN
240     RAISE FND_API.G_EXC_UNEXPECTED_ERROR;
241   END IF;
242   IF (FND_API.to_Boolean(p_init_msg_list)) THEN
243     FND_MSG_PUB.initialize;
244   END IF;
245   X_return_status := FND_API.G_RET_STS_SUCCESS;
246 
247 /* Bug No.6346013 - Start */
248 
249   /* Delete from this table for any existing data */
250   DELETE FROM GMD_VAL_RULE_GTMP;
251 
252 /* Bug No.6346013 - End */
253 
254   -- NPD Convergence. Get FM_YIELD_TYPE profile value for the organization.
255   GMD_API_GRP.FETCH_PARM_VALUES(P_orgn_id    => p_organization_id,
256                                 P_parm_name  => 'FM_YIELD_TYPE',
257                                 P_parm_value => l_uom_class,
258 				x_return_status => l_return_status);
259   /* Get yield type um */
260   OPEN Cur_std_um (l_uom_class);
261   FETCH Cur_std_um INTO l_yield_um;
262   IF (Cur_std_um%NOTFOUND) THEN
263     CLOSE Cur_std_um;
264     RAISE NO_YIELD_TYPE_UM;
265   END IF;
266   CLOSE Cur_std_um;
267 
268   IF p_recipe_id IS NULL THEN
269     IF p_recipe_no IS NOT NULL AND
270        p_recipe_version IS NOT NULL THEN
271       OPEN Cur_get_recipe (p_recipe_no, p_recipe_version);
272       FETCH Cur_get_recipe INTO l_recipe_id;
273       CLOSE Cur_get_recipe;
274     END IF;
275   ELSE
276     l_recipe_id := p_recipe_id;
277   END IF;
278 
279   /* Check for possible ways to get validity rules */
280   IF (l_recipe_id IS NOT NULL AND p_total_output IS NOT NULL OR
281       l_recipe_id IS NOT NULL AND p_total_input IS NOT NULL) THEN
282     /* Get the formula for this recipe */
283     OPEN Cur_get_formula (l_recipe_id);
284     FETCH Cur_get_formula INTO l_formula_id;
285     CLOSE Cur_get_formula;
286 
287     -- S.Dulyk 1/8/02 added b/c calculate_total_qty wouldn't use p_uom
288     l_uom := p_uom;
289     gmd_common_val.calculate_total_qty(formula_id       => l_formula_id,
290                                        x_product_qty    => l_formula_output,
291                                        x_ingredient_qty => l_formula_input,
292                                        x_uom            => l_uom,
293                                        x_return_status  => l_return_status,
294                                        x_msg_count      => l_msg_count,
295                                        x_msg_data       => l_msg_data    );
296     /*Bug 2962277 - Thomas Daniel */
297     /*The return status can be 'Q' from the above call for two reasons either */
298     /*the total input qty was not calculatable or the total output qty is not */
299     /*calculatable, we need to see the mode in which this procedure was invoked */
300     /*to determine if an error should be raised */
301     IF (l_return_status <> FND_API.G_RET_STS_SUCCESS) AND
302        (l_return_status <> 'Q') THEN
303       RAISE GET_TOTAL_QTY_ERR;
304     ELSIF l_return_status = 'Q' THEN
305       IF (p_total_output IS NOT NULL) AND
306          (l_formula_output IS NULL) THEN
307         /*This implies that the system cannot calculate the total output qty and */
308         /*the validity rules are being fetched based on total ouput then this should */
309         /*be raised as an error */
310         FND_MESSAGE.SET_NAME('GMD', 'GMD_ERR_CALC_OUTPUT');
311         FND_MESSAGE.SET_TOKEN('UOM', l_uom);
312         FND_MSG_PUB.add;
313         RAISE GET_TOTAL_QTY_ERR;
314       ELSIF (p_total_input IS NOT NULL) AND
315          (l_formula_input IS NULL) THEN
316         /*This implies that the system cannot calculate the total input qty and */
317         /*the validity rules are being fetched based on total input then this should */
318         /*be raised as an error */
319         FND_MESSAGE.SET_NAME('GMD', 'GMD_ERR_CALC_INPUT');
320         FND_MESSAGE.SET_TOKEN('UOM', l_uom);
321         FND_MSG_PUB.add;
322         RAISE GET_TOTAL_QTY_ERR;
323       END IF;
324     END IF;
325 
326 
327     IF (p_total_output IS NOT NULL) THEN
328 
329       /* Try to get validity rules based on recipe ID and total output qty */
330       /* Get the ratio of the batch output qty to the ratio of the formula ouput qty */
331       gmd_validity_rules.get_output_ratio(p_formula_id     => l_formula_id,
332                                                 p_batch_output   => p_total_output,
333                                                 p_yield_um       => l_uom,
334                                                 p_formula_output => l_formula_output,
335                                                 x_return_status  => l_return_status,
336                                                 X_output_ratio   => l_output_ratio);
337       IF (l_return_status <> FND_API.G_RET_STS_SUCCESS) THEN
338         RAISE GET_OUTPUT_RATIO_ERR;
339       END IF;
340     ELSIF (p_total_input IS NOT NULL) THEN
341 
342       /* Get the product to ingredient ratio for the formula */
343       gmd_validity_rules.get_ingredprod_ratio(p_formula_id        => l_formula_id,
344                                               p_yield_um          => l_uom,
345                                               x_return_status     => l_return_status,
346                                               X_ingred_prod_ratio => l_ingred_prod_ratio);
347       IF (l_return_status <> FND_API.G_RET_STS_SUCCESS) THEN
348         RAISE GET_INGREDPROD_RATIO_ERR;
349       END IF;
350       /* Get the ratio of the batch input to the formula input */
351       gmd_validity_rules.get_batchformula_ratio(p_formula_id         => l_formula_id,
352                                                 p_batch_input        => p_total_input,
353                                                 p_yield_um           => l_uom,
354                                                 p_formula_input      => l_formula_input,
355                                                 x_return_status      => l_return_status,
356                                                 X_batchformula_ratio => l_batchformula_ratio);
357       IF (l_return_status <> FND_API.G_RET_STS_SUCCESS) THEN
358         RAISE GET_BATCHFORMULA_RATIO_ERR;
359       END IF;
360 
361       /* Get the contributing qty of the formula */
362       gmd_validity_rules.get_contributing_qty(p_formula_id          => l_formula_id,
363                                               p_recipe_id           => l_recipe_id,
364                                               p_batchformula_ratio  => l_batchformula_ratio,
365                                               p_yield_um            => l_uom,
366                                               x_return_status       => l_return_status,
367                                               X_contributing_qty    => l_contributing_qty);
368       IF (l_return_status <> FND_API.G_RET_STS_SUCCESS) THEN
369         RAISE GET_CONTRIBUTING_QTY_ERR;
370       END IF;
371       /* Calculate actual contributing qty of formula */
372       l_contributing_qty := l_contributing_qty * l_ingred_prod_ratio;
373 
374       /* Get the ratio of the product based on contributing qty */
375       gmd_validity_rules.get_input_ratio(p_formula_id       => l_formula_id,
376                                          p_contributing_qty => l_contributing_qty,
377                                          p_yield_um         => l_uom,
378                                          p_formula_output   => l_formula_input,
379                                          x_return_status    => l_return_status,
380                                          X_output_ratio     => l_output_ratio);
381       IF (l_return_status <> FND_API.G_RET_STS_SUCCESS) THEN
382         RAISE GET_INPUT_RATIO_ERR;
383       END IF;
384     END IF;
385 
386     /* Get all the possible validity rules and check if it can be used for this input/output qty */
387 
388     FOR get_rec IN get_val LOOP
389     BEGIN
390       -- NPD Conv.
391       IF (p_orgn_code IS NOT NULL OR (p_orgn_code IS NULL AND p_organization_id IS NOT NULL)) THEN
392 
393          IF p_orgn_code IS NULL THEN
394 		OPEN Cur_get_orgn_code;
395 		FETCH Cur_get_orgn_code INTO l_orgn_code;
396 		CLOSE Cur_get_orgn_code;
397 	 ELSE
398 		l_orgn_code := p_orgn_code;
399 	 END IF;
400 	 GMD_API_GRP.check_item_exists (p_formula_id        => l_formula_id
401 	                               ,p_organization_id   => p_organization_id
402 	                               ,p_orgn_code         => l_orgn_code
403 	                               ,x_return_status     => l_return_status
404 	                               ,p_Production_check  => TRUE);
405          IF l_return_status <> FND_API.G_RET_STS_SUCCESS THEN
406 	   RAISE ITEM_ORGN_MISSING;
407 	 END IF;
408       END IF;
409       -- End NPD Conv.
410 
411       OPEN Cur_get_qty(get_rec.inventory_item_id);
412       FETCH Cur_get_qty INTO l_item_qty, l_scale_type, l_line_um;
413       CLOSE Cur_get_qty;
414       IF (l_scale_type = 1) THEN
415         l_item_qty := l_item_qty * l_output_ratio;
416         IF (l_line_um <> get_rec.detail_uom) THEN
417 
418           -- NPD Conv. Changed the call to INV_CONVERT.inv_um_convert from gmicuom.uom_conversion
419 
420           l_item_qty := INV_CONVERT.inv_um_convert(item_id         => get_rec.inventory_item_id
421                                                    ,precision      => 5
422                                                    ,from_quantity  => l_item_qty
423                                                    ,from_unit      => l_line_um
424                                                    ,to_unit        => get_rec.detail_uom
425                                                    ,from_name      => NULL
426                                                    ,to_name	   => NULL);
427           IF l_item_qty < 0 THEN
428             RAISE UOM_CONVERSION_ERROR;
429           END IF;
430           /* gmicuom.icuomcv(get_rec.item_id, 0, l_item_qty, l_line_um, get_rec.item_um, l_item_qty); */
431         END IF;
432         IF (l_item_qty >= get_rec.min_qty AND l_item_qty <= get_rec.max_qty) THEN
433           IF p_least_cost_validity = 'T' THEN
434             GMD_VALIDITY_RULES.get_formula_cost (p_formula_id => l_formula_id
435                                                 ,p_requested_qty => l_item_qty
436                                                 ,p_requested_uom => get_rec.detail_uom
437                                                 ,p_product_id => get_rec.inventory_item_id
438                                                 ,p_organization_id   => p_organization_id
439                                                 ,X_unit_cost => l_unit_cost
440                                                 ,X_total_cost => l_total_cost
441                                                 ,X_return_status => l_return_status);
442             IF l_return_status <> FND_API.g_ret_sts_success THEN
443               RAISE GET_FORMULA_COST_ERR;
444             END IF;
445           END IF; /* IF p_least_cost_validity = 'T' */
446           GMD_VALIDITY_RULES.insert_val_temp_tbl(p_val_rec => get_rec
447                                                 ,p_unit_cost => l_unit_cost
448                                                 ,p_total_cost => l_total_cost);
449         END IF; /* IF (l_item_qty >= get_rec.min_qty AND l_item_qty <= get_rec.max_qty) */
450       END IF; /* IF (l_scale_type = 1) */
451      EXCEPTION
452        WHEN ITEM_ORGN_MISSING THEN
453          x_return_status := FND_API.G_RET_STS_ERROR;
454      END;
455      END LOOP;
456    ELSIF (p_item_id IS NOT NULL or p_item_no IS NOT NULL) THEN
457 
458     /* Try to get validity rules based on Item */
459     OPEN cur_item_uom(p_item_id);
460     FETCH cur_item_uom INTO l_item_uom;
461     CLOSE cur_item_uom;
462 
463     IF (p_uom <> l_item_uom) THEN
464       -- NPD Conv. Changed the call to INV_CONVERT.inv_um_convert from gmicuom.uom_conversion
465        l_quantity := ROUND(gmicuom.uom_conversion(p_item_id,0,p_product_qty, p_uom, l_item_uom, 0),9);
466 
467  l_quantity := INV_CONVERT.inv_um_convert(item_id        => p_item_id
468                                               ,precision      => 5
469                                               ,from_quantity  => p_product_qty
470                                               ,from_unit      => p_uom
471                                               ,to_unit        => l_item_uom
472                                               ,from_name      => NULL
473                                               ,to_name	      => NULL);
474 
475       IF (l_quantity < 0) THEN
476         RAISE UOM_CONVERSION_ERROR;
477       END IF;
478     ELSE
479       l_quantity := p_product_qty;
480     END IF;
481 
482     /* Get item id if it is not passed in */
483     IF (p_item_id IS NOT NULL) THEN
484     	l_item_id := p_item_id;
485     ELSIF (p_item_no IS NOT NULL) THEN
486       OPEN get_item_id(p_item_no);
487       FETCH get_item_id INTO l_item_id;
488         IF get_item_id%NOTFOUND THEN
489           CLOSE get_item_id;
490           RAISE ITEM_NOT_FOUND_ERROR;
491         END IF;
492       CLOSE get_item_id;
493     ELSE
494       RAISE ITEM_NOT_FOUND_ERROR;
495     END IF;
496 
497     FOR get_rec IN get_val_item(l_quantity) LOOP
498     BEGIN
499       x_return_status := FND_API.G_RET_STS_SUCCESS;
500 
501       /* Get the formula for this recipe */
502       OPEN Cur_get_formula (get_rec.recipe_id);
503       FETCH Cur_get_formula INTO l_formula_id;
504       CLOSE Cur_get_formula;
505 
506       -- NPD Conv.
507       IF (p_orgn_code IS NOT NULL OR (p_orgn_code IS NULL AND p_organization_id IS NOT NULL)) THEN
508          IF p_orgn_code IS NULL THEN
509 		OPEN Cur_get_orgn_code;
510 		FETCH Cur_get_orgn_code INTO l_orgn_code;
511 		CLOSE Cur_get_orgn_code;
512 	 ELSE
513 		l_orgn_code := p_orgn_code;
514 	 END IF;
515          GMD_API_GRP.check_item_exists (p_formula_id            => l_formula_id
516 	                               ,p_organization_id       => p_organization_id
517 	                               ,p_orgn_code             => p_orgn_code
518 	                               ,x_return_status         => l_return_status
519 	                               ,p_Production_check      => TRUE);
520 	 IF l_return_status <> FND_API.G_RET_STS_SUCCESS THEN
521 	        RAISE ITEM_ORGN_MISSING;
522 	 END IF;
523       END IF;
524       -- End NPD Conv.
525 
526       IF p_least_cost_validity = 'T' THEN
527         GMD_VALIDITY_RULES.get_formula_cost (p_formula_id => l_formula_id
528                                             ,p_requested_qty => l_quantity
529                                             ,p_requested_uom => l_item_uom
530                                             ,p_product_id => get_rec.inventory_item_id
531                                             ,p_organization_id   => p_organization_id
532                                             ,X_unit_cost => l_unit_cost
533                                             ,X_total_cost => l_total_cost
534                                             ,X_return_status => l_return_status);
535         IF l_return_status <> FND_API.g_ret_sts_success THEN
536           RAISE GET_FORMULA_COST_ERR;
537         END IF;
538       END IF; /* IF p_least_cost_validity = 'T' */
539 
540       GMD_VALIDITY_RULES.insert_val_temp_tbl(p_val_rec => get_rec
541                                             ,p_unit_cost => l_unit_cost
542                                             ,p_total_cost => l_total_cost);
543     EXCEPTION
544       WHEN ITEM_ORGN_MISSING THEN
545         x_return_status := FND_API.G_RET_STS_ERROR;
546     END;
547     END LOOP;
548 
549   ELSE
550     /* Try to get validity rules based on recipe ID */
551     -- Changed IF p_recipe_id NOT NULL to IF l_recipe_id IS NOT NULL as it fails when recipe no and vers
552     -- are passed instead of id
553     -- Bug 3818835 - Start
554     IF l_recipe_id IS NOT NULL THEN
555 
556       -- Get the formula attached with the recipe
557       OPEN Cur_get_formula (l_recipe_id);
558       FETCH Cur_get_formula INTO l_formula_id;
559       CLOSE Cur_get_formula;
560 
561       -- Get formula product quantity
562       OPEN  get_form_prod(l_formula_id);
563       FETCH get_form_prod INTO l_prod_id,l_form_qty,l_prod_uom;
564       CLOSE get_form_prod;
565 
566       IF p_product_qty IS NOT NULL THEN -- Add Check to see if Prod Qty. is passed as NULL
567         -- check uom conversion here
568         -- NPD Conv. Changed the call to INV_CONVERT.inv_um_convert from gmicuom.uom_conversion
569         l_quantity := INV_CONVERT.inv_um_convert(item_id        => p_item_id
570                                                 ,precision      => 5
571                                                 ,from_quantity  => p_product_qty
572                                                 ,from_unit      => p_uom
573                                                 ,to_unit        => l_item_uom
574                                                 ,from_name      => NULL
575                                                 ,to_name	=> NULL);
576         IF (l_quantity < 0) THEN
577           RAISE UOM_CONVERSION_ERROR;
578         END IF;
579       ELSE
580         -- NPD Conv. Commented out below logic as ic_plnt_inv table is obsolete after conv.
581         l_quantity := l_form_qty;
582       END IF;
583     END IF; /* IF l_recipe_id IS NOT NULL THEN */
584     -- Bug 3818835 - End
585 
586     FOR get_rec IN get_val LOOP
587     BEGIN
588       x_return_status := FND_API.G_RET_STS_SUCCESS;
589 
590        -- NPD Conv.
591       IF (p_orgn_code IS NOT NULL OR (p_orgn_code IS NULL AND p_organization_id IS NOT NULL)) THEN
592 
593          IF p_orgn_code IS NULL THEN
594 		OPEN Cur_get_orgn_code;
595 		FETCH Cur_get_orgn_code INTO l_orgn_code;
596 		CLOSE Cur_get_orgn_code;
597 	 ELSE
598 		l_orgn_code := p_orgn_code;
599 	 END IF;
600          GMD_API_GRP.check_item_exists (p_formula_id        => l_formula_id
601 	                               ,p_organization_id   => NULL
602 	                               ,p_orgn_code         => l_orgn_code
603 	                               ,x_return_status     => l_return_status
604 	                               ,p_Production_check  => TRUE);
605 
606 	 IF l_return_status <> FND_API.G_RET_STS_SUCCESS THEN
607 		RAISE ITEM_ORGN_MISSING;
608 	 END IF;
609       END IF;
610       -- End NPD Conv.
611 
612       -- Bug 3818835
613       -- Select validity rule only if qty. is greater than min qty and lesser than max qty of validity rule.
614       IF (l_quantity >= get_rec.inv_min_qty AND l_quantity <= get_rec.inv_max_qty) THEN  -- Bug #5211935 inv_min_qty , inv_max_qty instead of min_qty, max_qty
615 
616         IF p_least_cost_validity = 'T' THEN
617           GMD_VALIDITY_RULES.get_formula_cost (p_formula_id => l_formula_id
618                                               ,p_requested_qty => l_quantity
619                                               ,p_requested_uom => get_rec.detail_uom
620                                               ,p_product_id => get_rec.inventory_item_id
621                                               ,p_organization_id   => p_organization_id
622                                               ,X_unit_cost => l_unit_cost
623                                               ,X_total_cost => l_total_cost
624                                               ,X_return_status => l_return_status);
625           IF l_return_status <> FND_API.g_ret_sts_success THEN
626             RAISE GET_FORMULA_COST_ERR;
627           END IF;
628         END IF; /* IF p_least_cost_validity = 'T' */
629 
630         GMD_VALIDITY_RULES.insert_val_temp_tbl(p_val_rec => get_rec
631                                               ,p_unit_cost => l_unit_cost
632                                               ,p_total_cost => l_total_cost);
633 
634       END IF; /* IF (l_quantity >= get_rec.min_qty AND l_quantity <= get_rec.max_qty) */
635     EXCEPTION
636       WHEN ITEM_ORGN_MISSING THEN
637         x_return_status := FND_API.G_RET_STS_ERROR;
638     END;
639     END LOOP;
640   END IF;
641 
642   i := 0;
643   FOR l_rec IN Cur_get_VR LOOP
644     i := i + 1;
645     x_recipe_validity_out(i).recipe_validity_rule_id := l_rec.recipe_validity_rule_id ;
646     x_recipe_validity_out(i).recipe_id               := l_rec.recipe_id ;
647     x_recipe_validity_out(i).orgn_code               := l_rec.orgn_code ;
648     x_recipe_validity_out(i).recipe_use              := l_rec.recipe_use ;
649     x_recipe_validity_out(i).preference              := l_rec.preference ;
650     x_recipe_validity_out(i).start_date              := l_rec.start_date ;
651     x_recipe_validity_out(i).end_date                := l_rec.end_date ;
652     x_recipe_validity_out(i).min_qty                 := l_rec.min_qty ;
653     x_recipe_validity_out(i).max_qty                 := l_rec.max_qty ;
654     x_recipe_validity_out(i).std_qty                 := l_rec.std_qty ;
655     x_recipe_validity_out(i).inv_min_qty             := l_rec.inv_min_qty ;
656     x_recipe_validity_out(i).inv_max_qty             := l_rec.inv_max_qty ;
657     x_recipe_validity_out(i).text_code               := l_rec.text_code ;
658     x_recipe_validity_out(i).attribute_category      := l_rec.attribute_category ;
659     x_recipe_validity_out(i).attribute1              := l_rec.attribute1 ;
660     x_recipe_validity_out(i).attribute2              := l_rec.attribute2 ;
661     x_recipe_validity_out(i).attribute3              := l_rec.attribute3 ;
662     x_recipe_validity_out(i).attribute4              := l_rec.attribute4 ;
663     x_recipe_validity_out(i).attribute5              := l_rec.attribute5 ;
664     x_recipe_validity_out(i).attribute6              := l_rec.attribute6 ;
665     x_recipe_validity_out(i).attribute7              := l_rec.attribute7 ;
666     x_recipe_validity_out(i).attribute8              := l_rec.attribute8 ;
667     x_recipe_validity_out(i).attribute9              := l_rec.attribute9 ;
668     x_recipe_validity_out(i).attribute10             := l_rec.attribute10 ;
669     x_recipe_validity_out(i).attribute11             := l_rec.attribute11;
670     x_recipe_validity_out(i).attribute12             := l_rec.attribute12 ;
671     x_recipe_validity_out(i).attribute13             := l_rec.attribute13 ;
672     x_recipe_validity_out(i).attribute14             := l_rec.attribute14 ;
673     x_recipe_validity_out(i).attribute15             := l_rec.attribute15 ;
674     x_recipe_validity_out(i).attribute16             := l_rec.attribute16 ;
675     x_recipe_validity_out(i).attribute17             := l_rec.attribute17 ;
676     x_recipe_validity_out(i).attribute18             := l_rec.attribute18 ;
677     x_recipe_validity_out(i).attribute19             := l_rec.attribute19 ;
678     x_recipe_validity_out(i).attribute20             := l_rec.attribute20 ;
679     x_recipe_validity_out(i).attribute21             := l_rec.attribute21 ;
680     x_recipe_validity_out(i).attribute22             := l_rec.attribute22 ;
681     x_recipe_validity_out(i).attribute23             := l_rec.attribute23 ;
682     x_recipe_validity_out(i).attribute24             := l_rec.attribute24 ;
683     x_recipe_validity_out(i).attribute25             := l_rec.attribute25 ;
684     x_recipe_validity_out(i).attribute26             := l_rec.attribute26 ;
685     x_recipe_validity_out(i).attribute27             := l_rec.attribute27 ;
686     x_recipe_validity_out(i).attribute28             := l_rec.attribute28 ;
687     x_recipe_validity_out(i).attribute29             := l_rec.attribute29 ;
688     x_recipe_validity_out(i).attribute30             := l_rec.attribute30 ;
689     x_recipe_validity_out(i).created_by              := l_rec.created_by ;
690     x_recipe_validity_out(i).creation_date           := l_rec.creation_date ;
691     x_recipe_validity_out(i).last_updated_by         := l_rec.last_updated_by ;
692     x_recipe_validity_out(i).last_update_date        := l_rec.last_update_date ;
693     x_recipe_validity_out(i).last_update_login       := l_rec.last_update_login ;
694     x_recipe_validity_out(i).validity_rule_status    := l_rec.validity_rule_status ;
695     x_recipe_validity_out(i).planned_process_loss    := l_rec.planned_process_loss ;
696     x_recipe_validity_out(i).organization_id         := l_rec.organization_id ;
697     x_recipe_validity_out(i).inventory_item_id       := l_rec.inventory_item_id ;
698     x_recipe_validity_out(i).revision                := l_rec.revision ;
699     x_recipe_validity_out(i).detail_uom              := l_rec.detail_uom ;
700     x_recipe_validity_out(i).unit_cost		 := l_rec.unit_cost ;
701     x_recipe_validity_out(i).total_cost		 := l_rec.total_cost ;
702   END LOOP;
703 
704   IF i > 0 THEN
705     X_return_status := Fnd_api.G_ret_sts_success;
706   END IF;
707 
708   -- standard call to get msge cnt, and if cnt is 1, get mesg info
709   FND_MSG_PUB.Count_And_Get(p_count=>x_msg_count, p_data=>x_msg_data);
710 EXCEPTION
711   WHEN NO_YIELD_TYPE_UM THEN
712       x_return_status := FND_API.G_RET_STS_ERROR;
713       FND_MESSAGE.SET_NAME('GMD', 'FM_SCALE_BAD_YIELD_TYPE');
714       FND_MSG_PUB.ADD;
715       FND_MSG_PUB.COUNT_AND_GET (P_count => x_msg_count,
716                                  P_data  => x_msg_data);
717   WHEN GET_FORMULA_COST_ERR THEN
718       x_return_status := FND_API.G_RET_STS_ERROR;
719       FND_MSG_PUB.COUNT_AND_GET (P_count => x_msg_count,
720                                  P_data  => x_msg_data);
721   WHEN GET_FORMULA_ERR THEN
722       x_return_status := FND_API.G_RET_STS_ERROR;
723       FND_MSG_PUB.COUNT_AND_GET (P_count => x_msg_count,
724                                  P_data  => x_msg_data);
725   WHEN GET_TOTAL_QTY_ERR OR GET_OUTPUT_RATIO_ERR
726        OR GET_INGREDPROD_RATIO_ERR OR GET_BATCHFORMULA_RATIO_ERR
727        OR GET_CONTRIBUTING_QTY_ERR OR GET_INPUT_RATIO_ERR THEN
728       x_return_status := FND_API.G_RET_STS_ERROR;
729       FND_MSG_PUB.COUNT_AND_GET (P_count => x_msg_count,
730                                  P_data  => x_msg_data);
731   WHEN UOM_CONVERSION_ERROR THEN
732       x_return_status := FND_API.G_RET_STS_ERROR;
733       gmd_validity_rules.uom_conversion_mesg(p_item_id => p_item_id,
734                                                    p_from_um => p_uom,
735                                                    p_to_um   => l_item_uom);
736       FND_MSG_PUB.COUNT_AND_GET (P_count => x_msg_count,
737                                  P_data  => x_msg_data);
738 
739   WHEN FND_API.G_EXC_ERROR THEN
740       X_return_code   := SQLCODE;
741       x_return_status := FND_API.G_RET_STS_ERROR;
742       FND_MSG_PUB.Count_And_Get(p_count=>x_msg_count, p_data=>x_msg_data);
743 
744   WHEN FND_API.G_EXC_UNEXPECTED_ERROR THEN
745       X_return_code   := SQLCODE;
746       x_return_status := FND_API.G_RET_STS_UNEXP_ERROR;
747       FND_MSG_PUB.Count_And_Get(p_count=>x_msg_count, p_data=>x_msg_data);
748 
749   WHEN OTHERS THEN
750       X_return_code   := SQLCODE;
751       x_return_status := FND_API.G_RET_STS_ERROR;
752       FND_MSG_PUB.Count_And_Get(p_count=>x_msg_count, p_data=>x_msg_data);
753 END get_validity_rules;
754 
755 /*======================================================================
756 --  PROCEDURE :
757 --   get_output_ratio
758 --
759 --  DESCRIPTION:
760 --    This PL/SQL procedure is responsible for determining
761 --    the output ratio which is the ratio of the batch output
762 --    to the formula output when a total output qty is used as
763 --    the criteria for a validity rule.
764 --
765 --  REQUIREMENTS
766 --
767 --  SYNOPSIS:
768 --    get_output_ratio (X_formula_id, X_batch_output, X_yield_um,
769 --                      X_formula_output, X_return_status, X_output_ratio);
770 --
771 --===================================================================== */
772 PROCEDURE get_output_ratio(p_formula_id     IN  NUMBER,
773                            p_batch_output   IN  NUMBER,
774                            p_yield_um       IN  VARCHAR2,
775                            p_formula_output IN NUMBER,
776                            x_return_status  OUT NOCOPY VARCHAR2,
777                            X_output_ratio   OUT NOCOPY NUMBER) IS
778   CURSOR Cur_get_prods IS
779     SELECT inventory_item_id, qty, detail_uom, scale_type
780     FROM   fm_matl_dtl
781     WHERE  formula_id = p_formula_id
782            AND line_type IN (1,2);
783 
784   l_batch_output       NUMBER := 0;
785   l_formula_output     NUMBER := 0;
786   l_conv_qty           NUMBER := 0;
787   l_total_fixed_qty    NUMBER := 0;
788   X_item_id            NUMBER;
789   X_detail_uom         VARCHAR2(4);
790   UOM_CONVERSION_ERROR EXCEPTION;
791 
792 BEGIN
793   x_return_status := FND_API.G_RET_STS_SUCCESS;
794   FOR get_rec IN Cur_get_prods
795   LOOP
796     IF (get_rec.scale_type = 0) THEN
797       IF (get_rec.detail_uom <> p_yield_um) THEN
798 
799         -- NPD Conv. Changed the call to INV_CONVERT.inv_um_convert from gmicuom.uom_conversion
800         l_conv_qty := INV_CONVERT.inv_um_convert(item_id         => get_rec.inventory_item_id
801                                                 ,precision       => 5
802                                                 ,from_quantity   => get_rec.qty
803                                                 ,from_unit       => get_rec.detail_uom
804                                                 ,to_unit         => p_yield_um
805                                                 ,from_name       => NULL
806                                                 ,to_name	 => NULL);
807         IF (l_conv_qty < 0) THEN
808           X_item_id     := get_rec.inventory_item_id;
809           X_detail_uom := get_rec.detail_uom;
810           RAISE UOM_CONVERSION_ERROR;
811         END IF;
812         l_total_fixed_qty := l_total_fixed_qty + l_conv_qty;
813       ELSE
814         l_total_fixed_qty := l_total_fixed_qty + get_rec.qty;
815       END IF;
816     END IF;
817   END LOOP;
818 
819   l_batch_output   := p_batch_output - l_total_fixed_qty;
820   l_formula_output := p_formula_output - l_total_fixed_qty;
821   X_output_ratio   := l_batch_output/l_formula_output;
822 
823   EXCEPTION
824     WHEN UOM_CONVERSION_ERROR THEN
825       x_return_status := FND_API.G_RET_STS_ERROR;
826       gmd_validity_rules.uom_conversion_mesg(p_item_id => X_item_id,
827                                                    p_from_um => X_detail_uom,
828                                                    p_to_um   => p_yield_um);
829 END get_output_ratio;
830 
831 /*======================================================================
832 --  PROCEDURE :
833 --   get_ingredprod_ratio
834 --
835 --  DESCRIPTION:
836 --    This PL/SQL procedure is responsible for determining
837 --    the ratio of the products to ingredients while trying
838 --    to determine validity rules based on total input qty.
839 --
840 --  REQUIREMENTS
841 --
842 --  SYNOPSIS:
843 --    get_ingredprod_ratio (X_formula_id, X_yield_um,
844 --                          X_ingred_prod_ratio, X_status);
845 --
846 --===================================================================== */
847 PROCEDURE get_ingredprod_ratio(p_formula_id        IN  NUMBER,
848                                p_yield_um          IN  VARCHAR2,
849                                X_ingred_prod_ratio OUT NOCOPY NUMBER,
850                                x_return_status     OUT NOCOPY VARCHAR2) IS
851   -- NPD Conv.
852   CURSOR Cur_get_details(V_line_type NUMBER) IS
853     SELECT inventory_item_id, qty, detail_uom, scale_type, contribute_yield_ind
854     FROM   fm_matl_dtl
855     WHERE  formula_id = p_formula_id
856            AND line_type = V_line_type;
857 
858   l_sum_prods        NUMBER := 0;
859   l_sum_ingreds      NUMBER := 0;
860   l_conv_qty           NUMBER := 0;
861   X_item_id            NUMBER;
862   X_detail_uom         VARCHAR2(4);
863   UOM_CONVERSION_ERROR EXCEPTION;
864 BEGIN
865   x_return_status := FND_API.G_RET_STS_SUCCESS;
866   --Get sum of products in yield UM.
867   FOR get_rec IN Cur_get_details(1)
868   LOOP
869     IF (get_rec.detail_uom <> p_yield_um) THEN
870       -- NPD Conv. Changed the call to INV_CONVERT.inv_um_convert from gmicuom.uom_conversion
871      l_conv_qty := INV_CONVERT.inv_um_convert(item_id        => get_rec.inventory_item_id
872                                              ,precision      => 5
873                                              ,from_quantity  => get_rec.qty
874                                              ,from_unit      => get_rec.detail_uom
875                                              ,to_unit        => p_yield_um
876                                              ,from_name      => NULL
877                                              ,to_name	     => NULL);
878 
879       IF (l_conv_qty < 0) THEN
880         X_item_id := get_rec.inventory_item_id;
881         X_detail_uom := get_rec.detail_uom;
882         RAISE UOM_CONVERSION_ERROR;
883       END IF;
884       l_sum_prods := l_sum_prods + l_conv_qty;
885     ELSE
886       l_sum_prods := l_sum_prods + get_rec.qty;
887     END IF;
888   END LOOP;
889   --Get sum of ingredients in yield UM contributing to yield.
890   FOR get_rec IN Cur_get_details(-1)
891   LOOP
892     IF (get_rec.contribute_yield_ind = 'Y') THEN
893       IF (get_rec.detail_uom <> p_yield_um) THEN
894         -- NPD Conv. Changed the call to INV_CONVERT.inv_um_convert from gmicuom.uom_conversion
895         l_conv_qty := INV_CONVERT.inv_um_convert(item_id        => get_rec.inventory_item_id
896                                                 ,precision      => 5
897                                                 ,from_quantity  => get_rec.qty
898                                                 ,from_unit      => get_rec.detail_uom
899                                                 ,to_unit        => p_yield_um
900                                                 ,from_name      => NULL
901                                                 ,to_name	=> NULL);
902         IF (l_conv_qty < 0) THEN
903           X_item_id := get_rec.inventory_item_id;
904           X_detail_uom := get_rec.detail_uom;
905           RAISE UOM_CONVERSION_ERROR;
906         END IF;
907         l_sum_ingreds := l_sum_ingreds + l_conv_qty;
908       ELSE
909         l_sum_ingreds := l_sum_ingreds + get_rec.qty;
910       END IF;
911     END IF;
912   END LOOP;
913 
914   --Get ratio and return.
915   X_ingred_prod_ratio := l_sum_prods/l_sum_ingreds;
916   EXCEPTION
917     WHEN UOM_CONVERSION_ERROR THEN
918       x_return_status := FND_API.G_RET_STS_ERROR;
919       gmd_validity_rules.uom_conversion_mesg(p_item_id => X_item_id,
920                                                    p_from_um => X_detail_uom,
921                                                    p_to_um   => p_yield_um);
922 END get_ingredprod_ratio;
923 
924 /*======================================================================
925 --  PROCEDURE :
926 --   get_batchformula_ratio
927 --
928 --  DESCRIPTION:
929 --    This PL/SQL procedure is responsible for determining
930 --    the ratio of the batch input qty to the formula input qty
931 --    while determining validity rules based on total input qty.
932 --
933 --  REQUIREMENTS
934 --
935 --  SYNOPSIS:
936 --    get_batchformula_ratio (X_formula_id, X_batch_input, X_yield_um,
937 --                            X_formula_input, X_batchformula_ratio,
938 --                            X_status);
939 --
940 --===================================================================== */
941 PROCEDURE get_batchformula_ratio(p_formula_id         IN  NUMBER,
942                                  p_batch_input        IN  NUMBER,
943                                  p_yield_um           IN  VARCHAR2,
944                                  p_formula_input      IN  NUMBER,
945                                  X_batchformula_ratio OUT NOCOPY NUMBER,
946                                  X_return_status      OUT NOCOPY VARCHAR2) IS
947   CURSOR Cur_get_ingreds IS
948     -- NPD Conv.
949     SELECT inventory_item_id, qty, detail_uom, scale_type
950     FROM   fm_matl_dtl
951     WHERE  formula_id = p_formula_id
952            AND line_type = -1;
953 
954   CURSOR Cur_get_total_input IS
955     SELECT total_input_qty, yield_uom
956     FROM   fm_form_mst
957     WHERE  formula_id = p_formula_id;
958   l_formula_input      NUMBER := 0;
959   l_fixed_ingred       NUMBER := 0;
960   l_batch_input        NUMBER := 0;
961   l_conv_qty           NUMBER := 0;
962   X_item_id            NUMBER;
963   X_detail_uom         VARCHAR2(4);
964   UOM_CONVERSION_ERROR EXCEPTION;
965 BEGIN
966   x_return_status := FND_API.G_RET_STS_SUCCESS;
967   FOR get_rec IN Cur_get_ingreds LOOP
968     IF (get_rec.scale_type = 0) THEN
969       IF (get_rec.detail_uom <> p_yield_um) THEN
970 
971         -- NPD Conv. Changed the call to INV_CONVERT.inv_um_convert from gmicuom.uom_conversion
972         l_conv_qty := INV_CONVERT.inv_um_convert(item_id        => get_rec.inventory_item_id
973                                                 ,precision      => 5
974                                                 ,from_quantity  => get_rec.qty
975                                                 ,from_unit      => get_rec.detail_uom
976                                                 ,to_unit        => p_yield_um
977                                                 ,from_name      => NULL
978                                                 ,to_name	   => NULL);
979         IF (l_conv_qty < 0) THEN
980           X_item_id := get_rec.inventory_item_id;
981           X_detail_uom := get_rec.detail_uom;
982           RAISE UOM_CONVERSION_ERROR;
983         END IF;
984         l_fixed_ingred := l_fixed_ingred + l_conv_qty;
985       ELSE
986         l_fixed_ingred := l_fixed_ingred + get_rec.qty;
987       END IF;
988     END IF;
989   END LOOP;
990   l_batch_input        := p_batch_input - l_fixed_ingred;
991   l_formula_input      := p_formula_input - l_fixed_ingred;
992   X_batchformula_ratio := l_batch_input / l_formula_input;
993   EXCEPTION
994     WHEN UOM_CONVERSION_ERROR THEN
995       x_return_status := FND_API.G_RET_STS_ERROR;
996       gmd_validity_rules.uom_conversion_mesg(p_item_id => X_item_id,
997                                                    p_from_um => X_detail_uom,
998                                                    p_to_um   => p_yield_um);
999 END get_batchformula_ratio;
1000 
1001 /*======================================================================
1002 --  PROCEDURE :
1003 --   get_contibuting_qty
1004 --
1005 --  DESCRIPTION:
1006 --    This PL/SQL procedure is responsible for determining
1007 --    the actual contributing qty of the formula.
1008 --
1009 --  REQUIREMENTS
1010 --
1011 --  SYNOPSIS:
1012 --    get_contributing_qty (X_formula_id, X_recipe_id,
1013 --                          X_formula_batch_ratio, X_yield_um,
1014 --                          X_formula_input, X_ratio, X_status);
1015 --
1016 --===================================================================== */
1017 PROCEDURE get_contributing_qty(p_formula_id          IN  NUMBER,
1018                                p_recipe_id           IN  NUMBER,
1019                                p_batchformula_ratio  IN  NUMBER,
1020                                p_yield_um            IN  VARCHAR2,
1021                                X_contributing_qty    OUT NOCOPY NUMBER,
1022                                X_return_status       OUT NOCOPY VARCHAR2) IS
1023   -- NPD Conv.
1024   CURSOR Cur_get_ingreds IS
1025     SELECT inventory_item_id, qty, detail_uom, scale_type, contribute_yield_ind
1026     FROM   fm_matl_dtl
1027     WHERE  formula_id = p_formula_id
1028            AND line_type = -1;
1029 
1030   l_conv_qty           NUMBER := 0;
1031   l_process_loss       NUMBER := 0;
1032   l_theo_process_loss   NUMBER := 0;
1033   l_msg_count          Number := 0;
1034   l_msg_data  Varchar2(240);
1035   X_item_id            NUMBER;
1036   X_detail_uom         VARCHAR2(4);
1037   X_status             VARCHAR2(100);
1038   l_process_rec        gmd_common_val.process_loss_rec;
1039   UOM_CONVERSION_ERROR EXCEPTION;
1040   PROCESS_LOSS_ERR     EXCEPTION;
1041 BEGIN
1042   x_contributing_qty := 0;
1043   x_return_status := FND_API.G_RET_STS_SUCCESS;
1044   /* Loop through ingredients and determine total contributing qty */
1045   FOR get_rec IN Cur_get_ingreds LOOP
1046     IF (get_rec.contribute_yield_ind = 'Y') THEN
1047       /* Convert all ingredient values to yield UM and determine contributing qty */
1048       IF (get_rec.detail_uom <> p_yield_um) THEN
1049          -- NPD Conv. Changed the call to INV_CONVERT.inv_um_convert from gmicuom.uom_conversion
1050         l_conv_qty := INV_CONVERT.inv_um_convert(item_id        => get_rec.inventory_item_id
1051                                                 ,precision      => 5
1052                                                 ,from_quantity  => get_rec.qty
1053                                                 ,from_unit      => get_rec.detail_uom
1054                                                 ,to_unit        => p_yield_um
1055                                                 ,from_name      => NULL
1056                                                 ,to_name	=> NULL);
1057         IF (l_conv_qty < 0) THEN
1058           X_item_id := get_rec.inventory_item_id;
1059           X_detail_uom := get_rec.detail_uom;
1060           RAISE UOM_CONVERSION_ERROR;
1061         END IF;
1062       ELSE
1063         l_conv_qty := get_rec.qty;
1064       END IF;
1065       /* If ingredient scalable multiply by ratio and calculate contributing qty */
1066       IF (get_rec.scale_type = 1) THEN
1067         X_contributing_qty := X_contributing_qty + (l_conv_qty * p_batchformula_ratio);
1068       ELSE
1069         X_contributing_qty := X_contributing_qty + l_conv_qty;
1070       END IF;
1071     END IF;
1072   END LOOP;
1073   /* Get process loss for this qty */
1074   l_process_rec.qty       := X_contributing_qty;
1075   l_process_rec.recipe_id := p_recipe_id;
1076   gmd_common_val.calculate_process_loss(process_loss    => l_process_rec,
1077                                         Entity_type => 'RECIPE' ,
1078                                         x_recipe_theo_loss => l_theo_process_loss,
1079                                         x_process_loss  => l_process_loss,
1080                                         x_return_status => X_status,
1081                                         x_msg_count => l_msg_count,
1082                                         x_msg_data => l_msg_data);
1083 
1084  /* IF (X_status <> FND_API.G_RET_STS_SUCCESS) THEN
1085     RAISE PROCESS_LOSS_ERR;
1086   END IF;*/
1087   /* Shrikant : Added NVL and / 100 in the following equation */
1088   X_contributing_qty := X_contributing_qty * (100 - NVL(l_process_loss,0))/100;
1089   EXCEPTION
1090     WHEN UOM_CONVERSION_ERROR THEN
1091       x_return_status := FND_API.G_RET_STS_ERROR;
1092       gmd_validity_rules.uom_conversion_mesg(p_item_id => X_item_id,
1093                                                    p_from_um => X_detail_uom,
1094                                                    p_to_um   => p_yield_um);
1095 END get_contributing_qty;
1096 
1097 /*======================================================================
1098 --  PROCEDURE :
1099 --   get_input_ratio
1100 --
1101 --  DESCRIPTION:
1102 --    This PL/SQL procedure is responsible for determining
1103 --    the actual ratio of product for the total input qty.
1104 --
1105 --  REQUIREMENTS
1106 --
1107 --  SYNOPSIS:
1108 --    get_input_ratio (X_formula_id, X_contributing_qty, X_yield_um,
1109 --                     X_formula_output, X_output_ratio, X_status);
1110 --
1111 --===================================================================== */
1112 PROCEDURE get_input_ratio(p_formula_id       IN  NUMBER,
1113                           p_contributing_qty IN  NUMBER,
1114                           p_yield_um         IN  VARCHAR2,
1115                           p_formula_output   IN  NUMBER,
1116                           X_output_ratio     OUT NOCOPY NUMBER,
1117                           X_return_status    OUT NOCOPY VARCHAR2) IS
1118   -- NPD Conv.
1119   CURSOR Cur_get_prods IS
1120     SELECT inventory_item_id, qty, detail_uom, scale_type
1121     FROM   fm_matl_dtl
1122     WHERE  formula_id = p_formula_id
1123            AND line_type = 1;
1124 
1125   l_contributing_qty   NUMBER := 0;
1126   l_formula_output     NUMBER := 0;
1127   l_conv_qty           NUMBER := 0;
1128   l_fixed_prod         NUMBER := 0;
1129   X_item_id            NUMBER ;
1130   X_detail_uom            VARCHAR2(4);
1131   UOM_CONVERSION_ERROR EXCEPTION;
1132 BEGIN
1133   FOR get_rec IN Cur_get_prods LOOP
1134     IF (get_rec.scale_type = 0) THEN
1135       IF (get_rec.detail_uom <> p_yield_um) THEN
1136 
1137         -- NPD Conv. Changed the call to INV_CONVERT.inv_um_convert from gmicuom.uom_conversion
1138         l_conv_qty := INV_CONVERT.inv_um_convert(item_id        => get_rec.inventory_item_id
1139                                                 ,precision      => 5
1140                                                 ,from_quantity  => get_rec.qty
1141                                                 ,from_unit      => get_rec.detail_uom
1142                                                 ,to_unit        => p_yield_um
1143                                                 ,from_name      => NULL
1144                                                 ,to_name	=> NULL);
1145         IF (l_conv_qty < 0) THEN
1146           X_item_id := get_rec.inventory_item_id;
1147           X_detail_uom := get_rec.detail_uom;
1148           RAISE UOM_CONVERSION_ERROR;
1149         END IF;
1150         l_fixed_prod := l_fixed_prod + l_conv_qty;
1151       ELSE
1152         l_fixed_prod := l_fixed_prod + get_rec.qty;
1153       END IF;
1154     END IF;
1155   END LOOP;
1156   l_contributing_qty := p_contributing_qty - l_fixed_prod;
1157   l_formula_output   := P_formula_output - l_fixed_prod;
1158   X_output_ratio     := l_contributing_qty / l_formula_output;
1159   EXCEPTION
1160     WHEN UOM_CONVERSION_ERROR THEN
1161       x_return_status := FND_API.G_RET_STS_ERROR;
1162       gmd_validity_rules.uom_conversion_mesg(p_item_id => X_item_id,
1163                                                    p_from_um => X_detail_uom,
1164                                                    p_to_um   => p_yield_um);
1165 END get_input_ratio;
1166 
1167 /*======================================================================
1168 --  PROCEDURE :
1169 --   uom_conversion_mesg
1170 --
1171 --  DESCRIPTION:
1172 --    This PL/SQL procedure is responsible for showing
1173 --    the the message about uom conversion errors.
1174 --
1175 --  REQUIREMENTS
1176 --
1177 --  SYNOPSIS:
1178 --    uom_conversion_mesg (X_item_id, X_from_um, X_to_um);
1179 --
1180 --===================================================================== */
1181 PROCEDURE uom_conversion_mesg(p_item_id IN NUMBER,
1182                               p_from_um IN VARCHAR2,
1183                               p_to_um   IN VARCHAR2) IS
1184 
1185   -- NPD Conv. Modified cursor to get concatenated segments for the item_id
1186   CURSOR Cur_get_item IS
1187     SELECT concatenated_segments
1188     FROM   mtl_system_items_kfv
1189     WHERE  inventory_item_id = p_item_id;
1190   X_item_no VARCHAR2(32);
1191 BEGIN
1192   OPEN Cur_get_item;
1193   FETCH Cur_get_item INTO X_item_no;
1194   CLOSE Cur_get_item;
1195   FND_MESSAGE.SET_NAME('GMI', 'IC_API_UOM_CONVERSION_ERROR');
1196   FND_MESSAGE.SET_TOKEN('ITEM_NO', X_item_no);
1197   FND_MESSAGE.SET_TOKEN('FROM_UOM', p_from_um);
1198   FND_MESSAGE.SET_TOKEN('TO_UOM', p_to_um);
1199   FND_MSG_PUB.ADD;
1200 END uom_conversion_mesg;
1201 
1202 
1203 /*======================================================================
1204 --  PROCEDURE :
1205 --   get_all_validity_rules
1206 --
1207 --  DESCRIPTION:
1208 --    This PL/SQL procedure  is responsible for getting all the
1209 --    validity rules based on the input parameters.
1210 --
1211 --  REQUIREMENTS
1212 --
1213 --  SYNOPSIS:
1214 --    get_all_validity_rules (1.0, X_init_msg_list, X_recipe_id, X_item_id,
1215 --                        X_return_status, X_msg_count, X_msg_data,
1216 --                        X_return_code, X_vr_table);
1217 --
1218 --  HISTORY
1219 --   RajaSekhar  11-Jul-2002 BUG#2436355  Added to get all ( Planning,costing,
1220 --                           prodoction etc) validity rules of all the statuses.
1221 --===================================================================== */
1222 /* Formatted on 2002/07/11 18:01 (RevealNet Formatter v4.4.0) */
1223 PROCEDURE Get_all_validity_rules (
1224    P_api_version           IN           NUMBER,
1225    P_init_msg_list         IN           VARCHAR2 := Fnd_api.G_false,
1226    P_recipe_id             IN           NUMBER   := NULL,
1227    P_item_id               IN           NUMBER   := NULL,
1228    p_revision              IN           VARCHAR2 := NULL,
1229    p_least_cost_validity   IN		VARCHAR2 := 'F',
1230    X_return_status         OUT NOCOPY   VARCHAR2,
1231    X_msg_count             OUT NOCOPY   NUMBER,
1232    X_msg_data              OUT NOCOPY   VARCHAR2,
1233    X_return_code           OUT NOCOPY   NUMBER,
1234    X_recipe_validity_out   OUT NOCOPY   Recipe_validity_tbl
1235 )
1236 IS
1237    --  local Variables
1238    L_api_name                    VARCHAR2 (30) := 'get_validity_rules';
1239    L_api_version                 NUMBER := 1.0;
1240    I                             NUMBER := 0;
1241    L_msg_count                   NUMBER;
1242    L_msg_data                    VARCHAR2 (100);
1243    L_return_status		 VARCHAR2(10);
1244    L_return_code                 VARCHAR2 (10);
1245 
1246    l_unit_cost		   NUMBER;
1247    l_total_cost		   NUMBER;
1248    l_formula_id		   NUMBER;
1249    l_quantity		   NUMBER;
1250    l_uom		   VARCHAR2(3);
1251 
1252    --Cursor to get data based on recipe ID
1253    CURSOR Get_val_recipe   IS
1254       SELECT   v.*
1255       FROM Gmd_recipe_validity_rules V, Gmd_recipes R, Gmd_status S
1256       WHERE V.Recipe_id = R.Recipe_id
1257       AND V.Validity_rule_status = S.Status_code
1258       AND V.Recipe_id = NVL (P_recipe_id, V.Recipe_id)
1259       AND v.delete_mark = 0
1260       ORDER BY R.Recipe_no,R.Recipe_version, V.Recipe_use,Orgn_code, Preference,S.Status_type;
1261 
1262    --Cursor to get data based on item.
1263 
1264    CURSOR Get_val_item   IS
1265      SELECT   V.*
1266      FROM Gmd_recipe_validity_rules V,
1267           Gmd_recipes R,
1268           Gmd_status S
1269      WHERE V.Recipe_id = R.Recipe_id
1270      AND V.Validity_rule_status = S.Status_code
1271      AND V.inventory_item_id = P_item_id
1272      AND (p_revision IS NULL OR (p_revision IS NOT NULL AND v.revision = p_revision))
1273      AND v.delete_mark = 0
1274      ORDER BY R.Recipe_no,R.Recipe_version, V.Recipe_use,Orgn_code, Preference,S.Status_type;
1275 
1276   CURSOR Cur_get_VR IS
1277     SELECT *
1278     FROM GMD_VAL_RULE_GTMP;
1279 
1280   CURSOR Cur_get_form_id (v_recipe_id NUMBER, V_inventory_item_id NUMBER) IS
1281     SELECT rcp.formula_id, SUM(qty), MAX(detail_uom)
1282     FROM gmd_recipes rcp, fm_matl_dtl d
1283     WHERE rcp.recipe_id = v_recipe_id
1284     AND   rcp.formula_id = d.formula_id
1285     AND   d.line_type = 1
1286     AND   d.inventory_item_id = V_inventory_item_id;
1287 
1288   GET_FORMULA_COST_ERR EXCEPTION;
1289 
1290 BEGIN
1291    IF (NOT Fnd_api.Compatible_api_call ( L_api_version,
1292                                          P_api_version,
1293                                          L_api_name,
1294                                          G_pkg_name ))
1295    THEN
1296       RAISE Fnd_api.G_exc_unexpected_error;
1297    END IF;
1298 
1299    IF (Fnd_api.To_boolean (P_init_msg_list))
1300    THEN
1301       Fnd_msg_pub.Initialize;
1302    END IF;
1303 
1304    X_return_status            := Fnd_api.G_ret_sts_success;
1305 
1306   /* Delete from this table for any existing data */
1307   DELETE FROM GMD_VAL_RULE_GTMP;
1308 
1309   IF (P_item_id IS NOT NULL)  THEN
1310     FOR Get_rec IN Get_val_item LOOP
1311       X_return_status            := Fnd_api.G_ret_sts_success;
1312 
1313       IF p_least_cost_validity = 'T' THEN
1314         OPEN Cur_get_form_id (get_rec.recipe_id, get_rec.inventory_item_id);
1315         FETCH Cur_get_form_id INTO l_formula_id, l_quantity, l_uom;
1316         CLOSE Cur_get_form_id;
1317         IF (get_rec.organization_id IS NOT NULL) THEN
1318           GMD_VALIDITY_RULES.get_formula_cost (p_formula_id => l_formula_id
1319                                               ,p_requested_qty => l_quantity
1320                                               ,p_requested_uom => l_uom
1321                                               ,p_product_id => get_rec.inventory_item_id
1322                                               ,p_organization_id   => get_rec.organization_id
1323                                               ,X_unit_cost => l_unit_cost
1324                                               ,X_total_cost => l_total_cost
1325                                               ,X_return_status => l_return_status);
1326           IF l_return_status <> FND_API.g_ret_sts_success THEN
1327             RAISE GET_FORMULA_COST_ERR;
1328           END IF;
1329         END IF;
1330       END IF; /* IF p_least_cost_validity = 'T' */
1331       GMD_VALIDITY_RULES.insert_val_temp_tbl(p_val_rec => get_rec
1332                                             ,p_unit_cost => l_unit_cost
1333                                             ,p_total_cost => l_total_cost);
1334     END LOOP;
1335   ELSE
1336     /* Try to get validity rules based on recipe ID */
1337     FOR Get_rec IN Get_val_recipe LOOP
1338       X_return_status            := Fnd_api.G_ret_sts_success;
1339 
1340       IF p_least_cost_validity = 'T' THEN
1341         OPEN Cur_get_form_id (get_rec.recipe_id, get_rec.inventory_item_id);
1342         FETCH Cur_get_form_id INTO l_formula_id, l_quantity, l_uom;
1343         CLOSE Cur_get_form_id;
1344         IF (get_rec.organization_id IS NOT NULL) THEN
1345           GMD_VALIDITY_RULES.get_formula_cost (p_formula_id => l_formula_id
1346                                               ,p_requested_qty => l_quantity
1347                                               ,p_requested_uom => l_uom
1348                                               ,p_product_id => get_rec.inventory_item_id
1349                                               ,p_organization_id   => get_rec.organization_id
1350                                               ,X_unit_cost => l_unit_cost
1351                                               ,X_total_cost => l_total_cost
1352                                               ,X_return_status => l_return_status);
1353           IF l_return_status <> FND_API.g_ret_sts_success THEN
1354             RAISE GET_FORMULA_COST_ERR;
1355           END IF;
1356         END IF;
1357       END IF; /* IF p_least_cost_validity = 'T' */
1358       GMD_VALIDITY_RULES.insert_val_temp_tbl(p_val_rec => get_rec
1359                                             ,p_unit_cost => l_unit_cost
1360                                             ,p_total_cost => l_total_cost);
1361     END LOOP;
1362   END IF;
1363 
1364   i := 0;
1365   FOR l_rec IN Cur_get_VR LOOP
1366     i := i + 1;
1367     x_recipe_validity_out(i).recipe_validity_rule_id := l_rec.recipe_validity_rule_id ;
1368     x_recipe_validity_out(i).recipe_id               := l_rec.recipe_id ;
1369     x_recipe_validity_out(i).orgn_code               := l_rec.orgn_code ;
1370     x_recipe_validity_out(i).recipe_use              := l_rec.recipe_use ;
1371     x_recipe_validity_out(i).preference              := l_rec.preference ;
1372     x_recipe_validity_out(i).start_date              := l_rec.start_date ;
1373     x_recipe_validity_out(i).end_date                := l_rec.end_date ;
1374     x_recipe_validity_out(i).min_qty                 := l_rec.min_qty ;
1375     x_recipe_validity_out(i).max_qty                 := l_rec.max_qty ;
1376     x_recipe_validity_out(i).std_qty                 := l_rec.std_qty ;
1377     x_recipe_validity_out(i).inv_min_qty             := l_rec.inv_min_qty ;
1378     x_recipe_validity_out(i).inv_max_qty             := l_rec.inv_max_qty ;
1379     x_recipe_validity_out(i).text_code               := l_rec.text_code ;
1380     x_recipe_validity_out(i).attribute_category      := l_rec.attribute_category ;
1381     x_recipe_validity_out(i).attribute1              := l_rec.attribute1 ;
1382     x_recipe_validity_out(i).attribute2              := l_rec.attribute2 ;
1383     x_recipe_validity_out(i).attribute3              := l_rec.attribute3 ;
1384     x_recipe_validity_out(i).attribute4              := l_rec.attribute4 ;
1385     x_recipe_validity_out(i).attribute5              := l_rec.attribute5 ;
1386     x_recipe_validity_out(i).attribute6              := l_rec.attribute6 ;
1387     x_recipe_validity_out(i).attribute7              := l_rec.attribute7 ;
1388     x_recipe_validity_out(i).attribute8              := l_rec.attribute8 ;
1389     x_recipe_validity_out(i).attribute9              := l_rec.attribute9 ;
1390     x_recipe_validity_out(i).attribute10             := l_rec.attribute10 ;
1391     x_recipe_validity_out(i).attribute11             := l_rec.attribute11;
1392     x_recipe_validity_out(i).attribute12             := l_rec.attribute12 ;
1393     x_recipe_validity_out(i).attribute13             := l_rec.attribute13 ;
1394     x_recipe_validity_out(i).attribute14             := l_rec.attribute14 ;
1395     x_recipe_validity_out(i).attribute15             := l_rec.attribute15 ;
1396     x_recipe_validity_out(i).attribute16             := l_rec.attribute16 ;
1397     x_recipe_validity_out(i).attribute17             := l_rec.attribute17 ;
1398     x_recipe_validity_out(i).attribute18             := l_rec.attribute18 ;
1399     x_recipe_validity_out(i).attribute19             := l_rec.attribute19 ;
1400     x_recipe_validity_out(i).attribute20             := l_rec.attribute20 ;
1401     x_recipe_validity_out(i).attribute21             := l_rec.attribute21 ;
1402     x_recipe_validity_out(i).attribute22             := l_rec.attribute22 ;
1403     x_recipe_validity_out(i).attribute23             := l_rec.attribute23 ;
1404     x_recipe_validity_out(i).attribute24             := l_rec.attribute24 ;
1405     x_recipe_validity_out(i).attribute25             := l_rec.attribute25 ;
1406     x_recipe_validity_out(i).attribute26             := l_rec.attribute26 ;
1407     x_recipe_validity_out(i).attribute27             := l_rec.attribute27 ;
1408     x_recipe_validity_out(i).attribute28             := l_rec.attribute28 ;
1409     x_recipe_validity_out(i).attribute29             := l_rec.attribute29 ;
1410     x_recipe_validity_out(i).attribute30             := l_rec.attribute30 ;
1411     x_recipe_validity_out(i).created_by              := l_rec.created_by ;
1412     x_recipe_validity_out(i).creation_date           := l_rec.creation_date ;
1413     x_recipe_validity_out(i).last_updated_by         := l_rec.last_updated_by ;
1414     x_recipe_validity_out(i).last_update_date        := l_rec.last_update_date ;
1415     x_recipe_validity_out(i).last_update_login       := l_rec.last_update_login ;
1416     x_recipe_validity_out(i).validity_rule_status    := l_rec.validity_rule_status ;
1417     x_recipe_validity_out(i).planned_process_loss    := l_rec.planned_process_loss ;
1418     x_recipe_validity_out(i).organization_id         := l_rec.organization_id ;
1419     x_recipe_validity_out(i).inventory_item_id       := l_rec.inventory_item_id ;
1420     x_recipe_validity_out(i).revision                := l_rec.revision ;
1421     x_recipe_validity_out(i).detail_uom              := l_rec.detail_uom ;
1422     x_recipe_validity_out(i).unit_cost		 := l_rec.unit_cost ;
1423     x_recipe_validity_out(i).total_cost		 := l_rec.total_cost ;
1424   END LOOP;
1425 
1426   -- standard call to get msge cnt, and if cnt is 1, get mesg info
1427   Fnd_msg_pub.Count_and_get (P_count => X_msg_count, P_data => X_msg_data);
1428 
1429 EXCEPTION
1430    WHEN GET_FORMULA_COST_ERR THEN
1431       x_return_status := FND_API.G_RET_STS_ERROR;
1432       FND_MSG_PUB.COUNT_AND_GET (P_count => x_msg_count,
1433                                  P_data  => x_msg_data);
1434    WHEN Fnd_api.G_exc_error THEN
1435       X_return_code              := SQLCODE;
1436       X_return_status            := Fnd_api.G_ret_sts_error;
1437       Fnd_msg_pub.Count_and_get ( P_count=> X_msg_count,
1438                                   P_data=> X_msg_data );
1439    WHEN Fnd_api.G_exc_unexpected_error  THEN
1440       X_return_code              := SQLCODE;
1441       X_return_status            := Fnd_api.G_ret_sts_unexp_error;
1442       Fnd_msg_pub.Count_and_get ( P_count=> X_msg_count,
1443                                   P_data=> X_msg_data );
1444    WHEN OTHERS THEN
1445       X_return_code              := SQLCODE;
1446       X_return_status            := Fnd_api.G_ret_sts_error;
1447       Fnd_msg_pub.Count_and_get ( P_count=> X_msg_count,
1448                                   P_data=> X_msg_data );
1449 END Get_all_validity_rules;
1450 
1451 /*======================================================================
1452 --  PROCEDURE :
1453 --   get_validity_scale_factor
1454 --
1455 --  DESCRIPTION:
1456 --    This PL/SQL procedure  is responsible for deriving the validity rule
1457 --    scale factor based on the std qty and the formula product qty.
1458 --
1459 --  REQUIREMENTS
1460 --
1461 --  SYNOPSIS:
1462 --    get_validity_scale_factor (p_recipe_id, p_item_id, p_std_qty, p_std_um,
1463 --                               x_scale_factor, x_return_status);
1464 --
1465 --
1466 --===================================================================== */
1467 PROCEDURE get_validity_scale_factor(p_recipe_id           IN  NUMBER ,
1468                                     p_item_id             IN  NUMBER ,
1469                                     p_std_qty             IN  NUMBER ,
1470                                     p_std_um              IN  VARCHAR2 ,
1471                                     x_scale_factor        OUT NOCOPY NUMBER,
1472                                     x_return_status       OUT NOCOPY VARCHAR2) IS
1473   CURSOR Cur_get_product_lines IS
1474     SELECT qty, detail_uom
1475     FROM   gmd_recipes_b r, fm_matl_dtl d
1476     WHERE  r.recipe_id = p_recipe_id
1477     AND    r.formula_id = d.formula_id
1478     AND    d.line_type = 1
1479     AND    d.inventory_item_id = p_item_id;
1480   l_prod_rec    Cur_get_product_lines%ROWTYPE;
1481   l_prod_qty    NUMBER DEFAULT 0;
1482   l_temp_qty    NUMBER;
1483 
1484   ITEM_NOT_FOUND        EXCEPTION;
1485   UOM_CONVERSION_ERR    EXCEPTION;
1486 BEGIN
1487   /* Let us initialize the return status to success */
1488   x_return_status := FND_API.g_ret_sts_success;
1489 
1490   /* Let us fetch the product quantities in the formula for the item passed in */
1491   OPEN Cur_get_product_lines;
1492   FETCH Cur_get_product_lines INTO l_prod_rec;
1493   IF Cur_get_product_lines%NOTFOUND THEN
1494     CLOSE Cur_get_product_lines;
1495     RAISE ITEM_NOT_FOUND;
1496   END IF;
1497   WHILE Cur_get_product_lines%FOUND
1498   LOOP
1499     IF l_prod_rec.detail_uom = p_std_um THEN
1500       l_prod_qty := l_prod_qty + l_prod_rec.qty;
1501     ELSE
1502      -- NPD Conv. Changed the call to INV_CONVERT.inv_um_convert from gmicuom.uom_conversion
1503      l_temp_qty := INV_CONVERT.inv_um_convert(item_id        => p_item_id
1504                                              ,precision      => 5
1505                                              ,from_quantity  => l_prod_rec.qty
1506                                              ,from_unit      => l_prod_rec.detail_uom
1507                                              ,to_unit        => p_std_um
1508                                              ,from_name      => NULL
1509                                              ,to_name	     => NULL);
1510       IF l_temp_qty < 0 THEN
1511         RAISE uom_conversion_err;
1512       ELSE
1513         l_prod_qty := l_prod_qty + l_temp_qty;
1514       END IF;
1515     END IF; /* IF l_prod_rec.item_um = p_std_um */
1516     FETCH Cur_get_product_lines INTO l_prod_rec;
1517   END LOOP; /* WHILE Cur_get_product_lines%FOUND */
1518   CLOSE Cur_get_product_lines;
1519 
1520   /* OK, now we have the product qty let us evaluate the ratio */
1521   IF l_prod_qty > 0 THEN
1522     x_scale_factor := p_std_qty / l_prod_qty;
1523   ELSE
1524     x_scale_factor := p_std_qty;
1525   END IF;
1526 EXCEPTION
1527   WHEN item_not_found THEN
1528     x_return_status := FND_API.g_ret_sts_error;
1529   WHEN uom_conversion_err THEN
1530     x_return_status := FND_API.g_ret_sts_error;
1531     uom_conversion_mesg (p_item_id, l_prod_rec.detail_uom, p_std_um);
1532   WHEN OTHERS THEN
1533     x_return_status := FND_API.g_ret_sts_unexp_error;
1534     fnd_msg_pub.add_exc_msg ('GMD_VALIDITY_RULES', 'GET_VALIDITY_SCALE_FACTOR');
1535 END get_validity_scale_factor;
1536 
1537 /*======================================================================
1538 --  PROCEDURE :
1539 --   get_validity_output_factor
1540 --
1541 --  DESCRIPTION:
1542 --    This PL/SQL procedure  is responsible for deriving the validity rule
1543 --    scale factor based on the std qty and the formula product qty.
1544 --
1545 --  REQUIREMENTS
1546 --
1547 --  SYNOPSIS:
1548 --    get_validity_output_factor (p_recipe_id, p_item_id, p_std_qty, p_std_um,
1549 --                               x_scale_factor, x_return_status);
1550 --
1551 --
1552 --===================================================================== */
1553 PROCEDURE get_validity_output_factor(p_recipe_id           IN  NUMBER ,
1554                                      p_item_id             IN  NUMBER ,
1555                                      p_std_qty             IN  NUMBER ,
1556                                      p_std_um              IN  VARCHAR2 ,
1557                                      x_scale_factor        OUT NOCOPY NUMBER,
1558                                      x_return_status       OUT NOCOPY VARCHAR2) IS
1559   CURSOR Cur_get_tot_qty IS
1560     SELECT f.formula_id, total_output_qty, yield_uom
1561     FROM   fm_form_mst_b f, gmd_recipes_b r
1562     WHERE  r.recipe_id = p_recipe_id
1563     AND    r.formula_id = f.formula_id;
1564 
1565   l_form_rec            Cur_get_tot_qty%ROWTYPE;
1566   l_total_output_qty    NUMBER;
1567   l_scaled_output_qty   NUMBER;
1568   l_ing_qty             NUMBER;
1569   l_temp_qty            NUMBER;
1570   l_scale_factor        NUMBER;
1571   l_msg_count           NUMBER;
1572   l_msg_data            VARCHAR2(2000);
1573   l_uom                 mtl_units_of_measure.unit_of_measure%TYPE;
1574 
1575 BEGIN
1576   /* Let us initialize the return status to success */
1577   x_return_status := FND_API.g_ret_sts_success;
1578 
1579   /* Lets get the scale factor between the validity std qty and the formula product qty */
1580   gmd_validity_rules.get_validity_scale_factor (p_recipe_id => p_recipe_id
1581                                                 ,p_item_id => p_item_id
1582                                                 ,p_std_qty => p_std_qty
1583                                                 ,p_std_um => p_std_um
1584                                                 ,x_scale_factor => l_scale_factor
1585                                                 ,x_return_status => x_return_status);
1586 
1587   OPEN Cur_get_tot_qty;
1588   FETCH Cur_get_tot_qty INTO l_form_rec;
1589   CLOSE Cur_get_tot_qty;
1590 
1591   IF l_form_rec.total_output_qty IS NULL THEN
1592     /* If the total output qty was not calculated previously let us recalculate it */
1593     l_uom := p_std_um;
1594     GMD_COMMON_VAL.Calculate_total_qty(formula_id => l_form_rec.formula_id,
1595                                         x_product_qty => l_total_output_qty,
1596                                         x_ingredient_qty => l_ing_qty,
1597                                         x_uom => l_uom,
1598                                         x_return_status => x_return_status,
1599                                         x_msg_count => l_msg_count,
1600                                         x_msg_data => l_msg_data);
1601   ELSE
1602     l_total_output_qty := l_form_rec.total_output_qty;
1603     l_uom := l_form_rec.yield_uom;
1604   END IF;
1605 
1606   /* Let us now fetch the total output qty based on the factor derived from std qty */
1607   GMD_COMMON_VAL.Calculate_total_qty(formula_id => l_form_rec.formula_id,
1608                                       x_product_qty => l_scaled_output_qty,
1609                                       x_ingredient_qty => l_ing_qty,
1610                                       x_uom => l_uom,
1611                                       x_return_status => x_return_status,
1612                                       x_msg_count => l_msg_count,
1613                                       x_msg_data => l_msg_data,
1614                                       p_scale_factor => l_scale_factor,
1615                                       p_primaries => 'OUTPUTS');
1616 
1617   /* OK, now we have the scaled and the formula total qty let us evaluate the ratio */
1618   IF l_scaled_output_qty > 0 THEN
1619     x_scale_factor := l_scaled_output_qty / l_total_output_qty;
1620   ELSIF l_scaled_output_qty IS NOT NULL THEN
1621     x_scale_factor := l_scaled_output_qty;
1622   ELSE
1623     x_scale_factor := 1;
1624   END IF;
1625 EXCEPTION
1626   WHEN OTHERS THEN
1627     x_return_status := FND_API.g_ret_sts_unexp_error;
1628     fnd_msg_pub.add_exc_msg ('GMD_VALIDITY_RULES', 'GET_VALIDITY_OUTPUT_FACTOR');
1629 END get_validity_output_factor;
1630 
1631 /*=================================================================================
1632 --  PROCEDURE :
1633 --   insert_val_temp_tbl
1634 --
1635 --  DESCRIPTION:
1636 --    This PL/SQL procedure  is responsible for inserting the validity rule to the
1637 --    temp table.
1638 --  REQUIREMENTS
1639 --
1640 --  SYNOPSIS:
1641 --    insert_val_temp_tbl
1642 --
1643 --  HISTORY
1644 --   Thomas Daniel  16-Nov-2005 Created.
1645 --===================================================================== */
1646 PROCEDURE insert_val_temp_tbl (p_val_rec IN GMD_RECIPE_VALIDITY_RULES%ROWTYPE
1647                               ,p_unit_cost IN NUMBER
1648                               ,p_total_cost IN NUMBER) IS
1649 BEGIN
1650   INSERT INTO GMD_VAL_RULE_GTMP(
1651 	recipe_validity_rule_id, recipe_id              , orgn_code              , recipe_use             ,
1652 	preference             , start_date             , end_date               , min_qty                ,
1653 	max_qty                , std_qty                , inv_min_qty            , inv_max_qty            ,
1654 	text_code              , attribute_category     , attribute1             , attribute2             ,
1655 	attribute3             , attribute4             , attribute5             , attribute6             ,
1656 	attribute7             , attribute8             , attribute9             , attribute10            ,
1657 	attribute11            , attribute12            , attribute13            , attribute14            ,
1658 	attribute15            , attribute16            , attribute17            , attribute18            ,
1659 	attribute19            , attribute20            , attribute21            , attribute22            ,
1660 	attribute23            , attribute24            , attribute25            , attribute26            ,
1661 	attribute27            , attribute28            , attribute29            , attribute30            ,
1662 	created_by             , creation_date          , last_updated_by        , last_update_date       ,
1663 	last_update_login      , validity_rule_status   , planned_process_loss   , organization_id        ,
1664 	inventory_item_id      , revision               , detail_uom             , unit_cost		  ,
1665 	total_cost	       , delete_mark)
1666   VALUES
1667 	(
1668 	p_val_rec.recipe_validity_rule_id, p_val_rec.recipe_id              ,
1669 	p_val_rec.orgn_code              , p_val_rec.recipe_use             ,
1670 	p_val_rec.preference             , p_val_rec.start_date             ,
1671 	p_val_rec.end_date               , p_val_rec.min_qty                ,
1672 	p_val_rec.max_qty                , p_val_rec.std_qty                ,
1673 	p_val_rec.inv_min_qty            , p_val_rec.inv_max_qty            ,
1674 	p_val_rec.text_code              , p_val_rec.attribute_category     ,
1675 	p_val_rec.attribute1             , p_val_rec.attribute2             ,
1676 	p_val_rec.attribute3             , p_val_rec.attribute4             ,
1677 	p_val_rec.attribute5             , p_val_rec.attribute6             ,
1678 	p_val_rec.attribute7             , p_val_rec.attribute8             ,
1679 	p_val_rec.attribute9             , p_val_rec.attribute10            ,
1680 	p_val_rec.attribute11            , p_val_rec.attribute12            ,
1681 	p_val_rec.attribute13            , p_val_rec.attribute14            ,
1682 	p_val_rec.attribute15            , p_val_rec.attribute16            ,
1683 	p_val_rec.attribute17            , p_val_rec.attribute18            ,
1684 	p_val_rec.attribute19            , p_val_rec.attribute20            ,
1685 	p_val_rec.attribute21            , p_val_rec.attribute22            ,
1686 	p_val_rec.attribute23            , p_val_rec.attribute24            ,
1687 	p_val_rec.attribute25            , p_val_rec.attribute26            ,
1688 	p_val_rec.attribute27            , p_val_rec.attribute28            ,
1689 	p_val_rec.attribute29            , p_val_rec.attribute30            ,
1690 	p_val_rec.created_by             , p_val_rec.creation_date          ,
1691 	p_val_rec.last_updated_by        , p_val_rec.last_update_date       ,
1692 	p_val_rec.last_update_login      , p_val_rec.validity_rule_status   ,
1693 	p_val_rec.planned_process_loss   , p_val_rec.organization_id        ,
1694 	p_val_rec.inventory_item_id      , p_val_rec.revision               ,
1695 	p_val_rec.detail_uom             , p_unit_cost		            ,
1696 	p_total_cost		         , p_val_rec.delete_mark);
1697 END insert_val_temp_tbl;
1698 
1699 
1700 /*=================================================================================
1701 --  PROCEDURE :
1702 --   get_formula_cost
1703 --
1704 --  DESCRIPTION:
1705 --    This PL/SQL procedure  is responsible for scaling the formula appropriately
1706 --    and getting the cost for the formula.
1707 --
1708 --  REQUIREMENTS
1709 --
1710 --  SYNOPSIS:
1711 --    get_formula_cost
1712 --
1713 --  HISTORY
1714 --   Thomas Daniel  16-Nov-2005 Created.
1715 --===================================================================== */
1716 PROCEDURE Get_Formula_Cost (
1717    p_formula_id            IN  NUMBER,
1718    p_requested_qty         IN  NUMBER,
1719    p_requested_uom         IN  VARCHAR2,
1720    p_product_id            IN  NUMBER,
1721    p_organization_id       IN  NUMBER,
1722    X_unit_cost             OUT NOCOPY  NUMBER,
1723    X_total_cost            OUT NOCOPY  NUMBER,
1724    X_return_status         OUT NOCOPY  VARCHAR2) IS
1725 
1726   CURSOR Cur_get_cost_method (v_orgn_id NUMBER) IS
1727     SELECT Cost_Type, cost_source
1728     FROM gmd_tech_parameters_b
1729     WHERE organization_id = v_orgn_id
1730     AND Default_cost_parameter = 1;
1731 
1732   CURSOR Cur_get_lines IS
1733     SELECT *
1734     FROM   fm_matl_dtl
1735     WHERE  formula_id = p_formula_id
1736     ORDER BY line_type, line_no;
1737 
1738   l_cost_mthd	VARCHAR2(25);
1739   l_cost_source NUMBER(15);
1740   l_product_qty NUMBER := 0;
1741   l_product_uom VARCHAR2(3);
1742   l_scale_tab_in  GMD_COMMON_SCALE.scale_tab;
1743   l_scale_tab_out GMD_COMMON_SCALE.scale_tab;
1744   l_count  BINARY_INTEGER := 0;
1745   l_return_status VARCHAR2(1);
1746   l_return_id BINARY_INTEGER;
1747   l_cost NUMBER;
1748   l_ing_cost NUMBER;
1749   l_ing_qty NUMBER := 0;
1750   l_organization_id BINARY_INTEGER;
1751   l_msg_count BINARY_INTEGER;
1752   l_msg_data VARCHAR2(2000);
1753   l_cost_component_class_id BINARY_INTEGER;
1754   l_cost_analysis_code VARCHAR2(20);
1755   l_rows BINARY_INTEGER;
1756 
1757   SCALE_ERROR	EXCEPTION;
1758 BEGIN
1759   /* Initialize return status to success */
1760   X_return_status := FND_API.G_RET_STS_SUCCESS;
1761 
1762   l_organization_id := P_organization_id;
1763 
1764   /* Get the cost source organization for the organization passed in */
1765   IF G_cost_source_orgn_id IS NULL THEN
1766     GMD_API_GRP.FETCH_PARM_VALUES(P_orgn_id       => l_organization_id,
1767                                   P_parm_name     => 'GMD_COST_SOURCE_ORGN',
1768                                   P_parm_value    => G_cost_source_orgn_id,
1769 				  x_return_status => l_return_status);
1770 
1771   END IF;
1772   -- Get cost method in cost source orgn
1773 
1774   IF G_default_cost_mthd IS NULL THEN
1775     OPEN Cur_get_cost_method(l_organization_id);
1776     FETCH Cur_get_cost_method INTO l_cost_mthd, l_cost_source;
1777     CLOSE Cur_get_cost_method;
1778   END IF;
1779 
1780   IF l_cost_mthd IS NULL THEN
1781     OPEN Cur_get_cost_method(G_cost_source_orgn_id);
1782     FETCH Cur_get_cost_method INTO G_default_cost_mthd, G_cost_source;
1783     CLOSE Cur_get_cost_method;
1784   END IF;
1785 
1786   X_unit_cost := 0;
1787   X_total_cost := 0;
1788 
1789   FOR l_rec IN Cur_get_lines LOOP
1790     l_count := l_count + 1;
1791     l_scale_tab_in(l_count).line_no := l_rec.line_no;
1792     l_scale_tab_in(l_count).line_type := l_rec.line_type;
1793     l_scale_tab_in(l_count).inventory_item_id := l_rec.inventory_item_id;
1794     l_scale_tab_in(l_count).qty := l_rec.qty;
1795     l_scale_tab_in(l_count).detail_uom := l_rec.detail_uom;
1796     l_scale_tab_in(l_count).scale_type := l_rec.scale_type;
1797     l_scale_tab_in(l_count).contribute_yield_ind := l_rec.contribute_yield_ind;
1798     l_scale_tab_in(l_count).scale_multiple := l_rec.scale_multiple;
1799     l_scale_tab_in(l_count).scale_rounding_variance := l_rec.scale_rounding_variance;
1800     l_scale_tab_in(l_count).rounding_direction := l_rec.rounding_direction;
1801     IF (l_rec.line_type = 1) AND
1802        (p_product_id = l_rec.inventory_item_id) THEN
1803       l_product_qty := l_product_qty + l_rec.qty;
1804       l_product_uom := l_rec.detail_uom;
1805     END IF;
1806   END LOOP;
1807 
1808   /* Lets check if we need to scale the formula based on the requested qty */
1809   IF (l_product_qty <> p_requested_qty) OR
1810      (p_requested_uom <> l_product_uom) THEN
1811     GMD_COMMON_SCALE.scale(p_scale_tab => l_scale_tab_in
1812                           ,p_orgn_id => G_cost_source_orgn_id
1813                           ,p_scale_factor => p_requested_qty / l_product_qty
1814                           ,p_primaries => 'PRODUCT'
1815                           ,x_scale_tab => l_scale_tab_out
1816                           ,x_return_status => l_return_status);
1817     IF l_return_status <> FND_API.G_ret_sts_success THEN
1818       RAISE SCALE_ERROR;
1819     END IF;
1820   ELSE
1821     l_scale_tab_out := l_scale_tab_in;
1822   END IF;
1823 
1824   -- Now lets loop through the scaled tab and calculate the total cost
1825   FOR i IN 1..l_scale_tab_out.COUNT LOOP
1826     -- Get cost for each ingredient
1827     IF l_scale_tab_out(i).line_type = -1 THEN
1828       GMD_LCF_FETCH_PKG.load_cost_values (V_orgn_id => l_organization_id
1829                                          ,V_inv_item_id => l_scale_tab_out(i).inventory_item_id
1830                                          ,V_cost_type => NVL(l_cost_mthd,G_default_cost_mthd )
1831                                          ,V_date => SYSDATE
1832                                          ,V_cost_orgn => NVL(G_cost_source_orgn_id, l_organization_id)
1833                                          ,V_source => NVL(l_cost_source,G_cost_source)
1834                                          ,X_value => l_cost);
1835       IF NVL(l_cost,0) > 0 THEN
1836         l_ing_cost := NVL(l_ing_cost,0) + NVL(l_cost, 0) * l_scale_tab_out(i).qty;
1837       END IF;
1838       l_ing_qty := l_ing_qty + l_scale_tab_out(i).qty;
1839     END IF;
1840   END LOOP;
1841   X_total_cost := l_ing_cost;
1842   IF l_ing_qty > 0 THEN
1843     X_unit_cost := l_ing_cost / l_ing_qty;
1844   END IF;
1845 EXCEPTION
1846   WHEN SCALE_ERROR THEN
1847     x_return_status := FND_API.G_RET_STS_ERROR;
1848 END Get_Formula_Cost;
1849 
1850 
1851 END GMD_VALIDITY_RULES;