DBA Data[Home] [Help]

PACKAGE BODY: APPS.GMD_SPEC_VRS_GRP

Source


1 PACKAGE BODY GMD_SPEC_VRS_GRP AS
2 /* $Header: GMDGSVRB.pls 120.18.12020000.2 2012/07/17 10:29:47 mtou ship $ */
3 
4 -- Start of comments
5 --+==========================================================================+
6 --|                   Copyright (c) 1998 Oracle Corporation                  |
7 --|                          Redwood Shores, CA, USA                         |
8 --|                            All rights reserved.                          |
9 --+==========================================================================+
10 --| File Name          : GMDGSVRB.pls                                        |
11 --| Package Name       : GMD_SPEC_VRS_GRP                                    |
12 --| Type               : Group                                               |
13 --|                                                                          |
14 --| Notes                                                                    |
15 --|    This package contains group layer APIs for Specification Validity     |
16 --|    Rules.                                                                |
17 --|                                                                          |
18 --| HISTORY                                                                  |
19 --|    Chetan Nagar	26-Jul-2002	Created.                             |
20 --|    Olivier Daboval  17-OCT-2002     bug 2630007, added spec_name in      |
21 --|                                     the VR_EXIST message                 |
22 --|    Olivier Daboval  14-NOV-2002     Added NVL(spec_vr_id, -1) because    |
23 --|                                     the API passes a NULL spec_vr_id     |
24 --|                                     in insert mode.                      |
25 --|    Olivier Daboval  02-DEC-2002     Added x_wip_vr and x_inv_vr in the   |
26 --|                                     validation procedures                |
27 --|    Olivier Daboval  01-APR-2003     Now, populate the lower levels       |
28 --|                     Bug 2733426   Formula/Routing when recipe is given   |
29 --|                                                                          |
30 --|    Brenda Stone     20-NOV-2003     Bug 3090290; allow duplicate spec vr |
31 --|                                     with "OBSOLUTE" status               |
32 --|                                     Bug 2984784; add Version to msg for  |
33 --|                                     existing spec vr.                    |
34 --|    Jeff Baird       30-Apr-2004     Bug #3500024  Front port os 3381762  |
35 --|                                                                          |
36 --|    SaiKiran		04-MAY-2004	Enhancement #3476560. added          |
37 --|                                    'delayed_lot_entry' to the call to    |
38 --|                                    'check_vr_controls' procedure at all  |
39 --|                                     places                               |
40 --|                                                                          |
41 --|    Saikiran         04-MAY-2004     Enhancement# 3476560                 |
42 --|	                                Added 'delayed_lot_entry' to the     |
43 --|                     		'c_details_null' cursor and          |
44 --|		                        'c_details_NOT_null' cursor. Added   |
45 --|		                       'x_delayed_lot_entry' to the procedure|
46 --|		                         signature                           |
47 --|                                                                          |
48 --|    Saikiran         04-MAY-2004     Enhancement# 3476560. Added          |
49 --|                               'Delayed Lot Entry' field to the signature.|
50 --|                             Added validation for 'Delayed Lot Entry' that|
51 --|                      it should be 'Y' or Null. Removed special validation|
52 --|                for 'Lot Optional on sample' in case of WIP Validity rule.|
53 --|                                                                          |
54 --|    Saikiran         28-MAY-2004    Bug# 3652938                          |
55 --|                                   Added validation for the invalid       |
56 --|                              combination of 'Lot Optional on Sample' and |
57 --|                              'Delayed Lot Entry' in 'Check_VR_controls'  |
58 --|                              procedure                                   |
59 --|                                                                          |
60 --|  Saikiran            28-Apr-2005 Made Convergence changes                |
61 --|  RLNAGARA     27-Dec-2005 Bug # 4900420                                  |
62 --|		    Modified the procedure check_VR_controls                 |
63 --|  PLOWE               22-MAR-2006    Bug # 4619570  			     |
64 --|                         Changed the c_batch cursor to include closed     |
65 --|                         batches as per the profile option.               |
66 --|  PLOWE		  04-Apr-2006    Bug 5117733 - added item revision to|
67 --|                                     match in functions inv_vr_exist,     |
68 --|					  wip_vr_exist,cust_vr_exist,        |
69 --|					and supp_vr_exist                    |
70 --|  PLOWE                25-MAY-2006    -- bug 5223014 sql id 17532992      |
71 --|                       and 17532478                                       |
72 --|  PLOWE                07-JUN-2006    -- bug 5223014 rework               |
73 --|  replace cursor with function  as check was not working as designed      |
74 --|  bug 5223014 rework in proc check_for_null_and_fks_in_cvr  		     |
75 --|  srakrish  		  15-June-2006  Bug 5276602: Checking if the Lot     |
76 --|					optional feild is set when  	     |
77 --|					lot or parent lot or entered.	     |
78 --|				 	This scenario exists when the 	     |
79 --|					api is called from the wrapper.      |
80 --|  srakrish 		  15-june-06    BUG 5251172: Checking if the         |
81 --|					responsibility is available to the   |
82 --|					organization in all of the 	     |
83 --|					check_for_null_and_fks_in_ functions.|
84 --|RLNAGARA LPN ME 7027149 08-May-2008  Added new function check_wms_enabled |
85 --|                                  and signature of check_VR_controls procedure|
86 --|				and also added code to check_for_null_and_fks_in_*vr                |
87 --|  PLOWE               05-OCT-2011    Bug # 13027522  			     |
88 --|                         Changed the c_batch cursor to tidy up work for
89 --|   bug 6278463 as this was not working for when noo route was passed thru API params |
90 --|   PLOWE         25-OCT-2011    Bug # 13105549  			                     |
91 --|                 Changed the c_batch cursor to tidy up work for
92 --|                 bug 6278463 as this was not working for when batch with recipe has a route |
93 --|   PLOWE         5-MAR-2012    Bug # 13451274  			                             |
94 --|             Changed the c_batch cursor to so that we can retreive rows when the  |
95 --|             batch has an item that is is not on formula                          |
96 --|=================================================================================================+
97 -- End of comments
98 
99 -- Global variables
100 G_PKG_NAME      CONSTANT VARCHAR2(30) := 'GMD_SPEC_VRS_GRP';
101 
102 -- Global Cursors
103 
104 CURSOR c_orgn ( p_organization_id NUMBER) IS
105   SELECT 1
106   FROM mtl_parameters m
107   WHERE m.process_enabled_flag = 'Y';
108 
109 
110 CURSOR c_status (p_status_code NUMBER) IS
111   SELECT 1
112   FROM   gmd_qc_status
113   WHERE  status_code = p_status_code
114   AND    delete_mark = 0;
115 
116 
117 
118 
119 --Start of comments
120 --+========================================================================+
121 --| API Name    : validate_mon_vr                                          |
122 --| TYPE        : Group                                                    |
123 --| Notes       : This procedure validates all the fields of               |
124 --|               monitoring validity rule record. This procedure can be    |
125 --|               called from FORM or API and the caller need              |
126 --|               to specify this in p_called_from parameter               |
127 --|               while calling this procedure. Based on where             |
128 --|               it is called from certain validations will               |
129 --|               either be performed or skipped.                          |
130 --|                                                                        |
131 --|               If everything is fine then OUT parameter                 |
132 --|               x_return_status is set to 'S' else appropriate           |
133 --|               error message is put on the stack and error              |
134 --|               is returned.                                             |
135 --|                                                                        |
136 --| HISTORY                                                                |
137 --|    Olivier Daboval  11-MAR-2003     Created                            |
138 --|                                                                        |
139 --|                                                                        |
140 --+========================================================================+
141 -- End of comments
142 
143 PROCEDURE validate_mon_vr
144 (
145   p_mon_vr        IN  GMD_MONITORING_SPEC_VRS%ROWTYPE
146 , p_called_from   IN  VARCHAR2
147 , p_operation     IN  VARCHAR2
148 , x_mon_vr        OUT NOCOPY GMD_MONITORING_SPEC_VRS%ROWTYPE
149 , x_return_status OUT NOCOPY VARCHAR2
150 ) IS
151 
152   -- Local Variables
153   dummy                          NUMBER;
154   l_return_status                VARCHAR2(1);
155 
156   l_spec                         GMD_SPECIFICATIONS%ROWTYPE;
157   l_spec_out                     GMD_SPECIFICATIONS%ROWTYPE;
158   l_mon_vr                       GMD_MONITORING_SPEC_VRS%ROWTYPE;
159   l_mon_vr_tmp                   GMD_MONITORING_SPEC_VRS%ROWTYPE;
160   l_item_mst                     IC_ITEM_MST%ROWTYPE;
161   l_item_mst_out                 IC_ITEM_MST%ROWTYPE;
162   l_sampling_plan                GMD_SAMPLING_PLANS%ROWTYPE;
163   l_sampling_plan_out            GMD_SAMPLING_PLANS%ROWTYPE;
164 
165   -- Exceptions
166   e_spec_fetch_error             EXCEPTION;
167   e_smpl_plan_fetch_error        EXCEPTION;
168   e_error_fetch_item             EXCEPTION;
169 
170 BEGIN
171   --  Initialize API return status to success
172   x_return_status := FND_API.G_RET_STS_SUCCESS;
173 
174   IF NOT (p_operation in ('INSERT', 'UPDATE', 'DELETE')) THEN
175     -- Invalid Operation
176     GMD_API_PUB.Log_Message('GMD_INVALID_OPERATION');
177     RAISE FND_API.G_EXC_ERROR;
178   END IF;
179 
180   -- Verify that the specification exists.
181   l_spec.spec_id := p_mon_vr.spec_id;
182   IF NOT (GMD_Specifications_PVT.Fetch_Row(
183                            p_specifications => l_spec,
184                            x_specifications => l_spec_out)
185           ) THEN
186     -- Fetch Error
187     GMD_API_PUB.Log_Message('GMD_SPEC_FETCH_ERROR');
188     RAISE e_spec_fetch_error;
189   END IF;
190 
191   l_spec := l_spec_out ;
192 
193   -- Verify that the Sampling Plan exists.
194   --odab added this test.
195   IF (p_mon_vr.sampling_plan_id IS NOT NULL)
196   THEN
197     l_sampling_plan.sampling_plan_id := p_mon_vr.sampling_plan_id;
198     IF NOT (GMD_Sampling_Plans_PVT.Fetch_Row(
199                            p_sampling_plan => l_sampling_plan,
200                            x_sampling_plan => l_sampling_plan_out)
201           ) THEN
202       -- Fetch Error
203       GMD_API_PUB.Log_Message('GMD_SAMPLING_PLAN_FETCH_ERROR');
204       RAISE e_smpl_plan_fetch_error;
205     END IF;
206     l_sampling_plan:= l_sampling_plan_out ;
207   END IF;
208 
209   -- odaboval From this point, the l_mon_vr is used
210   --      and will populate the return parameter x_mon_vr
211   l_mon_vr := p_mon_vr;
212   IF (p_called_from = 'API') THEN
213     -- Check for NULLs and Valid Foreign Keys in the input parameter
214     check_for_null_and_fks_in_mvr
215       (
216         p_mon_vr        => p_mon_vr
217       , p_spec          => l_spec
218       , x_mon_vr        => l_mon_vr_tmp
219       , x_return_status => l_return_status
220       );
221     -- No need if called from FORM since it is already
222     -- done in the form
223     -- All messages should be already raised
224     IF l_return_status = FND_API.G_RET_STS_ERROR THEN
225       -- Message is alrady logged by check_for_null procedure
226       RAISE FND_API.G_EXC_ERROR;
227     ELSIF l_return_status = FND_API.G_RET_STS_UNEXP_ERROR THEN
228       -- Message is alrady logged by check_for_null procedure
229       RAISE FND_API.G_EXC_UNEXPECTED_ERROR;
230     END IF;
231 
232     l_mon_vr := l_mon_vr_tmp;
233   END IF;
234 
235   -- First Verify that the SAME VR does not exists
236   --IF (p_operation IN ('INSERT')
237   IF (p_operation IN ('INSERT', 'UPDATE')
238      AND mon_vr_exist(l_mon_vr, l_spec))
239   THEN
240     -- Disaster, Trying to insert duplicate
241     -- Put the message in function mon_vr_exist.
242     -- GMD_API_PUB.Log_Message('GMD_MON_VR_EXIST');
243     RAISE FND_API.G_EXC_ERROR;
244   END IF;
245 
246   -- No need to check the return status because above procedure
247   -- logs appropriate message on the stack and raises an exception.
248 
249   -- The Start Date must be less than the End Date
250   If ( l_mon_vr.end_date IS NOT NULL AND
251        l_mon_vr.start_date > l_mon_vr.end_date) THEN
252     GMD_API_PUB.Log_Message('GMD_SPEC_VR_EFF_DATE_ERROR');
253     RAISE FND_API.G_EXC_ERROR;
254   END IF;
255 
256   -- Spec VR Status Must be less than Spec Status upto Appoved Stages
257   IF (floor(l_spec.spec_status/100) <= 7 AND
258       floor(l_mon_vr.spec_vr_status/100) <= 7 AND
259       l_mon_vr.spec_vr_status > l_spec.spec_status) THEN
260     GMD_API_PUB.Log_Message('GMD_SPEC_VR_STATUS_HIGHER');
261     RAISE FND_API.G_EXC_ERROR;
262   END IF;
263 
264   -- All systems GO...
265   x_mon_vr := l_mon_vr;
266 
267 EXCEPTION
268   WHEN FND_API.G_EXC_ERROR     OR
269        e_spec_fetch_error      OR
270        e_smpl_plan_fetch_error OR
271        e_error_fetch_item
272   THEN
273     x_return_status := FND_API.G_RET_STS_ERROR ;
274   WHEN FND_API.G_EXC_UNEXPECTED_ERROR THEN
275     x_return_status := FND_API.G_RET_STS_UNEXP_ERROR ;
276   WHEN OTHERS THEN
277     x_return_status := FND_API.G_RET_STS_UNEXP_ERROR ;
278 
279 
280 END validate_mon_vr;
281 
282 
283 --Start of comments
284 --+========================================================================+
285 --| API Name    : check_for_null_and_fks_in_mvr                            |
286 --| TYPE        : Group                                                    |
287 --| Notes       : This procedure checks for NULL and Foreign Key           |
288 --|               constraints for the required filed in the Spec           |
289 --|               Monitoring VR record.                                    |
290 --|                                                                        |
291 --|               If everything is fine then 'S' is returned in the        |
292 --|               parameter - x_return_status otherwise error message      |
293 --|               is logged and error status - E or U returned             |
294 --|                                                                        |
295 --| HISTORY                                                                |
296 --|    Olivier Daboval  11-MAR-2003     Created                            |
297 --| Saikiran Vankadari  24-Apr-2005     Convergence Changes                |
298 --|    srakrish  	15-june-06      BUG 5251172: Checking if the       |
299 --|					responsibility is available to the |
300 --|					organization.			   |
301 --+========================================================================+
302 -- End of comments
303 
304 PROCEDURE check_for_null_and_fks_in_mvr
305 (
306   p_mon_vr        IN  GMD_MONITORING_SPEC_VRS%ROWTYPE
307 , p_spec          IN  GMD_SPECIFICATIONS%ROWTYPE
308 , x_mon_vr        OUT NOCOPY GMD_MONITORING_SPEC_VRS%ROWTYPE
309 , x_return_status OUT NOCOPY VARCHAR2
310 )
311 IS
312 
313 l_mon_vr           GMD_MONITORING_SPEC_VRS%ROWTYPE;
314 
315 CURSOR c_subinventory IS
316 SELECT 1
317 FROM   mtl_secondary_inventories
318 WHERE  secondary_inventory_name   = l_mon_vr.subinventory
319 AND organization_id = l_mon_vr.locator_organization_id;
320 
321 CURSOR c_locator IS
322 SELECT 1
323 FROM   mtl_item_locations
324 WHERE  organization_id   = l_mon_vr.locator_organization_id
325 AND    inventory_location_id    = l_mon_vr.locator_id;
326 
327 cursor c_resources is
328 select 1
329 from cr_rsrc_mst
330 where resources = l_mon_vr.resources
331 and delete_mark = 0;
332 
333 cursor c_resource_instance is
334 SELECT ri.INSTANCE_NUMBER
335 FROM GMP_RESOURCE_INSTANCES ri, CR_RSRC_DTL rd
336 WHERE rd.resource_id = ri.resource_id
337 AND   rd.organization_id = NVL(l_mon_vr.resource_organization_id, rd.organization_id)
338 AND   rd.resources = NVL(l_mon_vr.resources, rd.resources)
339 AND   ri.INACTIVE_IND = 0
340 ORDER BY 1 ;
341 
342 dummy              NUMBER;
343 l_locator_type     NUMBER;
344 l_return_status    VARCHAR2(1);
345 
346 BEGIN
347 
348   l_mon_vr := p_mon_vr;
349 
350   check_who( p_user_id  => l_mon_vr.created_by);
351   check_who( p_user_id  => l_mon_vr.last_updated_by);
352   IF (l_mon_vr.creation_date IS NULL
353    OR l_mon_vr.last_update_date IS NULL)
354   THEN
355     GMD_API_PUB.Log_Message('GMD_WRONG_VALUE',
356                             'WHAT', 'the dates must not be NULL');
357     RAISE FND_API.G_EXC_ERROR;
358   END IF;
359 
360 
361   -- Bug 3451798
362   -- In case rule type is location, all resource-related info should be nulled
363   -- In case rule type is resource, all location-related info should be nulled
364   if (l_mon_vr.rule_type = 'R') then
365      l_mon_vr.locator_id := NULL;
366      l_mon_vr.locator_organization_id := NULL;
367      l_mon_vr.subinventory := NULL;
368   elsif (l_mon_vr.rule_type = 'L') then
369      l_mon_vr.resources := NULL;
370      l_mon_vr.resource_organization_id := NULL;
371      l_mon_vr.resource_instance_id := NULL;
372   else
373    -- Bug 3451839
374    -- Invalid Rule Type
375     GMD_API_PUB.Log_Message('GMD_WRONG_VALUE',
376                             'WHAT', 'The monitoring spec rule type');
377     RAISE FND_API.G_EXC_ERROR;
378   end if ;
379 
380 
381   -- Loct Organization is valid
382   IF (l_mon_vr.locator_organization_id IS NOT NULL) THEN
383     OPEN c_orgn( l_mon_vr.locator_organization_id);
384     FETCH c_orgn INTO dummy;
385     IF (c_orgn%NOTFOUND)
386     THEN
387       CLOSE c_orgn;
388       GMD_API_PUB.Log_Message('GMD_ORGANIZATION_ID_NOT_FOUND',
389                               'ORGN_ID', l_mon_vr.locator_organization_id);
390       RAISE FND_API.G_EXC_ERROR;
391     END IF;
392     CLOSE c_orgn;
393   END IF;
394 
395   --srakrish BUG 5251172: Checking if the responsibility is available to the Locator organization.
396   IF NOT (gmd_api_grp.OrgnAccessible(l_mon_vr.locator_organization_id)) THEN
397     	  RAISE FND_API.G_EXC_ERROR;
398   END IF;
399 
400   -- Resource is valid (Bug 3451868)
401   IF (l_mon_vr.resources IS NOT NULL) THEN
402     -- Check that Resource exists
403     OPEN c_resources ;
404     FETCH c_resources INTO dummy;
405     IF (c_resources%NOTFOUND)
406     THEN
407       CLOSE c_resources;
408       GMD_API_PUB.Log_Message('GMD_RESOURCE_NOT_FOUND',
409                               'RESOURCE', l_mon_vr.resources);
410       RAISE FND_API.G_EXC_ERROR;
411     END IF;
412     CLOSE c_resources;
413   END IF;
414 
415 
416   -- Resource Organization is valid
417   IF (l_mon_vr.resource_organization_id IS NOT NULL) THEN
418     OPEN c_orgn( l_mon_vr.resource_organization_id);
419     FETCH c_orgn INTO dummy;
420     IF (c_orgn%NOTFOUND)
421     THEN
422       CLOSE c_orgn;
423       GMD_API_PUB.Log_Message('GMD_ORGANIZATION_ID_NOT_FOUND',
424                               'ORGN_ID', l_mon_vr.resource_organization_id);
425       RAISE FND_API.G_EXC_ERROR;
426     END IF;
427     CLOSE c_orgn;
428   END IF;
429 
430   --srakrish BUG 5251172: Checking if the responsibility is available to the Resource organization.
431   IF NOT (gmd_api_grp.OrgnAccessible(l_mon_vr.resource_organization_id)) THEN
432     	  RAISE FND_API.G_EXC_ERROR;
433   END IF;
434 
435   -- Resource Instance is valid (Bug 3451868)
436   IF (l_mon_vr.resource_instance_id IS NOT NULL) THEN
437     -- Check that Resource instance idexists
438     OPEN c_resource_instance ;
439     FETCH c_resource_instance INTO dummy;
440     IF (c_resource_instance%NOTFOUND)
441     THEN
442       CLOSE c_resource_instance;
443       GMD_API_PUB.Log_Message('GMD_WRONG_VALUE',
444                             'WHAT', 'The resource instance');
445       RAISE FND_API.G_EXC_ERROR;
446     END IF;
447     CLOSE c_resource_instance;
448   END IF;
449 
450 
451   -- Subinventory is Valid
452   IF (l_mon_vr.subinventory IS NOT NULL) THEN
453     -- Check that Subinventory exist and is associated with locator organization.
454     OPEN c_subinventory;
455     FETCH c_subinventory INTO dummy;
456     IF (c_subinventory%NOTFOUND)
457     THEN
458       CLOSE c_subinventory;
459       GMD_API_PUB.Log_Message('GMD_SUBINVENTORY_NOT_FOUND',
460                               'SUBINVENTORY', l_mon_vr.subinventory);
461       RAISE FND_API.G_EXC_ERROR;
462     END IF;
463     CLOSE c_subinventory;
464 
465   END IF;
466 
467   --Find out if it is locator controlled
468   GMD_COMMON_GRP.item_is_locator_controlled (
469                       p_organization_id => l_mon_vr.locator_organization_id
470                      ,p_subinventory => l_mon_vr.subinventory
471                      ,p_inventory_item_id => NULL
472                      ,x_locator_type   => l_locator_type
473                      ,x_return_status  => l_return_status);
474 
475   -- Location is valid
476   IF (l_locator_type IN (2,3))
477   THEN
478     -- Here l_locator_type IN (2,3)
479     IF (l_mon_vr.locator_id IS NULL)
480     THEN
481       -- Location can be NULL in this case.
482       null;
483     ELSE
484       -- Check that Location exist in MTL_ITEM_LOCATIONS
485       OPEN c_locator;
486       FETCH c_locator INTO dummy;
487       IF (c_locator%NOTFOUND)
488       THEN
489         CLOSE c_locator;
490         GMD_API_PUB.Log_Message('GMD_LOCT_NOT_FOUND');
491         RAISE FND_API.G_EXC_ERROR;
492       END IF;
493       CLOSE c_locator;
494     END IF;   -- location IS NOT NULL
495   ELSE --l_locator_type NOT IN (2,3)
496     IF (l_mon_vr.locator_id IS NOT NULL)
497     THEN
498         GMD_API_PUB.Log_Message('GMD_WRONG_VALUE',
499                                 'WHAT', 'locator should be NULL');
500         RAISE FND_API.G_EXC_ERROR;
501     END IF;
502   END IF;   -- l_locator_type IN (2,3)
503 
504   --=========================================================================
505   -- spec_vr_status :
506   --=========================================================================
507   -- Check that Spec VR Status exist in GMD_QC_STATUS
508   OPEN c_status(l_mon_vr.spec_vr_status);
509   FETCH c_status
510    INTO dummy;
511   IF (c_status%NOTFOUND)
512   THEN
513     CLOSE c_status;
514     GMD_API_PUB.Log_Message('GMD_SPEC_STATUS_NOT_FOUND',
515                             'STATUS', l_mon_vr.spec_vr_status);
516     RAISE FND_API.G_EXC_ERROR;
517   END IF;
518   CLOSE c_status;
519 
520   --=========================================================================
521   -- start_date : This field is mandatory
522   --=========================================================================
523   IF (l_mon_vr.start_date IS NULL)
524   THEN
525       GMD_API_PUB.Log_Message('GMD_SPEC_VR_START_DATE_REQD');
526       RAISE FND_API.G_EXC_ERROR;
527   END IF;
528 
529   x_mon_vr := l_mon_vr;
530 
531 
532 EXCEPTION
533   WHEN FND_API.G_EXC_ERROR THEN
534     x_return_status := FND_API.G_RET_STS_ERROR ;
535   WHEN FND_API.G_EXC_UNEXPECTED_ERROR THEN
536     x_return_status := FND_API.G_RET_STS_UNEXP_ERROR ;
537   WHEN OTHERS THEN
538     x_return_status := FND_API.G_RET_STS_UNEXP_ERROR ;
539 
540 END check_for_null_and_fks_in_mvr;
541 
542 
543 
544 
545 
546 --Start of comments
547 --+========================================================================+
548 --| API Name    : mon_vr_exist                                             |
549 --| TYPE        : Group                                                    |
550 --| Notes       : This function returns TRUE if the monitoring VR already   |
551 --|               exists for the spcified parameter in the database, FALSE |
552 --|               otherwise.                                               |
553 --|                                                                        |
554 --| HISTORY                                                                |
555 --|    Chetan Nagar	26-Jul-2002	Created.                           |
556 --|    Olivier Daboval  17-OCT-2002     bug 2630007, added spec_name in    |
557 --|                                     the VR_EXIST message               |
558 --|    Olivier Daboval  14-NOV-2002     Added NVL(spec_vr_id, -1) because  |
559 --|                                     the API passes a NULL spec_vr_id   |
560 --|                                     in insert mode.                    |
561 --|    Brenda Stone     20-NOV-2003     Bug 3090290; allow duplicate spec vr |
562 --|                                     with "OBSOLUTE" status               |
563 --|                                     Bug 2984784; add Version to msg for  |
564 --|                                     existing spec vr.                    |
565 --|                                                                        |
566 --|  Saikiran          12-Apr-2005      Convergence Changes                |
567 --+========================================================================+
568 -- End of comments
569 
570 FUNCTION mon_vr_exist(p_mon_vr GMD_MONITORING_SPEC_VRS%ROWTYPE,
571                       p_spec   GMD_SPECIFICATIONS%ROWTYPE)
572 RETURN BOOLEAN IS
573 
574   CURSOR c_mon_vr IS
575   SELECT vr.spec_vr_id, s.spec_name, s.spec_vers
576   FROM   gmd_specifications_b s, gmd_monitoring_spec_vrs vr
577   WHERE  s.spec_id = vr.spec_id
578   AND    ((s.grade_code is NULL AND p_spec.grade_code is NULL) OR
579           (s.grade_code = p_spec.grade_code)
580          )
581   AND    ((vr.locator_organization_id is NULL AND p_mon_vr.locator_organization_id is NULL) OR
582           (vr.locator_organization_id = p_mon_vr.locator_organization_id)
583          )
584   AND    ((vr.subinventory is NULL AND p_mon_vr.subinventory is NULL) OR
585           (vr.subinventory = p_mon_vr.subinventory)
586          )
587   AND    ((vr.locator_id is NULL  AND p_mon_vr.locator_id is NULL) OR
588           (vr.locator_id = p_mon_vr.locator_id)
589          )
590   AND    ((vr.resource_organization_id is NULL AND p_mon_vr.resource_organization_id is NULL) OR
591           (vr.resource_organization_id = p_mon_vr.resource_organization_id)
592          )
593   AND    ((vr.resources is NULL AND p_mon_vr.resources is NULL) OR
594           (vr.resources = p_mon_vr.resources)
595          )
596   AND    ((vr.resource_instance_id is NULL AND p_mon_vr.resource_instance_id is NULL) OR
597           (vr.resource_instance_id = p_mon_vr.resource_instance_id)
598          )
599   AND    ((vr.end_date is NULL AND (p_mon_vr.end_date IS NULL OR
600                                     p_mon_vr.end_date >= vr.start_date)) OR
601 	  (p_mon_vr.end_date IS NULL AND
602 	     p_mon_vr.start_date <= nvl(vr.end_date, p_mon_vr.start_date)) OR
603           (p_mon_vr.start_date <= vr.end_date AND p_mon_vr.end_date >= vr.start_date)
604          )
605   AND   ( floor(vr.spec_vr_status / 100) = floor(p_mon_vr.spec_vr_status/100)  AND
606 /*      Bug 3090290; allow duplicate spec vr with "OBSOLUTE" status   */
607          p_mon_vr.spec_vr_status <> 1000 )
608   AND    vr.spec_vr_status NOT IN (SELECT status_code FROM gmd_qc_status
609                                    WHERE status_type = 800)
610   AND    vr.delete_mark = 0
611   AND    s.delete_mark = 0
612   AND    vr.spec_vr_id <> NVL(p_mon_vr.spec_vr_id, -1)
613   ;
614 
615   dummy    PLS_INTEGER;
616   specname VARCHAR2(80);
617   specvers NUMBER;
618 
619 BEGIN
620 
621   OPEN c_mon_vr;
622   FETCH c_mon_vr INTO dummy, specname, specvers;
623   IF c_mon_vr%FOUND THEN
624     CLOSE c_mon_vr;
625     FND_MESSAGE.SET_NAME('GMD', 'GMD_MON_VR_EXIST');
626     FND_MESSAGE.SET_TOKEN('spec', specname);
627     FND_MESSAGE.SET_TOKEN('vers', specvers);
628     FND_MSG_PUB.ADD;
629     RETURN TRUE;
630   ELSE
631     CLOSE c_mon_vr;
632     RETURN FALSE;
633   END IF;
634 
635 EXCEPTION
636   -- Though there is no reason the program can reach
637   -- here, this is coded just for the reasons we can
638   -- not think of!
639   WHEN OTHERS THEN
640     FND_MESSAGE.SET_NAME('GMD', 'GMD_API_ERROR');
641     FND_MESSAGE.SET_TOKEN('PACKAGE', 'GMD_SPEC_VRS_GRP.MON_VR_EXIST' );
642     FND_MESSAGE.SET_TOKEN('ERROR', SUBSTR(SQLERRM,1,200));
643     FND_MSG_PUB.ADD;
644 
645     RETURN TRUE;
646 
647 END mon_vr_exist;
648 
649 
650 --Start of comments
651 --+========================================================================+
652 --| API Name    : validate_inv_vr                                          |
653 --| TYPE        : Group                                                    |
654 --| Notes       : This procedure validates all the fields of               |
655 --|               inventory validity rule record. This procedure can be    |
656 --|               called from FORM or API and the caller need              |
657 --|               to specify this in p_called_from parameter               |
658 --|               while calling this procedure. Based on where             |
659 --|               it is called from certain validations will               |
660 --|               either be performed or skipped.                          |
661 --|                                                                        |
662 --|               If everything is fine then OUT parameter                 |
663 --|               x_return_status is set to 'S' else appropriate           |
664 --|               error message is put on the stack and error              |
665 --|               is returned.                                             |
666 --|                                                                        |
667 --| HISTORY                                                                |
668 --|    Chetan Nagar	26-Jul-2002	Created.                           |
669 --|    Olivier Daboval  02-DEC-2002     Added x_inv_vr as out parameter    |
670 --|    srakrish  	15-June-2006  Bug 5276602: Checking if the Lot     |
671 --|					optionalfeild is  set to yes when  |
672 --|					lot or parent lot or entered.	   |
673 --|				 	This scenario exists when the 	   |
674 --|					api is called from the wrapper.    |
675 --|                                                                        |
676 --|                                                                        |
677 --+========================================================================+
678 -- End of comments
679 
680 PROCEDURE validate_inv_vr
681 (
682   p_inv_vr        IN  GMD_INVENTORY_SPEC_VRS%ROWTYPE
683 , p_called_from   IN  VARCHAR2
684 , p_operation     IN  VARCHAR2
685 , x_inv_vr        OUT NOCOPY GMD_INVENTORY_SPEC_VRS%ROWTYPE
686 , x_return_status OUT NOCOPY VARCHAR2
687 ) IS
688 
689   -- Local Variables
690   dummy                          NUMBER;
691   l_return_status                VARCHAR2(1);
692 
693   l_spec                         GMD_SPECIFICATIONS%ROWTYPE;
694   l_spec_out                     GMD_SPECIFICATIONS%ROWTYPE;
695   l_inv_vr                       GMD_INVENTORY_SPEC_VRS%ROWTYPE;
696   l_inv_vr_tmp                   GMD_INVENTORY_SPEC_VRS%ROWTYPE;
697   l_item_mst                     MTL_SYSTEM_ITEMS_B%ROWTYPE;
698   l_sampling_plan                GMD_SAMPLING_PLANS%ROWTYPE;
699   l_sampling_plan_out            GMD_SAMPLING_PLANS%ROWTYPE;
700   l_inventory_item_id            NUMBER;
701   l_organization_id              NUMBER;
702   l_uom_rate                     NUMBER;
703 
704   -- Exceptions
705   e_spec_fetch_error             EXCEPTION;
706   e_smpl_plan_fetch_error        EXCEPTION;
707   e_error_fetch_item               EXCEPTION;
708 
709 BEGIN
710   --  Initialize API return status to success
711   x_return_status := FND_API.G_RET_STS_SUCCESS;
712 
713   IF NOT (p_operation in ('INSERT', 'UPDATE', 'DELETE')) THEN
714     -- Invalid Operation
715     GMD_API_PUB.Log_Message('GMD_INVALID_OPERATION');
716     RAISE FND_API.G_EXC_ERROR;
717   END IF;
718 
719   -- Verify that the specification exists.
720   l_spec.spec_id := p_inv_vr.spec_id;
721   IF NOT (GMD_Specifications_PVT.Fetch_Row(
722                            p_specifications => l_spec,
723                            x_specifications => l_spec_out)
724           ) THEN
725     -- Fetch Error
726     GMD_API_PUB.Log_Message('GMD_SPEC_FETCH_ERROR');
727     RAISE e_spec_fetch_error;
728   END IF;
729 
730   l_spec := l_spec_out ;
731 
732   -- Verify that the Sampling Plan exists.
733   --odab added this test.
734   IF (p_inv_vr.sampling_plan_id IS NOT NULL)
735   THEN
736     l_sampling_plan.sampling_plan_id := p_inv_vr.sampling_plan_id;
737     IF NOT (GMD_Sampling_Plans_PVT.Fetch_Row(
738                            p_sampling_plan => l_sampling_plan,
739                            x_sampling_plan => l_sampling_plan_out)
740           ) THEN
741       -- Fetch Error
742       GMD_API_PUB.Log_Message('GMD_SAMPLING_PLAN_FETCH_ERROR');
743       RAISE e_smpl_plan_fetch_error;
744     END IF;
745     l_sampling_plan:= l_sampling_plan_out ;
746   END IF;
747 
748   -- bug 2691994  02-DEC-02:
749   -- odaboval From this point, the l_inv_vr is used
750   --      and will populate the return parameter x_inv_vr
751   l_inv_vr := p_inv_vr;
752   IF (p_called_from = 'API') THEN
753     --For mini pack L, bug 3439865
754     IF ( nvl(p_inv_vr.auto_sample_ind,'N') not in ('N','Y')) THEN
755       GMD_API_PUB.Log_Message('GMD_WRONG_VALUE',
756                             'WHAT', 'INVALID_AUTO_SAMPLE_IND');
757       RAISE FND_API.G_EXC_ERROR;
758     END IF;
759     -- end 3439865
760     -- Check for NULLs and Valid Foreign Keys in the input parameter
761     check_for_null_and_fks_in_ivr
762       (
763         p_inv_vr        => p_inv_vr
764       , p_spec          => l_spec
765       , x_inv_vr        => l_inv_vr_tmp
766       , x_return_status => l_return_status
767       );
768     -- No need if called from FORM since it is already
769     -- done in the form
770 
771     IF l_return_status = FND_API.G_RET_STS_ERROR THEN
772       -- Message is alrady logged by check_for_null procedure
773       RAISE FND_API.G_EXC_ERROR;
774     ELSIF l_return_status = FND_API.G_RET_STS_UNEXP_ERROR THEN
775       -- Message is alrady logged by check_for_null procedure
776       RAISE FND_API.G_EXC_UNEXPECTED_ERROR;
777     END IF;
778 
779     l_inv_vr := l_inv_vr_tmp;
780   END IF;
781 
782   -- First Verify that the SAME VR does not exists
783   -- bug 2691994  02-DEC-02, odaboval changed p_inv_vr by l_inv_vr
784   --IF (p_operation IN ('INSERT')
785   IF (p_operation IN ('INSERT', 'UPDATE')
786      AND inv_vr_exist(l_inv_vr, l_spec))
787   THEN
788     -- Disaster, Trying to insert duplicate
789     -- bug 2630007, odaboval put the message in function inv_vr_exist.
790     -- GMD_API_PUB.Log_Message('GMD_INV_VR_EXIST');
791     RAISE FND_API.G_EXC_ERROR;
792   END IF;
793 
794 
795   -- Check to make sure that a samplingplan exists
796   -- if auto sample flag on
797   IF ((p_inv_vr.sampling_plan_id IS NULL) and
798        (p_inv_vr.auto_sample_ind = 'Y'))
799   THEN
800       GMD_API_PUB.Log_Message('GMD_NEED_SAMPLE_PLAN');
801       RAISE e_smpl_plan_fetch_error;
802   END IF;
803 
804 
805   -- Sample Quantity UOM must be convertible to Item's UOM
806   BEGIN
807     SELECT inventory_item_id INTO l_inventory_item_id FROM
808     gmd_specifications WHERE spec_id = p_inv_vr.spec_id;
809     SELECT owner_organization_id INTO l_organization_id FROM
810     gmd_specifications WHERE spec_id = p_inv_vr.spec_id;
811     SELECT * INTO l_item_mst
812     FROM mtl_system_items_b
813     WHERE inventory_item_id = l_inventory_item_id
814     AND organization_id = l_organization_id;
815   EXCEPTION
816   WHEN OTHERS THEN
817     GMD_API_PUB.Log_Message('GMD_ITEM_FETCH_ERROR');
818     RAISE e_error_fetch_item;
819   END;
820 
821   IF (l_inv_vr.sampling_plan_id IS NOT NULL)
822   THEN
823     --As part of Convergence, the following call is replaced with new one.
824     /*GMICUOM.icuomcv(pitem_id => l_item_mst.item_id,
825                       plot_id  => 0,
826                       pcur_qty => 1,
827                       pcur_uom => l_sampling_plan.sample_uom,
828                       pnew_uom => l_item_mst.item_um,
829                       onew_qty => dummy);*/
830     inv_convert.inv_um_conversion (
831       from_unit  => l_sampling_plan.sample_qty_uom,
832       to_unit    =>  l_item_mst.primary_uom_code,
833       item_id    =>  l_inventory_item_id,
834       lot_number => NULL,
835       organization_id => l_organization_id  ,
836       uom_rate   => l_uom_rate );
837 
838     IF l_uom_rate = -99999 THEN
839       GMD_API_PUB.Log_Message('GMD_UOM_CONVERSION_ERROR');
840       RAISE FND_API.G_EXC_ERROR;
841     END IF;
842   END IF;
843 
844   -- No need to check the return status because above procedure
845   -- logs appropriate message on the stack and raises an exception.
846 
847   -- The Start Date must be less than the End Date
848   -- bug 2691994  02-DEC-02, odaboval changed p_inv_vr by l_inv_vr
849   If ( l_inv_vr.end_date IS NOT NULL AND
850        l_inv_vr.start_date > l_inv_vr.end_date) THEN
851     GMD_API_PUB.Log_Message('GMD_SPEC_VR_EFF_DATE_ERROR');
852     RAISE FND_API.G_EXC_ERROR;
853   END IF;
854 
855   -- Spec VR Status Must be less than Spec Status upto Appoved Stages
856   IF (floor(l_spec.spec_status/100) <= 7 AND
857       floor(l_inv_vr.spec_vr_status/100) <= 7 AND
858       l_inv_vr.spec_vr_status > l_spec.spec_status) THEN
859     GMD_API_PUB.Log_Message('GMD_SPEC_VR_STATUS_HIGHER');
860     RAISE FND_API.G_EXC_ERROR;
861   END IF;
862 
863   -- srakrish Bug 5276602: Checking if the Lot optionalfeild is set to yes when lot or parent lot or entered.
864   -- This scenario exists when the api is called from the wrapper.
865   IF l_inv_vr.lot_number IS NOT NULL or l_inv_vr.parent_lot_number IS NOT NULL then
866    IF l_inv_vr.lot_optional_on_sample = 'Y'  THEN
867      GMD_API_PUB.Log_Message('GMD_SPEC_VR_LOT_CNTRL_INVALID');
868      RAISE FND_API.G_EXC_ERROR;
869    END IF;
870   END IF;
871 
872   -- All systems GO...
873   x_inv_vr := l_inv_vr;
874 
875 EXCEPTION
876   WHEN FND_API.G_EXC_ERROR     OR
877        e_spec_fetch_error      OR
878        e_smpl_plan_fetch_error OR
879        e_error_fetch_item
880   THEN
881     x_return_status := FND_API.G_RET_STS_ERROR ;
882   WHEN FND_API.G_EXC_UNEXPECTED_ERROR THEN
883     x_return_status := FND_API.G_RET_STS_UNEXP_ERROR ;
884   WHEN OTHERS THEN
885     x_return_status := FND_API.G_RET_STS_UNEXP_ERROR ;
886 
887 
888 END validate_inv_vr;
889 
890 
891 --Start of comments
892 --+========================================================================+
893 --| API Name    : check_for_null_and_fks_in_ivr                            |
894 --| TYPE        : Group                                                    |
895 --| Notes       : This procedure checks for NULL and Foreign Key           |
896 --|               constraints for the required filed in the Spec           |
897 --|               Inventory VR record.                                     |
898 --|                                                                        |
899 --|               If everything is fine then 'S' is returned in the        |
900 --|               parameter - x_return_status otherwise error message      |
901 --|               is logged and error status - E or U returned             |
902 --|                                                                        |
903 --| HISTORY                                                                |
904 --|    Chetan Nagar	26-Jul-2002	Created.                           |
905 --|    Olivier Daboval  02-DEC-2002     Added x_inv_vr as out parameter    |
906 --|    Jeff Baird       30-Apr-2004     Bug #3500024                       |
907 --|                     Three following fixes ported to L.                 |
908 --|    P.Raghu          23-JAN-2004     Bug#3381762                        |
909 --|                     Modified the existing logic for Validation of      |
910 --|                     lot_id and lot_no and sublot as suggested          |
911 --|    Jeff Baird       05-Mar-2004     Bug #3476572                       |
912 --|                     Added update to lot_id if lot_no / sublot_no passed|
913 --|    Jeff Baird       20-Apr-2004     Bug #3582010                       |
914 --|                     Added l_sublot_no where it was left out.           |
915 --|                                                                        |
916 --|    SaiKiran		04-MAY-2004	Enhancement #3476560. added        |
917 --|                  'delayed_lot_entry' to the call to 'check_vr_controls'|
918 --|                   procedure.                                           |
919 --|                                                                        |
920 --|  Saikiran          24-Apr-2005  Convergence Changes                    |
921 --|  srakrish 	       15-june-06    BUG 5251172: Checking if the          |
922 --|					responsibility is available to the |
923 --|					organization			   |
924 --+========================================================================+
925 -- End of comments
926 
927 PROCEDURE check_for_null_and_fks_in_ivr
928 (
929   p_inv_vr        IN  GMD_INVENTORY_SPEC_VRS%ROWTYPE
930 , p_spec          IN  GMD_SPECIFICATIONS%ROWTYPE
931 , x_inv_vr        OUT NOCOPY GMD_INVENTORY_SPEC_VRS%ROWTYPE
932 , x_return_status OUT NOCOPY VARCHAR2
933 )
934 IS
935 
936 l_inv_vr           GMD_INVENTORY_SPEC_VRS%ROWTYPE;
937 l_spec             GMD_SPECIFICATIONS%ROWTYPE;
938 
939 CURSOR c_item_lot_number IS
940 SELECT 1
941 FROM mtl_lot_numbers
942 WHERE organization_id = l_inv_vr.organization_id
943 AND inventory_item_id = l_spec.inventory_item_id
944 AND lot_number = l_inv_vr.lot_number;
945 
946 CURSOR c_item_parent_lot IS
947 SELECT 1
948 FROM mtl_lot_numbers
949 WHERE organization_id = l_inv_vr.organization_id
950 AND inventory_item_id = l_spec.inventory_item_id
951 AND parent_lot_number = l_inv_vr.parent_lot_number;
952 
953 
954 CURSOR c_subinventory IS
955 SELECT 1
956 FROM   mtl_secondary_inventories
957 WHERE  secondary_inventory_name   = l_inv_vr.subinventory
958 AND organization_id = l_inv_vr.organization_id;
959 
960 CURSOR c_locator IS
961 SELECT 1
962 FROM   mtl_item_locations
963 WHERE  organization_id   = l_inv_vr.organization_id
964 AND    inventory_location_id    = l_inv_vr.locator_id;
965 
966 
967 
968 l_sample_display   GMD_SAMPLES_GRP.sample_display_rec;
969 dummy              NUMBER;
970 l_status_ctl       VARCHAR2(1);
971 l_lot_ctl          NUMBER;
972 l_child_lot_ctl       VARCHAR2(1);
973 l_locator_type     NUMBER;
974 l_return_status    VARCHAR2(1);
975 
976 BEGIN
977   l_inv_vr := p_inv_vr;
978   l_spec := p_spec;
979 
980   check_who( p_user_id  => l_inv_vr.created_by);
981   check_who( p_user_id  => l_inv_vr.last_updated_by);
982   IF (l_inv_vr.creation_date IS NULL
983    OR l_inv_vr.last_update_date IS NULL)
984   THEN
985     GMD_API_PUB.Log_Message('GMD_WRONG_VALUE',
986                             'WHAT', 'the dates must not be NULL');
987     RAISE FND_API.G_EXC_ERROR;
988   END IF;
989 
990   -- Organization is valid
991   IF (l_inv_vr.organization_id IS NOT NULL) THEN
992     -- Check that Organization is a valid one.
993     OPEN c_orgn( l_inv_vr.organization_id);
994     FETCH c_orgn INTO dummy;
995     IF (c_orgn%NOTFOUND)
996     THEN
997       CLOSE c_orgn;
998       GMD_API_PUB.Log_Message('GMD_ORGANIZATION_ID_NOT_FOUND',
999                               'ORGN_ID', l_inv_vr.organization_id);
1000       RAISE FND_API.G_EXC_ERROR;
1001     END IF;
1002     CLOSE c_orgn;
1003   END IF;
1004 
1005   --srakrish BUG 5251172: Checking if the responsibility is available to the organization.
1006   IF NOT (gmd_api_grp.OrgnAccessible(l_inv_vr.organization_id)) THEN
1007    	  RAISE FND_API.G_EXC_ERROR;
1008   END IF;
1009 
1010   --=========================================================================
1011   -- Get Item Controls
1012   --=========================================================================
1013 
1014   l_sample_display.organization_id := l_inv_vr.organization_id;
1015   l_sample_display.inventory_item_id := l_spec.inventory_item_id;
1016   GMD_SAMPLES_GRP.get_item_values (p_sample_display => l_sample_display);
1017   l_lot_ctl := l_sample_display.lot_control_code;
1018   l_status_ctl := l_sample_display.lot_status_enabled;
1019   l_child_lot_ctl := l_sample_display.child_lot_flag;
1020 
1021   GMD_COMMON_GRP.item_is_locator_controlled (
1022                       p_organization_id   => l_inv_vr.organization_id
1023                      ,p_subinventory      => l_inv_vr.subinventory
1024                      ,p_inventory_item_id => l_spec.inventory_item_id
1025                      ,x_locator_type      => l_locator_type
1026                      ,x_return_status     => l_return_status);
1027 
1028   IF (l_inv_vr.lot_number IS NOT NULL)
1029   THEN
1030       IF (l_lot_ctl = 2) THEN --Item is lot controlled
1031         OPEN c_item_lot_number;
1032         FETCH c_item_lot_number INTO dummy;
1033         IF (c_item_lot_number%NOTFOUND)
1034         THEN
1035           CLOSE c_item_lot_number;
1036           GMD_API_PUB.Log_Message('GMD_WRONG_VALUE',
1037                               'WHAT', 'lot_number');
1038           RAISE FND_API.G_EXC_ERROR;
1039         END IF;
1040         CLOSE c_item_lot_number;
1041       ELSE --Item is not lot controlled
1042          FND_MESSAGE.SET_NAME('GMD','GMD_ITEM_NOT_LOT_CONTROL');
1043          FND_MSG_PUB.ADD;
1044          RAISE FND_API.G_EXC_ERROR;
1045       END IF;
1046   END IF;
1047 
1048   IF (l_inv_vr.parent_lot_number IS NOT NULL)
1049   THEN
1050       IF (l_child_lot_ctl = 'Y') THEN --Item is child lot controlled
1051         OPEN c_item_parent_lot;
1052         FETCH c_item_parent_lot INTO dummy;
1053         IF (c_item_parent_lot%NOTFOUND)
1054         THEN
1055           CLOSE c_item_parent_lot;
1056           GMD_API_PUB.Log_Message('GMD_WRONG_VALUE',
1057                               'WHAT', 'parent_lot_number');
1058           RAISE FND_API.G_EXC_ERROR;
1059         END IF;
1060         CLOSE c_item_parent_lot;
1061       ELSE --Item is not child lot controlled
1062          FND_MESSAGE.SET_NAME('GMD','GMD_ITEM_NOT_CHILD_LOT_CONTROL');
1063          FND_MSG_PUB.ADD;
1064          RAISE FND_API.G_EXC_ERROR;
1065       END IF;
1066   END IF;
1067 
1068   -- Subinventory is Valid
1069   IF (l_inv_vr.subinventory IS NOT NULL) THEN
1070     OPEN c_subinventory;
1071     FETCH c_subinventory INTO dummy;
1072     IF (c_subinventory%NOTFOUND)
1073     THEN
1074       CLOSE c_subinventory;
1075       GMD_API_PUB.Log_Message('GMD_SUBINVENTORY_NOT_FOUND',
1076                               'SUBINVENTORY', l_inv_vr.subinventory);
1077       RAISE FND_API.G_EXC_ERROR;
1078     END IF;
1079     CLOSE c_subinventory;
1080   END IF;
1081 
1082   -- Location is valid
1083   IF (l_locator_type IN (2,3))
1084   THEN
1085     -- Here l_locator_type IN (2,3)
1086     IF (l_inv_vr.locator_id IS NULL)
1087     THEN
1088       -- Location can be NULL in this case.
1089       null;
1090     ELSE
1091       -- Check that Location exist in MTL_ITEM_LOCATIONS
1092       OPEN c_locator;
1093       FETCH c_locator INTO dummy;
1094       IF (c_locator%NOTFOUND)
1095       THEN
1096         CLOSE c_locator;
1097         GMD_API_PUB.Log_Message('GMD_LOCT_NOT_FOUND');
1098         RAISE FND_API.G_EXC_ERROR;
1099       END IF;
1100       CLOSE c_locator;
1101     END IF;   -- location IS NOT NULL
1102   ELSE     -- Here l_locator_type not IN (2,3)
1103     IF (l_inv_vr.locator_id IS NOT NULL)
1104     THEN
1105         GMD_API_PUB.Log_Message('GMD_WRONG_VALUE',
1106                                 'WHAT', 'locator should be NULL');
1107         RAISE FND_API.G_EXC_ERROR;
1108     END IF;
1109   END IF;   -- l_locator_type IN (2,3)
1110   --=========================================================================
1111   -- lot_optional_on_sample :
1112   -- When this field is NOT NULL, all the following fields must be null :
1113   -- sample_inv_trans_ind, control_lot_attrib_ind, in_spec_lot_status, out_of_spec_lot_status
1114   --=========================================================================
1115   --Enhancement #3476560. added 'delayed_lot_entry' to the call to 'check_vr_controls' procedure
1116   check_VR_Controls( p_VR_type                  => 'INVENTORY'
1117                    , p_lot_optional_on_sample   => l_inv_vr.lot_optional_on_sample
1118 		   , p_delayed_lot_entry        => l_inv_vr.delayed_lot_entry
1119                    , p_sample_inv_trans_ind     => l_inv_vr.sample_inv_trans_ind
1120                    , p_lot_ctl                  => l_lot_ctl
1121                    , p_status_ctl               => l_status_ctl
1122                    , p_control_lot_attrib_ind   => l_inv_vr.control_lot_attrib_ind
1123                    , p_in_spec_lot_status_id    => l_inv_vr.in_spec_lot_status_id
1124                    , p_out_of_spec_lot_status_id=> l_inv_vr.out_of_spec_lot_status_id
1125                    , p_control_batch_step_ind   => NULL
1126 		   , p_delayed_lpn_entry        => l_inv_vr.delayed_lpn_entry);    --RLNAGARA LPN ME 7027149
1127 
1128 
1129   --RLNAGARA LPN ME 7027149 start  Check for WMS enabled organization.
1130   IF (l_inv_vr.organization_id IS NOT NULL) THEN
1131     IF NOT check_wms_enabled(l_inv_vr.organization_id) THEN  -- If the Org is not a wms enabled then delayed_lpn_entry should be NULL
1132       IF l_inv_vr.delayed_lpn_entry IS NOT NULL THEN
1133         GMD_API_PUB.Log_Message('GMD_WRONG_VALUE',
1134                                 'WHAT', 'Delayed_LPN_Entry should be NULL for Non-WMS Enabled Organization.');
1135         RAISE FND_API.G_EXC_ERROR;
1136       END IF;
1137     END IF;
1138   END IF;
1139   --RLNAGARA LPN ME 7027149 end
1140 
1141   --=========================================================================
1142   -- spec_vr_status :
1143   --=========================================================================
1144   -- Check that Spec VR Status exist in GMD_QC_STATUS
1145   OPEN c_status(l_inv_vr.spec_vr_status);
1146   FETCH c_status
1147    INTO dummy;
1148   IF (c_status%NOTFOUND)
1149   THEN
1150     CLOSE c_status;
1151     GMD_API_PUB.Log_Message('GMD_SPEC_STATUS_NOT_FOUND',
1152                             'STATUS', l_inv_vr.spec_vr_status);
1153     RAISE FND_API.G_EXC_ERROR;
1154   END IF;
1155   CLOSE c_status;
1156 
1157   --=========================================================================
1158   -- start_date : This field is mandatory
1159   --=========================================================================
1160   IF (l_inv_vr.start_date IS NULL)
1161   THEN
1162       GMD_API_PUB.Log_Message('GMD_SPEC_VR_START_DATE_REQD');
1163       RAISE FND_API.G_EXC_ERROR;
1164   END IF;
1165 
1166   --=========================================================================
1167   -- COA section :
1168   --=========================================================================
1169   check_COA( p_coa_type              => l_inv_vr.coa_type
1170            , p_coa_at_ship_ind       => l_inv_vr.coa_at_ship_ind
1171            , p_coa_at_invoice_ind    => l_inv_vr.coa_at_invoice_ind
1172            , p_coa_req_from_supl_ind => l_inv_vr.coa_req_from_supl_ind);
1173 
1174   x_inv_vr := l_inv_vr;
1175 
1176 
1177 EXCEPTION
1178   WHEN FND_API.G_EXC_ERROR THEN
1179     x_return_status := FND_API.G_RET_STS_ERROR ;
1180   WHEN FND_API.G_EXC_UNEXPECTED_ERROR THEN
1181     x_return_status := FND_API.G_RET_STS_UNEXP_ERROR ;
1182   WHEN OTHERS THEN
1183     x_return_status := FND_API.G_RET_STS_UNEXP_ERROR ;
1184 
1185 END check_for_null_and_fks_in_ivr;
1186 
1187 
1188 
1189 
1190 
1191 --Start of comments
1192 --+========================================================================+
1193 --| API Name    : inv_vr_exist                                             |
1194 --| TYPE        : Group                                                    |
1195 --| Notes       : This function returns TRUE if the inventory VR already   |
1196 --|               exists for the spcified parameter in the database, FALSE |
1197 --|               otherwise.                                               |
1198 --|                                                                        |
1199 --| HISTORY                                                                |
1200 --|    Chetan Nagar	26-Jul-2002	Created.                           |
1201 --|    Olivier Daboval  17-OCT-2002     bug 2630007, added spec_name in    |
1202 --|                                     the VR_EXIST message               |
1203 --|    Olivier Daboval  14-NOV-2002     Added NVL(spec_vr_id, -1) because  |
1204 --|                                     the API passes a NULL spec_vr_id   |
1205 --|                                     in insert mode.                    |
1206 --|    Brenda Stone     20-NOV-2003     Bug 3090290; allow duplicate spec vr |
1207 --|                                     with "OBSOLUTE" status               |
1208 --|                                     Bug 2984784; add Version to msg for  |
1209 --|                                     existing spec vr.                    |
1210 --|                                                                        |
1211 --|  Saikiran          12-Apr-2005      Convergence Changes                |
1212 --|  Plowe						 04-Apr-2006      Bug 5117733 - added item revision to match
1213 --+========================================================================+
1214 -- End of comments
1215 
1216 FUNCTION inv_vr_exist(p_inv_vr GMD_INVENTORY_SPEC_VRS%ROWTYPE,
1217                       p_spec   GMD_SPECIFICATIONS%ROWTYPE)
1218 RETURN BOOLEAN IS
1219 
1220   CURSOR c_inv_vr IS
1221   SELECT vr.spec_vr_id, s.spec_name, s.spec_vers
1222   FROM   gmd_specifications_b s, gmd_inventory_spec_vrs vr
1223   WHERE  s.spec_id = vr.spec_id
1224   AND    s.owner_organization_id = p_spec.owner_organization_id
1225   AND    s.inventory_item_id = p_spec.inventory_item_id
1226   AND   ( (s.revision is null and p_spec.revision is NULL ) OR -- handle item revision 5117733
1227           (s.revision  = p_spec.revision )
1228   			 )
1229   AND    ((s.grade_code is NULL AND p_spec.grade_code is NULL) OR
1230           (s.grade_code = p_spec.grade_code)
1231          )
1232 
1233   AND    ((vr.organization_id is NULL AND p_inv_vr.organization_id is NULL) OR
1234           (vr.organization_id = p_inv_vr.organization_id)
1235          )
1236   AND    ((vr.lot_number is NULL AND p_inv_vr.lot_number is NULL) OR
1237           (vr.lot_number = p_inv_vr.lot_number)
1238          )
1239   AND    ((vr.parent_lot_number is NULL AND p_inv_vr.parent_lot_number is NULL) OR
1240           (vr.parent_lot_number = p_inv_vr.parent_lot_number)
1241          )
1242   AND    ((vr.subinventory is NULL AND p_inv_vr.subinventory is NULL) OR
1243           (vr.subinventory = p_inv_vr.subinventory)
1244          )
1245   AND    ((vr.locator_id is NULL  AND p_inv_vr.locator_id is NULL) OR
1246           (vr.locator_id = p_inv_vr.locator_id)
1247          )
1248   AND    ((vr.end_date is NULL AND (p_inv_vr.end_date IS NULL OR
1249                                     p_inv_vr.end_date >= vr.start_date)) OR
1250 	  (p_inv_vr.end_date IS NULL AND
1251 	     p_inv_vr.start_date <= nvl(vr.end_date, p_inv_vr.start_date)) OR
1252           (p_inv_vr.start_date <= vr.end_date AND p_inv_vr.end_date >= vr.start_date)
1253          )
1254   AND   ( floor(vr.spec_vr_status / 100) = floor(p_inv_vr.spec_vr_status/100)  AND
1255 /*      Bug 3090290; allow duplicate spec vr with "OBSOLUTE" status   */
1256          p_inv_vr.spec_vr_status <> 1000 )
1257   AND    vr.spec_vr_status NOT IN (SELECT status_code FROM gmd_qc_status
1258                                    WHERE status_type = 800)
1259   AND    vr.delete_mark = 0
1260   AND    s.delete_mark = 0
1261   AND    vr.spec_vr_id <> NVL(p_inv_vr.spec_vr_id, -1)
1262   ;
1263 
1264   dummy    PLS_INTEGER;
1265   specname VARCHAR2(80);
1266   specvers NUMBER;
1267 
1268 BEGIN
1269 
1270   OPEN c_inv_vr;
1271   FETCH c_inv_vr INTO dummy, specname, specvers;
1272   IF c_inv_vr%FOUND THEN
1273     CLOSE c_inv_vr;
1274     FND_MESSAGE.SET_NAME('GMD', 'GMD_INV_VR_EXIST');
1275     FND_MESSAGE.SET_TOKEN('spec', specname);
1276     FND_MESSAGE.SET_TOKEN('vers', specvers);
1277     FND_MSG_PUB.ADD;
1278     RETURN TRUE;
1279   ELSE
1280     CLOSE c_inv_vr;
1281     RETURN FALSE;
1282   END IF;
1283 
1284 EXCEPTION
1285   -- Though there is no reason the program can reach
1286   -- here, this is coded just for the reasons we can
1287   -- not think of!
1288   WHEN OTHERS THEN
1289     FND_MESSAGE.SET_NAME('GMD', 'GMD_API_ERROR');
1290     FND_MESSAGE.SET_TOKEN('PACKAGE', 'GMD_SPEC_VRS_GRP.INV_VR_EXIST' );
1291     FND_MESSAGE.SET_TOKEN('ERROR', SUBSTR(SQLERRM,1,200));
1292     FND_MSG_PUB.ADD;
1293 
1294     RETURN TRUE;
1295 
1296 END inv_vr_exist;
1297 
1298 
1299 --Start of comments
1300 --+========================================================================+
1301 --| API Name    : validate_wip_vr                                          |
1302 --| TYPE        : Group                                                    |
1303 --| Notes       : This procedure validates all the fields of               |
1304 --|               WIP       validity rule record. This procedure can be    |
1305 --|               called from FORM or API and the caller need              |
1306 --|               to specify this in p_called_from parameter               |
1307 --|               while calling this procedure. Based on where             |
1308 --|               it is called from certain validations will               |
1309 --|               either be performed or skipped.                          |
1310 --|                                                                        |
1311 --|               If everything is fine then OUT parameter                 |
1312 --|               x_return_status is set to 'S' else appropriate           |
1313 --|               error message is put on the stack and error              |
1314 --|               is returned.                                             |
1315 --|                                                                        |
1316 --| HISTORY                                                                |
1317 --|    Chetan Nagar	26-Jul-2002	Created.                           |
1318 --|    Olivier Daboval  02-DEC-2002     Added x_wip_vr as out parameter    |
1319 --|                                                                        |
1320 --+========================================================================+
1321 -- End of comments
1322 
1323 PROCEDURE validate_wip_vr
1324 (
1325   p_wip_vr        IN  GMD_WIP_SPEC_VRS%ROWTYPE
1326 , p_called_from   IN  VARCHAR2
1327 , p_operation     IN  VARCHAR2
1328 , x_wip_vr        OUT NOCOPY GMD_WIP_SPEC_VRS%ROWTYPE
1329 , x_return_status OUT NOCOPY VARCHAR2
1330 ) IS
1331 
1332   -- Local Variables
1333   dummy                          NUMBER;
1334   l_return_status                VARCHAR2(1);
1335 
1336   l_spec                         GMD_SPECIFICATIONS%ROWTYPE;
1337   l_spec_out                     GMD_SPECIFICATIONS%ROWTYPE;
1338   l_wip_vr                       GMD_WIP_SPEC_VRS%ROWTYPE;
1339   l_wip_vr_tmp                   GMD_WIP_SPEC_VRS%ROWTYPE;
1340   l_item_mst                     MTL_SYSTEM_ITEMS_B%ROWTYPE;
1341   l_sampling_plan                GMD_SAMPLING_PLANS%ROWTYPE;
1342   l_sampling_plan_out            GMD_SAMPLING_PLANS%ROWTYPE;
1343   l_inventory_item_id            NUMBER;
1344   l_organization_id              NUMBER;
1345   l_uom_rate                     NUMBER;
1346 
1347   -- Exceptions
1348   e_spec_fetch_error             EXCEPTION;
1349   e_smpl_plan_fetch_error        EXCEPTION;
1350   e_error_fetch_item             EXCEPTION;
1351 
1352 BEGIN
1353   --  Initialize API return status to success
1354   x_return_status := FND_API.G_RET_STS_SUCCESS;
1355 
1356   IF NOT (p_operation in ('INSERT', 'UPDATE', 'DELETE')) THEN
1357     -- Invalid Operation
1358     GMD_API_PUB.Log_Message('GMD_INVALID_OPERATION');
1359     RAISE FND_API.G_EXC_ERROR;
1360   END IF;
1361 
1362   -- Verify that the specification exists.
1363   l_spec.spec_id := p_wip_vr.spec_id;
1364   IF NOT (GMD_Specifications_PVT.Fetch_Row(
1365                            p_specifications => l_spec,
1366                            x_specifications => l_spec_out)
1367           ) THEN
1368     -- Fetch Error
1369     GMD_API_PUB.Log_Message('GMD_SPEC_FETCH_ERROR');
1370     RAISE e_spec_fetch_error;
1371   END IF;
1372 
1373   l_spec := l_spec_out ;
1374 
1375   -- Verify that the Sampling Plan exists.
1376   --odab added this test.
1377   IF (p_wip_vr.sampling_plan_id IS NOT NULL)
1378   THEN
1379     l_sampling_plan.sampling_plan_id := p_wip_vr.sampling_plan_id;
1380     IF NOT (GMD_Sampling_Plans_PVT.Fetch_Row(
1381                            p_sampling_plan => l_sampling_plan,
1382                            x_sampling_plan => l_sampling_plan_out)
1383           ) THEN
1384       -- Fetch Error
1385       GMD_API_PUB.Log_Message('GMD_SAMPLING_PLAN_FETCH_ERROR');
1386       RAISE e_smpl_plan_fetch_error;
1387     END IF;
1388     l_sampling_plan := l_sampling_plan_out ;
1389   END IF;
1390 
1391   -- Check to make sure that a samplingplan exists
1392   -- if auto sample flag on
1393 
1394   IF ((p_wip_vr.sampling_plan_id IS NULL) and
1395        (p_wip_vr.auto_sample_ind = 'Y'))
1396   THEN
1397       GMD_API_PUB.Log_Message('GMD_NEED_SAMPLE_PLAN');
1398       RAISE FND_API.G_EXC_ERROR;
1399   END IF;
1400 
1401 
1402   -- bug 2691994  02-DEC-02:
1403   -- odaboval From this point, the l_wip_vr is used
1404   --      and will populate the return parameter x_wip_vr
1405   l_wip_vr := p_wip_vr;
1406   IF (p_called_from = 'API') THEN
1407     --For mini pack L, bug 3439865
1408     IF (nvl(p_wip_vr.auto_sample_ind,'N') not in ('N','Y')) THEN
1409       GMD_API_PUB.Log_Message('GMD_WRONG_VALUE',
1410                             'WHAT', 'INVALID_AUTO_SAMPLE_IND');
1411       RAISE FND_API.G_EXC_ERROR;
1412     END IF;
1413     -- end 3439865
1414     -- Check for NULLs and Valid Foreign Keys in the input parameter
1415     GMD_SPEC_VRS_GRP.check_for_null_and_fks_in_wvr
1416       (
1417         p_wip_vr        => p_wip_vr
1418       , p_spec          => l_spec
1419       , x_wip_vr        => l_wip_vr_tmp
1420       , x_return_status => l_return_status
1421       );
1422     -- No need if called from FORM since it is already
1423     -- done in the form
1424 
1425     IF l_return_status = FND_API.G_RET_STS_ERROR THEN
1426       -- Message is alrady logged by check_for_null procedure
1427       RAISE FND_API.G_EXC_ERROR;
1428     ELSIF l_return_status = FND_API.G_RET_STS_UNEXP_ERROR THEN
1429       -- Message is alrady logged by check_for_null procedure
1430       RAISE FND_API.G_EXC_UNEXPECTED_ERROR;
1431     END IF;
1432 
1433     l_wip_vr := l_wip_vr_tmp;
1434   END IF;
1435 
1436   -- First Verify that the SAME VR does not exists
1437   -- bug 2691994  02-DEC-02, odaboval changed p_wip_vr by l_wip_vr
1438   IF (p_operation IN ('INSERT', 'UPDATE')
1439    AND wip_vr_exist(l_wip_vr, l_spec))
1440   THEN
1441     -- Disaster, Trying to insert duplicate
1442     -- bug 2630007, odaboval put the message in function wip_vr_exist.
1443     -- GMD_API_PUB.Log_Message('GMD_WIP_VR_EXIST');
1444     RAISE FND_API.G_EXC_ERROR;
1445   END IF;
1446 
1447   -- Sample Quantity UOM must be convertible to Item's UOM
1448   BEGIN
1449     SELECT inventory_item_id INTO l_inventory_item_id FROM
1450     gmd_specifications WHERE spec_id = p_wip_vr.spec_id;
1451     SELECT owner_organization_id INTO l_organization_id FROM
1452     gmd_specifications WHERE spec_id = p_wip_vr.spec_id;
1453     SELECT * INTO l_item_mst
1454     FROM mtl_system_items_b
1455     WHERE inventory_item_id = l_inventory_item_id
1456     AND organization_id = l_organization_id;
1457   EXCEPTION
1458   WHEN OTHERS THEN
1459     GMD_API_PUB.Log_Message('GMD_ITEM_FETCH_ERROR');
1460     RAISE e_error_fetch_item;
1461   END;
1462 
1463 
1464   --odab added this test.
1465   -- bug 2691994  02-DEC-02, odaboval changed p_wip_vr by l_wip_vr
1466   IF (l_wip_vr.sampling_plan_id IS NOT NULL)
1467   THEN
1468 
1469     inv_convert.inv_um_conversion (
1470       from_unit  => l_sampling_plan.sample_qty_uom,
1471       to_unit    =>  l_item_mst.primary_uom_code,
1472       item_id    =>  l_inventory_item_id,
1473       lot_number => NULL,
1474       organization_id => l_organization_id,
1475       uom_rate   => l_uom_rate );
1476 
1477     IF l_uom_rate = -99999 THEN
1478       GMD_API_PUB.Log_Message('GMD_UOM_CONVERSION_ERROR');
1479       RAISE FND_API.G_EXC_ERROR;
1480     END IF;
1481   END IF;
1482 
1483   -- No need to check the return status because above procedure
1484   -- logs appropriate message on the stack and raises an exception.
1485 
1486   -- The Start Date must be less than the End Date
1487   -- bug 2691994  02-DEC-02, odaboval changed p_wip_vr by l_wip_vr
1488   If ( l_wip_vr.end_date IS NOT NULL AND
1489        l_wip_vr.start_date > l_wip_vr.end_date) THEN
1490     GMD_API_PUB.Log_Message('GMD_SPEC_VR_EFF_DATE_ERROR');
1491     RAISE FND_API.G_EXC_ERROR;
1492   END IF;
1493 
1494   -- Spec VR Status Must be less than Spec Status upto Appoved Stages
1495   -- bug 2691994  02-DEC-02, odaboval changed p_wip_vr by l_wip_vr
1496   IF (floor(l_spec.spec_status/100) <= 7 AND
1497       floor(l_wip_vr.spec_vr_status/100) <= 7 AND
1498       l_wip_vr.spec_vr_status > l_spec.spec_status) THEN
1499     GMD_API_PUB.Log_Message('GMD_SPEC_VR_STATUS_HIGHER');
1500     RAISE FND_API.G_EXC_ERROR;
1501   END IF;
1502 
1503   -- All systems GO...
1504   x_wip_vr := l_wip_vr;
1505 
1506 EXCEPTION
1507   WHEN FND_API.G_EXC_ERROR     OR
1508        e_spec_fetch_error      OR
1509        e_smpl_plan_fetch_error OR
1510        e_error_fetch_item
1511 
1512   THEN
1513     x_return_status := FND_API.G_RET_STS_ERROR ;
1514   WHEN FND_API.G_EXC_UNEXPECTED_ERROR THEN
1515     x_return_status := FND_API.G_RET_STS_UNEXP_ERROR ;
1516   WHEN OTHERS THEN
1517     x_return_status := FND_API.G_RET_STS_UNEXP_ERROR ;
1518 
1519 
1520 END validate_wip_vr;
1521 
1522 
1523 
1524 
1525 --Start of comments
1526 --+========================================================================+
1527 --| API Name    : check_for_null_and_fks_in_wvr                            |
1528 --| TYPE        : Group                                                    |
1529 --| Notes       : This procedure checks for NULL and Foreign Key           |
1530 --|               constraints for the required filed in the Spec           |
1531 --|               WIP       VR record.                                     |
1532 --|                                                                        |
1533 --|               If everything is fine then 'S' is returned in the        |
1534 --|               parameter - x_return_status otherwise error message      |
1535 --|               is logged and error status - E or U returned             |
1536 --|                                                                        |
1537 --| HISTORY                                                                |
1538 --|    Chetan Nagar	26-Jul-2002	Created.                           |
1539 --|    Olivier Daboval  02-DEC-2002     Added x_wip_vr as out parameter    |
1540 --|    Olivier Daboval  01-APR-2003     Now, populate the lower levels     |
1541 --|                     Bug 2733426   Formula/Routing when recipe is given |
1542 --|    SaiKiran		04-MAY-2004	Enhancement #3476560. added        |
1543 --|                  'delayed_lot_entry' to the call to 'check_vr_controls'|
1544 --|                   procedure.                                           |
1545 --|									   |
1546 --|    Saikiran         11-Apr-05      Convergence changes                 |
1547 --|    srakrish 	15-june-06     BUG 5251172: Checking if the        |
1548 --|				       responsibility is available to the  |
1549 --|				       organization			   |
1550 --|                                                                        |
1551 --|    Kishore    -       30-Sep-2008     -       Bug No.7419838    |
1552 --|      Changed the cursor c_orgn_plant, as Spec VR can be created for plant also |
1553 --|
1554 --|    Michael Tou - 25-Aug-2011 - Bug No. 6278463    |
1555 --|                   Implemented outer-join on all the columns of gmd_routings table |
1556 --|                   in the cursors c_recipe_id , c_recipe_no, c_batch, c_routing_id and c_routing_no |
1557 --|   PLOWE         05-OCT-2011    Bug # 13027522  			                     |
1558 --|                 Changed the c_batch cursor to tidy up work for
1559 --|   bug 6278463 as this was not working for when no route was passed thru API params |
1560 --|   PLOWE         25-OCT-2011    Bug # 13105549  			                     |
1561 --|                 Changed the c_batch cursor to tidy up work for
1562 --|                 bug 6278463 as this was not working for when batch with recipe has a route |
1563 --|   PLOWE         5-MAR-2012    Bug # 13451274  			                                       |
1564 --|             Changed the c_batch cursor to so that we can retreive rows when the            |
1565 --|             batch has an item that is is not on formula                                    |
1566 --|
1567 --+========================================================================+
1568 -- End of comments
1569 
1570 PROCEDURE check_for_null_and_fks_in_wvr
1571 (
1572   p_wip_vr        IN  GMD_WIP_SPEC_VRS%ROWTYPE
1573 , p_spec          IN  GMD_SPECIFICATIONS%ROWTYPE
1574 , x_wip_vr        OUT NOCOPY GMD_WIP_SPEC_VRS%ROWTYPE
1575 , x_return_status OUT NOCOPY VARCHAR2
1576 )
1577 IS
1578 
1579 l_wip_vr           GMD_WIP_SPEC_VRS%ROWTYPE;
1580 l_spec             GMD_SPECIFICATIONS%ROWTYPE;
1581 
1582 -- bug 4924483   sql id 14687134 MJC take out org_access_view as not used in query
1583 -- bug 5223014 - sql id 17532478 NO change required as added created an index on Organization_Id
1584 -- to stop FTS on gmd_parameters_hdr
1585 CURSOR c_orgn_plant ( p_organization_id IN NUMBER) IS
1586 SELECT 1
1587 FROM
1588 -- org_access_view o,
1589      mtl_parameters m,
1590      gmd_parameters_hdr h
1591 WHERE h.organization_id = m.organization_id
1592   AND m.process_enabled_flag = 'Y'
1593   AND m.organization_id = p_organization_id;
1594  -- AND h.lab_ind = 1; /* Commented in Bug No. 7419838 */
1595 
1596 
1597 -- bug 4924483 sql id 14687160 (shared mem > 1 mill)   use base tables
1598 CURSOR c_batch IS
1599 SELECT gr.recipe_id, gr.recipe_no, gr.recipe_version
1600 , ffm.formula_id, ffm.formula_no, ffm.formula_vers
1601 , rout.routing_id, rout.routing_no, rout.routing_vers
1602 FROM gme_batch_header bh
1603 , gme_material_details md
1604 , gmd_recipes_b gr  -- just need base table here not view
1605 , gmd_recipe_validity_rules rvr
1606 , gmd_status gs
1607 , fm_matl_dtl fmd
1608 , fm_form_mst_b ffm -- just need base table here not view
1609 , gmd_routings_b rout -- just need base table here not view
1610 WHERE rout.routing_id(+) = bh.routing_id
1611 AND rvr.recipe_validity_rule_id = bh.recipe_validity_rule_id
1612 AND rvr.recipe_id = gr.recipe_id
1613 AND ffm.formula_id = bh.formula_id
1614 AND ffm.formula_id = fmd.formula_id
1615 AND fmd.formula_id = bh.formula_id
1616 AND rout.delete_mark(+) = 0  /*changed in bug 6278463 */
1617 AND gs.delete_mark = 0
1618 AND rvr.delete_mark = 0
1619 AND gr.delete_mark = 0
1620 AND bh.delete_mark = 0
1621 AND ffm.delete_mark = 0
1622 AND fmd.formula_id = gr.formula_id
1623 AND  ( fmd.inventory_item_id = p_spec.inventory_item_id
1624 OR    MD.FORMULALINE_ID IS NULL)   -- 13451274  added for when item is not on formula
1625 AND gr.recipe_status = gs.status_code
1626 AND gs.status_code <> '1000'
1627 AND gr.formula_id = bh.formula_id
1628 AND bh.batch_id = md.batch_id
1629 AND bh.batch_type = 0   -- Only BATCH, no FPO
1630 --AND bh.batch_status IN (1, 2)   -- PENDING or WIP BATCH only.
1631 AND ( (  bh.batch_status IN (1,2, 3)     and     ( NVL(fnd_profile.value('GMD_SAMPLE_CLOSED_BATCHES'),'N') = 'N') )
1632 or  ( bh.batch_status IN (1,2, 3,4 )   and  ( NVL(fnd_profile.value('GMD_SAMPLE_CLOSED_BATCHES'),'N') = 'Y') )  )  -- Bug # 4619570
1633 AND md.inventory_item_id = p_spec.inventory_item_id
1634 AND bh.organization_id = l_wip_vr.organization_id
1635 AND bh.batch_id = l_wip_vr.batch_id
1636 AND NVL( l_wip_vr.recipe_id, gr.recipe_id) = gr.recipe_id
1637 AND NVL( l_wip_vr.formula_id, bh.formula_id) = bh.formula_id
1638 AND  ( NVL( l_wip_vr.routing_id, 0) = nvl(bh.routing_id,0)   --  13027522 - better fix than one for 6278463 as when there was no routing id passed then the batch with no routing was not hit
1639 OR    NVL( l_wip_vr.routing_id, 0) = nvl(l_wip_vr.routing_id,0)  ) ; -- extra line -- 13105549  to handle behaviour for recipe with route.
1640 --AND NVL( l_wip_vr.routing_id, bh.routing_id) = bh.routing_id;/*commented in bug# 6278463 */
1641 --AND NVL( l_wip_vr.routing_id, 0) = bh.routing_id(+);/*added in bug bug# 6278463 for the first time,but this fix is wrong*/
1642 --AND NVL( l_wip_vr.routing_id, 0) = rout.routing_id(+);/*modification for Bug#6278463 for the second time ,this fix is equal to Bug13027522's Fix ,finally use Bug13027522's fix,here is just for record trace.*/
1643 
1644 
1645 CURSOR c_recipe_id IS
1646 SELECT r.recipe_no, r.recipe_version
1647 , ffm.formula_id, ffm.formula_no, ffm.formula_vers
1648 , rout.routing_id, rout.routing_no, rout.routing_vers
1649 FROM gmd_recipes r
1650 , gmd_status s
1651 , gmd_recipe_validity_rules rvr
1652 , gmd_routings rout
1653 , fm_form_mst ffm
1654 , fm_matl_dtl fmd
1655 WHERE rout.routing_id(+) = r.routing_id
1656 AND ffm.formula_id = r.formula_id
1657 AND rvr.recipe_id = r.recipe_id
1658 AND (NVL( l_wip_vr.organization_id, rvr.organization_id) = rvr.organization_id OR rvr.organization_id IS NULL)
1659 AND r.recipe_status = s.status_code
1660 AND r.formula_id = fmd.formula_id
1661 AND fmd.inventory_item_id = p_spec.inventory_item_id
1662 --AND NVL(rout.delete_mark, 0) = 0/*commented in  bug# 6278463 */
1663 AND rout.delete_mark(+) = 0 /*changed in   bug# 6278463 */
1664 AND rvr.delete_mark = 0
1665 AND s.delete_mark = 0
1666 AND r.delete_mark = 0
1667 AND ffm.delete_mark = 0
1668 AND s.status_type <> '1000'
1669 AND r.recipe_id = l_wip_vr.recipe_id
1670 AND NVL( l_wip_vr.formula_id, r.formula_id) = r.formula_id
1671 --AND NVL( l_wip_vr.routing_id, rout.routing_id) = rout.routing_id;/*commented in  bug# 6278463 */
1672 AND NVL( l_wip_vr.routing_id, 0) = rout.routing_id(+);/*changed in  bug# 6278463 */
1673 
1674 CURSOR c_recipe_no IS
1675 SELECT r.recipe_id, r.recipe_version
1676 FROM gmd_recipes r
1677 , gmd_status s
1678 , gmd_recipe_validity_rules rvr
1679 , gmd_routings rout
1680 , fm_form_mst ffm
1681 , fm_matl_dtl fmd
1682 WHERE rout.routing_id(+) = r.routing_id
1683 AND ffm.formula_id = r.formula_id
1684 AND rvr.recipe_id = r.recipe_id
1685 AND (NVL( l_wip_vr.organization_id, rvr.organization_id) = rvr.organization_id OR rvr.organization_id IS NULL)
1686 AND r.recipe_status = s.status_code
1687 AND r.formula_id = fmd.formula_id
1688 AND fmd.inventory_item_id = p_spec.inventory_item_id
1689 --AND NVL(rout.delete_mark, 0) = 0/*changed in   bug# 6278463 */
1690 AND rout.delete_mark(+) = 0/*changed in  bug# 6278463 */
1691 AND rvr.delete_mark = 0
1692 AND s.delete_mark = 0
1693 AND r.delete_mark = 0
1694 AND ffm.delete_mark = 0
1695 AND s.status_type <> '1000'
1696 AND r.recipe_no = l_wip_vr.recipe_no
1697 AND NVL( l_wip_vr.recipe_version, r.recipe_version) = r.recipe_version
1698 AND NVL( l_wip_vr.formula_id, r.formula_id) = r.formula_id
1699 --AND NVL( l_wip_vr.routing_id, rout.routing_id) = rout.routing_id;/*changed in  bug# 6278463 */
1700 AND NVL( l_wip_vr.routing_id, 0) = rout.routing_id(+);/*added in bug #6278463 */
1701 
1702 CURSOR c_formula_id IS
1703 SELECT ffm.formula_no, ffm.formula_vers
1704 FROM gmd_recipes grec
1705 , fm_form_mst ffm
1706 , fm_matl_dtl fmd
1707 , gem_lookups gl
1708 , gmd_status s
1709 WHERE s.status_code = ffm.formula_status
1710 AND gl.lookup_code = fmd.line_type
1711 AND gl.lookup_type = 'LINE_TYPE'
1712 AND grec.formula_id(+) = ffm.formula_id
1713 AND fmd.formula_id = ffm.formula_id
1714 AND fmd.inventory_item_id = p_spec.inventory_item_id
1715 AND s.delete_mark = 0
1716 AND grec.delete_mark = 0
1717 AND ffm.delete_mark = 0
1718 AND NVL( l_wip_vr.recipe_id, grec.recipe_id) = grec.recipe_id
1719 AND NVL( l_wip_vr.formulaline_id, fmd.formulaline_id) = fmd.formulaline_id
1720 AND ffm.formula_id = l_wip_vr.formula_id;
1721 
1722 CURSOR c_formula_no IS
1723 SELECT ffm.formula_id, ffm.formula_vers
1724 FROM gmd_recipes grec
1725 , fm_form_mst ffm
1726 , fm_matl_dtl fmd
1727 , gem_lookups gl
1728 , gmd_status s
1729 WHERE s.status_code = ffm.formula_status
1730 AND gl.lookup_code = fmd.line_type
1731 AND gl.lookup_type = 'LINE_TYPE'
1732 AND grec.formula_id(+) = ffm.formula_id
1733 AND fmd.formula_id = ffm.formula_id
1734 AND fmd.inventory_item_id = p_spec.inventory_item_id
1735 AND s.delete_mark = 0
1736 AND grec.delete_mark = 0
1737 AND ffm.delete_mark = 0
1738 AND NVL( l_wip_vr.recipe_id, grec.recipe_id) = grec.recipe_id
1739 AND NVL( l_wip_vr.formulaline_id, fmd.formulaline_id) = fmd.formulaline_id
1740 AND NVL( l_wip_vr.formula_vers, ffm.formula_vers) = ffm.formula_vers
1741 AND ffm.formula_no = l_wip_vr.formula_no;
1742 
1743 
1744 CURSOR c_formulaline_id IS
1745 SELECT 1
1746 FROM fm_matl_dtl fmd
1747 WHERE fmd.inventory_item_id = p_spec.inventory_item_id
1748 AND fmd.formula_id = l_wip_vr.formula_id
1749 AND fmd.formulaline_id = l_wip_vr.formulaline_id;
1750 
1751 
1752 -- Bug 4640143: added this cursor
1753 CURSOR c_material_detail_id IS
1754 SELECT 1
1755 FROM gme_material_details
1756 WHERE inventory_item_id   = p_spec.inventory_item_id
1757   AND batch_id            = l_wip_vr.batch_id
1758   AND organization_id     = l_wip_vr.organization_id
1759   AND material_detail_id  = l_wip_vr.material_detail_id;
1760 
1761 
1762 CURSOR c_routing_id IS
1763 SELECT r.routing_no, r.routing_vers
1764 FROM gmd_recipes grec
1765 , gmd_status s
1766 , gmd_routings r
1767 WHERE grec.routing_id(+) = r.routing_id
1768 AND s.status_code = r.routing_status
1769 AND NVL( l_wip_vr.recipe_id, 0) = grec.recipe_id(+) /*changed in bug# 6278463 */
1770 AND NVL( l_wip_vr.formula_id, 0) = grec.formula_id(+) /*changed in  bug# 6278463 */
1771 AND s.delete_mark = 0
1772 AND grec.delete_mark(+) = 0 /*changed in  bug# 6278463 */
1773 AND r.delete_mark = 0
1774 AND r.routing_id = l_wip_vr.routing_id;
1775 
1776 CURSOR c_routing_no IS
1777 SELECT r.routing_id, r.routing_vers
1778 FROM gmd_recipes grec
1779 , gmd_status s
1780 , gmd_routings r
1781 WHERE grec.routing_id(+) = r.routing_id
1782 AND s.status_code = r.routing_status
1783 AND NVL( l_wip_vr.recipe_id, 0) = grec.recipe_id(+)  /*changed in  bug# 6278463 */
1784 AND NVL( l_wip_vr.formula_id, 0) = grec.formula_id(+) /*changed in  bug# 6278463 */
1785 AND s.delete_mark = 0
1786 AND grec.delete_mark(+) = 0  /*changed in  bug# 6278463 */
1787 AND r.delete_mark = 0
1788 AND NVL( l_wip_vr.routing_vers, r.routing_vers) = r.routing_vers
1789 AND r.routing_no = l_wip_vr.routing_no;
1790 
1791 CURSOR c_batchstep IS
1792 SELECT bs.batchstep_no
1793 FROM gme_batch_steps bs
1794 , gmd_operations o
1795 WHERE bs.oprn_id = o.oprn_id
1796 AND o.delete_mark = 0
1797 AND bs.delete_mark = 0
1798 AND NVL( l_wip_vr.oprn_id, o.oprn_id) = o.oprn_id
1799 AND NVL( l_wip_vr.oprn_no, o.oprn_no) = o.oprn_no
1800 AND NVL( l_wip_vr.step_no, bs.batchstep_no) = bs.batchstep_no
1801 AND bs.batchstep_id = l_wip_vr.step_id
1802 AND bs.batch_id = l_wip_vr.batch_id;
1803 
1804 CURSOR c_routingstep IS
1805 SELECT rd.routingstep_no
1806 FROM fm_rout_dtl rd
1807 , gmd_operations o
1808 WHERE rd.oprn_id = o.oprn_id
1809 AND o.delete_mark = 0
1810 AND NVL( l_wip_vr.oprn_id, o.oprn_id) = o.oprn_id
1811 AND NVL( l_wip_vr.oprn_no, o.oprn_no) = o.oprn_no
1812 AND NVL( l_wip_vr.step_no, rd.routingstep_no) = rd.routingstep_no
1813 AND rd.routingstep_id = l_wip_vr.step_id
1814 AND rd.routing_id = l_wip_vr.routing_id;
1815 
1816 
1817 CURSOR c_oprn IS
1818 SELECT oprn_no, oprn_vers
1819 FROM gmd_operations o
1820 WHERE o.delete_mark = 0
1821 AND o.oprn_id = l_wip_vr.oprn_id;
1822 
1823 -- 8901257 start
1824 CURSOR c_recipe_id_no_route IS
1825 SELECT r.recipe_no, r.recipe_version
1826 , ffm.formula_id, ffm.formula_no, ffm.formula_vers
1827 FROM gmd_recipes r
1828 , gmd_status s
1829 , gmd_recipe_validity_rules rvr
1830 , fm_form_mst ffm
1831 , fm_matl_dtl fmd
1832 WHERE ffm.formula_id = r.formula_id
1833 AND rvr.recipe_id = r.recipe_id
1834 AND (NVL( l_wip_vr.organization_id, rvr.organization_id) = rvr.organization_id OR rvr.organization_id IS NULL)
1835 AND r.recipe_status = s.status_code
1836 AND r.formula_id = fmd.formula_id
1837 AND fmd.inventory_item_id = p_spec.inventory_item_id
1838 AND rvr.delete_mark = 0
1839 AND s.delete_mark = 0
1840 AND r.delete_mark = 0
1841 AND ffm.delete_mark = 0
1842 AND s.status_type <> '1000'
1843 AND r.recipe_id = l_wip_vr.recipe_id
1844 AND NVL( l_wip_vr.formula_id, r.formula_id) = r.formula_id;
1845 
1846 CURSOR c_recipe_no_no_route IS
1847 SELECT r.recipe_id, r.recipe_version
1848 FROM gmd_recipes r
1849 , gmd_status s
1850 , gmd_recipe_validity_rules rvr
1851 , fm_form_mst ffm
1852 , fm_matl_dtl fmd
1853 WHERE ffm.formula_id = r.formula_id
1854 AND rvr.recipe_id = r.recipe_id
1855 AND (NVL( l_wip_vr.organization_id, rvr.organization_id) = rvr.organization_id OR rvr.organization_id IS NULL)
1856 AND r.recipe_status = s.status_code
1857 AND r.formula_id = fmd.formula_id
1858 AND fmd.inventory_item_id = p_spec.inventory_item_id
1859 AND rvr.delete_mark = 0
1860 AND s.delete_mark = 0
1861 AND r.delete_mark = 0
1862 AND ffm.delete_mark = 0
1863 AND s.status_type <> '1000'
1864 AND r.recipe_no = l_wip_vr.recipe_no
1865 AND NVL( l_wip_vr.recipe_version, r.recipe_version) = r.recipe_version
1866 AND NVL( l_wip_vr.formula_id, r.formula_id) = r.formula_id;
1867 
1868 -- 8901257 end
1869 
1870 
1871 
1872 
1873 dummy              PLS_INTEGER;
1874 l_status_ctl       VARCHAR2(1);
1875 l_lot_ctl          NUMBER;
1876 
1877 l_recipe_id        GMD_RECIPES.RECIPE_ID%TYPE;
1878 l_recipe_no        GMD_RECIPES.RECIPE_NO%TYPE;
1879 l_recipe_version   GMD_RECIPES.RECIPE_VERSION%TYPE;
1880 l_formula_id       FM_FORM_MST.FORMULA_ID%TYPE;
1881 l_formula_no       FM_FORM_MST.FORMULA_NO%TYPE;
1882 l_formula_vers     FM_FORM_MST.FORMULA_VERS%TYPE;
1883 l_routing_id       GMD_ROUTINGS.ROUTING_ID%TYPE;
1884 l_routing_no       GMD_ROUTINGS.ROUTING_NO%TYPE;
1885 l_routing_vers     GMD_ROUTINGS.ROUTING_VERS%TYPE;
1886 l_step_no          GMD_WIP_SPEC_VRS.STEP_NO%TYPE;
1887 l_oprn_no          GMD_OPERATIONS.OPRN_NO%TYPE;
1888 l_oprn_vers        GMD_OPERATIONS.OPRN_VERS%TYPE;
1889 l_sample_display   GMD_SAMPLES_GRP.sample_display_rec;
1890 
1891 BEGIN
1892   l_wip_vr := p_wip_vr;
1893   l_spec := p_spec;
1894 
1895   -- At least one parameter is required for the WIP VR.
1896   IF (l_wip_vr.batch_id IS NULL AND
1897       l_wip_vr.recipe_id IS NULL AND
1898       l_wip_vr.recipe_no IS NULL AND
1899       l_wip_vr.formula_id IS NULL AND
1900       l_wip_vr.formula_no IS NULL AND
1901       l_wip_vr.routing_id IS NULL AND
1902       l_wip_vr.routing_no IS NULL AND
1903       l_wip_vr.oprn_id IS NULL AND
1904       l_wip_vr.oprn_no IS NULL) THEN
1905     GMD_API_PUB.Log_Message('GMD_WIP_VR_ALL_NULL');
1906     RAISE FND_API.G_EXC_ERROR;
1907   END IF;
1908 
1909   --=========================================================================
1910   -- WHO section :
1911   --=========================================================================
1912   check_who( p_user_id  => l_wip_vr.created_by);
1913   check_who( p_user_id  => l_wip_vr.last_updated_by);
1914   IF (l_wip_vr.creation_date IS NULL
1915    OR l_wip_vr.last_update_date IS NULL)
1916   THEN
1917     GMD_API_PUB.Log_Message('GMD_WRONG_VALUE',
1918                             'WHAT', 'the dates must not be NULL');
1919     RAISE FND_API.G_EXC_ERROR;
1920   END IF;
1921 
1922   --=========================================================================
1923   -- Organization : must be a PLANT and belong to the USER
1924   --=========================================================================
1925   IF (l_wip_vr.organization_id IS NOT NULL)
1926   THEN
1927     -- Check that Owner Organization id exist in ORG_ACCESS_VIEW
1928     OPEN c_orgn_plant( l_wip_vr.organization_id);
1929     FETCH c_orgn_plant INTO dummy;
1930     IF (c_orgn_plant%NOTFOUND)
1931     THEN
1932       CLOSE c_orgn_plant;
1933       GMD_API_PUB.Log_Message('GMD_ORGANIZATION_ID_NOT_FOUND',
1934                               'ORGN_ID', l_wip_vr.organization_id);
1935       RAISE FND_API.G_EXC_ERROR;
1936     END IF;
1937     CLOSE c_orgn_plant;
1938   END IF;
1939 
1940   --srakrish BUG 5251172: Checking if the responsibility is available to the organization.
1941   IF NOT (gmd_api_grp.OrgnAccessible(l_wip_vr.organization_id)) THEN
1942       	  RAISE FND_API.G_EXC_ERROR;
1943   END IF;
1944 
1945   --=========================================================================
1946   -- Get Item Controls
1947   --=========================================================================
1948 
1949   l_sample_display.organization_id := l_wip_vr.organization_id;
1950   l_sample_display.inventory_item_id := l_spec.inventory_item_id;
1951   GMD_SAMPLES_GRP.get_item_values (p_sample_display => l_sample_display);
1952   l_lot_ctl := l_sample_display.lot_control_code;
1953   l_status_ctl := l_sample_display.lot_status_enabled;
1954 
1955   --=========================================================================
1956   -- lot_optional_on_sample :
1957   -- When this field is NOT NULL, all the following fields must be null :
1958   -- sample_inv_trans_ind, control_lot_attrib_ind, in_spec_lot_status, out_of_spec_lot_status
1959   -- and control_batch_step_ind
1960   --=========================================================================
1961   --Enhancement #3476560. added 'delayed_lot_entry' to the call to 'check_vr_controls' procedure
1962   check_VR_Controls( p_VR_type                  => 'WIP'
1963                    , p_lot_optional_on_sample   => l_wip_vr.lot_optional_on_sample
1964 		   , p_delayed_lot_entry        => l_wip_vr.delayed_lot_entry
1965                    , p_sample_inv_trans_ind     => l_wip_vr.sample_inv_trans_ind
1966                    , p_lot_ctl                  => l_lot_ctl
1967                    , p_status_ctl               => l_status_ctl
1968                    , p_control_lot_attrib_ind   => l_wip_vr.control_lot_attrib_ind
1969                    , p_in_spec_lot_status_id       => l_wip_vr.in_spec_lot_status_id
1970                    , p_out_of_spec_lot_status_id   => l_wip_vr.out_of_spec_lot_status_id
1971                    , p_control_batch_step_ind   => l_wip_vr.control_batch_step_ind
1972 		   , p_auto_complete_batch_step => l_wip_vr.auto_complete_batch_step   -- Bug# 5440347
1973 		   , p_delayed_lpn_entry        => l_wip_vr.delayed_lpn_entry);    --RLNAGARA LPN ME 7027149
1974 
1975   --RLNAGARA LPN ME 7027149 start  Check for WMS enabled organization.
1976   IF (l_wip_vr.organization_id IS NOT NULL) THEN
1977     IF NOT check_wms_enabled(l_wip_vr.organization_id) THEN  -- If the Org is not a wms enabled then delayed_lpn_entry should be NULL
1978       IF l_wip_vr.delayed_lpn_entry IS NOT NULL THEN
1979         GMD_API_PUB.Log_Message('GMD_WRONG_VALUE',
1980                                 'WHAT', 'Delayed_LPN_Entry should be NULL for Non-WMS Enabled Organization.');
1981         RAISE FND_API.G_EXC_ERROR;
1982       END IF;
1983     END IF;
1984   END IF;
1985   --RLNAGARA LPN ME 7027149 end
1986 
1987   --=========================================================================
1988   -- spec_vr_status :
1989   --=========================================================================
1990   OPEN c_status(l_wip_vr.spec_vr_status);
1991   FETCH c_status
1992    INTO dummy;
1993   IF (c_status%NOTFOUND)
1994   THEN
1995     CLOSE c_status;
1996     GMD_API_PUB.Log_Message('GMD_SPEC_STATUS_NOT_FOUND',
1997                             'STATUS', l_wip_vr.spec_vr_status);
1998     RAISE FND_API.G_EXC_ERROR;
1999   END IF;
2000   CLOSE c_status;
2001 
2002   --=========================================================================
2003   -- start_date : This field is mandatory
2004   --=========================================================================
2005   IF (l_wip_vr.start_date IS NULL)
2006   THEN
2007       GMD_API_PUB.Log_Message('GMD_SPEC_VR_START_DATE_REQD');
2008       RAISE FND_API.G_EXC_ERROR;
2009   END IF;
2010 
2011   --=========================================================================
2012   -- COA section :
2013   --=========================================================================
2014   check_COA( p_coa_type              => l_wip_vr.coa_type
2015            , p_coa_at_ship_ind       => l_wip_vr.coa_at_ship_ind
2016            , p_coa_at_invoice_ind    => l_wip_vr.coa_at_invoice_ind
2017            , p_coa_req_from_supl_ind => l_wip_vr.coa_req_from_supl_ind);
2018 
2019   --=========================================================================
2020   -- Batch ID is valid
2021   -- When batch_id is NOT NULL, then orgn_code must be MOT NULL
2022   --=========================================================================
2023   IF (l_wip_vr.batch_id IS NOT NULL)
2024   THEN
2025     IF (l_wip_vr.organization_id IS NULL)
2026     THEN
2027       GMD_API_PUB.Log_Message('GMD_WRONG_VALUE',
2028                               'WHAT', 'the organization id must not be NULL');
2029       RAISE FND_API.G_EXC_ERROR;
2030     END IF;
2031 
2032     OPEN c_batch;
2033     FETCH c_batch
2034      INTO l_recipe_id, l_recipe_no, l_recipe_version
2035         , l_formula_id, l_formula_no, l_formula_vers
2036         , l_routing_id, l_routing_no, l_routing_vers;
2037     IF (c_batch%NOTFOUND)
2038     THEN
2039       CLOSE c_batch;
2040       GMD_API_PUB.Log_Message('GMD_BATCH_NOT_FOUND');
2041       RAISE FND_API.G_EXC_ERROR;
2042     END IF;
2043     CLOSE c_batch;
2044 
2045     --=========================================================================
2046     -- Check the entered values with the one retrieved by cursor c_batch :
2047     -- recipe_id, recipe_no, recipe_version
2048     -- formula_id, formula_no, formula_vers
2049     -- routing_id, routing_no, routing_vers
2050     --=========================================================================
2051     -- 1: recipe_id
2052     IF ( NVL(l_wip_vr.recipe_id, l_recipe_id) <> l_recipe_id)
2053     THEN
2054       GMD_API_PUB.Log_Message('GMD_WRONG_VALUE',
2055                               'WHAT', 'Passed recipe_id doesn''t match the batch''s recipe_id.');
2056       RAISE FND_API.G_EXC_ERROR;
2057     END IF;
2058     -- 2: recipe_no
2059     IF ( NVL(l_wip_vr.recipe_no, l_recipe_no) <> l_recipe_no)
2060     THEN
2061       GMD_API_PUB.Log_Message('GMD_WRONG_VALUE',
2062                               'WHAT', 'Passed recipe_no doesn''t match the batch''s recipe_no.');
2063       RAISE FND_API.G_EXC_ERROR;
2064     END IF;
2065     -- 3: recipe_version
2066     IF ( NVL(l_wip_vr.recipe_version, l_recipe_version) <> l_recipe_version)
2067     THEN
2068       GMD_API_PUB.Log_Message('GMD_WRONG_VALUE',
2069                               'WHAT', 'Passed recipe_version doesn''t match the batch''s recipe_version.');
2070       RAISE FND_API.G_EXC_ERROR;
2071     END IF;
2072 
2073     -- 4: formula_id
2074     IF ( NVL(l_wip_vr.formula_id, l_formula_id) <> l_formula_id)
2075     THEN
2076       GMD_API_PUB.Log_Message('GMD_WRONG_VALUE',
2077                               'WHAT', 'Passed formula_id doesn''t match the batch''s formula_id.');
2078       RAISE FND_API.G_EXC_ERROR;
2079     END IF;
2080     -- 5: formula_no
2081     IF ( NVL(l_wip_vr.formula_no,  l_formula_no) <> l_formula_no)
2082     THEN
2083       GMD_API_PUB.Log_Message('GMD_WRONG_VALUE',
2084                               'WHAT', 'Passed formula_no doesn''t match the batch''s formula_no.');
2085       RAISE FND_API.G_EXC_ERROR;
2086     END IF;
2087     -- 6: formula_vers
2088     IF ( NVL(l_wip_vr.formula_vers, l_formula_vers) <> l_formula_vers)
2089     THEN
2090       GMD_API_PUB.Log_Message('GMD_WRONG_VALUE',
2091                               'WHAT', 'Passed formula_vers doesn''t match the batch''s formula_vers.');
2092       RAISE FND_API.G_EXC_ERROR;
2093     END IF;
2094 
2095     -- 7: routing_id
2096     IF ( NVL(l_wip_vr.routing_id, l_routing_id) <> l_routing_id)
2097     THEN
2098       GMD_API_PUB.Log_Message('GMD_WRONG_VALUE',
2099                               'WHAT', 'Passed routing_id doesn''t match the batch''s routing_id.');
2100       RAISE FND_API.G_EXC_ERROR;
2101     END IF;
2102     -- 8: routing_no
2103     IF ( NVL(l_wip_vr.routing_no, l_routing_no) <> l_routing_no)
2104     THEN
2105       GMD_API_PUB.Log_Message('GMD_WRONG_VALUE',
2106                               'WHAT', 'Passed routing_no doesn''t match the batch''s routing_no.');
2107       RAISE FND_API.G_EXC_ERROR;
2108     END IF;
2109     -- 9: routing_vers
2110     IF ( NVL(l_wip_vr.routing_vers, l_routing_vers) <> l_routing_vers)
2111     THEN
2112       GMD_API_PUB.Log_Message('GMD_WRONG_VALUE',
2113                               'WHAT', 'Passed routing_vers doesn''t match the batch''s routing_vers.');
2114       RAISE FND_API.G_EXC_ERROR;
2115     END IF;
2116 
2117     -- At this stage, either l_wip_vr.recipe.... are NULL
2118     --   or they are equal to the local variables. I re-populate the fields (when they are NULL)
2119     l_wip_vr.recipe_id := l_recipe_id;
2120     l_wip_vr.recipe_no := l_recipe_no;
2121     l_wip_vr.recipe_version := l_recipe_version;
2122     l_wip_vr.formula_id := l_formula_id;
2123     l_wip_vr.formula_no := l_formula_no;
2124     l_wip_vr.formula_vers := l_formula_vers;
2125     l_wip_vr.routing_id := l_routing_id;
2126     l_wip_vr.routing_no := l_routing_no;
2127     l_wip_vr.routing_vers := l_routing_vers;
2128   ELSE
2129     -- In this part, batch_id is NULL...
2130 
2131     --=========================================================================
2132     -- Recipe is valid
2133     -- If recipe_id NOT NULL, then recipe_no AND recipe_version populated
2134     --                      And formula and routing (bug 2733426)
2135     -- If recipe_no NOT NULL, and recipe_version NOT NULL, then recipe_id populated
2136     -- If recipe_no NOT NULL, and recipe_version NULL, then nothing else populated
2137     --=========================================================================
2138     IF (l_wip_vr.recipe_id IS NOT NULL)
2139     THEN
2140 
2141     -- 8901257   allow creation of a wip svr even if no routing info is input by using a dfferent cursor
2142       IF l_wip_vr.routing_id IS NOT NULL THEN
2143 
2144 		      OPEN c_recipe_id;
2145 		      FETCH c_recipe_id
2146 		       INTO l_recipe_no, l_recipe_version
2147 		          , l_formula_id, l_formula_no, l_formula_vers
2148 		          , l_routing_id, l_routing_no, l_routing_vers;
2149 		      IF (c_recipe_id%NOTFOUND)
2150 		      THEN
2151 		        CLOSE c_recipe_id;
2152 		        GMD_API_PUB.Log_Message('GMD_RECIPE_NOT_FOUND');
2153 		        RAISE FND_API.G_EXC_ERROR;
2154 		      END IF;
2155 		      CLOSE c_recipe_id;
2156       ELSE
2157           OPEN c_recipe_id_no_route;
2158 		      FETCH c_recipe_id_no_route
2159 		       INTO l_recipe_no, l_recipe_version
2160 		          , l_formula_id, l_formula_no, l_formula_vers;
2161 
2162 		      IF (c_recipe_id_no_route%NOTFOUND)
2163 		      THEN
2164 		        CLOSE c_recipe_id_no_route;
2165 		        GMD_API_PUB.Log_Message('GMD_RECIPE_NOT_FOUND');
2166 		        RAISE FND_API.G_EXC_ERROR;
2167 		      END IF;
2168 		      CLOSE c_recipe_id_no_route;
2169 		      l_routing_id := NULL;   -- 8901257
2170 		      l_routing_no := NULL;   -- 8901257
2171 		      l_routing_vers := NULL;   -- 8901257
2172 
2173       END IF;
2174       -- 4: formula_id
2175       IF ( NVL(l_wip_vr.formula_id, l_formula_id) <> l_formula_id)
2176       THEN
2177         GMD_API_PUB.Log_Message('GMD_WRONG_VALUE',
2178                                 'WHAT', 'Passed formula_id doesn''t match the batch''s formula_id.');
2179         RAISE FND_API.G_EXC_ERROR;
2180       END IF;
2181       -- 5: formula_no
2182       IF ( NVL(l_wip_vr.formula_no,  l_formula_no) <> l_formula_no)
2183       THEN
2184         GMD_API_PUB.Log_Message('GMD_WRONG_VALUE',
2185                                 'WHAT', 'Passed formula_no doesn''t match the batch''s formula_no.');
2186         RAISE FND_API.G_EXC_ERROR;
2187       END IF;
2188       -- 6: formula_vers
2189       IF ( NVL(l_wip_vr.formula_vers, l_formula_vers) <> l_formula_vers)
2190       THEN
2191         GMD_API_PUB.Log_Message('GMD_WRONG_VALUE',
2192                                 'WHAT', 'Passed formula_vers doesn''t match the batch''s formula_vers.');
2193         RAISE FND_API.G_EXC_ERROR;
2194       END IF;
2195 
2196       -- 7: routing_id
2197       IF ( NVL(l_wip_vr.routing_id, l_routing_id) <> l_routing_id)
2198       THEN
2199         GMD_API_PUB.Log_Message('GMD_WRONG_VALUE',
2200                                 'WHAT', 'Passed routing_id doesn''t match the batch''s routing_id.');
2201         RAISE FND_API.G_EXC_ERROR;
2202       END IF;
2203       -- 8: routing_no
2204       IF ( NVL(l_wip_vr.routing_no, l_routing_no) <> l_routing_no)
2205       THEN
2206         GMD_API_PUB.Log_Message('GMD_WRONG_VALUE',
2207                                 'WHAT', 'Passed routing_no doesn''t match the batch''s routing_no.');
2208         RAISE FND_API.G_EXC_ERROR;
2209       END IF;
2210       -- 9: routing_vers
2211       IF ( NVL(l_wip_vr.routing_vers, l_routing_vers) <> l_routing_vers)
2212       THEN
2213         GMD_API_PUB.Log_Message('GMD_WRONG_VALUE',
2214                                 'WHAT', 'Passed routing_vers doesn''t match the batch''s routing_vers.');
2215         RAISE FND_API.G_EXC_ERROR;
2216       END IF;
2217 
2218       -- At this stage, either l_wip_vr.formula/routing.... are NULL
2219       --   or they are equal to the local variables.
2220       -- Populated the defaults, ignoring the passed values :
2221       l_wip_vr.recipe_no := l_recipe_no;
2222       l_wip_vr.recipe_version := l_recipe_version;
2223       l_wip_vr.formula_id := l_formula_id;
2224       l_wip_vr.formula_no := l_formula_no;
2225       l_wip_vr.formula_vers := l_formula_vers;
2226       l_wip_vr.routing_id := l_routing_id;
2227       l_wip_vr.routing_no := l_routing_no;
2228       l_wip_vr.routing_vers := l_routing_vers;
2229 
2230     ELSIF (l_wip_vr.recipe_no IS NOT NULL)
2231     THEN
2232       -- 8901257  allow creation of a wip svr even if no routing info is input by using a dfferent cursor
2233       IF l_wip_vr.routing_id IS NOT NULL THEN
2234 
2235 			      OPEN c_recipe_no;
2236 			      FETCH c_recipe_no
2237 			       INTO l_recipe_id, l_recipe_version;
2238 			      IF (c_recipe_no%NOTFOUND)
2239 			      THEN
2240 			        CLOSE c_recipe_no;
2241 			        GMD_API_PUB.Log_Message('GMD_RECIPE_NOT_FOUND');
2242 			        RAISE FND_API.G_EXC_ERROR;
2243 			      END IF;
2244 			      CLOSE c_recipe_no;
2245 
2246 			ELSE
2247 			    OPEN c_recipe_no_no_route;
2248 		      FETCH c_recipe_no_no_route
2249 		       INTO l_recipe_no, l_recipe_version;
2250 
2251 		      IF (c_recipe_no_no_route%NOTFOUND)
2252 		      THEN
2253 		        CLOSE c_recipe_no_no_route;
2254 		        GMD_API_PUB.Log_Message('GMD_RECIPE_NOT_FOUND');
2255 		        RAISE FND_API.G_EXC_ERROR;
2256 		      END IF;
2257 		      CLOSE c_recipe_no_no_route;
2258 
2259 			END IF; --  IF l_wip_vr.routing_id IS NOT NULL THEN
2260 
2261       -- Populated the defaults :
2262       IF (l_wip_vr.recipe_version IS NOT NULL)
2263       THEN
2264           -- In that case : recipe_no, and recipe_version were given,
2265           -- So, I populate recipe_id
2266           l_wip_vr.recipe_id := l_recipe_id;
2267       END IF;
2268     END IF;
2269 
2270     --=========================================================================
2271     -- Formula is valid
2272     -- If formula_id NOT NULL, then formula_no AND formula_vers populated
2273     -- If formula_no NOT NULL, and formula_vers NOT NULL, then formula_id populated
2274     -- If formula_no NOT NULL, and formula_vers NULL, then nothing else populated
2275     --=========================================================================
2276     IF (l_wip_vr.formula_id IS NOT NULL)
2277     THEN
2278       OPEN c_formula_id;
2279       FETCH c_formula_id
2280        INTO l_formula_no, l_formula_vers;
2281 
2282       IF (c_formula_id%NOTFOUND)
2283       THEN
2284         CLOSE c_formula_id;
2285         GMD_API_PUB.Log_Message('GMD_FORMULA_NOT_FOUND');
2286         RAISE FND_API.G_EXC_ERROR;
2287       END IF;
2288       CLOSE c_formula_id;
2289 
2290       -- Populated the defaults, ignoring the passed values :
2291       l_wip_vr.formula_no := l_formula_no;
2292       l_wip_vr.formula_vers := l_formula_vers;
2293 
2294     ELSIF (l_wip_vr.formula_no IS NOT NULL)
2295     THEN
2296 
2297       OPEN c_formula_no;
2298       FETCH c_formula_no
2299        INTO l_formula_id, l_formula_vers;
2300 
2301       IF (c_formula_no%NOTFOUND)
2302       THEN
2303         CLOSE c_formula_no;
2304         GMD_API_PUB.Log_Message('GMD_FORMULA_NOT_FOUND');
2305         RAISE FND_API.G_EXC_ERROR;
2306       END IF;
2307       CLOSE c_formula_no;
2308 
2309       -- Populated the defaults :
2310       IF (l_wip_vr.formula_vers IS NOT NULL)
2311       THEN
2312           -- In that case : formula_no, and formula_vers were given,
2313           -- So, I populate formula_id
2314           l_wip_vr.formula_id := l_formula_id;
2315       END IF;
2316     END IF;
2317 
2318     --=========================================================================
2319     -- Routing is valid
2320     -- If routing_id NOT NULL, then routing_no AND routing_version populated
2321     -- If routing_no NOT NULL, and routing_vers NOT NULL, then routing_id populated
2322     -- If routing_no NOT NULL, and routing_vers NULL, then nothing else populated
2323     --=========================================================================
2324     IF (l_wip_vr.routing_id IS NOT NULL)
2325     THEN
2326       OPEN c_routing_id;
2327       FETCH c_routing_id
2328        INTO l_routing_no, l_routing_vers;
2329 
2330       IF (c_routing_id%NOTFOUND)
2331       THEN
2332         CLOSE c_routing_id;
2333         GMD_API_PUB.Log_Message('GMD_ROUTING_NOT_FOUND');
2334         RAISE FND_API.G_EXC_ERROR;
2335       END IF;
2336       CLOSE c_routing_id;
2337 
2338       -- Populated the defaults, ignoring the passed values :
2339       l_wip_vr.routing_no := l_routing_no;
2340       l_wip_vr.routing_vers := l_routing_vers;
2341 
2342     ELSIF (l_wip_vr.routing_no IS NOT NULL)
2343     THEN
2344 
2345       OPEN c_routing_no;
2346       FETCH c_routing_no
2347        INTO l_routing_id, l_routing_vers;
2348       IF (c_routing_no%NOTFOUND)
2349       THEN
2350         CLOSE c_routing_no;
2351         GMD_API_PUB.Log_Message('GMD_ROUTING_NOT_FOUND');
2352         RAISE FND_API.G_EXC_ERROR;
2353       END IF;
2354       CLOSE c_routing_no;
2355 
2356       -- Populated the defaults :
2357       IF (l_wip_vr.routing_vers IS NOT NULL)
2358       THEN
2359           -- In that case : routing_no, and routing_vers were given,
2360           -- So, I populate routing_id
2361           l_wip_vr.routing_id := l_routing_id;
2362       END IF;
2363     END IF;
2364   END IF;     -- batch_id NULL
2365 
2366   --=========================================================================
2367   -- Formula Line is valid
2368   -- If formulaline_id is NOT NULL, then formula_id must be NOT NULL
2369   --=========================================================================
2370   IF (l_wip_vr.formulaline_id IS NOT NULL)
2371    AND (l_wip_vr.material_detail_id IS NULL)
2372   THEN
2373     IF (l_wip_vr.formula_id IS NULL)
2374     THEN
2375       GMD_API_PUB.Log_Message('GMD_WRONG_VALUE',
2376                               'WHAT', 'Formula id must be NOT NULL');
2377       RAISE FND_API.G_EXC_ERROR;
2378     END IF;
2379 
2380     OPEN c_formulaline_id;
2381     FETCH c_formulaline_id
2382      INTO dummy;
2383     IF (c_formulaline_id%NOTFOUND)
2384     THEN
2385       CLOSE c_formulaline_id;
2386       GMD_API_PUB.Log_Message('GMD_FORMULA_LINE_NOT_FOUND');
2387       RAISE FND_API.G_EXC_ERROR;
2388     END IF;
2389     CLOSE c_formulaline_id;
2390   END IF;
2391 
2392 
2393   --=========================================================================
2394   -- Batch Line (material detail id) is valid
2395   -- If material_detail_id is NOT NULL, then batch_id must be NOT NULL
2396   --=========================================================================
2397   IF (l_wip_vr.material_detail_id IS NOT NULL)
2398   THEN
2399     IF (l_wip_vr.batch_id IS NULL)
2400     THEN
2401       GMD_API_PUB.Log_Message('GMD_WRONG_VALUE',
2402                               'WHAT', 'Batch id must be NOT NULL');
2403       RAISE FND_API.G_EXC_ERROR;
2404     END IF;
2405 
2406     OPEN c_material_detail_id;
2407     FETCH c_material_detail_id
2408      INTO dummy;
2409     IF (c_material_detail_id%NOTFOUND)
2410     THEN
2411       CLOSE c_material_detail_id;
2412       GMD_API_PUB.Log_Message('GMD_MATERIAL_DTL_NOT_FOUND');
2413       RAISE FND_API.G_EXC_ERROR;
2414     END IF;
2415     CLOSE c_material_detail_id;
2416   END IF;
2417 
2418 
2419   --=========================================================================
2420   -- Step is valid
2421   -- A step can be either a batch step or a routing step
2422   -- If step_no NULL and step_id NOT NULL, then populate step_no
2423   -- If step_no NOT NULL and step_id NULL, then error.
2424   --=========================================================================
2425   IF (l_wip_vr.step_id IS NULL AND l_wip_vr.step_no IS NOT NULL)
2426   THEN
2427       GMD_API_PUB.Log_Message('GMD_WRONG_VALUE',
2428                               'WHAT', 'Step id must be populated');
2429       RAISE FND_API.G_EXC_ERROR;
2430   END IF;
2431 
2432   IF (l_wip_vr.batch_id IS NOT NULL AND l_wip_vr.step_id IS NOT NULL)
2433   THEN
2434     -- Step No is from Batch
2435     OPEN c_batchstep;
2436     FETCH c_batchstep
2437      INTO l_step_no;
2438     IF (c_batchstep%NOTFOUND)
2439     THEN
2440       CLOSE c_batchstep;
2441       GMD_API_PUB.Log_Message('GMD_BATCH_STEP_NOT_FOUND');
2442       RAISE FND_API.G_EXC_ERROR;
2443     END IF;
2444     CLOSE c_batchstep;
2445 
2446     -- Populated the defaults, ignoring the passed values :
2447     l_wip_vr.step_no := l_step_no;
2448 
2449   ELSIF (l_wip_vr.routing_id IS NOT NULL AND l_wip_vr.step_id IS NOT NULL)
2450   THEN
2451     -- Step No is from Routing
2452     OPEN c_routingstep;
2453     FETCH c_routingstep
2454      INTO l_step_no;
2455     IF (c_routingstep%NOTFOUND)
2456     THEN
2457       CLOSE c_routingstep;
2458       GMD_API_PUB.Log_Message('GMD_ROUTING_STEP_NOT_FOUND');
2459       RAISE FND_API.G_EXC_ERROR;
2460     END IF;
2461     CLOSE c_routingstep;
2462 
2463     -- Populated the defaults, ignoring the passed values :
2464     l_wip_vr.step_no := l_step_no;
2465 
2466   END IF;
2467 
2468   -- Operation is valid (check only if step is not specified, because
2469   --                     otherwise it will default from the step chosen.)
2470   IF (l_wip_vr.step_id IS NULL AND l_wip_vr.oprn_id IS NOT NULL)
2471   THEN
2472     OPEN c_oprn;
2473     FETCH c_oprn
2474      INTO l_oprn_no, l_oprn_vers;
2475     IF (c_oprn%NOTFOUND)
2476     THEN
2477       CLOSE c_oprn;
2478       GMD_API_PUB.Log_Message('GMD_BATCH_STEP_NOT_FOUND');
2479       RAISE FND_API.G_EXC_ERROR;
2480     END IF;
2481     CLOSE c_oprn;
2482 
2483     -- Populated the defaults, ignoring the passed values :
2484     l_wip_vr.oprn_no   := l_oprn_no;
2485     l_wip_vr.oprn_vers := l_oprn_vers;
2486 
2487   END IF;
2488 
2489 
2490   -- All Systems Go...
2491   x_wip_vr := l_wip_vr;
2492 
2493 EXCEPTION
2494   WHEN FND_API.G_EXC_ERROR THEN
2495     x_return_status := FND_API.G_RET_STS_ERROR ;
2496   WHEN FND_API.G_EXC_UNEXPECTED_ERROR THEN
2497     x_return_status := FND_API.G_RET_STS_UNEXP_ERROR ;
2498   WHEN OTHERS THEN
2499     x_return_status := FND_API.G_RET_STS_UNEXP_ERROR ;
2500 
2501 END check_for_null_and_fks_in_wvr;
2502 
2503 
2504 
2505 
2506 --Start of comments
2507 --+========================================================================+
2508 --| API Name    : wip_vr_exist                                             |
2509 --| TYPE        : Group                                                    |
2510 --| Notes       : This function returns TRUE if the WIP VR already         |
2511 --|               exists for the spcified parameter in the database, FALSE |
2512 --|               otherwise.                                               |
2513 --|                                                                        |
2514 --| HISTORY                                                                |
2515 --|    Chetan Nagar	26-Jul-2002	Created.                           |
2516 --|    Olivier Daboval  17-OCT-2002     bug 2630007, added spec_name in    |
2517 --|                                     the VR_EXIST message               |
2518 --|    Olivier Daboval  14-NOV-2002     Added NVL(spec_vr_id, -1) because  |
2519 --|                                     the API passes a NULL spec_vr_id   |
2520 --|                                     in insert mode.                    |
2521 --|    Brenda Stone     20-NOV-2003     Bug 3090290; allow duplicate spec vr
2522 --|                                     with "OBSOLUTE" status             |
2523 --|                                     Bug 2984784; add Version to msg for|
2524 --|                                     existing spec vr.                  |
2525 --|                                                                        |
2526 --|  Saikiran          12-Apr-2005      Convergence Changes                |
2527 --|  Feinstein         18-Oct-2005      Added material detail id to samples|
2528 --|  Plowe						 04-Apr-2006      Bug 5117733 - added item revision to match
2529 --+========================================================================+
2530 -- End of comments
2531 
2532 FUNCTION wip_vr_exist(p_wip_vr GMD_WIP_SPEC_VRS%ROWTYPE,
2533                       p_spec   GMD_SPECIFICATIONS%ROWTYPE)
2534 RETURN BOOLEAN IS
2535 
2536     -- added material detail to cursor
2537   CURSOR c_wip_vr IS
2538   SELECT vr.spec_vr_id, s.spec_name, s.spec_vers
2539   FROM   gmd_specifications_b s,
2540          gmd_wip_spec_vrs vr
2541   WHERE  s.spec_id = vr.spec_id
2542   AND    s.owner_organization_id = p_spec.owner_organization_id
2543   AND    s.inventory_item_id = p_spec.inventory_item_id
2544   AND   ( (s.revision is null and p_spec.revision is NULL ) OR -- handle item revision 5117733
2545           (s.revision  = p_spec.revision )
2546   			 )
2547   AND    ((s.grade_code is NULL AND p_spec.grade_code is NULL) OR
2548           (s.grade_code = p_spec.grade_code)
2549          )
2550   AND    ((vr.organization_id is NULL AND p_wip_vr.organization_id is NULL) OR
2551           (vr.organization_id = p_wip_vr.organization_id)
2552          )
2553   AND    ((vr.batch_id is NULL AND p_wip_vr.batch_id is NULL) OR
2554           (vr.batch_id = p_wip_vr.batch_id)
2555          )
2556   AND    ((vr.recipe_id is NULL AND p_wip_vr.recipe_id is NULL) OR
2557           (vr.recipe_id = p_wip_vr.recipe_id)
2558          )
2559   AND    ((vr.recipe_no is NULL AND p_wip_vr.recipe_no is NULL) OR
2560           (vr.recipe_no = p_wip_vr.recipe_no)
2561          )
2562   AND    ((vr.formula_id is NULL AND p_wip_vr.formula_id is NULL) OR
2563           (vr.formula_id = p_wip_vr.formula_id)
2564          )
2565   AND    ((vr.formula_no is NULL AND p_wip_vr.formula_no is NULL) OR
2566           (vr.formula_no = p_wip_vr.formula_no)
2567          )
2568   AND    ((vr.formulaline_id is NULL AND p_wip_vr.formulaline_id is NULL) OR
2569           (vr.formulaline_id = p_wip_vr.formulaline_id) OR
2570           (vr.batch_id IS NOT NULL)                          -- added for new Material detail field
2571          )
2572   AND    ((vr.material_detail_id is NULL AND p_wip_vr.material_detail_id is NULL) OR
2573           (vr.material_detail_id = p_wip_vr.material_detail_id)
2574          )
2575   AND    ((vr.routing_id is NULL AND p_wip_vr.routing_id is NULL) OR
2576           (vr.routing_id = p_wip_vr.routing_id)
2577          )
2578   AND    ((vr.routing_no is NULL AND p_wip_vr.routing_no is NULL) OR
2579           (vr.routing_no = p_wip_vr.routing_no)
2580          )
2581   AND    ((vr.step_id is NULL AND p_wip_vr.step_id is NULL) OR
2582           (vr.step_id = p_wip_vr.step_id)
2583          )
2584   AND    ((vr.oprn_id is NULL AND p_wip_vr.oprn_id is NULL) OR
2585           (vr.oprn_id = p_wip_vr.oprn_id)
2586          )
2587   AND    ((vr.oprn_no is NULL AND p_wip_vr.oprn_no is NULL) OR
2588           (vr.oprn_no = p_wip_vr.oprn_no)
2589          )
2590   AND    ((vr.charge is NULL AND p_wip_vr.charge is NULL) OR
2591           (vr.charge = p_wip_vr.charge)
2592          )
2593   AND    ((vr.end_date is NULL AND (p_wip_vr.end_date IS NULL OR
2594                                     p_wip_vr.end_date >= vr.start_date)) OR
2595 	  (p_wip_vr.end_date IS NULL AND
2596 	     p_wip_vr.start_date <= nvl(vr.end_date, p_wip_vr.start_date)) OR
2597           (p_wip_vr.start_date <= vr.end_date AND p_wip_vr.end_date >= vr.start_date)
2598          )
2599   AND  (floor(vr.spec_vr_status/100) = floor(p_wip_vr.spec_vr_status/100)  AND
2600 /*      Bug 3090290; allow duplicate spec vr with "OBSOLUTE" status   */
2601         p_wip_vr.spec_vr_status <> 1000 )
2602 
2603 /* Bug 3090290 - Here's the problem - Both spec vr's have the same status 1000  */
2604 /* obsolete                                                                     */
2605   AND    vr.spec_vr_status NOT IN (SELECT status_code FROM gmd_qc_status
2606                                    WHERE status_type = 800)
2607   AND    vr.delete_mark = 0
2608   AND    s.delete_mark = 0
2609   AND    vr.spec_vr_id <> NVL(p_wip_vr.spec_vr_id, -1)
2610   ;
2611 
2612   dummy    PLS_INTEGER;
2613   specname VARCHAR2(80);
2614   specvers NUMBER;
2615 
2616 BEGIN
2617 
2618   OPEN c_wip_vr;
2619   FETCH c_wip_vr INTO dummy, specname, specvers;
2620   IF c_wip_vr%FOUND THEN
2621     CLOSE c_wip_vr;
2622     FND_MESSAGE.SET_NAME('GMD', 'GMD_WIP_VR_EXIST');
2623     FND_MESSAGE.SET_TOKEN('spec', specname);
2624     FND_MESSAGE.SET_TOKEN('vers', specvers);
2625     FND_MSG_PUB.ADD;
2626     RETURN TRUE;
2627   ELSE
2628     CLOSE c_wip_vr;
2629     RETURN FALSE;
2630   END IF;
2631 
2632 EXCEPTION
2633   -- Though there is no reason the program can reach
2634   -- here, this is coded just for the reasons we can
2635   -- not think of!
2636   WHEN OTHERS THEN
2637     FND_MESSAGE.SET_NAME('GMD', 'GMD_API_ERROR');
2638     FND_MESSAGE.SET_TOKEN('PACKAGE', 'GMD_SPEC_VRS_GRP.WIP_VR_EXIST' );
2639     FND_MESSAGE.SET_TOKEN('ERROR', SUBSTR(SQLERRM,1,200));
2640     RETURN TRUE;
2641 
2642 END wip_vr_exist;
2643 
2644 
2645 
2646 --Start of comments
2647 --+========================================================================+
2648 --| API Name    : validate_cust_vr                                         |
2649 --| TYPE        : Group                                                    |
2650 --| Notes       : This procedure validates all the fields of               |
2651 --|               Customer  validity rule record. This procedure can be    |
2652 --|               called from FORM or API and the caller need              |
2653 --|               to specify this in p_called_from parameter               |
2654 --|               while calling this procedure. Based on where             |
2655 --|               it is called from certain validations will               |
2656 --|               either be performed or skipped.                          |
2657 --|                                                                        |
2658 --|               If everything is fine then OUT parameter                 |
2659 --|               x_return_status is set to 'S' else appropriate           |
2660 --|               error message is put on the stack and error              |
2661 --|               is returned.                                             |
2662 --|                                                                        |
2663 --| HISTORY                                                                |
2664 --|    Chetan Nagar	26-Jul-2002	Created.                           |
2665 --|                                                                        |
2666 --+========================================================================+
2667 -- End of comments
2668 
2669 PROCEDURE validate_cust_vr
2670 (
2671   p_cust_vr       IN  GMD_CUSTOMER_SPEC_VRS%ROWTYPE
2672 , p_called_from   IN  VARCHAR2
2673 , p_operation     IN  VARCHAR2
2674 , x_return_status OUT NOCOPY VARCHAR2
2675 ) IS
2676 
2677   -- Local Variables
2678   dummy                          NUMBER;
2679   l_return_status                VARCHAR2(1);
2680 
2681   l_spec                         GMD_SPECIFICATIONS%ROWTYPE;
2682   l_spec_out                     GMD_SPECIFICATIONS%ROWTYPE;
2683   l_item_mst                     MTL_SYSTEM_ITEMS_B%ROWTYPE;
2684   l_sampling_plan                GMD_SAMPLING_PLANS%ROWTYPE;
2685   l_sampling_plan_out            GMD_SAMPLING_PLANS%ROWTYPE;
2686   l_inventory_item_id            NUMBER;
2687   l_organization_id              NUMBER;
2688   l_uom_rate                     NUMBER;
2689 
2690   -- Exceptions
2691   e_spec_fetch_error             EXCEPTION;
2692   e_smpl_plan_fetch_error        EXCEPTION;
2693   e_error_fetch_item             EXCEPTION;
2694 
2695 BEGIN
2696   --  Initialize API return status to success
2697   x_return_status := FND_API.G_RET_STS_SUCCESS;
2698 
2699   IF NOT (p_operation in ('INSERT', 'UPDATE', 'DELETE')) THEN
2700     -- Invalid Operation
2701     GMD_API_PUB.Log_Message('GMD_INVALID_OPERATION');
2702     RAISE FND_API.G_EXC_ERROR;
2703   END IF;
2704 
2705   -- Verify that the specification exists.
2706   l_spec.spec_id := p_cust_vr.spec_id;
2707   IF NOT (GMD_Specifications_PVT.Fetch_Row(
2708                            p_specifications => l_spec,
2709                            x_specifications => l_spec_out)
2710           ) THEN
2711     -- Fetch Error
2712     GMD_API_PUB.Log_Message('GMD_SPEC_FETCH_ERROR');
2713     RAISE e_spec_fetch_error;
2714   END IF;
2715 
2716   l_spec := l_spec_out ;
2717 
2718   -- Verify that the Sampling Plan exists.
2719   --odab added this test.
2720   IF (p_cust_vr.sampling_plan_id IS NOT NULL)
2721   THEN
2722     l_sampling_plan.sampling_plan_id := p_cust_vr.sampling_plan_id;
2723     IF NOT (GMD_Sampling_Plans_PVT.Fetch_Row(
2724                            p_sampling_plan => l_sampling_plan,
2725                            x_sampling_plan => l_sampling_plan_out)
2726           ) THEN
2727       -- Fetch Error
2728       GMD_API_PUB.Log_Message('GMD_SAMPLING_PLAN_FETCH_ERROR');
2729       RAISE e_smpl_plan_fetch_error;
2730     END IF;
2731     l_sampling_plan := l_sampling_plan_out;
2732   END IF;
2733 
2734   IF (p_called_from = 'API') THEN
2735     -- Check for NULLs and Valid Foreign Keys in the input parameter
2736     GMD_SPEC_VRS_GRP.check_for_null_and_fks_in_cvr
2737       (
2738         p_cust_vr       => p_cust_vr
2739       , p_spec          => l_spec
2740       , x_return_status => l_return_status
2741       );
2742     -- No need if called from FORM since it is already
2743     -- done in the form
2744 
2745     IF l_return_status = FND_API.G_RET_STS_ERROR THEN
2746       -- Message is alrady logged by check_for_null procedure
2747       RAISE FND_API.G_EXC_ERROR;
2748     ELSIF l_return_status = FND_API.G_RET_STS_UNEXP_ERROR THEN
2749       -- Message is alrady logged by check_for_null procedure
2750       RAISE FND_API.G_EXC_UNEXPECTED_ERROR;
2751     END IF;
2752   END IF;
2753 
2754   -- First Verify that the SAME VR does not exists
2755   IF (p_operation IN ('INSERT', 'UPDATE')
2756     AND cust_vr_exist(p_cust_vr, l_spec))
2757   THEN
2758     -- Disaster, Trying to insert duplicate
2759     -- bug 2630007, odaboval put the message in function cust_vr_exist.
2760     -- GMD_API_PUB.Log_Message('GMD_CUST_VR_EXIST');
2761     RAISE FND_API.G_EXC_ERROR;
2762   END IF;
2763 
2764   -- Sample Quantity UOM must be convertible to Item's UOM
2765   BEGIN
2766     SELECT inventory_item_id INTO l_inventory_item_id FROM
2767     gmd_specifications WHERE spec_id = p_cust_vr.spec_id;
2768     SELECT owner_organization_id INTO l_organization_id FROM
2769     gmd_specifications WHERE spec_id = p_cust_vr.spec_id;
2770     SELECT * INTO l_item_mst
2771     FROM mtl_system_items_b
2772     WHERE inventory_item_id = l_inventory_item_id
2773     AND organization_id = l_organization_id;
2774   EXCEPTION
2775   WHEN OTHERS THEN
2776     GMD_API_PUB.Log_Message('GMD_ITEM_FETCH_ERROR');
2777     RAISE e_error_fetch_item;
2778   END;
2779 
2780   --odab added this test.
2781   IF (p_cust_vr.sampling_plan_id IS NOT NULL)
2782   THEN
2783     inv_convert.inv_um_conversion (
2784       from_unit  => l_sampling_plan.sample_qty_uom,
2785       to_unit    =>  l_item_mst.primary_uom_code,
2786       item_id    =>  l_inventory_item_id,
2787       lot_number => NULL,
2788       organization_id => l_organization_id  ,
2789       uom_rate   => l_uom_rate );
2790 
2791     IF l_uom_rate = -99999 THEN
2792       GMD_API_PUB.Log_Message('GMD_UOM_CONVERSION_ERROR');
2793       RAISE FND_API.G_EXC_ERROR;
2794     END IF;
2795   END IF;
2796 
2797   -- No need to check the return status because above procedure
2798   -- logs appropriate message on the stack and raises an exception.
2799 
2800   -- The Start Date must be less than the End Date
2801   If ( p_cust_vr.end_date IS NOT NULL AND
2802        p_cust_vr.start_date > p_cust_vr.end_date) THEN
2803     GMD_API_PUB.Log_Message('GMD_SPEC_VR_EFF_DATE_ERROR');
2804     RAISE FND_API.G_EXC_ERROR;
2805   END IF;
2806 
2807   -- Spec VR Status Must be less than Spec Status upto Appoved Stages
2808   IF (floor(l_spec.spec_status/100) <= 7 AND
2809       floor(p_cust_vr.spec_vr_status/100) <= 7 AND
2810       p_cust_vr.spec_vr_status > l_spec.spec_status) THEN
2811     GMD_API_PUB.Log_Message('GMD_SPEC_VR_STATUS_HIGHER');
2812     RAISE FND_API.G_EXC_ERROR;
2813   END IF;
2814 
2815   -- All systems GO...
2816 
2817 EXCEPTION
2818   WHEN FND_API.G_EXC_ERROR     OR
2819        e_spec_fetch_error      OR
2820        e_smpl_plan_fetch_error OR
2821        e_error_fetch_item
2822   THEN
2823     x_return_status := FND_API.G_RET_STS_ERROR ;
2824   WHEN FND_API.G_EXC_UNEXPECTED_ERROR THEN
2825     x_return_status := FND_API.G_RET_STS_UNEXP_ERROR ;
2826   WHEN OTHERS THEN
2827     x_return_status := FND_API.G_RET_STS_UNEXP_ERROR ;
2828 
2829 
2830 END validate_cust_vr;
2831 
2832 
2833 
2834 
2835 --Start of comments
2836 --+========================================================================+
2837 --| API Name    : check_for_null_and_fks_in_cvr                            |
2838 --| TYPE        : Group                                                    |
2839 --| Notes       : This procedure checks for NULL and Foreign Key           |
2840 --|               constraints for the required filed in the Spec           |
2841 --|               Customer  VR record.                                     |
2842 --|                                                                        |
2843 --|               If everything is fine then 'S' is returned in the        |
2844 --|               parameter - x_return_status otherwise error message      |
2845 --|               is logged and error status - E or U returned             |
2846 --|                                                                        |
2847 --| HISTORY                                                                |
2848 --|    Chetan Nagar	26-Jul-2002	Created.                           |
2849 --|                                                                        |
2850 --|    SaiKiran		04-MAY-2004	Enhancement #3476560. added        |
2851 --|                  'delayed_lot_entry' to the call to 'check_vr_controls'|
2852 --|                   procedure.                                           |
2853 --|                                                                        |
2854 --|    Saikiran        11-Apr-2005      Convergence Changes                |
2855 --|  PLOWE             07-JUN-2006    -- bug 5223014 rework                |
2856 --|  replace cursor with function  as check was not working as designed    |
2857 --|  bug 5223014 rework in proc check_for_null_and_fks_in_cvr              |
2858 --|========================================================================+
2859 -- End of comments
2860 
2861 PROCEDURE check_for_null_and_fks_in_cvr
2862 (
2863   p_cust_vr       IN  gmd_customer_spec_vrs%ROWTYPE
2864 , p_spec          IN  gmd_specifications%ROWTYPE
2865 , x_return_status OUT NOCOPY VARCHAR2
2866 )
2867 IS
2868 
2869 CURSOR c_cust IS
2870 SELECT 1
2871 FROM hr_operating_units ou
2872    , hz_cust_acct_sites_all casa
2873    , hz_cust_site_uses_all csua
2874    , hz_parties hzp
2875    , hz_cust_accounts_all hzca
2876 WHERE ou.organization_id = csua.org_id
2877   AND casa.cust_acct_site_id = csua.cust_acct_site_id
2878   AND casa.cust_account_id = hzca.cust_account_id
2879   AND casa.org_id = csua.org_id
2880   AND hzp.party_id = hzca.party_id
2881   AND NVL( p_cust_vr.org_id, csua.org_id) = csua.org_id
2882   AND hzca.cust_account_id = p_cust_vr.cust_id;
2883 
2884 -- bug 4924483 sql id 14687576 (MJC)  don't use view
2885 CURSOR c_org IS
2886 /*SELECT 1
2887 FROM hr_operating_units
2888 WHERE organization_id = p_cust_vr.org_id; */
2889 -- bug 5223014 sql id 17532992 (MJC)  don't need 2nd HR_ORGANIZATION_INFORMATION O3 for identification
2890 -- (takes out MJC)
2891 SELECT 1
2892 FROM HR_ALL_ORGANIZATION_UNITS O,
2893 HR_ORGANIZATION_INFORMATION O2
2894 --HR_ORGANIZATION_INFORMATION O3
2895 WHERE o.organization_id = p_cust_vr.org_id
2896 and O2.ORGANIZATION_ID = o.organization_id
2897 AND O2.ORG_INFORMATION_CONTEXT||'' = 'CLASS'
2898 AND O2.ORG_INFORMATION1 = 'OPERATING_UNIT'
2899 AND O2.ORG_INFORMATION2 = 'Y';
2900 --and O3.ORGANIZATION_ID = O2.ORGANIZATION_ID
2901 --AND O3.ORG_INFORMATION_CONTEXT = 'Operating Unit Information';
2902 
2903 
2904 CURSOR c_orgn_check ( p_organization_id NUMBER) IS
2905   SELECT 1
2906   FROM GMD_ORG_ACCESS_VW;
2907 
2908 CURSOR c_ship_to IS
2909 SELECT 1
2910 FROM hz_cust_acct_sites_all casa
2911    , hz_cust_site_uses_all csua
2912    , hz_cust_accounts_all caa
2913 WHERE casa.cust_acct_site_id = csua.cust_acct_site_id
2914   AND casa.org_id = csua.org_id
2915   AND casa.cust_account_id = caa.cust_account_id
2916   AND csua.site_use_code = 'SHIP_TO'
2917   AND NVL( p_cust_vr.org_id, csua.org_id) = csua.org_id
2918   AND caa.cust_account_id = p_cust_vr.cust_id
2919   AND csua.site_use_id = p_cust_vr.ship_to_site_id;
2920 
2921 CURSOR c_order IS
2922 SELECT 1
2923 FROM oe_order_headers_all oha
2924    , oe_order_lines_all oola
2925    , oe_transaction_types_tl ttt
2926 WHERE oola.header_id = oha.header_id
2927   AND oola.inventory_item_id = p_spec.inventory_item_id
2928   AND oha.order_type_id = ttt.transaction_type_id
2929   AND NVL( p_cust_vr.ship_to_site_id, oola.ship_to_org_id) = oola.ship_to_org_id
2930   AND NVL( p_cust_vr.org_id, oha.org_id) = oha.org_id
2931   AND NVL( p_cust_vr.cust_id, oha.sold_to_org_id) = oha.sold_to_org_id
2932   AND oha.header_id = p_cust_vr.order_id
2933   AND oha.cancelled_flag <> 'Y'
2934   AND ttt.language = USERENV('LANG');
2935 
2936 
2937 CURSOR c_order_line IS
2938 SELECT 1
2939 FROM oe_order_lines_all oola
2940 WHERE oola.header_id = p_cust_vr.order_id
2941   AND NVL( p_cust_vr.ship_to_site_id, oola.ship_to_org_id) = oola.ship_to_org_id
2942   AND oola.inventory_item_id = p_spec.inventory_item_id
2943   AND oola.header_id = p_cust_vr.order_id
2944   AND (oola.line_number + (oola.shipment_number / 10)) = p_cust_vr.order_line
2945   AND oola.line_id = p_cust_vr.order_line_id;
2946 
2947   -- Local Variables
2948 dummy              PLS_INTEGER;
2949 l_lot_ctl          NUMBER;
2950 l_sample_display   GMD_SAMPLES_GRP.sample_display_rec;
2951 
2952 BEGIN
2953 
2954   --=========================================================================
2955   -- WHO section :
2956   --=========================================================================
2957   check_who( p_user_id  => p_cust_vr.created_by);
2958   check_who( p_user_id  => p_cust_vr.last_updated_by);
2959   IF (p_cust_vr.creation_date IS NULL
2960    OR p_cust_vr.last_update_date IS NULL)
2961   THEN
2962     GMD_API_PUB.Log_Message('GMD_WRONG_VALUE',
2963                             'WHAT', 'the dates must not be NULL');
2964     RAISE FND_API.G_EXC_ERROR;
2965   END IF;
2966 
2967   --=========================================================================
2968   -- Organization : must belong to the USER
2969   --=========================================================================
2970 
2971 
2972   IF (p_cust_vr.organization_id IS NOT NULL)
2973    -- Check that Organization is a valid one
2974   THEN
2975        /*
2976     OPEN c_orgn( p_cust_vr.organization_id);
2977     FETCH c_orgn INTO dummy;
2978     IF (c_orgn%NOTFOUND)
2979     THEN
2980       CLOSE c_orgn;
2981       GMD_API_PUB.Log_Message('GMD_ORGANIZATION_ID_NOT_FOUND',
2982                               'ORGN_ID', p_cust_vr.organization_id);
2983       RAISE FND_API.G_EXC_ERROR;
2984     END IF;
2985     CLOSE c_orgn;*/
2986 
2987   --  replace above with function  as above check was not working as designed  - bug 5223014 rework
2988 
2989     IF NOT (gmd_api_grp.OrgnAccessible(p_cust_vr.organization_id)) THEN
2990     	  RAISE FND_API.G_EXC_ERROR;
2991     END IF;
2992 
2993   END IF;
2994 
2995   --=========================================================================
2996   -- Get Item Controls
2997   --=========================================================================
2998   l_sample_display.organization_id := p_cust_vr.organization_id;
2999   l_sample_display.inventory_item_id := p_spec.inventory_item_id;
3000   GMD_SAMPLES_GRP.get_item_values (p_sample_display => l_sample_display);
3001   l_lot_ctl := l_sample_display.lot_control_code;
3002 
3003 
3004   --=========================================================================
3005   -- lot_optional_on_sample :
3006   -- When this field is NOT NULL, all the following fields must be null :
3007   -- sample_inv_trans_ind
3008   --=========================================================================
3009   --Enhancement #3476560. added 'delayed_lot_entry' to the call to 'check_vr_controls' procedure
3010   check_VR_Controls( p_VR_type                  => 'CUSTOMER'
3011                    , p_lot_optional_on_sample   => p_cust_vr.lot_optional_on_sample
3012 		   , p_delayed_lot_entry        => NULL
3013                    , p_sample_inv_trans_ind     => p_cust_vr.sample_inv_trans_ind
3014                    , p_lot_ctl                  => l_lot_ctl
3015                    , p_status_ctl               => NULL
3016                    , p_control_lot_attrib_ind   => NULL
3017                    , p_in_spec_lot_status_id    => NULL
3018                    , p_out_of_spec_lot_status_id=> NULL
3019                    , p_control_batch_step_ind   => NULL
3020 		   , p_delayed_lpn_entry        => NULL);    --RLNAGARA LPN ME 7027149
3021 
3022   --=========================================================================
3023   -- spec_vr_status :
3024   --=========================================================================
3025   OPEN c_status(p_cust_vr.spec_vr_status);
3026   FETCH c_status
3027    INTO dummy;
3028   IF (c_status%NOTFOUND)
3029   THEN
3030     CLOSE c_status;
3031     GMD_API_PUB.Log_Message('GMD_SPEC_STATUS_NOT_FOUND',
3032                             'STATUS', p_cust_vr.spec_vr_status);
3033     RAISE FND_API.G_EXC_ERROR;
3034   END IF;
3035   CLOSE c_status;
3036 
3037 
3038   --=========================================================================
3039   -- start_date : This field is mandatory
3040   --=========================================================================
3041   IF (p_cust_vr.start_date IS NULL)
3042   THEN
3043       GMD_API_PUB.Log_Message('GMD_SPEC_VR_START_DATE_REQD');
3044       RAISE FND_API.G_EXC_ERROR;
3045   END IF;
3046 
3047   --=========================================================================
3048   -- COA section :
3049   --=========================================================================
3050   check_COA( p_coa_type              => p_cust_vr.coa_type
3051            , p_coa_at_ship_ind       => p_cust_vr.coa_at_ship_ind
3052            , p_coa_at_invoice_ind    => p_cust_vr.coa_at_invoice_ind
3053            , p_coa_req_from_supl_ind => p_cust_vr.coa_req_from_supl_ind);
3054 
3055   --=========================================================================
3056   -- cust_id : This field is mandatory
3057   --=========================================================================
3058   IF (p_cust_vr.cust_id IS NULL)
3059   THEN
3060     GMD_API_PUB.Log_Message('GMD_CUSTOMER_REQD');
3061     RAISE FND_API.G_EXC_ERROR;
3062   ELSE
3063     OPEN c_cust;
3064     FETCH c_cust
3065      INTO dummy;
3066     IF (c_cust%NOTFOUND)
3067     THEN
3068       CLOSE c_cust;
3069       GMD_API_PUB.Log_Message('GMD_CUSTOMER_NOT_FOUND');
3070       RAISE FND_API.G_EXC_ERROR;
3071     END IF;
3072     CLOSE c_cust;
3073   END IF;
3074 
3075   --=========================================================================
3076   -- Org ID
3077   --=========================================================================
3078   IF (p_cust_vr.org_id IS NOT NULL)
3079   THEN
3080     OPEN c_org;
3081     FETCH c_org
3082      INTO dummy;
3083     IF (c_org%NOTFOUND)
3084     THEN
3085       CLOSE c_org;
3086       GMD_API_PUB.Log_Message('GMD_ORG_NOT_FOUND');
3087       RAISE FND_API.G_EXC_ERROR;
3088     END IF;
3089     CLOSE c_org;
3090   END IF;
3091 
3092   --=========================================================================
3093   -- Ship To
3094   --=========================================================================
3095   IF (p_cust_vr.ship_to_site_id IS NOT NULL)
3096   THEN
3097     IF (p_cust_vr.cust_id IS NULL)
3098     THEN
3099       GMD_API_PUB.Log_Message('GMD_WRONG_VALUE',
3100                               'WHAT', 'the customer number must not be NULL');
3101       RAISE FND_API.G_EXC_ERROR;
3102     END IF;
3103 
3104     OPEN c_ship_to;
3105     FETCH c_ship_to
3106      INTO dummy;
3107     IF (c_ship_to%NOTFOUND)
3108     THEN
3109       CLOSE c_ship_to;
3110       GMD_API_PUB.Log_Message('GMD_SHIP_TO_NOT_FOUND');
3111       RAISE FND_API.G_EXC_ERROR;
3112     END IF;
3113     CLOSE c_ship_to;
3114   END IF;
3115 
3116   --=========================================================================
3117   -- Order ID
3118   --=========================================================================
3119   IF (p_cust_vr.order_id IS NOT NULL)
3120   THEN
3121     OPEN c_order;
3122     FETCH c_order
3123      INTO dummy;
3124     IF (c_order%NOTFOUND)
3125     THEN
3126       CLOSE c_order;
3127       GMD_API_PUB.Log_Message('GMD_ORDER_NOT_FOUND');
3128       RAISE FND_API.G_EXC_ERROR;
3129     END IF;
3130     CLOSE c_order;
3131   END IF;
3132 
3133   --=========================================================================
3134   -- Order Line ID
3135   -- Both order_line AND order_line_id are mandatory
3136   -- Also order_id must be NOT NULL
3137   --=========================================================================
3138   IF (p_cust_vr.order_line_id IS NOT NULL
3139      OR p_cust_vr.order_line IS NOT NULL)
3140   THEN
3141     IF (p_cust_vr.order_id IS NULL)
3142     THEN
3143       GMD_API_PUB.Log_Message('GMD_WRONG_VALUE',
3144                               'WHAT', 'the order number must not be NULL');
3145       RAISE FND_API.G_EXC_ERROR;
3146     END IF;
3147     IF (p_cust_vr.order_line_id IS NULL
3148       OR p_cust_vr.order_line IS NULL)
3149     THEN
3150       GMD_API_PUB.Log_Message('GMD_WRONG_VALUE',
3151                               'WHAT', 'the order line AND id must not be NULL');
3152       RAISE FND_API.G_EXC_ERROR;
3153     END IF;
3154 
3155     OPEN c_order_line;
3156     FETCH c_order_line
3157      INTO dummy;
3158     IF (c_order_line%NOTFOUND)
3159     THEN
3160       CLOSE c_order_line;
3161       GMD_API_PUB.Log_Message('GMD_ORDER_LINE_NOT_FOUND');
3162       RAISE FND_API.G_EXC_ERROR;
3163     END IF;
3164     CLOSE c_order_line;
3165   END IF;
3166 
3167   -- All Systems Go...
3168 
3169 EXCEPTION
3170   WHEN FND_API.G_EXC_ERROR THEN
3171     x_return_status := FND_API.G_RET_STS_ERROR ;
3172   WHEN FND_API.G_EXC_UNEXPECTED_ERROR THEN
3173     x_return_status := FND_API.G_RET_STS_UNEXP_ERROR ;
3174   WHEN OTHERS THEN
3175     x_return_status := FND_API.G_RET_STS_UNEXP_ERROR ;
3176 
3177 END check_for_null_and_fks_in_cvr;
3178 
3179 
3180 
3181 
3182 --Start of comments
3183 --+========================================================================+
3184 --| API Name    : cust_vr_exist                                            |
3185 --| TYPE        : Group                                                    |
3186 --| Notes       : This function returns TRUE if the customer VR already    |
3187 --|               exists for the spcified parameter in the database, FALSE |
3188 --|               otherwise.                                               |
3189 --|                                                                        |
3190 --| HISTORY                                                                |
3191 --|    Chetan Nagar	26-Jul-2002	Created.                           |
3192 --|    Olivier Daboval  17-OCT-2002     bug 2630007, added spec_name in    |
3193 --|                                     the VR_EXIST message               |
3194 --|    Olivier Daboval  14-NOV-2002     Added NVL(spec_vr_id, -1) because  |
3195 --|                                     the API passes a NULL spec_vr_id   |
3196 --|                                     in insert mode.                    |
3197 --|    Brenda Stone     20-NOV-2003     Bug 3090290; allow duplicate spec vr |
3198 --|                                     with "OBSOLUTE" status               |
3199 --|                                     Bug 2984784; add Version to msg for  |
3200 --|                                     existing spec vr.                    |
3201 --|                                                                        |
3202 --|  Saikiran          12-Apr-2005      Convergence Changes                |
3203 --|  Plowe						 04-Apr-2006      Bug 5117733 - added item revision to match
3204 --+========================================================================+
3205 -- End of comments
3206 
3207 FUNCTION cust_vr_exist(p_cust_vr GMD_CUSTOMER_SPEC_VRS%ROWTYPE,
3208                        p_spec    GMD_SPECIFICATIONS%ROWTYPE)
3209 RETURN BOOLEAN IS
3210 
3211   CURSOR c_cust_vr IS
3212   SELECT vr.spec_vr_id, s.spec_name, s.spec_vers
3213   FROM   gmd_specifications_b s, gmd_customer_spec_vrs vr
3214   WHERE  s.spec_id = vr.spec_id
3215   AND    s.owner_organization_id = p_spec.owner_organization_id
3216   AND    s.inventory_item_id = p_spec.inventory_item_id
3217   AND   ( (s.revision is null and p_spec.revision is NULL ) OR -- handle item revision 5117733
3218           (s.revision  = p_spec.revision )
3219   			 )
3220   AND    ((s.grade_code is NULL AND p_spec.grade_code is NULL) OR
3221           (s.grade_code = p_spec.grade_code)
3222          )
3223   AND    ((vr.organization_id is NULL AND p_cust_vr.organization_id is NULL) OR
3224           (vr.organization_id = p_cust_vr.organization_id)
3225          )
3226   AND    ((vr.cust_id is NULL AND p_cust_vr.cust_id is NULL) OR
3227           (vr.cust_id = p_cust_vr.cust_id)
3228          )
3229   AND    ((vr.org_id is NULL AND p_cust_vr.org_id is NULL) OR
3230           (vr.org_id = p_cust_vr.org_id)
3231          )
3232   AND    ((vr.order_id is NULL AND p_cust_vr.order_id is NULL) OR
3233           (vr.order_id = p_cust_vr.order_id)
3234          )
3235   AND    ((vr.order_line is NULL AND p_cust_vr.order_line is NULL) OR
3236           (vr.order_line = p_cust_vr.order_line)
3237          )
3238   AND    ((vr.order_line_id is NULL AND p_cust_vr.order_line_id is NULL) OR
3239           (vr.order_line_id = p_cust_vr.order_line_id)
3240          )
3241   AND    ((vr.ship_to_site_id is NULL AND p_cust_vr.ship_to_site_id is NULL) OR
3242           (vr.ship_to_site_id = p_cust_vr.ship_to_site_id)
3243          )
3244   AND    ((vr.end_date is NULL AND (p_cust_vr.end_date IS NULL OR
3245                                     p_cust_vr.end_date >= vr.start_date)) OR
3246 	  (p_cust_vr.end_date IS NULL AND
3247 	     p_cust_vr.start_date <= nvl(vr.end_date, p_cust_vr.start_date)) OR
3248           (p_cust_vr.start_date <= vr.end_date AND p_cust_vr.end_date >= vr.start_date)
3249          )
3250   AND   ( floor(vr.spec_vr_status/100) = floor(p_cust_vr.spec_vr_status/100) AND
3251 /*      Bug 3090290; allow duplicate spec vr with "OBSOLUTE" status   */
3252          p_cust_vr.spec_vr_status <> 1000 )
3253   AND    vr.spec_vr_status NOT IN (SELECT status_code FROM gmd_qc_status
3254                                    WHERE status_type = 800)
3255   AND    vr.delete_mark = 0
3256   AND    s.delete_mark = 0
3257   AND    vr.spec_vr_id <> NVL(p_cust_vr.spec_vr_id, -1)
3258   ;
3259 
3260   dummy    PLS_INTEGER;
3261   specname VARCHAR2(80);
3262   specvers NUMBER;
3263 
3264 BEGIN
3265 
3266   OPEN c_cust_vr;
3267   FETCH c_cust_vr INTO dummy, specname, specvers;
3268   IF c_cust_vr%FOUND THEN
3269     CLOSE c_cust_vr;
3270     FND_MESSAGE.SET_NAME('GMD', 'GMD_CUST_VR_EXIST');
3271     FND_MESSAGE.SET_TOKEN('spec', specname);
3272     FND_MESSAGE.SET_TOKEN('vers', specvers);
3273     FND_MSG_PUB.ADD;
3274     RETURN TRUE;
3275   ELSE
3276     CLOSE c_cust_vr;
3277     RETURN FALSE;
3278   END IF;
3279 
3280 EXCEPTION
3281   -- Though there is no reason the program can reach
3282   -- here, this is coded just for the reasons we can
3283   -- not think of!
3284   WHEN OTHERS THEN
3285     FND_MESSAGE.SET_NAME('GMD', 'GMD_API_ERROR');
3286     FND_MESSAGE.SET_TOKEN('PACKAGE', 'GMD_SPEC_VRS_GRP.CUST_VR_EXIST' );
3287     FND_MESSAGE.SET_TOKEN('ERROR', SUBSTR(SQLERRM,1,200));
3288     RETURN TRUE;
3289 
3290 END cust_vr_exist;
3291 
3292 
3293 
3294 
3295 
3296 
3297 --Start of comments
3298 --+========================================================================+
3299 --| API Name    : validate_supp_vr                                         |
3300 --| TYPE        : Group                                                    |
3301 --| Notes       : This procedure validates all the fields of               |
3302 --|               Supplier  validity rule record. This procedure can be    |
3303 --|               called from FORM or API and the caller need              |
3304 --|               to specify this in p_called_from parameter               |
3305 --|               while calling this procedure. Based on where             |
3306 --|               it is called from certain validations will               |
3307 --|               either be performed or skipped.                          |
3308 --|                                                                        |
3309 --|               If everything is fine then OUT parameter                 |
3310 --|               x_return_status is set to 'S' else appropriate           |
3311 --|               error message is put on the stack and error              |
3312 --|               is returned.                                             |
3313 --|                                                                        |
3314 --| HISTORY                                                                |
3315 --|    Chetan Nagar	26-Jul-2002	Created.                           |
3316 --|                                                                        |
3317 --+========================================================================+
3318 -- End of comments
3319 
3320 PROCEDURE validate_supp_vr
3321 (
3322   p_supp_vr       IN  GMD_SUPPLIER_SPEC_VRS%ROWTYPE
3323 , p_called_from   IN  VARCHAR2
3324 , p_operation     IN  VARCHAR2
3325 , x_return_status OUT NOCOPY VARCHAR2
3326 ) IS
3327 
3328   -- Local Variables
3329   dummy                          NUMBER;
3330   l_return_status                VARCHAR2(1);
3331 
3332   l_spec                         GMD_SPECIFICATIONS%ROWTYPE;
3333   l_spec_out                     GMD_SPECIFICATIONS%ROWTYPE;
3334   l_item_mst                     MTL_SYSTEM_ITEMS_B%ROWTYPE;
3335   l_sampling_plan                GMD_SAMPLING_PLANS%ROWTYPE;
3336   l_sampling_plan_out            GMD_SAMPLING_PLANS%ROWTYPE;
3337   l_inventory_item_id            NUMBER;
3338   l_organization_id              NUMBER;
3339   l_uom_rate                     NUMBER;
3340 
3341   -- Exceptions
3342   e_spec_fetch_error             EXCEPTION;
3343   e_smpl_plan_fetch_error        EXCEPTION;
3344   e_error_fetch_item             EXCEPTION;
3345 
3346 BEGIN
3347   --  Initialize API return status to success
3348   x_return_status := FND_API.G_RET_STS_SUCCESS;
3349 
3350   IF NOT (p_operation in ('INSERT', 'UPDATE', 'DELETE')) THEN
3351     -- Invalid Operation
3352     GMD_API_PUB.Log_Message('GMD_INVALID_OPERATION');
3353     RAISE FND_API.G_EXC_ERROR;
3354   END IF;
3355 
3356   -- Verify that the specification exists.
3357   l_spec.spec_id := p_supp_vr.spec_id;
3358   IF NOT (GMD_Specifications_PVT.Fetch_Row(
3359                            p_specifications => l_spec,
3360                            x_specifications => l_spec_out)
3361           ) THEN
3362     -- Fetch Error
3363     GMD_API_PUB.Log_Message('GMD_SPEC_FETCH_ERROR');
3364     RAISE e_spec_fetch_error;
3365   END IF;
3366 
3367   l_spec := l_spec_out ;
3368 
3369   -- Verify that the Sampling Plan exists.
3370   --odab added this test.
3371   IF (p_supp_vr.sampling_plan_id IS NOT NULL)
3372   THEN
3373     l_sampling_plan.sampling_plan_id := p_supp_vr.sampling_plan_id;
3374     IF NOT (GMD_Sampling_Plans_PVT.Fetch_Row(
3375                            p_sampling_plan => l_sampling_plan,
3376                            x_sampling_plan => l_sampling_plan_out)
3377           ) THEN
3378       -- Fetch Error
3379       GMD_API_PUB.Log_Message('GMD_SAMPLING_PLAN_FETCH_ERROR');
3380       RAISE e_smpl_plan_fetch_error;
3381     END IF;
3382     l_sampling_plan := l_sampling_plan_out ;
3383   END IF;
3384 
3385   IF (p_called_from = 'API') THEN
3386     --For mini pack L, bug 3439865
3387     IF (nvl(p_supp_vr.auto_sample_ind,'N') not in ('N','Y')) THEN
3388       GMD_API_PUB.Log_Message('GMD_WRONG_VALUE',
3389                             'WHAT', 'INVALID_AUTO_SAMPLE_IND');
3390       RAISE FND_API.G_EXC_ERROR;
3391     END IF;
3392     -- end 3439865
3393     -- Check for NULLs and Valid Foreign Keys in the input parameter
3394     GMD_SPEC_VRS_GRP.check_for_null_and_fks_in_svr
3395       (
3396         p_supp_vr       => p_supp_vr
3397       , p_spec          => l_spec
3398       , x_return_status => l_return_status
3399       );
3400     -- No need if called from FORM since it is already
3401     -- done in the form
3402 
3403     IF l_return_status = FND_API.G_RET_STS_ERROR THEN
3404       -- Message is alrady logged by check_for_null procedure
3405       RAISE FND_API.G_EXC_ERROR;
3406     ELSIF l_return_status = FND_API.G_RET_STS_UNEXP_ERROR THEN
3407       -- Message is alrady logged by check_for_null procedure
3408       RAISE FND_API.G_EXC_UNEXPECTED_ERROR;
3409     END IF;
3410   END IF;
3411 
3412   -- First Verify that the SAME VR does not exists
3413   IF (p_operation IN ('INSERT', 'UPDATE')
3414     AND supp_vr_exist(p_supp_vr, l_spec))
3415   THEN
3416     -- Disaster, Trying to insert duplicate
3417     -- bug 2630007, odaboval put the message in function supp_vr_exist.
3418     -- GMD_API_PUB.Log_Message('GMD_SUPP_VR_EXIST');
3419     RAISE FND_API.G_EXC_ERROR;
3420   END IF;
3421 
3422   -- Check to make sure that a samplingplan exists
3423   -- if auto sample flag on
3424   IF ((p_supp_vr.sampling_plan_id IS NULL) and
3425        (p_supp_vr.auto_sample_ind = 'Y'))
3426   THEN
3427       GMD_API_PUB.Log_Message('GMD_NEED_SAMPLE_PLAN');
3428       RAISE e_smpl_plan_fetch_error;
3429   END IF;
3430 
3431   -- Sample Quantity UOM must be convertible to Item's UOM
3432   BEGIN
3433     SELECT inventory_item_id INTO l_inventory_item_id FROM
3434     gmd_specifications WHERE spec_id = p_supp_vr.spec_id;
3435     SELECT owner_organization_id INTO l_organization_id FROM
3436     gmd_specifications WHERE spec_id = p_supp_vr.spec_id;
3437     SELECT * INTO l_item_mst
3438     FROM mtl_system_items_b
3439     WHERE inventory_item_id = l_inventory_item_id
3440     AND organization_id = l_organization_id;
3441   EXCEPTION
3442   WHEN OTHERS THEN
3443     GMD_API_PUB.Log_Message('GMD_ITEM_FETCH_ERROR');
3444     RAISE e_error_fetch_item;
3445   END;
3446 
3447   --odab added this test.
3448   IF (p_supp_vr.sampling_plan_id IS NOT NULL)
3449   THEN
3450     inv_convert.inv_um_conversion (
3451       from_unit  => l_sampling_plan.sample_qty_uom,
3452       to_unit    =>  l_item_mst.primary_uom_code,
3453       item_id    =>  l_inventory_item_id,
3454       lot_number => NULL,
3455       organization_id => l_organization_id  ,
3456       uom_rate   => l_uom_rate );
3457 
3458     IF l_uom_rate = -99999 THEN
3459       GMD_API_PUB.Log_Message('GMD_UOM_CONVERSION_ERROR');
3460       RAISE FND_API.G_EXC_ERROR;
3461     END IF;
3462   END IF;
3463 
3464   -- No need to check the return status because above procedure
3465   -- logs appropriate message on the stack and raises an exception.
3466 
3467   -- The Start Date must be less than the End Date
3468   If ( p_supp_vr.end_date IS NOT NULL AND
3469        p_supp_vr.start_date > p_supp_vr.end_date) THEN
3470     GMD_API_PUB.Log_Message('GMD_SPEC_VR_EFF_DATE_ERROR');
3471     RAISE FND_API.G_EXC_ERROR;
3472   END IF;
3473 
3474   -- Spec VR Status Must be less than Spec Status upto Appoved Stages
3475   IF (floor(l_spec.spec_status/100) <= 7 AND
3476       floor(p_supp_vr.spec_vr_status/100) <= 7 AND
3477       p_supp_vr.spec_vr_status > l_spec.spec_status) THEN
3478     GMD_API_PUB.Log_Message('GMD_SPEC_VR_STATUS_HIGHER');
3479     RAISE FND_API.G_EXC_ERROR;
3480   END IF;
3481 
3482   -- All systems GO...
3483 
3484 EXCEPTION
3485   WHEN FND_API.G_EXC_ERROR     OR
3486        e_spec_fetch_error      OR
3487        e_smpl_plan_fetch_error OR
3488        e_error_fetch_item
3489   THEN
3490     x_return_status := FND_API.G_RET_STS_ERROR ;
3491   WHEN FND_API.G_EXC_UNEXPECTED_ERROR THEN
3492     x_return_status := FND_API.G_RET_STS_UNEXP_ERROR ;
3493   WHEN OTHERS THEN
3494     x_return_status := FND_API.G_RET_STS_UNEXP_ERROR ;
3495 
3496 
3497 END validate_supp_vr;
3498 
3499 
3500 
3501 
3502 --Start of comments
3503 --+========================================================================+
3504 --| API Name    : check_for_null_and_fks_in_svr                            |
3505 --| TYPE        : Group                                                    |
3506 --| Notes       : This procedure checks for NULL and Foreign Key           |
3507 --|               constraints for the required filed in the Spec           |
3508 --|               Supplier  VR record.                                     |
3509 --|                                                                        |
3510 --|               If everything is fine then 'S' is returned in the        |
3511 --|               parameter - x_return_status otherwise error message      |
3512 --|               is logged and error status - E or U returned             |
3513 --|                                                                        |
3514 --| HISTORY                                                                |
3515 --|    Chetan Nagar     26-Jul-2002     Created.                           |
3516 --|                                                                        |
3517 --|    SaiKiran		04-MAY-2004	Enhancement #3476560. added        |
3518 --|                  'delayed_lot_entry' to the call to 'check_vr_controls'|
3519 --|                   procedure.                                           |
3520 --|                                                                        |
3521 --|    Saikiran        11-Apr-2005      Convergence Changes                |
3522 --|    srakrish        15-june-06    BUG 5251172: Checking if the          |
3523 --|					responsibility is available to the |
3524 --|					organization			   |
3525 --+========================================================================+
3526 -- End of comments
3527 
3528 PROCEDURE check_for_null_and_fks_in_svr
3529 (
3530   p_supp_vr       IN  gmd_supplier_spec_vrs%ROWTYPE
3531 , p_spec          IN  gmd_specifications%ROWTYPE
3532 , x_return_status OUT NOCOPY VARCHAR2
3533 )
3534 IS
3535 
3536 CURSOR c_item_controls IS
3537 SELECT lot_control_code
3538 FROM   mtl_system_items_b
3539 WHERE  inventory_item_id = p_spec.inventory_item_id
3540 AND organization_id = p_spec.owner_organization_id;
3541 
3542 CURSOR c_supplier IS
3543 SELECT 1
3544 FROM po_vendors v
3545 WHERE v.vendor_id = p_supp_vr.supplier_id
3546   AND v.enabled_flag = 'Y'
3547   AND sysdate between nvl(v.start_date_active, sysdate-1)
3548                AND     nvl(v.end_date_active, sysdate+1);
3549 
3550 CURSOR c_supplier_site IS
3551 SELECT 1
3552 FROM po_vendor_sites_all v
3553 WHERE (v.purchasing_site_flag = 'Y'
3554    OR v.rfq_only_site_flag = 'Y')
3555   AND sysdate < NVL(inactive_date, sysdate + 1)
3556   AND v.vendor_id = p_supp_vr.supplier_id
3557   AND v.vendor_site_id = p_supp_vr.supplier_site_id;
3558 
3559 -- bug 4924483 sql id 14687791 - cost is down from 4,380,562   to 6  - no IN
3560 
3561 /*CURSOR c_po IS
3562 SELECT 1
3563 FROM po_headers_all pha
3564 WHERE pha.po_header_id IN
3565   (SELECT pla.po_header_id
3566    FROM po_lines_all pla
3567    WHERE pla.po_header_id = pha.po_header_id
3568    AND pla.item_id = p_spec.inventory_item_id
3569   AND pha.vendor_id      = p_supp_vr.supplier_id
3570   AND pha.vendor_site_id = p_supp_vr.supplier_site_id
3571   AND pha.po_header_id   = p_supp_vr.po_header_id); */
3572 
3573 -- fix
3574 CURSOR c_po IS
3575 SELECT 1
3576 FROM po_headers_all pha, po_lines_all pla
3577 WHERE pha.po_header_id   = p_supp_vr.po_header_id
3578 AND pha.vendor_id      = p_supp_vr.supplier_id
3579 AND pha.vendor_site_id = p_supp_vr.supplier_site_id
3580 AND pha.po_header_id  = pla.po_header_id
3581 AND pla.item_id = p_spec.inventory_item_id;
3582 
3583 
3584 
3585 
3586 
3587 
3588 CURSOR c_po_line IS
3589 SELECT 1
3590 FROM po_lines_all pla
3591 WHERE pla.item_id = p_spec.inventory_item_id
3592   AND pla.po_header_id = p_supp_vr.po_header_id
3593   AND pla.po_line_id   = p_Supp_vr.po_line_id;
3594 
3595 -- Local variables
3596 dummy              PLS_INTEGER;
3597 l_lot_ctl          NUMBER;
3598 
3599 BEGIN
3600 
3601   --=========================================================================
3602   -- WHO section :
3603   --=========================================================================
3604   check_who( p_user_id  => p_supp_vr.created_by);
3605   check_who( p_user_id  => p_supp_vr.last_updated_by);
3606   IF (p_supp_vr.creation_date IS NULL
3607    OR p_supp_vr.last_update_date IS NULL)
3608   THEN
3609     GMD_API_PUB.Log_Message('GMD_WRONG_VALUE',
3610                             'WHAT', 'the dates must not be NULL');
3611     RAISE FND_API.G_EXC_ERROR;
3612   END IF;
3613 
3614 
3615 
3616   -- Organization is valid
3617   IF (p_supp_vr.organization_id IS NOT NULL) THEN
3618     -- Check that organization is accessible to the user's responsibility
3619     OPEN c_orgn( p_supp_vr.organization_id);
3620     FETCH c_orgn INTO dummy;
3621     IF c_orgn%NOTFOUND THEN
3622       CLOSE c_orgn;
3623       GMD_API_PUB.Log_Message('GMD_ORGANIZATION_ID_NOT_FOUND',
3624                               'ORGN_ID', p_supp_vr.organization_id);
3625       RAISE FND_API.G_EXC_ERROR;
3626     END IF;
3627     CLOSE c_orgn;
3628   END IF;
3629 
3630   --srakrish BUG 5251172: Checking if the responsibility is available to the organization.
3631   IF NOT (gmd_api_grp.OrgnAccessible(p_supp_vr.organization_id)) THEN
3632     	  RAISE FND_API.G_EXC_ERROR;
3633   END IF;
3634 
3635 
3636 
3637 
3638 
3639   --=========================================================================
3640   -- Get Item Controls
3641   --=========================================================================
3642   OPEN c_item_controls;
3643   FETCH c_item_controls
3644    INTO l_lot_ctl;
3645   IF (c_item_controls%NOTFOUND)
3646   THEN
3647       CLOSE c_item_controls;
3648       FND_MESSAGE.SET_NAME('GMD','GMD_NOTFOUND');
3649       FND_MESSAGE.SET_TOKEN('WHAT', 'INVENTORY_ITEM_ID');
3650       FND_MESSAGE.SET_TOKEN('VALUE', p_spec.inventory_item_id);
3651       FND_MSG_PUB.ADD;
3652       RAISE FND_API.G_EXC_ERROR;
3653   END IF;
3654   CLOSE c_item_controls;
3655 
3656   --=========================================================================
3657   -- lot_optional_on_sample :
3658   -- When this field is NOT NULL, all the following fields must be null :
3659   -- sample_inv_trans_ind
3660   --=========================================================================
3661   --Enhancement #3476560. added 'delayed_lot_entry' to the call to 'check_vr_controls' procedure
3662   check_VR_Controls( p_VR_type                  => 'SUPPLIER'
3663                    , p_lot_optional_on_sample   => p_supp_vr.lot_optional_on_sample
3664 		   , p_delayed_lot_entry        => p_supp_vr.delayed_lot_entry
3665                    , p_sample_inv_trans_ind     => p_supp_vr.sample_inv_trans_ind
3666                    , p_lot_ctl                  => l_lot_ctl
3667                    , p_status_ctl               => NULL
3668                    , p_control_lot_attrib_ind   => p_supp_vr.CONTROL_LOT_ATTRIB_IND
3669                    , p_in_spec_lot_status_id    => p_supp_vr.in_spec_lot_status_id
3670                    , p_out_of_spec_lot_status_id => p_supp_vr.out_of_spec_lot_status_id
3671                    , p_control_batch_step_ind   => NULL
3672 		   , p_delayed_lpn_entry        => p_supp_vr.delayed_lpn_entry);    --RLNAGARA LPN ME 7027149
3673 
3674   --RLNAGARA LPN ME 7027149 start  Check for WMS enabled organization.
3675   IF (p_supp_vr.organization_id IS NOT NULL) THEN
3676     IF NOT check_wms_enabled(p_supp_vr.organization_id) THEN  -- If the Org is not a wms enabled then delayed_lpn_entry should be NULL
3677       IF p_supp_vr.delayed_lpn_entry IS NOT NULL THEN
3678         GMD_API_PUB.Log_Message('GMD_WRONG_VALUE',
3679                                 'WHAT', 'Delayed_LPN_Entry should be NULL for Non-WMS Enabled Organization.');
3680         RAISE FND_API.G_EXC_ERROR;
3681       END IF;
3682     END IF;
3683   END IF;
3684   --RLNAGARA LPN ME 7027149 end
3685 
3686   --=========================================================================
3687   -- spec_vr_status :
3688   --=========================================================================
3689   OPEN c_status(p_supp_vr.spec_vr_status);
3690   FETCH c_status
3691    INTO dummy;
3692   IF (c_status%NOTFOUND)
3693   THEN
3694     CLOSE c_status;
3695     GMD_API_PUB.Log_Message('GMD_SPEC_STATUS_NOT_FOUND',
3696                             'STATUS', p_supp_vr.spec_vr_status);
3697     RAISE FND_API.G_EXC_ERROR;
3698   END IF;
3699   CLOSE c_status;
3700 
3701   --=========================================================================
3702   -- start_date : This field is mandatory
3703   --=========================================================================
3704   IF (p_supp_vr.start_date IS NULL)
3705   THEN
3706       GMD_API_PUB.Log_Message('GMD_SPEC_VR_START_DATE_REQD');
3707       RAISE FND_API.G_EXC_ERROR;
3708   END IF;
3709 
3710   --=========================================================================
3711   -- COA section :
3712   --=========================================================================
3713   check_COA( p_coa_type              => p_supp_vr.coa_type
3714            , p_coa_at_ship_ind       => p_supp_vr.coa_at_ship_ind
3715            , p_coa_at_invoice_ind    => p_supp_vr.coa_at_invoice_ind
3716            , p_coa_req_from_supl_ind => p_supp_vr.coa_req_from_supl_ind);
3717 
3718   --=========================================================================
3719   -- supplier_id : This field is mandatory
3720   --=========================================================================
3721   IF (p_supp_vr.supplier_id IS NULL)
3722   THEN
3723     GMD_API_PUB.Log_Message('GMD_SUPPLIER_REQD');
3724     RAISE FND_API.G_EXC_ERROR;
3725   ELSE
3726     OPEN c_supplier;
3727     FETCH c_supplier INTO dummy;
3728     IF (c_supplier%NOTFOUND)
3729     THEN
3730       CLOSE c_supplier;
3731       GMD_API_PUB.Log_Message('GMD_SUPPLIER_NOT_FOUND');
3732       RAISE FND_API.G_EXC_ERROR;
3733     END IF;
3734     CLOSE c_supplier;
3735   END IF;
3736 
3737   --=========================================================================
3738   -- supplier_site_id :
3739   --=========================================================================
3740   IF ( p_supp_vr.supplier_site_id IS NOT NULL)
3741   THEN
3742     OPEN c_supplier_site;
3743     FETCH c_supplier_site
3744      INTO dummy;
3745     IF (c_supplier_site%NOTFOUND)
3746     THEN
3747       CLOSE c_supplier_site;
3748       FND_MESSAGE.SET_NAME('GMD','GMD_NOTFOUND');
3749       FND_MESSAGE.SET_TOKEN('WHAT', 'SUPPLIER_SITE_ID');
3750       FND_MESSAGE.SET_TOKEN('VALUE', p_supp_vr.supplier_site_id);
3751       FND_MSG_PUB.ADD;
3752       RAISE FND_API.G_EXC_ERROR;
3753     END IF;
3754     CLOSE c_supplier_site;
3755   END IF;
3756 
3757   --=========================================================================
3758   -- po_header_id :
3759   -- When po_header_id is NOT NULL, then supplier_site_id must be NOT NULL
3760   --=========================================================================
3761   -- PO
3762   IF (p_supp_vr.po_header_id IS NOT NULL)
3763   THEN
3764     IF (p_supp_vr.supplier_site_id IS NULL)
3765     THEN
3766       GMD_API_PUB.Log_Message('GMD_WRONG_VALUE',
3767                               'WHAT', 'supplier_site_id must not be NULL');
3768       RAISE FND_API.G_EXC_ERROR;
3769     END IF;
3770 
3771     OPEN c_po;
3772     FETCH c_po INTO dummy;
3773     IF (c_po%NOTFOUND)
3774     THEN
3775       CLOSE c_po;
3776       GMD_API_PUB.Log_Message('GMD_PO_NOT_FOUND');
3777       RAISE FND_API.G_EXC_ERROR;
3778     END IF;
3779     CLOSE c_po;
3780   END IF;
3781 
3782   --=========================================================================
3783   -- po_line_id :
3784   -- When po_line_id is NOT NULL, then supplier_site_id AND po_header_id must be NOT NULL
3785   --=========================================================================
3786   -- PO Line
3787   IF (p_supp_vr.po_line_id IS NOT NULL)
3788   THEN
3789     IF (p_supp_vr.po_header_id IS NULL)
3790     THEN
3791       GMD_API_PUB.Log_Message('GMD_WRONG_VALUE',
3792                               'WHAT', 'po_header_id must not be NULL');
3793       RAISE FND_API.G_EXC_ERROR;
3794     END IF;
3795 
3796     IF (p_supp_vr.supplier_site_id IS NULL)
3797     THEN
3798       GMD_API_PUB.Log_Message('GMD_WRONG_VALUE',
3799                               'WHAT', 'supplier site must not be NULL');
3800       RAISE FND_API.G_EXC_ERROR;
3801     END IF;
3802 
3803     OPEN c_po_line;
3804     FETCH c_po_line INTO dummy;
3805     IF (c_po_line%NOTFOUND)
3806     THEN
3807       CLOSE c_po_line;
3808       GMD_API_PUB.Log_Message('GMD_PO_LINE_NOT_FOUND');
3809       RAISE FND_API.G_EXC_ERROR;
3810     END IF;
3811     CLOSE c_po_line;
3812   END IF;
3813 
3814   -- All Systems Go...
3815 
3816 EXCEPTION
3817   WHEN FND_API.G_EXC_ERROR THEN
3818     x_return_status := FND_API.G_RET_STS_ERROR ;
3819   WHEN FND_API.G_EXC_UNEXPECTED_ERROR THEN
3820     x_return_status := FND_API.G_RET_STS_UNEXP_ERROR ;
3821   WHEN OTHERS THEN
3822     x_return_status := FND_API.G_RET_STS_UNEXP_ERROR ;
3823 
3824 END check_for_null_and_fks_in_svr;
3825 
3826 
3827 
3828 
3829 --Start of comments
3830 --+========================================================================+
3831 --| API Name    : supp_vr_exist                                            |
3832 --| TYPE        : Group                                                    |
3833 --| Notes       : This function returns TRUE if the supplier VR already    |
3834 --|               exists for the spcified parameter in the database, FALSE |
3835 --|               otherwise.                                               |
3836 --|                                                                        |
3837 --| HISTORY                                                                |
3838 --|    Chetan Nagar     26-Jul-2002     Created.                           |
3839 --|    Olivier Daboval  17-OCT-2002     bug 2630007, added spec_name in    |
3840 --|                                     the VR_EXIST message               |
3841 --|    Olivier Daboval  14-NOV-2002     Added NVL(spec_vr_id, -1) because  |
3842 --|                                     the API passes a NULL spec_vr_id   |
3843 --|                                     in insert mode.                    |
3844 --|    Brenda Stone     20-NOV-2003     Bug 3090290; allow duplicate spec vr |
3845 --|                                     with "OBSOLUTE" status               |
3846 --|                                     Bug 2984784; add Version to msg for  |
3847 --|                                     existing spec vr.                    |
3848 --|                                                                        |
3849 --|  Saikiran          12-Apr-2005      Convergence Changes                |
3850 --|  Plowe						 04-Apr-2006      Bug 5117733 - added item revision to match
3851 --+========================================================================+
3852 -- End of comments
3853 
3854 FUNCTION supp_vr_exist(p_supp_vr GMD_SUPPLIER_SPEC_VRS%ROWTYPE,
3855                        p_spec    GMD_SPECIFICATIONS%ROWTYPE)
3856 RETURN BOOLEAN IS
3857 
3858   CURSOR c_supp_vr IS
3859   SELECT vr.spec_vr_id, s.spec_name, s.spec_vers
3860   FROM   gmd_specifications_b s, gmd_supplier_spec_vrs vr
3861   WHERE  s.spec_id = vr.spec_id
3862   AND    s.owner_organization_id = p_spec.owner_organization_id
3863   AND    s.inventory_item_id = p_spec.inventory_item_id
3864   AND   ( (s.revision is null and p_spec.revision is NULL ) OR -- handle item revision 5117733
3865           (s.revision  = p_spec.revision )
3866   			 )
3867   AND    ((s.grade_code is NULL AND p_spec.grade_code is NULL) OR
3868           (s.grade_code = p_spec.grade_code)
3869          )
3870   AND    ((vr.organization_id is NULL AND p_supp_vr.organization_id is NULL) OR
3871           (vr.organization_id = p_supp_vr.organization_id)
3872          )
3873   AND    ((vr.supplier_id is NULL AND p_supp_vr.supplier_id is NULL) OR
3874           (vr.supplier_id = p_supp_vr.supplier_id)
3875          )
3876   AND    ((vr.supplier_site_id is NULL AND p_supp_vr.supplier_site_id is NULL) OR
3877           (vr.supplier_site_id = p_supp_vr.supplier_site_id)
3878          )
3879   AND    ((vr.po_header_id is NULL AND p_supp_vr.po_header_id is NULL) OR
3880           (vr.po_header_id = p_supp_vr.po_header_id)
3881          )
3882   AND    ((vr.po_line_id is NULL AND p_supp_vr.po_line_id is NULL) OR
3883           (vr.po_line_id = p_supp_vr.po_line_id)
3884          )
3885   AND    ((vr.end_date is NULL AND (p_supp_vr.end_date IS NULL OR
3886                                     p_supp_vr.end_date >= vr.start_date)) OR
3887 	  (p_supp_vr.end_date IS NULL AND
3888 	     p_supp_vr.start_date <= nvl(vr.end_date, p_supp_vr.start_date)) OR
3889           (p_supp_vr.start_date <= vr.end_date AND p_supp_vr.end_date >= vr.start_date)
3890          )
3891   AND   ( floor(vr.spec_vr_status/100) = floor(p_supp_vr.spec_vr_status/100) AND
3892 /*      Bug 3090290; allow duplicate spec vr with "OBSOLUTE" status   */
3893          p_supp_vr.spec_vr_status <> 1000 )
3894   AND    vr.spec_vr_status NOT IN (SELECT status_code FROM gmd_qc_status
3895                                    WHERE status_type = 800)
3896   AND    vr.delete_mark = 0
3897   AND    s.delete_mark = 0
3898   AND    vr.spec_vr_id <> NVL(p_supp_vr.spec_vr_id, -1)
3899   ;
3900 
3901   dummy    PLS_INTEGER;
3902   specname VARCHAR2(80);
3903   specvers NUMBER;
3904 
3905 BEGIN
3906 
3907   OPEN c_supp_vr;
3908   FETCH c_supp_vr INTO dummy, specname, specvers;
3909   IF c_supp_vr%FOUND THEN
3910     CLOSE c_supp_vr;
3911     FND_MESSAGE.SET_NAME('GMD', 'GMD_SUPP_VR_EXIST');
3912     FND_MESSAGE.SET_TOKEN('spec', specname);
3913     FND_MESSAGE.SET_TOKEN('vers', specvers);
3914     FND_MSG_PUB.ADD;
3915     RETURN TRUE;
3916   ELSE
3917     CLOSE c_supp_vr;
3918     RETURN FALSE;
3919   END IF;
3920 
3921 EXCEPTION
3922   -- Though there is no reason the program can reach
3923   -- here, this is coded just for the reasons we can
3924   -- not think of!
3925   WHEN OTHERS THEN
3926     FND_MESSAGE.SET_NAME('GMD', 'GMD_API_ERROR');
3927     FND_MESSAGE.SET_TOKEN('PACKAGE', 'GMD_SPEC_VRS_GRP.SUPP_VR_EXIST' );
3928     FND_MESSAGE.SET_TOKEN('ERROR', SUBSTR(SQLERRM,1,200));
3929     RETURN TRUE;
3930 
3931 END supp_vr_exist;
3932 
3933 /*===========================================================================
3934   PROCEDURE  NAME:	validate_before_delete_inv_vrs
3935 
3936   DESCRIPTION:		This procedure validates:
3937                         a) Primary key supplied
3938                         b) Inventory Spec VRS is not already delete_marked
3939 
3940   PARAMETERS:
3941 
3942   CHANGE HISTORY:	Created		09-JUL-02	KYH
3943 ===========================================================================*/
3944 
3945 PROCEDURE VALIDATE_BEFORE_DELETE_INV_VRS(
3946 	p_spec_id          IN NUMBER,
3947 	p_spec_vr_id       IN NUMBER,
3948 	x_return_status    OUT NOCOPY VARCHAR2,
3949         x_message_data     OUT NOCOPY VARCHAR2) IS
3950 
3951 l_progress           VARCHAR2(3);
3952 l_temp               VARCHAR2(1);
3953 l_inventory_spec_vrs GMD_INVENTORY_SPEC_VRS%ROWTYPE;
3954 l_inventory_spec_vrs_out GMD_INVENTORY_SPEC_VRS%ROWTYPE;
3955 
3956 BEGIN
3957 	l_progress := '010';
3958 	x_return_status := FND_API.G_RET_STS_SUCCESS ;
3959 
3960         -- validate for primary key
3961         -- ========================
3962 	IF p_spec_id IS NULL THEN
3963              GMD_API_PUB.Log_Message('GMD_SPEC_ID_REQUIRED');
3964 	     RAISE FND_API.G_EXC_ERROR;
3965         ELSE
3966              l_inventory_spec_vrs.spec_id := p_spec_id;
3967 	END IF;
3968 
3969 	IF p_spec_vr_id IS NULL THEN
3970              GMD_API_PUB.Log_Message('GMD_SPEC_VR_ID_REQUIRED');
3971 	     RAISE FND_API.G_EXC_ERROR;
3972         ELSE
3973              l_inventory_spec_vrs.spec_vr_id := p_spec_vr_id;
3974 	END IF;
3975 
3976         -- Fetch the row
3977         -- =============
3978         IF  NOT GMD_Inventory_Spec_VRS_PVT.Fetch_Row(l_inventory_spec_vrs,l_inventory_spec_vrs_out)
3979         THEN
3980           GMD_API_PUB.Log_Message('GMD_FAILED_TO_FETCH_ROW',
3981                               'l_table_name', 'GMD_INVENTORY_SPEC_VRS',
3982                               'l_column_name', 'SPEC_VR_ID',
3983                               'l_key_value', l_inventory_spec_vrs.spec_vr_id);
3984           RAISE FND_API.G_EXC_ERROR;
3985         END IF;
3986 
3987         l_inventory_spec_vrs := l_inventory_spec_vrs_out ;
3988 
3989         -- Terminate if the row is already delete marked
3990         -- =============================================
3991         IF l_inventory_spec_vrs.delete_mark <> 0
3992         THEN
3993           GMD_API_PUB.Log_Message('GMD_RECORD_DELETE_MARKED',
3994                               'l_table_name', 'GMD_INVENTORY_SPEC_VRS',
3995                               'l_column_name', 'SPEC_VR_ID',
3996                               'l_key_value', l_inventory_spec_vrs.spec_vr_id);
3997           RAISE FND_API.G_EXC_ERROR;
3998         END IF;
3999 
4000 
4001 EXCEPTION
4002 WHEN FND_API.G_EXC_ERROR THEN
4003       x_return_status := FND_API.G_RET_STS_ERROR ;
4004       x_message_data := FND_MSG_PUB.GET(FND_MSG_PUB.G_LAST,FND_API.G_FALSE);
4005 
4006 WHEN OTHERS THEN
4007       FND_MESSAGE.Set_Name('GMD','GMD_API_ERROR');
4008       FND_MESSAGE.Set_Token('PACKAGE','GMD_SPEC_GRP.VALIDATE_BEFORE_DELETE');
4009       FND_MESSAGE.Set_Token('ERROR', substr(sqlerrm,1,100));
4010       FND_MESSAGE.Set_Token('POSITION',l_progress );
4011       FND_MSG_PUB.ADD;
4012       x_message_data := FND_MSG_PUB.GET(FND_MSG_PUB.G_LAST,FND_API.G_FALSE);
4013       x_return_status := FND_API.G_RET_STS_UNEXP_ERROR;
4014 
4015 END VALIDATE_BEFORE_DELETE_INV_VRS ;
4016 
4017 /*===========================================================================
4018   PROCEDURE  NAME:	validate_before_delete_wip_vrs
4019 
4020   DESCRIPTION:		This procedure validates:
4021                         a) Primary key supplied
4022                         b) WIP Spec VRS is not already delete_marked
4023 
4024   PARAMETERS:
4025 
4026   CHANGE HISTORY:	Created		09-JUL-02	KYH
4027 ===========================================================================*/
4028 
4029 PROCEDURE VALIDATE_BEFORE_DELETE_WIP_VRS(
4030 	p_spec_id          IN NUMBER,
4031 	p_spec_vr_id       IN NUMBER,
4032 	x_return_status    OUT NOCOPY VARCHAR2,
4033         x_message_data     OUT NOCOPY VARCHAR2) IS
4034 
4035 l_progress           VARCHAR2(3);
4036 l_temp               VARCHAR2(1);
4037 l_wip_spec_vrs GMD_WIP_SPEC_VRS%ROWTYPE;
4038 l_wip_spec_vrs_out GMD_WIP_SPEC_VRS%ROWTYPE;
4039 
4040 BEGIN
4041 	l_progress := '010';
4042 	x_return_status := FND_API.G_RET_STS_SUCCESS ;
4043 
4044         -- validate for primary key
4045         -- ========================
4046 	IF p_spec_id IS NULL THEN
4047              GMD_API_PUB.Log_Message('GMD_SPEC_ID_REQUIRED');
4048 	     RAISE FND_API.G_EXC_ERROR;
4049         ELSE
4050              l_wip_spec_vrs.spec_id := p_spec_id;
4051 	END IF;
4052 
4053 	IF p_spec_vr_id IS NULL THEN
4054              GMD_API_PUB.Log_Message('GMD_SPEC_VR_ID_REQUIRED');
4055 	     RAISE FND_API.G_EXC_ERROR;
4056         ELSE
4057              l_wip_spec_vrs.spec_vr_id := p_spec_vr_id;
4058 	END IF;
4059 
4060         -- Fetch the row
4061         -- =============
4062         IF  NOT GMD_WIP_Spec_VRS_PVT.Fetch_Row(l_wip_spec_vrs,l_wip_spec_vrs_out)
4063         THEN
4064           GMD_API_PUB.Log_Message('GMD_FAILED_TO_FETCH_ROW',
4065                               'l_table_name', 'GMD_WIP_SPEC_VRS',
4066                               'l_column_name', 'SPEC_VR_ID',
4067                               'l_key_value', l_wip_spec_vrs.spec_vr_id);
4068           RAISE FND_API.G_EXC_ERROR;
4069         END IF;
4070 
4071         l_wip_spec_vrs := l_wip_spec_vrs_out ;
4072 
4073         -- Terminate if the row is already delete marked
4074         -- =============================================
4075         IF l_wip_spec_vrs.delete_mark <> 0
4076         THEN
4077           GMD_API_PUB.Log_Message('GMD_RECORD_DELETE_MARKED',
4078                               'l_table_name', 'GMD_WIP_SPEC_VRS',
4079                               'l_column_name', 'SPEC_VR_ID',
4080                               'l_key_value', l_wip_spec_vrs.spec_vr_id);
4081           RAISE FND_API.G_EXC_ERROR;
4082         END IF;
4083 
4084 
4085 EXCEPTION
4086 WHEN FND_API.G_EXC_ERROR THEN
4087       x_return_status := FND_API.G_RET_STS_ERROR ;
4088       x_message_data := FND_MSG_PUB.GET(FND_MSG_PUB.G_LAST,FND_API.G_FALSE);
4089 
4090 WHEN OTHERS THEN
4091       FND_MESSAGE.Set_Name('GMD','GMD_API_ERROR');
4092       FND_MESSAGE.Set_Token('PACKAGE','GMD_SPEC_GRP.VALIDATE_BEFORE_DELETE');
4093       FND_MESSAGE.Set_Token('ERROR', substr(sqlerrm,1,100));
4094       FND_MESSAGE.Set_Token('POSITION',l_progress );
4095       FND_MSG_PUB.ADD;
4096       x_message_data := FND_MSG_PUB.GET(FND_MSG_PUB.G_LAST,FND_API.G_FALSE);
4097       x_return_status := FND_API.G_RET_STS_UNEXP_ERROR;
4098 
4099 END VALIDATE_BEFORE_DELETE_WIP_VRS ;
4100 
4101 /*===========================================================================
4102   PROCEDURE  NAME:	validate_before_delete_cst_vrs
4103 
4104   DESCRIPTION:		This procedure validates:
4105                         a) Primary key supplied
4106                         b) Customer Spec VRS is not already delete_marked
4107 
4108   PARAMETERS:
4109 
4110   CHANGE HISTORY:	Created		09-JUL-02	KYH
4111 ===========================================================================*/
4112 
4113 PROCEDURE VALIDATE_BEFORE_DELETE_CST_VRS(
4114 	p_spec_id          IN NUMBER,
4115 	p_spec_vr_id       IN NUMBER,
4116 	x_return_status    OUT NOCOPY VARCHAR2,
4117         x_message_data     OUT NOCOPY VARCHAR2) IS
4118 
4119 l_progress           VARCHAR2(3);
4120 l_customer_spec_vrs GMD_CUSTOMER_SPEC_VRS%ROWTYPE;
4121 l_customer_spec_vrs_out GMD_CUSTOMER_SPEC_VRS%ROWTYPE;
4122 
4123 BEGIN
4124 	l_progress := '010';
4125 	x_return_status := FND_API.G_RET_STS_SUCCESS ;
4126 
4127         -- validate for primary key
4128         -- ========================
4129 	IF p_spec_id IS NULL THEN
4130              GMD_API_PUB.Log_Message('GMD_SPEC_ID_REQUIRED');
4131 	     RAISE FND_API.G_EXC_ERROR;
4132         ELSE
4133              l_customer_spec_vrs.spec_id := p_spec_id;
4134 	END IF;
4135 
4136 	IF p_spec_vr_id IS NULL THEN
4137              GMD_API_PUB.Log_Message('GMD_SPEC_VR_ID_REQUIRED');
4138 	     RAISE FND_API.G_EXC_ERROR;
4139         ELSE
4140              l_customer_spec_vrs.spec_vr_id := p_spec_vr_id;
4141 	END IF;
4142 
4143         -- Fetch the row
4144         -- =============
4145         IF  NOT GMD_Customer_Spec_VRS_PVT.Fetch_Row(l_customer_spec_vrs,l_customer_spec_vrs_out)
4146         THEN
4147           GMD_API_PUB.Log_Message('GMD_FAILED_TO_FETCH_ROW',
4148                               'l_table_name', 'GMD_CUSTOMER_SPEC_VRS',
4149                               'l_column_name', 'SPEC_VR_ID',
4150                               'l_key_value', l_customer_spec_vrs.spec_vr_id);
4151           RAISE FND_API.G_EXC_ERROR;
4152         END IF;
4153 
4154         l_customer_spec_vrs := l_customer_spec_vrs_out ;
4155 
4156         -- Terminate if the row is already delete marked
4157         -- =============================================
4158         IF l_customer_spec_vrs.delete_mark <> 0
4159         THEN
4160           GMD_API_PUB.Log_Message('GMD_RECORD_DELETE_MARKED',
4161                               'l_table_name', 'GMD_CUSTOMER_SPEC_VRS',
4162                               'l_column_name', 'SPEC_VR_ID',
4163                               'l_key_value', l_customer_spec_vrs.spec_vr_id);
4164           RAISE FND_API.G_EXC_ERROR;
4165         END IF;
4166 
4167 
4168 EXCEPTION
4169 WHEN FND_API.G_EXC_ERROR THEN
4170       x_return_status := FND_API.G_RET_STS_ERROR ;
4171       x_message_data := FND_MSG_PUB.GET(FND_MSG_PUB.G_LAST,FND_API.G_FALSE);
4172 
4173 WHEN OTHERS THEN
4174       FND_MESSAGE.Set_Name('GMD','GMD_API_ERROR');
4175       FND_MESSAGE.Set_Token('PACKAGE','GMD_SPEC_GRP.VALIDATE_BEFORE_DELETE');
4176       FND_MESSAGE.Set_Token('ERROR', substr(sqlerrm,1,100));
4177       FND_MESSAGE.Set_Token('POSITION',l_progress );
4178       FND_MSG_PUB.ADD;
4179       x_message_data := FND_MSG_PUB.GET(FND_MSG_PUB.G_LAST,FND_API.G_FALSE);
4180       x_return_status := FND_API.G_RET_STS_UNEXP_ERROR;
4181 
4182 END VALIDATE_BEFORE_DELETE_CST_VRS ;
4183 
4184 /*===========================================================================
4185   PROCEDURE  NAME:	validate_before_delete_sup_vrs
4186 
4187   DESCRIPTION:		This procedure validates:
4188                         a) Primary key supplied
4189                         b) Supplier Spec VRS is not already delete_marked
4190 
4191   PARAMETERS:
4192 
4193   CHANGE HISTORY:	Created		09-JUL-02	KYH
4194 ===========================================================================*/
4195 
4196 PROCEDURE VALIDATE_BEFORE_DELETE_SUP_VRS(
4197 	p_spec_id          IN NUMBER,
4198 	p_spec_vr_id       IN NUMBER,
4199 	x_return_status    OUT NOCOPY VARCHAR2,
4200         x_message_data     OUT NOCOPY VARCHAR2) IS
4201 
4202 l_progress           VARCHAR2(3);
4203 l_supplier_spec_vrs  GMD_SUPPLIER_SPEC_VRS%ROWTYPE;
4204 l_supplier_spec_vrs_out  GMD_SUPPLIER_SPEC_VRS%ROWTYPE;
4205 
4206 BEGIN
4207 	l_progress := '010';
4208 	x_return_status := FND_API.G_RET_STS_SUCCESS ;
4209 
4210         -- validate for primary key
4211         -- ========================
4212 	IF p_spec_id IS NULL THEN
4213              GMD_API_PUB.Log_Message('GMD_SPEC_ID_REQUIRED');
4214 	     RAISE FND_API.G_EXC_ERROR;
4215         ELSE
4216              l_supplier_spec_vrs.spec_id := p_spec_id;
4217 	END IF;
4218 
4219 	IF p_spec_vr_id IS NULL THEN
4220              GMD_API_PUB.Log_Message('GMD_SPEC_VR_ID_REQUIRED');
4221 	     RAISE FND_API.G_EXC_ERROR;
4222         ELSE
4223              l_supplier_spec_vrs.spec_vr_id := p_spec_vr_id;
4224 	END IF;
4225 
4226         -- Fetch the row
4227         -- =============
4228         IF  NOT GMD_Supplier_Spec_VRS_PVT.Fetch_Row(l_supplier_spec_vrs,l_supplier_spec_vrs_out)
4229         THEN
4230           GMD_API_PUB.Log_Message('GMD_FAILED_TO_FETCH_ROW',
4231                               'l_table_name', 'GMD_SUPPLIER_SPEC_VRS',
4232                               'l_column_name', 'SPEC_VR_ID',
4233                               'l_key_value', l_supplier_spec_vrs.spec_vr_id);
4234           RAISE FND_API.G_EXC_ERROR;
4235         END IF;
4236 
4237         l_supplier_spec_vrs := l_supplier_spec_vrs_out ;
4238 
4239         -- Terminate if the row is already delete marked
4240         -- =============================================
4241         IF l_supplier_spec_vrs.delete_mark <> 0
4242         THEN
4243           GMD_API_PUB.Log_Message('GMD_RECORD_DELETE_MARKED',
4244                               'l_table_name', 'GMD_SUPPLIER_SPEC_VRS',
4245                               'l_column_name', 'SPEC_VR_ID',
4246                               'l_key_value', l_supplier_spec_vrs.spec_vr_id);
4247           RAISE FND_API.G_EXC_ERROR;
4248         END IF;
4249 
4250 
4251 EXCEPTION
4252 WHEN FND_API.G_EXC_ERROR THEN
4253       x_return_status := FND_API.G_RET_STS_ERROR ;
4254       x_message_data := FND_MSG_PUB.GET(FND_MSG_PUB.G_LAST,FND_API.G_FALSE);
4255 
4256 WHEN OTHERS THEN
4257       FND_MESSAGE.Set_Name('GMD','GMD_API_ERROR');
4258       FND_MESSAGE.Set_Token('PACKAGE','GMD_SPEC_GRP.VALIDATE_BEFORE_DELETE');
4259       FND_MESSAGE.Set_Token('ERROR', substr(sqlerrm,1,100));
4260       FND_MESSAGE.Set_Token('POSITION',l_progress );
4261       FND_MSG_PUB.ADD;
4262       x_message_data := FND_MSG_PUB.GET(FND_MSG_PUB.G_LAST,FND_API.G_FALSE);
4263       x_return_status := FND_API.G_RET_STS_UNEXP_ERROR;
4264 
4265 END VALIDATE_BEFORE_DELETE_SUP_VRS ;
4266 
4267 /*===========================================================================
4268   PROCEDURE  NAME:	check_who
4269 
4270   DESCRIPTION:		This procedure validates the user_id
4271 
4272   PARAMETERS:
4273 
4274   CHANGE HISTORY:	Created		13-NOV-02	odaboval
4275 ===========================================================================*/
4276 PROCEDURE check_who( p_user_id  IN  NUMBER)
4277 IS
4278 
4279 CURSOR c_who (userid IN NUMBER) IS
4280 SELECT 1
4281 FROM fnd_user
4282 WHERE  user_id = userid;
4283 
4284 dummy    PLS_INTEGER;
4285 
4286 BEGIN
4287 
4288   IF (p_user_id IS NULL)
4289   THEN
4290     FND_MESSAGE.SET_NAME('GMD','GMD_WRONG_VALUE');
4291     FND_MESSAGE.SET_TOKEN('WHAT', 'USER_ID');
4292     FND_MSG_PUB.ADD;
4293     RAISE FND_API.G_EXC_ERROR;
4294   ELSE
4295     OPEN c_who( p_user_id);
4296     FETCH c_who
4297      INTO dummy;
4298 
4299     IF (c_who%NOTFOUND)
4300     THEN
4301       CLOSE c_who;
4302       FND_MESSAGE.SET_NAME('GMD','GMD_NOTFOUND');
4303       FND_MESSAGE.SET_TOKEN('WHAT', 'USER_ID');
4304       FND_MESSAGE.SET_TOKEN('VALUE', p_user_id);
4305       FND_MSG_PUB.ADD;
4306       RAISE FND_API.G_EXC_ERROR;
4307     END IF;
4308     CLOSE c_who;
4309   END IF;
4310 
4311 END check_who;
4312 
4313 
4314 /*===========================================================================
4315   PROCEDURE  NAME:	check_COA
4316 
4317   DESCRIPTION:		This procedure validates the Certificate Of Analysis fields
4318 
4319   PARAMETERS:
4320 
4321   CHANGE HISTORY:	Created		13-NOV-02	odaboval
4322 ===========================================================================*/
4323 PROCEDURE check_COA( p_coa_type              IN  VARCHAR2
4324                    , p_coa_at_ship_ind       IN VARCHAR2
4325                    , p_coa_at_invoice_ind    IN VARCHAR2
4326                    , p_coa_req_from_supl_ind IN VARCHAR2)
4327 IS
4328 
4329 CURSOR c_coa_type IS
4330 SELECT 1
4331 FROM gem_lookups
4332 WHERE lookup_type = 'GMD_QC_CERTIFICATE_TYPE'
4333 AND lookup_code = p_coa_type;
4334 
4335 dummy    PLS_INTEGER;
4336 
4337 BEGIN
4338 
4339 -- Value Check :
4340 -- The only value for these controls are (NULL, 'Y')
4341 IF (p_coa_at_ship_ind IS NOT NULL)
4342   AND (p_coa_at_ship_ind <> 'Y')
4343 THEN
4344    GMD_API_PUB.Log_Message('GMD_WRONG_VALUE',
4345                   'WHAT', 'coa_at_ship_ind value must be either NULL or Y');
4346    RAISE FND_API.G_EXC_ERROR;
4347 END IF;
4348 IF (p_coa_at_invoice_ind IS NOT NULL)
4349   AND (p_coa_at_invoice_ind <> 'Y')
4350 THEN
4351    GMD_API_PUB.Log_Message('GMD_WRONG_VALUE',
4352                   'WHAT', 'coa_at_invoice_ind value must be either NULL or Y');
4353    RAISE FND_API.G_EXC_ERROR;
4354 END IF;
4355 IF (p_coa_req_from_supl_ind IS NOT NULL)
4356   AND (p_coa_req_from_supl_ind <> 'Y')
4357 THEN
4358    GMD_API_PUB.Log_Message('GMD_WRONG_VALUE',
4359                   'WHAT', 'coa_req_from_supl_ind value must be either NULL or Y');
4360    RAISE FND_API.G_EXC_ERROR;
4361 END IF;
4362 IF (p_coa_type IS NOT NULL)
4363 THEN
4364   OPEN c_coa_type;
4365   FETCH c_coa_type
4366    INTO dummy;
4367   IF (c_coa_type%NOTFOUND)
4368   THEN
4369     CLOSE c_coa_type;
4370     FND_MESSAGE.Set_Name('GMD','GMD_NOTFOUND');
4371     FND_MESSAGE.Set_Token('WHAT', 'COA_TYPE');
4372     FND_MESSAGE.Set_Token('VALUE', p_coa_type);
4373     FND_MSG_PUB.Add;
4374     RAISE FND_API.G_EXC_ERROR;
4375   END IF;
4376   CLOSE c_coa_type;
4377 END IF;
4378 
4379 
4380 -- Functional Check :
4381 --=========================================================================
4382 -- COA :
4383 -- When COA_TYPE is NULL, then these following fields MUST be NULL :
4384 -- coa_at_ship_ind, coa_at_invoice_ind, coa_req_from_supl_ind
4385 --=========================================================================
4386 IF (p_coa_type IS NULL)
4387 THEN
4388    IF (p_coa_at_ship_ind IS NOT NULL)
4389    THEN
4390       GMD_API_PUB.Log_Message('GMD_WRONG_VALUE',
4391                               'WHAT', 'coa_at_ship_ind must be NULL');
4392       RAISE FND_API.G_EXC_ERROR;
4393    END IF;
4394 
4395    IF (p_coa_at_invoice_ind IS NOT NULL)
4396    THEN
4397       GMD_API_PUB.Log_Message('GMD_WRONG_VALUE',
4398                               'WHAT', 'coa_at_invoice_ind must be NULL');
4399       RAISE FND_API.G_EXC_ERROR;
4400    END IF;
4401 
4402    IF (p_coa_req_from_supl_ind IS NOT NULL)
4403    THEN
4404       GMD_API_PUB.Log_Message('GMD_WRONG_VALUE',
4405                               'WHAT', 'coa_req_from_supl_ind must be NULL');
4406       RAISE FND_API.G_EXC_ERROR;
4407    END IF;
4408 END IF;  -- coa_type is NULL
4409 
4410 END check_COA;
4411 
4412 /*===========================================================================
4413   PROCEDURE  NAME:	check_VR_controls
4414 
4415   DESCRIPTION:		This procedure validates the entries in the Controls group
4416 
4417   PARAMETERS:
4418 
4419   CHANGE HISTORY:	Created		13-NOV-02	odaboval
4420 
4421   Enhancement# 3476560. Added           04-MAY-04       Saikiran vankadari
4422   'Delayed Lot Entry' field to the signature.
4423    Added validation for 'Delayed Lot Entry' that
4424    it should be 'Y' or Null. Removed special validation
4425    for 'Lot Optional on sample' in case of WIP Validity rule.
4426 
4427   Bug# 3652938.                         28-MAY-04       Saikiran vankadari
4428  Added validation for the invalid combination of
4429  'Lot Optional on Sample' and 'Delayed Lot Entry'.
4430 
4431  Convergence changes                11-Apr-05           Saikiran Vankadari
4432 
4433  Bug # 4900420                         27-DEC-05  RLNAGARA
4434   Removed the code which was validating the control_lot_attributes when lot_optional_on_sample was not NULL
4435 ===========================================================================*/
4436 PROCEDURE check_VR_Controls
4437                    ( p_VR_type                  IN VARCHAR2
4438                    , p_lot_optional_on_sample   IN VARCHAR2
4439 		   , p_delayed_lot_entry        IN VARCHAR2 DEFAULT NULL
4440                    , p_sample_inv_trans_ind     IN VARCHAR2
4441                    , p_lot_ctl                  IN NUMBER
4442                    , p_status_ctl               IN VARCHAR2
4443                    , p_control_lot_attrib_ind   IN VARCHAR2
4444                    , p_in_spec_lot_status_id    IN NUMBER
4445                    , p_out_of_spec_lot_status_id IN NUMBER
4446                    , p_control_batch_step_ind   IN VARCHAR2
4447 		   , p_auto_complete_batch_step IN VARCHAR2 DEFAULT NULL  -- Bug# 5440347
4448 		   , p_delayed_lpn_entry        IN VARCHAR2 DEFAULT NULL) IS  --RLNAGARA LPN ME 7027149
4449 
4450 CURSOR c_lot_status (lot_status_id IN VARCHAR2) IS
4451 SELECT 1
4452 FROM mtl_material_statuses
4453 WHERE NVL(enabled_flag,0) = 1
4454 AND   status_id = lot_status_id;
4455 
4456 dummy              PLS_INTEGER;
4457 
4458 BEGIN
4459 
4460 -- Value Check :
4461 -- The only value for these controls are (NULL, 'Y')
4462 IF (p_lot_optional_on_sample IS NOT NULL)
4463   AND (p_lot_optional_on_sample <> 'Y')
4464 THEN
4465    GMD_API_PUB.Log_Message('GMD_WRONG_VALUE',
4466                   'WHAT', 'lot_optional_on_sample value must be either NULL or Y');
4467    RAISE FND_API.G_EXC_ERROR;
4468 END IF;
4469 
4470 --Enhancement# 3476560. Added validation for 'Delayed Lot Entry' that it should be 'Y' or Null.
4471 IF (p_delayed_lot_entry IS NOT NULL)
4472   AND(p_delayed_lot_entry<>'Y')
4473 THEN
4474   GMD_API_PUB.Log_Message('GMD_WRONG_VALUE',
4475                  'WHAT', 'delayed_lot_entry value must be either NULL or Y');
4476   RAISE FND_API.G_EXC_ERROR;
4477 END IF;
4478 
4479 --RLNAGARA LPN ME 7027149 start
4480 
4481 IF (p_delayed_lpn_entry IS NOT NULL) AND (p_delayed_lpn_entry <> 'Y') THEN
4482   GMD_API_PUB.Log_Message('GMD_WRONG_VALUE',
4483                  'WHAT', 'delayed_lpn_entry value must be either NULL or Y');
4484   RAISE FND_API.G_EXC_ERROR;
4485 END IF;
4486 
4487 IF (p_VR_type IN ('CUSTOMER') AND (p_delayed_lpn_entry IS NOT NULL)) THEN
4488   GMD_API_PUB.Log_Message('GMD_WRONG_VALUE',
4489                  'WHAT', 'delayed_lpn_entry value must be either NULL for CUSTOMER VRs');
4490   RAISE FND_API.G_EXC_ERROR;
4491 END IF;
4492 
4493 --RLNAGARA LPN ME 7027149 end
4494 
4495 --Bug# 3652938. Added validation for the invalid combination of 'Lot Optional on Sample' and 'Delayed Lot Entry'.
4496 IF (p_lot_optional_on_sample IS NULL)
4497   AND(p_delayed_lot_entry = 'Y')
4498 THEN
4499   GMD_API_PUB.Log_Message('GMD_WRONG_VALUE',
4500                  'WHAT', 'delayed_lot_entry value cannot be Y when lot_optional_on_sample is NULL');
4501   RAISE FND_API.G_EXC_ERROR;
4502 END IF;
4503 
4504 IF (p_VR_type IN ('INVENTORY', 'WIP','SUPPLIER'))
4505 THEN
4506   IF (p_control_lot_attrib_ind IS NOT NULL)
4507     AND (p_control_lot_attrib_ind <> 'Y')
4508   THEN
4509      GMD_API_PUB.Log_Message('GMD_WRONG_VALUE',
4510                   'WHAT', 'control_lot_attrib_ind value must be either NULL or Y');
4511      RAISE FND_API.G_EXC_ERROR;
4512   END IF;
4513 
4514   IF (p_sample_inv_trans_ind IS NOT NULL)
4515     AND (p_sample_inv_trans_ind <> 'Y')
4516   THEN
4517     GMD_API_PUB.Log_Message('GMD_WRONG_VALUE',
4518                   'WHAT', 'sample_inv_trans_ind value must be either NULL or Y');
4519     RAISE FND_API.G_EXC_ERROR;
4520   END IF;
4521 
4522   -- Extra field for WIP :
4523   IF (p_VR_type = 'WIP')
4524   THEN
4525     IF (p_control_batch_step_ind IS NOT NULL)
4526       AND (p_control_batch_step_ind <> 'Y')
4527     THEN
4528        GMD_API_PUB.Log_Message('GMD_WRONG_VALUE',
4529                   'WHAT', 'control_batch_step_ind value must be either NULL or Y');
4530        RAISE FND_API.G_EXC_ERROR;
4531     END IF;
4532 
4533     -- Bug# 5440347 start
4534     IF (p_auto_complete_batch_step IS NOT NULL)
4535       AND (p_auto_complete_batch_step <> 'Y')
4536     THEN
4537        GMD_API_PUB.Log_Message('GMD_WRONG_VALUE',
4538                   'WHAT', 'auto_complete_batch_step value must be either NULL or Y');
4539        RAISE FND_API.G_EXC_ERROR;
4540     END IF;
4541     -- Bug# 5440347 end
4542 
4543 
4544     --Enhancement# 3476560. Removed special validation for 'Lot Optional on sample'.
4545     --IF ( p_lot_optional_on_sample IS NOT NULL)
4546     --THEN
4547     --   GMD_API_PUB.Log_Message('GMD_WRONG_VALUE',
4548     --                         'WHAT', 'lot_optional_on_sample must be NULL');
4549     --   RAISE FND_API.G_EXC_ERROR;
4550     --END IF;
4551 
4552   END IF;
4553 
4554 END IF;
4555 
4556 -- Functional Check :
4557 -- Bug 2698118 : When non-lot-controlled item then lot_optional_on_sample MUST be NULL
4558 IF (p_lot_ctl = 1) AND (p_lot_optional_on_sample IS NOT NULL)
4559 THEN
4560    GMD_API_PUB.Log_Message('GMD_WRONG_VALUE',
4561              'WHAT', 'For a non controlled item, lot_optional_on_sample must be NULL');
4562    RAISE FND_API.G_EXC_ERROR;
4563 END IF;
4564 
4565 IF (p_VR_type IN ('INVENTORY', 'WIP','SUPPLIER'))
4566 THEN
4567   IF (p_lot_optional_on_sample IS NOT NULL ) THEN
4568        IF (p_sample_inv_trans_ind IS NOT NULL)
4569        THEN
4570           GMD_API_PUB.Log_Message('GMD_WRONG_VALUE',
4571                                 'WHAT', 'sample_inv_trans_ind must be NULL');
4572           RAISE FND_API.G_EXC_ERROR;
4573        END IF;
4574 
4575 --RLNAGARA Bug # 4900420 Removed the validation code for control_lot_attributes
4576 
4577        -- A special extra field for WIP :
4578        -- Bug# 5440347
4579        -- control_batch_step_ind is not dependent on lot_optional_on_sample.
4580        /*IF (p_VR_type = 'WIP')
4581        THEN
4582          IF (p_control_batch_step_ind IS NOT NULL)
4583          THEN
4584           GMD_API_PUB.Log_Message('GMD_WRONG_VALUE',
4585                                   'WHAT', 'control_batch_step_ind must be NULL');
4586           RAISE FND_API.G_EXC_ERROR;
4587          END IF;
4588        END IF;*/
4589   ELSE --p_lot_optional_on_sample IS NULL
4590 
4591     --=========================================================================
4592     -- status_ctl :
4593     -- When the item is NOT status_ctl, then these fields MUST be NULL :
4594     --  control_lot_attrib_ind, in_spec_lot_status_id, out_of_spec_lot_status_id
4595     --=========================================================================
4596     IF (p_status_ctl = 'N')
4597     THEN
4598        --=========================================================================
4599        -- In this case, these fields MUST be NULL :
4600        --  control_lot_attrib_ind, in_spec_lot_status_id, out_of_spec_lot_status_id
4601        --=========================================================================
4602        IF (p_control_lot_attrib_ind IS NOT NULL)
4603        THEN
4604           GMD_API_PUB.Log_Message('GMD_WRONG_VALUE',
4605                                 'WHAT', 'control_lot_attrib_ind must be NULL');
4606           RAISE FND_API.G_EXC_ERROR;
4607        END IF;
4608 
4609        IF (p_in_spec_lot_status_id IS NOT NULL)
4610        THEN
4611           GMD_API_PUB.Log_Message('GMD_WRONG_VALUE',
4612                                   'WHAT', 'in_spec_lot_status_id must be NULL');
4613           RAISE FND_API.G_EXC_ERROR;
4614        END IF;
4615 
4616        IF (p_out_of_spec_lot_status_id IS NOT NULL)
4617        THEN
4618           GMD_API_PUB.Log_Message('GMD_WRONG_VALUE',
4619                                   'WHAT', 'out_of_spec_lot_status_id must be NULL');
4620           RAISE FND_API.G_EXC_ERROR;
4621        END IF;
4622     ELSE --p_status_ctl <> 'N'
4623       IF (p_control_lot_attrib_ind IS NULL)
4624       THEN
4625        --=========================================================================
4626        -- In this case, these fields MUST be NULL :
4627        --  in_spec_lot_status_id, out_of_spec_lot_status_id
4628        --=========================================================================
4629        IF (p_in_spec_lot_status_id IS NOT NULL)
4630        THEN
4631           GMD_API_PUB.Log_Message('GMD_WRONG_VALUE',
4632                                   'WHAT', 'in_spec_lot_status_id must be NULL');
4633           RAISE FND_API.G_EXC_ERROR;
4634        END IF;
4635 
4636        IF (p_out_of_spec_lot_status_id IS NOT NULL)
4637        THEN
4638           GMD_API_PUB.Log_Message('GMD_WRONG_VALUE',
4639                                   'WHAT', 'out_of_spec_lot_status_id must be NULL');
4640           RAISE FND_API.G_EXC_ERROR;
4641        END IF;
4642       ELSE
4643          --=========================================================================
4644          -- In this case, control_lot_attrib_ind IS NOT NULL,
4645          --   then these fields are MANDATORY :
4646          --       in_spec_lot_status_id, out_of_spec_lot_status_id
4647          --=========================================================================
4648          -- Check the values of in_spec_lot_status_id and out_of_spec_lot_status_id
4649          IF (p_in_spec_lot_status_id IS NULL)
4650          THEN
4651            GMD_API_PUB.Log_Message('GMD_WRONG_VALUE',
4652                                    'WHAT', 'in_spec_lot_status_id is MANDATORY');
4653            RAISE FND_API.G_EXC_ERROR;
4654          ELSE
4655            OPEN c_lot_status(p_in_spec_lot_status_id);
4656            FETCH c_lot_status INTO dummy;
4657            IF (c_lot_status%NOTFOUND)
4658            THEN
4659              CLOSE c_lot_status;
4660              FND_MESSAGE.SET_NAME('GMD','GMD_NOTFOUND');
4661              FND_MESSAGE.SET_TOKEN('WHAT', 'IN_SPEC_LOT_STATUS_ID');
4662              FND_MESSAGE.SET_TOKEN('VALUE', p_in_spec_lot_status_id);
4663              FND_MSG_PUB.ADD;
4664              RAISE FND_API.G_EXC_ERROR;
4665            END IF;
4666            CLOSE c_lot_status;
4667          END IF;   -- in_spec_lot_status IS NULL
4668 
4669          IF (p_out_of_spec_lot_status_id IS NULL)
4670          THEN
4671            GMD_API_PUB.Log_Message('GMD_WRONG_VALUE',
4672                                    'WHAT', 'out_of_spec_lot_status_id is MANDATORY');
4673            RAISE FND_API.G_EXC_ERROR;
4674          ELSE
4675            OPEN c_lot_status(p_out_of_spec_lot_status_id);
4676            FETCH c_lot_status INTO dummy;
4677            IF (c_lot_status%NOTFOUND)
4678            THEN
4679              CLOSE c_lot_status;
4680              FND_MESSAGE.SET_NAME('GMD','GMD_NOTFOUND');
4681              FND_MESSAGE.SET_TOKEN('WHAT', 'OUT_OF_SPEC_LOT_STATUS_ID');
4682              FND_MESSAGE.SET_TOKEN('VALUE', p_out_of_spec_lot_status_id);
4683              FND_MSG_PUB.ADD;
4684              RAISE FND_API.G_EXC_ERROR;
4685            END IF;
4686            CLOSE c_lot_status;
4687          END IF;   -- out_of_spec_lot_status_id IS NULL
4688       END IF;    -- control_lot_attrib_ind IS NOT NULL
4689     END IF;   -- status_ctl
4690   END IF;    -- lot_optional_on_sample IS NOT NULL
4691 END IF;   --- p_VR_type IN ('INVENTORY', 'WIP')
4692 
4693 END check_VR_controls;
4694 
4695 
4696 --RLNAGARA LPN ME 7027149 Added this function
4697 FUNCTION check_wms_enabled(p_organization_id IN NUMBER)
4698 RETURN BOOLEAN IS
4699 l_wms_enabled_flag VARCHAR2(1);
4700 BEGIN
4701  SELECT NVL(wms_enabled_flag,'N')
4702  INTO l_wms_enabled_flag
4703  FROM mtl_parameters
4704  WHERE organization_id = p_organization_id;
4705 
4706  IF l_wms_enabled_flag = 'Y' THEN
4707    RETURN TRUE;
4708  ELSE
4709    RETURN FALSE;
4710  END IF;
4711 
4712 END check_wms_enabled;
4713 
4714 END GMD_SPEC_VRS_GRP;