DBA Data[Home] [Help]

PACKAGE BODY: APPS.GML_REQIMPORT_GRP

Source


1 PACKAGE BODY GML_ReqImport_GRP AS
2 /* $Header: GMLGREQB.pls 115.2 2003/11/05 18:34:07 pbamb noship $*/
3 
4 -----------------------------------------------------------------------
5 --Start of Comments
6 --Name: Validate_Requisition_Grp
7 --Pre-reqs:
8 --Modifies: po_requisitions_interface
9 --Locks:
10 --  None
11 --Function: validates OPM columns of interface records in po_requisitions_interface
12 --Parameters:
13 --IN:
14 --p_api_version
15 --  API Version the caller thinks this API is on
16 --p_init_msg_list
17 --  Whether the message stack should get initialized within the procedure
18 --p_commit
19 --  Whether the API should commit
20 --p_request_id
21 --  group of records to be validated per concurrent request identified by this id
22 --IN OUT:
23 --OUT:
24 --x_return_status
25 --  status of the procedure (FND_API.G_RET_STS_SUCCESS indicates a success,
26 --  otherwise there is an error occurred)
27 --x_msg_count
28 --  Number of messages in the stack
29 --x_msg_data
30 --  If x_msg_count is 1, this out parameter will be populated with that msg
31 --Returns:
32 --Notes:
33 --Testing:
34 --End of Comments
35 ------------------------------------------------------------------------
36 
37 PROCEDURE Validate_Requisition_Grp
38 ( p_api_version         IN               NUMBER
39 , p_init_msg_list    	IN  VARCHAR2 :=  FND_API.G_FALSE
40 , p_validation_level 	IN  NUMBER   :=  FND_API.G_VALID_LEVEL_FULL
41 , p_commit           	IN  VARCHAR2 :=  FND_API.G_FALSE
42 , p_request_id		IN 		 NUMBER
43 , x_return_status       OUT NOCOPY       VARCHAR2
44 , x_msg_count           OUT NOCOPY       NUMBER
45 , x_msg_data            OUT NOCOPY       VARCHAR2
46 )
47 
48 
49 IS
50   l_api_name            CONSTANT VARCHAR2(30)   := 'Validate_Requisiton_Grp';
51   l_api_version         CONSTANT NUMBER         := 1.0 ;
52 
53 
54 
55   l_secondary_unit_of_measure VARCHAR2(25);
56   l_passed_secondary_uom VARCHAR2(25);
57   l_secondary_quantity  NUMBER;
58   l_ret_val	        NUMBER;
59   l_opm_status		VARCHAR2(2);
60   l_opm_ind		VARCHAR2(2);
61   l_opm_ora_schema	VARCHAR2(31);
62   l_return_val	        BOOLEAN;
63 
64   l_rec PO_INTERFACE_ERRORS%ROWTYPE;
65   l_rtn_status VARCHAR2(1);
66   l_msg_count NUMBER;
67   l_msg_data VARCHAR2(2000);
68   l_row_id ROWID;
69 
70   v_item_no		VARCHAR(32);
71   v_item_um		VARCHAR(25);
72   v_item_um2		VARCHAR(25);
73   v_opm_item_id		NUMBER;
74   v_dualum_ind		NUMBER;
75   v_grade_ctl		NUMBER;
76   v_qc_grade		VARCHAR2(4);
77 
78   v_dummy		VARCHAR2(100);
79 
80   v_opm_item	        BOOLEAN := FALSE;
81   v_process_dest_org    VARCHAR2(2) := 'N';
82   v_process_source_org  VARCHAR2(2) := 'N';
83   v_header_processable_flag VARCHAR2(1) := 'N';
84 
85   v_uom_error		BOOLEAN := FALSE;
86 
87 Cursor Cr_int_req IS
88 Select	pri.rowid,
89         pri.transaction_id,
90         pri.source_type_code,
91 	pri.source_organization_id,
92 	pri.destination_organization_id,
93 	pri.item_id,
94 	pri.secondary_unit_of_measure,
95 	pri.secondary_uom_code,
96 	pri.secondary_quantity,
97 	pri.quantity,
98 	pri.preferred_grade
99 From	po_requisitions_interface pri
100 Where   pri.request_id = p_request_id
101 FOR UPDATE OF pri.secondary_unit_of_measure;
102 
103 Cursor Cr_opm_item_attr(p_inv_item_id IN NUMBER,p_organization_id IN NUMBER) IS
104 Select	i.item_id,
105 	i.item_no,
106 	i.dualum_ind,
107 	i.grade_ctl,
108 	i.item_um,
109 	i.item_um2
110 From	ic_item_mst i,
111 	mtl_system_items m
112 Where	m.inventory_item_id = p_inv_item_id
113 And	m.segment1 = i.item_no
114 And     m.organization_id = p_organization_id;
115 
116 BEGIN
117 
118   IF FND_API.to_boolean(p_init_msg_list) THEN
119     FND_MSG_PUB.Initialize;
120   END IF;
121 
122   -- Standard call to check for call compatibility.
123   IF NOT FND_API.Compatible_API_Call (   l_api_version,
124                                          p_api_version,
125                                          l_api_name   ,
126                                          G_PKG_NAME
127                                      ) THEN
128     RAISE FND_API.G_EXC_UNEXPECTED_ERROR;
129   END IF;
130 
131   x_return_status :=FND_API.G_RET_STS_SUCCESS;
132 
133   --cache in the opm installed status
134   IF G_OPM_INSTALLED IS NULL THEN
135      l_return_val := fnd_installation.get_app_info ('GMI',l_opm_status,l_opm_ind, l_opm_ora_schema);
136      G_OPM_INSTALLED := l_opm_status;
137   END IF;
138 
139   --do validations only if opm and common receiving are installed
140   --return true if in case opm is not installed or common receiving is not installed
141   IF G_OPM_INSTALLED <> 'I' OR NOT gml_po_for_process.check_po_for_proc THEN
142      RETURN;
143   END IF;
144 
145 --Loop for every record in the interface table for the current concurrent request.
146 FOR Cr_rec IN Cr_int_req LOOP
147 
148   l_secondary_unit_of_measure := NULL;
149   l_passed_secondary_uom := NULL;
150   l_secondary_quantity  := NULL;
151   l_ret_val	        := NULL;
152 
153   v_item_no		:= NULL;
154   v_item_um		:= NULL;
155   v_item_um2		:= NULL;
156   v_opm_item_id		:= NULL;
157   v_dualum_ind		:= NULL;
158   v_grade_ctl		:= NULL;
159   v_qc_grade		:= NULL;
160 
161   v_dummy		:= NULL;
162 
163   v_opm_item	        := FALSE;
164   v_process_dest_org    := 'N';
165   v_process_source_org  := 'N';
166 
167   --Only where item_id is specified.
168   IF Cr_rec.item_id IS NOT NULL THEN
169 
170     --initialize uom error flag
171     v_uom_error := FALSE;
172 
173     -- Check if item is OPM
174     BEGIN
175        OPEN Cr_opm_item_attr(cr_rec.item_id, cr_rec.destination_organization_id);
176        FETCH Cr_opm_item_attr INTO v_opm_item_id,
177        				   v_item_no,
178        				   v_dualum_ind,
179   	       			   v_grade_ctl,
180   	       			   v_item_um,
181   	       			   v_item_um2;
182        IF  Cr_opm_item_attr%NOTFOUND THEN
183   	v_opm_item := FALSE;
184        ELSE
185   	v_opm_item := TRUE;
186        END IF;
187 
188        CLOSE Cr_opm_item_attr;
189     END;
190 
191     --check whether destination organization is process.
192     v_process_dest_org   := po_gml_db_common.check_process_org(cr_rec.destination_organization_id);
193 
194     -- Error out if discrete items ordered in process organizations.
195     IF NOT v_opm_item and v_process_dest_org = 'Y' THEN
196        l_rec.interface_type     := 'REQIMPORT';
197        l_rec.interface_transaction_id       := cr_rec.transaction_id;
198        l_rec.column_name        := 'ITEM_ID';
199        l_rec.table_name        := 'PO_REQUISITIONS_INTERFACE';
200        l_rec.error_message_name := 'GML_OPM_ITEM_NOT_EXIST';
201 
202        fnd_message.set_name('GML', l_rec.error_message_name);
203        l_rec.error_message := FND_MESSAGE.get;
204 
205        PO_INTERFACE_ERRORS_GRP.log_error
206        ( p_api_version => 1.0,
207          p_init_msg_list => FND_API.G_TRUE,
208          x_return_status => l_rtn_status,
209          x_msg_count => l_msg_count,
210          x_msg_data => l_msg_data,
211          p_rec => l_rec,
212          x_row_id => l_row_id);
213 
214        IF (l_rtn_status <> FND_API.G_RET_STS_SUCCESS) THEN
215          x_msg_count := l_msg_count;
216          x_msg_data  := l_msg_data;
217          x_return_status := l_rtn_status;
218          RAISE FND_API.G_EXC_UNEXPECTED_ERROR;
219        END IF;
220     END IF;
221 
222     --Internal Orders
223     --Validate that if destination org is discrete
224     --then the source organization is also discrete else log exception
225     --validate source and destination organization to be both either process or discrete
226     --validate source and destination organization are process and not same
227     IF cr_rec.source_type_code = 'INVENTORY' THEN
228 
229        v_process_source_org   := po_gml_db_common.check_process_org(cr_rec.source_organization_id);
230 
231        IF (v_process_dest_org = 'N' AND v_process_source_org = 'Y' )
232         OR (v_process_dest_org = 'Y' AND v_process_source_org = 'N' )
233        THEN
234           l_rec.interface_type 	  := 'REQIMPORT';
235           l_rec.interface_transaction_id 	  := cr_rec.transaction_id;
236           l_rec.column_name        := 'SOURCE_ORGANIZATION_ID';
237           l_rec.table_name         := 'PO_REQUISITIONS_INTERFACE';
238           l_rec.error_message_name := 'GML_INVALID_ORG_TYPE_COMB';
239 
240           fnd_message.set_name('GML', l_rec.error_message_name);
241           l_rec.error_message := FND_MESSAGE.get;
242 
243           PO_INTERFACE_ERRORS_GRP.log_error
244           ( p_api_version => 1.0,
245             p_init_msg_list => FND_API.G_TRUE,
246             x_return_status => l_rtn_status,
247             x_msg_count => l_msg_count,
248             x_msg_data => l_msg_data,
249             p_rec => l_rec,
250             x_row_id => l_row_id);
251 
252           IF (l_rtn_status <> FND_API.G_RET_STS_SUCCESS) THEN
253              x_msg_count := l_msg_count;
254              x_msg_data  := l_msg_data;
255              x_return_status := l_rtn_status;
256              RAISE FND_API.G_EXC_UNEXPECTED_ERROR;
257           END IF;
258 
259        ELSIF  (v_process_dest_org = 'Y' AND v_process_source_org = 'Y' )
260        THEN
261           IF cr_rec.destination_organization_id = cr_rec.source_organization_id
262           THEN
263              l_rec.interface_type     := 'REQIMPORT';
264              l_rec.interface_transaction_id 	     := cr_rec.transaction_id;
265              l_rec.column_name        := 'SOURCE_ORGANIZATION_ID';
266              l_rec.table_name         := 'PO_REQUISITIONS_INTERFACE';
267              l_rec.error_message_name := 'GML_SAME_SOURCE_DEST_ORG';
268 
269              fnd_message.set_name('GML', l_rec.error_message_name);
270              l_rec.error_message := FND_MESSAGE.get;
271 
272              PO_INTERFACE_ERRORS_GRP.log_error
273               ( p_api_version => 1.0,
274                 p_init_msg_list => FND_API.G_TRUE,
275                 x_return_status => l_rtn_status,
276                 x_msg_count => l_msg_count,
277                 x_msg_data => l_msg_data,
278                 p_rec => l_rec,
279                 x_row_id => l_row_id);
280 
281              IF (l_rtn_status <> FND_API.G_RET_STS_SUCCESS) THEN
282                 x_msg_count := l_msg_count;
283                 x_msg_data  := l_msg_data;
284                 x_return_status := l_rtn_status;
285                 RAISE FND_API.G_EXC_UNEXPECTED_ERROR;
286              END IF;
287            END IF; /*cr_rec.destination_organization_id = cr_rec.source_organization_id */
288         END IF; /*(v_process_dest_org = 'Y' AND v_process_source_org = 'Y' )*/
289      END IF; /*cr_rec.source_type = 'INVENTORY'*/
290 
291       --If destination is process then check
292       --1. if either secondary unit of measure is specified or secondary uom code is specified then derive the other
293       --2. if secondary unit of measure and secondary quantity are null for opm item with dual type
294       --   greater than 1 then populate secondary unit of measure and compute secondary quantity
295       --3. if either secondary unit of measure or secondary quantity is null then populate or compute the other
296       --4. if item is dual uom type 2 or 3 then check for deviation between secondary and transaction qty
297       --5. if item is not grade controlled and preferred_grade is populated then log error for that transaction
298       --6. if secondary unit of measure is specified then check its validity
299 
300       IF v_opm_item AND v_process_dest_org = 'Y' THEN
301 
302          --get secondary_unit_of_measure from secondary_uom_code
303          IF cr_rec.secondary_uom_code IS NOT NULL and cr_rec.secondary_unit_of_measure is NULL
304             AND v_dualum_ind > 0
305          THEN
306             l_secondary_unit_of_measure := po_gml_db_common.get_apps_uom_code(v_item_um2);
307 
308             BEGIN
309                SELECT mum.unit_of_measure
310                INTO   l_passed_secondary_uom
311                FROM   mtl_units_of_measure mum
312                WHERE  mum.uom_code = cr_rec.secondary_uom_code;
313 
314                EXCEPTION WHEN NO_DATA_FOUND THEN
315     	          --mark that there is an error	to avoid quantity validations.
316     	          v_uom_error := TRUE;
317             END;
318 
319             --Invalid secondary uom_code or the secondary uom code is not of the item specified.
320             IF (l_passed_secondary_uom <> l_secondary_unit_of_measure) OR v_uom_error THEN
321                l_rec.interface_type     := 'REQIMPORT';
322                l_rec.interface_transaction_id 	     := cr_rec.transaction_id;
323                l_rec.column_name        := 'SECONDARY_UOM_CODE';
324                l_rec.table_name         := 'PO_REQUISITIONS_INTERFACE';
325                l_rec.error_message_name := 'GML_INVALID_SECONDARY_UOM';
326 
327                fnd_message.set_name('GML', l_rec.error_message_name);
328                l_rec.error_message := FND_MESSAGE.get;
329 
330                PO_INTERFACE_ERRORS_GRP.log_error
331                  ( p_api_version => 1.0,
332                    p_init_msg_list => FND_API.G_TRUE,
333                    x_return_status => l_rtn_status,
334                    x_msg_count => l_msg_count,
335                    x_msg_data => l_msg_data,
336                    p_rec => l_rec,
337                    x_row_id => l_row_id);
338 
339                IF (l_rtn_status <> FND_API.G_RET_STS_SUCCESS) THEN
340                   x_msg_count := l_msg_count;
341                   x_msg_data  := l_msg_data;
342                   x_return_status := l_rtn_status;
343                   RAISE FND_API.G_EXC_UNEXPECTED_ERROR;
344                END IF;
345   	       --mark that there is an error	to avoid quantity validations.
346   	       v_uom_error := TRUE;
347 
348             ELSE
349 
350                --if uom code is correct update the unit of measure.
351                UPDATE po_requisitions_interface pri
352                SET    pri.secondary_unit_of_measure = l_secondary_unit_of_measure
353                WHERE  rowid = cr_rec.rowid;
354 
355             END IF;
356 
357          --If both secondary uom and unit of measure are null then populate unit of measure
358          ELSIF cr_rec.secondary_uom_code IS NULL and cr_rec.secondary_unit_of_measure is NULL
359            AND v_dualum_ind > 0
360          THEN
361 
362             l_secondary_unit_of_measure := po_gml_db_common.get_apps_uom_code(v_item_um2);
363 
364             UPDATE po_requisitions_interface pri
365             SET pri.secondary_unit_of_measure = l_secondary_unit_of_measure
366             WHERE  rowid = cr_rec.rowid;
367 
368             --If unit of measure is provided then validate it.
369          ELSIF cr_rec.secondary_unit_of_measure is NOT NULL
370          THEN
371             l_secondary_unit_of_measure := po_gml_db_common.get_apps_uom_code(v_item_um2);
372 
373             --validate secondary_unit_of_measure
374             --error if its not valid or its different than Items secondary unit of measure
375             IF  cr_rec.secondary_unit_of_measure <> l_secondary_unit_of_measure THEN
376                --log error that unit of measure is not correct.
377                l_rec.interface_type     := 'REQIMPORT';
378                l_rec.interface_transaction_id 	     := cr_rec.transaction_id;
379                l_rec.column_name        := 'SECONDARY_UNIT_OF_MEASURE';
380                l_rec.table_name         := 'PO_REQUISITIONS_INTERFACE';
381                l_rec.error_message_name := 'GML_INVALID_SECONDARY_UOM';
382 
383                fnd_message.set_name('GML', l_rec.error_message_name);
384                l_rec.error_message := FND_MESSAGE.get;
385 
386                PO_INTERFACE_ERRORS_GRP.log_error
387                  ( p_api_version => 1.0,
388                    p_init_msg_list => FND_API.G_TRUE,
389                    x_return_status => l_rtn_status,
390                    x_msg_count => l_msg_count,
391                    x_msg_data => l_msg_data,
392                    p_rec => l_rec,
393                    x_row_id => l_row_id);
394 
395                 IF (l_rtn_status <> FND_API.G_RET_STS_SUCCESS) THEN
396                    x_msg_count := l_msg_count;
397                    x_msg_data  := l_msg_data;
398                    x_return_status := l_rtn_status;
399                    RAISE FND_API.G_EXC_UNEXPECTED_ERROR;
400                 END IF;
401     	      --mark that there is an error	to avoid quantity validations.
402     	      v_uom_error := TRUE;
403 
404              END IF;
405           END IF;
406 
407           --If secondary quantity is not provided and compute it and update interface table.
408           --only if the unit of measure is correctly validated 0 use falg v_uom_error
409           IF cr_rec.secondary_quantity IS NULL AND v_dualum_ind > 0 AND NOT v_uom_error THEN
410 
411                 po_gml_db_common.VALIDATE_QUANTITY(
412                                   v_opm_item_id,
413                                   v_dualum_ind,
414                                   cr_rec.quantity,
415                                   v_item_um,
416                                   v_item_um2,
417                                   l_secondary_quantity) ;
418 
419                 UPDATE po_requisitions_interface
420                 SET  secondary_unit_of_measure = nvl(secondary_unit_of_measure,l_secondary_unit_of_measure),
421                      secondary_quantity = l_secondary_quantity
422                 WHERE  rowid = cr_rec.rowid;
423 
424           --Else if secondary qty is provided then in case of duam um 1 just update it
425           --and incase of dual um 2,3 check for deviation and log error if out of deviation.
426           ELSIF cr_rec.secondary_quantity IS NOT NULL AND v_dualum_ind > 0 AND NOT v_uom_error THEN
427 
428               l_secondary_quantity := NULL;
429 
430               IF v_dualum_ind in (2,3) THEN
431                   l_ret_val := gmicval.dev_validation (
432                   			      v_opm_item_id,
433                                               0,
434 					      cr_rec.quantity,
435                                               v_item_um,
436 					      cr_rec.secondary_quantity,
437                                               v_item_um2,
438 		                              0 );
439 		  --If sec qty is out of deviation then log error. (hi or low).
440 	          IF ( l_ret_val = -68 ) THEN
441 	             l_rec.interface_type     := 'REQIMPORT';
442                      l_rec.interface_transaction_id       := cr_rec.transaction_id;
443                      l_rec.column_name        := 'SECONDARY_QUANTITY';
444                      l_rec.table_name         := 'PO_REQUISITIONS_INTERFACE';
445                      l_rec.error_message_name := 'IC_DEVIATION_HI_ERR';
446 
447                      fnd_message.set_name('GMI', l_rec.error_message_name);
448                      l_rec.error_message := FND_MESSAGE.get;
449 
450                      PO_INTERFACE_ERRORS_GRP.log_error
451                        ( p_api_version => 1.0,
452                          p_init_msg_list => FND_API.G_TRUE,
453                          x_return_status => l_rtn_status,
454                          x_msg_count => l_msg_count,
455                          x_msg_data => l_msg_data,
456                          p_rec => l_rec,
457                          x_row_id => l_row_id);
458 
459                      IF (l_rtn_status <> FND_API.G_RET_STS_SUCCESS) THEN
460                         x_msg_count := l_msg_count;
461                         x_msg_data  := l_msg_data;
462                         x_return_status := l_rtn_status;
463                         RAISE FND_API.G_EXC_UNEXPECTED_ERROR;
464                      END IF;
465 	          ELSIF ( l_ret_val = -69 ) OR cr_rec.secondary_quantity <= 0 THEN
466 		     l_rec.interface_type     := 'REQIMPORT';
467                      l_rec.interface_transaction_id       := cr_rec.transaction_id;
468                      l_rec.column_name        := 'SECONDARY_QUANTITY';
469                      l_rec.table_name         := 'PO_REQUISITIONS_INTERFACE';
470                      l_rec.error_message_name := 'IC_DEVIATION_LO_ERR';
471 
472                      fnd_message.set_name('GMI', l_rec.error_message_name);
473                      l_rec.error_message := FND_MESSAGE.get;
474 
475                      PO_INTERFACE_ERRORS_GRP.log_error
476                       ( p_api_version => 1.0,
477                         p_init_msg_list => FND_API.G_TRUE,
478                         x_return_status => l_rtn_status,
479                         x_msg_count => l_msg_count,
480                         x_msg_data => l_msg_data,
481                         p_rec => l_rec,
482                         x_row_id => l_row_id);
483 
484                      IF (l_rtn_status <> FND_API.G_RET_STS_SUCCESS) THEN
485                         x_msg_count := l_msg_count;
486                         x_msg_data  := l_msg_data;
487                         x_return_status := l_rtn_status;
488                         RAISE FND_API.G_EXC_UNEXPECTED_ERROR;
489                      END IF;
490 	          END IF ;
491 
492 	      --if dual um 1 then update the secondary quantity since its fixed conversion.
493 	      ELSIF  v_dualum_ind = 1 THEN
494 
495 	         po_gml_db_common.VALIDATE_QUANTITY(
496                                 v_opm_item_id,
497                                 v_dualum_ind,
498                                 cr_rec.quantity,
499                                 v_item_um,
500                                 v_item_um2,
501                                 l_secondary_quantity) ;
502 
503                  UPDATE po_requisitions_interface
504                  SET    secondary_quantity = l_secondary_quantity
505                  WHERE  rowid = cr_rec.rowid;
506 
507 	      END IF; /*v_dualum_ind in (2,3) */
508         END IF;/*cr_rec.secondary_quantity IS NULL */
509 
510         -- Check if item is not grade controlled and grade is specified then log error
511         IF v_grade_ctl = 0 and cr_rec.preferred_grade IS NOT NULL
512         THEN
513 
514 	   l_rec.interface_type     := 'REQIMPORT';
515            l_rec.interface_transaction_id       := cr_rec.transaction_id;
516            l_rec.column_name        := 'PREFFERED_GRADE';
517            l_rec.table_name         := 'PO_REQUISITIONS_INTERFACE';
518            l_rec.error_message_name := 'GML_NO_OPM_PREFERRED_GRADE';
519 
520            fnd_message.set_name('GML', l_rec.error_message_name);
521            l_rec.error_message := FND_MESSAGE.get;
522 
523            PO_INTERFACE_ERRORS_GRP.log_error
524             ( p_api_version => 1.0,
525               p_init_msg_list => FND_API.G_TRUE,
526               x_return_status => l_rtn_status,
527               x_msg_count => l_msg_count,
528               x_msg_data => l_msg_data,
529               p_rec => l_rec,
530               x_row_id => l_row_id);
531 
532            IF (l_rtn_status <> FND_API.G_RET_STS_SUCCESS) THEN
533               x_msg_count := l_msg_count;
534               x_msg_data  := l_msg_data;
535               x_return_status := l_rtn_status;
536               RAISE FND_API.G_EXC_UNEXPECTED_ERROR;
537            END IF;
538 
539            --if item is grade controlled and grade is speicified then validate grade.
540         ELSIF  v_grade_ctl = 1 and cr_rec.preferred_grade IS NOT NULL
541         THEN
542 
543            BEGIN
544               Select	qc_grade
545               Into      v_qc_grade
546               From 	qc_grad_mst
547               Where	qc_grade = cr_rec.preferred_grade
548               And       delete_mark <> 1;
549 
550               EXCEPTION
551                   WHEN NO_DATA_FOUND THEN
552                       l_rec.interface_type     := 'REQIMPORT';
553                       l_rec.interface_transaction_id       := cr_rec.transaction_id;
554                       l_rec.column_name        := 'PREFFERED_GRADE';
555                       l_rec.table_name         := 'PO_REQUISITIONS_INTERFACE';
556                       l_rec.error_message_name := 'GML_NO_OPM_PREFERRED_GRADE';
557 
558                       fnd_message.set_name('GML', l_rec.error_message_name);
559                       l_rec.error_message := FND_MESSAGE.get;
560 
561                       PO_INTERFACE_ERRORS_GRP.log_error
562                        ( p_api_version => 1.0,
563                          p_init_msg_list => FND_API.G_TRUE,
564                          x_return_status => l_rtn_status,
565                          x_msg_count => l_msg_count,
566                          x_msg_data => l_msg_data,
567                          p_rec => l_rec,
568                          x_row_id => l_row_id);
569 
570                       IF (l_rtn_status <> FND_API.G_RET_STS_SUCCESS) THEN
571                          x_msg_count := l_msg_count;
572                          x_msg_data  := l_msg_data;
573                          x_return_status := l_rtn_status;
574                          RAISE FND_API.G_EXC_UNEXPECTED_ERROR;
575                       END IF;
576                   END;
577   	END IF;/*v_grade_ctl = 0 */
578 
579         --Since item is not dual um controlled update all secondary attributes to NULL
580         IF v_dualum_ind  = 0 THEN
581 
582            UPDATE po_requisitions_interface
583            SET    secondary_quantity = NULL,
584                   secondary_uom_code = NULL,
585                   secondary_unit_of_measure = NULL
586            WHERE  rowid = cr_rec.rowid;
587         END IF;
588 
589       ELSE /*either item is discrete or destination organization is discrete */
590 
591          --since item is discrete or destination organization is discrete
592          --update all process attributes to NULL.
593          UPDATE po_requisitions_interface
594          SET    secondary_quantity = NULL,
595                 secondary_uom_code = NULL,
596                 secondary_unit_of_measure = NULL,
597                 preferred_grade = NULL
598          WHERE  rowid = cr_rec.rowid;
599 
600       END IF; /* v_opm_item AND v_process_dest_org = 'Y' */
601 
602   ELSE /*cr_rec.item_id IS NULL */
603 
604      --since its a one time item update all process attributes to NULL.
605      UPDATE po_requisitions_interface
606      SET    secondary_quantity = NULL,
607             secondary_uom_code = NULL,
608             secondary_unit_of_measure = NULL,
609             preferred_grade = NULL
610      WHERE  rowid = cr_rec.rowid;
611 
612   END IF;
613 
614 END LOOP;
615 
616 EXCEPTION
617 
618   WHEN FND_API.G_EXC_ERROR THEN
619      x_return_status := FND_API.G_RET_STS_ERROR;
620 
621   WHEN FND_API.G_EXC_UNEXPECTED_ERROR THEN
622      x_return_status := FND_API.G_RET_STS_UNEXP_ERROR;
623 
624   WHEN OTHERS THEN
625      x_return_status := FND_API.G_RET_STS_UNEXP_ERROR;
626 
627 END Validate_Requisition_Grp;
628 
629 END;