DBA Data[Home] [Help]

PACKAGE BODY: APPS.BOM_VALIDATE_COMP_OPERATION

Source


1 PACKAGE BODY BOM_Validate_Comp_Operation AS
2 /* $Header: BOMLCOPB.pls 120.4.12000000.3 2007/04/05 15:06:57 vggarg ship $ */
3 /**********************************************************************
4 --  Copyright (c) 1996 Oracle Corporation, Redwood Shores, CA, USA
5 --  All rights reserved.
6 --
7 --  FILENAME
8 --
9 --      BOMLCOPB.pls
10 --
11 --  DESCRIPTION
12 --
13 --      Body of package BOM_Validate_Comp_Operation
14 --
15 --  NOTES
16 --
17 --  HISTORY
18 --
19 --  27-AUG-2001   Refai Farook  Initial Creation
20 --
21 --
22 **************************************************************************/
23 G_PKG_NAME  CONSTANT VARCHAR2(30) := 'BOM_Validate_Comp_Operation';
24 ret_code     NUMBER;
25 l_dummy      VARCHAR2(80);
26 
27 
28 
29         /*******************************************************************
30         * Function      : Check_Overlap_Dates
31         * Parameter IN  : Effectivity Date
32         *                 Disable Date
33         *                 Bill Sequence Id
34         *                 Component Item Id
35         * Return        : True if dates are overlapping else false.
36         * Purpose       : The function will check if the same component is
37         *                 entered with overlapping dates. Components with
38         *                 overlapping dates will get an error.
39         ******************************************************************/
40         FUNCTION Check_Overlap_Dates
41                 ( p_Effectivity_Date DATE,
42                   p_Disable_Date     DATE,
43                   p_Component_Item_Id   NUMBER,
44                   p_Bill_Sequence_Id NUMBER,
45                   p_component_sequence_id   IN NUMBER := NULL,
46                   p_comp_operation_seq_id   IN NUMBER := NULL,
47                   p_Rowid            VARCHAR2 := NULL,
48                   p_Operation_Seq_Num NUMBER,
49                   p_entity           VARCHAR2 := 'COPS')
50         RETURN BOOLEAN
51         IS
52                 l_Count NUMBER := 0;
53                 CURSOR All_Dates IS
54                         SELECT 'X' date_available FROM sys.dual
55                         WHERE EXISTS (
56                                 SELECT 1 from BOM_Component_All_Operations_V
57                                  WHERE Component_Item_Id = p_Component_Item_Id
58                                    AND Bill_Sequence_Id  = p_Bill_Sequence_Id
59                                    AND Operation_Seq_Num = p_Operation_Seq_Num
60                                 /* AND
61                                    (
62                                      ( p_entity = 'COPS'
63                                        AND
64                                        (p_comp_operation_seq_id IS NULL
65                                         OR
66                                         p_comp_operation_seq_id = FND_API.G_MISS_NUM
67                                         OR
68                                         comp_operation_seq_id <> p_comp_operation_seq_id)
69                                      )
70                                        OR
71                                      ( p_entity = 'RC'
72                                        AND
73                                        (p_component_sequence_id IS NULL
74                                         OR
75                                         p_component_sequence_id = FND_API.G_MISS_NUM
76                                         OR
77                                         comp_operation_seq_id <> 0 -- row belongs to comp ops
78                                         OR
79                                         component_sequence_id <> p_component_sequence_id)
80                                      )
81                                    )
82                                  */
83 
84                                  /*    AND
85                                      (
86                                       p_RowId IS NULL
87                                       or
88                                       p_Rowid = FND_API.G_MISS_CHAR
89                                       or
90                                       ( decode(p_entity,'COPS',bco_rowid,
91                                                          'RC',bic_RowId,' ') <> p_RowID )
92                                       )
93                                  */
94                                      AND
95                                      (
96                                       p_RowId IS NULL
97                                       or
98                                       p_Rowid = FND_API.G_MISS_CHAR
99                                       or
100                                       row_id <> p_Rowid)
101                                    AND ( p_Disable_Date IS NULL
102                                         OR ( to_char(p_Disable_Date,'YYYY/MM/DD HH24:MI:SS') > to_char(Effectivity_Date,'YYYY/MM/DD HH24:MI:SS'))) -- 5954279
103                                    AND ( to_char(p_Effectivity_Date,'YYYY/MM/DD HH24:MI:SS') < to_char(Disable_Date,'YYYY/MM/DD HH24:MI:SS') -- 5954279
104                                          OR Disable_Date IS NULL
105                                         )
106                                    AND implementation_date IS NOT NULL  -- Bug 3182080
107                                );
108         BEGIN
109 
110                 FOR l_Date IN All_Dates LOOP
111                         l_Count := l_Count + 1;
112                 END LOOP;
113 
114                 -- If count <> 0 that means the current date is overlapping with
115                 -- some record.
116                 IF l_Count <> 0 THEN
117                         RETURN TRUE;
118                 ELSE
119                         RETURN FALSE;
120                 END IF;
121 
122         END Check_Overlap_Dates;
123 
124 
125         /*******************************************************************
126         * Function    : Check_Overlap_Numbers
127         * Parameter IN: from end item unit number
128         *               to end item unit number
129         *               Bill Sequence Id
130         *               Component Item Id
131         * Return      : True if unit numbers are overlapping, else false.
132         * Purpose     : The function will check if the same component is entered
133         *               with overlapping unit numbers. Components with
134         *               overlapping unit numbers will get an error.
135         *********************************************************************/
136         FUNCTION Check_Overlap_Numbers
137                  (  p_From_End_Item_Number VARCHAR2
138                   , p_To_End_Item_Number VARCHAR2
139                   , p_Component_Item_Id   NUMBER
140                   , p_Bill_Sequence_Id NUMBER
141                   , p_component_sequence_id   IN NUMBER := NULL
142                   , p_comp_operation_seq_id   IN NUMBER := NULL
143                   , p_Rowid            VARCHAR2 := NULL
144                   , p_Operation_Seq_Num NUMBER
145                   , p_entity           VARCHAR2 := 'COPS')
146         RETURN BOOLEAN
147         IS
148                 l_Count NUMBER := 0;
149                 CURSOR All_Numbers_BIC IS
150                         SELECT 'X' unit_available FROM sys.dual
151                         WHERE EXISTS (
152                                 SELECT 1 from BOM_INVENTORY_COMPONENTS
153                                  WHERE Component_Item_Id = p_Component_Item_Id
154                                    AND Bill_Sequence_Id  = p_Bill_Sequence_Id
155                                    AND Operation_Seq_Num = p_Operation_Seq_Num
156                                    /* AND
157                                    (
158                                      ( p_entity = 'COPS'
159                                        AND
160                                        (p_comp_operation_seq_id IS NULL
161                                         OR
162                                         p_comp_operation_seq_id = FND_API.G_MISS_NUM
163                                         OR
164                                         comp_operation_seq_id <> p_comp_operation_seq_id)
165                                      )
166                                        OR
167                                      ( p_entity = 'RC'
168                                        AND
169                                        (p_component_sequence_id IS NULL
170                                         OR
171                                         p_component_sequence_id = FND_API.G_MISS_NUM
172                                         OR
173                                         comp_operation_seq_id <> 0
174                                         OR
175                                         component_sequence_id <> p_component_sequence_id)
176                                      )
177                                    ) */
178 
179                                   /*
180                                    AND
181                                      (
182                                       p_RowId IS NULL
183                                       or
184                                       p_Rowid = FND_API.G_MISS_CHAR
185                                       or
186                                       ( decode(p_entity,'COPS',bco_rowid,
187                                                          'RC',bic_RowId,' ') <> p_RowID )
188                                       )
189                                    */
190                                    AND
191                                      (
192                                       p_RowId IS NULL
193                                       or
194                                       p_Rowid = FND_API.G_MISS_CHAR
195                                       or
196                                       rowid <> p_Rowid)
197                                    AND (p_To_End_Item_Number IS NULL
198                                         OR p_To_End_Item_Number >=
199                                            From_End_Item_Unit_Number)
200                                    AND (p_From_End_Item_Number <=
201                                          To_End_Item_Unit_Number
202                                          OR To_End_Item_Unit_Number IS NULL
203                                         )
204                                    AND  ( IMPLEMENTATION_DATE IS NOT NULL )
205                                    AND  ( DISABLE_DATE IS NULL ) --bug:5347036 Consider enabled components only
206                                );
207 
208                 CURSOR All_Numbers_BCO IS
209                         SELECT 'X' unit_available FROM sys.dual
210                         WHERE EXISTS (
211                                 SELECT 1 from BOM_COMPONENT_OPERATIONS BCO,
212                                               BOM_INVENTORY_COMPONENTS BIC
213                                  WHERE BCO.COMPONENT_SEQUENCE_ID = BIC.COMPONENT_SEQUENCE_ID
214                                  AND BIC.Component_Item_Id = p_Component_Item_Id
215                                    AND BIC.Bill_Sequence_Id  = p_Bill_Sequence_Id
216                                    AND BCO.Operation_Seq_Num = p_Operation_Seq_Num
217                                    /* AND
218                                    (
219                                      ( p_entity = 'COPS'
220                                        AND
221                                        (p_comp_operation_seq_id IS NULL
222                                         OR
223                                         p_comp_operation_seq_id = FND_API.G_MISS_NUM
224                                         OR
225                                         comp_operation_seq_id <> p_comp_operation_seq_id)
226                                      )
227                                        OR
228                                      ( p_entity = 'RC'
229                                        AND
230                                        (p_component_sequence_id IS NULL
231                                         OR
232                                         p_component_sequence_id = FND_API.G_MISS_NUM
233                                         OR
234                                         comp_operation_seq_id <> 0
235                                         OR
236                                         component_sequence_id <> p_component_sequence_id)
237                                      )
238                                    ) */
239 
240                                   /*
241                                    AND
242                                      (
243                                       p_RowId IS NULL
244                                       or
245                                       p_Rowid = FND_API.G_MISS_CHAR
246                                       or
247                                       ( decode(p_entity,'COPS',bco_rowid,
248                                                          'RC',bic_RowId,' ') <> p_RowID )
249                                       )
250                                    */
251                                    AND
252                                      (
253                                       p_RowId IS NULL
254                                       or
255                                       p_Rowid = FND_API.G_MISS_CHAR
256                                       or
257                                       bco.rowid <> p_Rowid)
258                                    AND (p_To_End_Item_Number IS NULL
259                                         OR p_To_End_Item_Number >=
260                                            BIC.From_End_Item_Unit_Number)
261                                    AND (p_From_End_Item_Number <=
262                                          BIC.To_End_Item_Unit_Number
263                                          OR BIC.To_End_Item_Unit_Number IS NULL
264                                         )
265                                    AND  ( bic.IMPLEMENTATION_DATE IS NOT NULL )
266                                    AND  ( bic.DISABLE_DATE IS NULL ) --bug:5347036 Consider enabled components only
267                                );
268         BEGIN
269 
270                 FOR l_Unit IN All_Numbers_BIC LOOP
271                         l_Count := l_Count + 1;
272                 END LOOP;
273 
274                 IF (l_count <> 0) THEN
275                   FOR l_Unit IN All_Numbers_BCO LOOP
276                         l_Count := l_Count + 1;
277                   END LOOP;
278                 END IF;
279 
280 
281                 -- If count <> 0 that means the unit numbers are overlapping
282                 IF l_Count <> 0 THEN
283                         RETURN TRUE;
284                 ELSE
285                         RETURN FALSE;
286                 END IF;
287 
288         END Check_Overlap_Numbers;
289 
290 /********************************************************************
291 *
292 * Procedure     : Check_Entity
293 * Parameters IN : Component Operation Record as given by the User
294 *                 Component Operation Unexposed Record
295 * Parameters OUT: Return_Status - Indicating success or faliure
296 *                 Mesg_Token_Tbl - Filled with any errors or warnings
297 * Purpose       : Entity validate procedure will execute the business
298 *     validations for the component operation entity
299 *     Any errors are loaded in the Mesg_Token_Tbl and
300 *     a return status value is set.
301 ********************************************************************/
302 
303 PROCEDURE Check_Entity
304 (   x_return_status             IN OUT NOCOPY VARCHAR2
305 ,   x_Mesg_Token_Tbl            IN OUT NOCOPY Error_Handler.Mesg_Token_Tbl_Type
306 ,   p_bom_comp_ops_rec          IN  Bom_Bo_Pub.Bom_Comp_Ops_Rec_Type
307 ,   p_bom_comp_ops_Unexp_Rec    IN  Bom_Bo_Pub.Bom_Comp_Ops_Unexp_Rec_Type
308 )
309 IS
310 
311 l_disable_date                Date;
312 l_token_tbl         Error_Handler.Token_tbl_Type;
313 l_Mesg_Token_Tbl        Error_Handler.Mesg_Token_Tbl_Type;
314 l_Additional_Op_Seq_Number    NUMBER;
315 l_temp_var          NUMBER :=0;
316 p_dummy     NUMBER;
317 l_assy_bom_enabled  VARCHAR2(1);
318 
319 BEGIN
320 
321       BEGIN
322         SELECT 1
323         INTO p_dummy
324         FROM bom_bill_of_materials
325         WHERE bill_sequence_id = source_bill_sequence_id
326         AND bill_sequence_id = p_bom_comp_ops_unexp_rec.bill_Sequence_id;
327       EXCEPTION
328         WHEN NO_DATA_FOUND THEN
329           Error_Handler.Add_Error_Token
330           (  p_Message_Name       => 'BOM_COMMON_COMP_OP'
331           , p_Mesg_Token_Tbl     => l_Mesg_Token_Tbl
332           , x_Mesg_Token_Tbl     => l_Mesg_Token_Tbl
333           , p_Token_Tbl          => l_Token_Tbl
334           );
335           x_Return_Status := FND_API.G_RET_STS_ERROR;
336       END;
337 
338 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Entity Validation for Comp. Operation begins . . .'); END IF;
339 
340 
341  SELECT msi.bom_enabled_flag
342  INTO l_assy_bom_enabled
343  FROM mtl_system_items_b msi,
344  bom_bill_of_materials bbom
345  WHERE bbom.bill_sequence_id = p_bom_comp_ops_Unexp_Rec.bill_sequence_id
346  AND bbom.assembly_item_id = msi.inventory_item_id
347  AND bbom.organization_id = msi.organization_id;
348 
349  IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Assy Bom Enabled flag : ' || l_assy_bom_enabled); END IF;
350 
351  IF l_assy_bom_enabled <> 'Y'
352  THEN
353        IF FND_MSG_PUB.Check_Msg_Level(FND_MSG_PUB.G_MSG_LVL_ERROR) THEN
354        l_token_tbl(1).token_name  := 'REVISED_ITEM_NAME';
355        l_token_tbl(1).token_value :=
356          p_bom_comp_ops_rec.assembly_Item_Name;
357                          Error_Handler.Add_Error_Token
358                          (  x_Mesg_Token_tbl => l_Mesg_Token_Tbl
359                           , p_Mesg_Token_Tbl => l_Mesg_Token_Tbl
360                           , p_message_name   => 'BOM_REV_ITEM_BOM_NOT_ENABLED'
361         , p_token_tbl      => l_token_tbl
362                           );
363                  END IF;
364      RAISE FND_API.G_EXC_ERROR;
365  END IF;
366 
367 
368   /* Select the didsable date which is one of the key parameters */
369 
370   SELECT disable_date INTO l_disable_date FROM bom_inventory_components WHERE
371    component_sequence_id = p_bom_comp_ops_unexp_rec.component_sequence_id;
372 
373   /* Validate for Duplicate entries/Overlapping of the component */
374 
375   /* While creating a new row, additional_operation_sequence_number should be checked and
376     while updating the existing additional_operation_sequence_number, new_addtional_op_sequence_number
377      should be checked for Overlapping entries */
378 
379      l_Additional_Op_Seq_Number := p_bom_comp_ops_rec.additional_operation_seq_num;
380 
381   If( p_bom_comp_ops_rec.transaction_type = BOM_globals.G_OPR_UPDATE and
382        p_bom_comp_ops_rec.new_additional_op_seq_num is not null
383        and  p_bom_comp_ops_rec.new_additional_op_seq_num <> FND_API.G_MISS_NUM) then
384      l_Additional_Op_Seq_Number := p_bom_comp_ops_rec.new_additional_op_seq_num;
385   End if;
386 
387   IF p_bom_comp_ops_rec.from_end_item_unit_number IS NULL or
388      p_bom_comp_ops_rec.from_end_item_unit_number = FND_API.G_MISS_CHAR THEN
389 
390     IF Check_Overlap_Dates ( p_Effectivity_Date => p_bom_comp_ops_rec.start_effective_date,
391                     p_Disable_Date     => l_disable_date,
392                     p_Component_Item_Id  =>p_bom_comp_ops_unexp_rec.component_item_id,
393                     p_Bill_Sequence_Id   => p_bom_comp_ops_unexp_rec.bill_sequence_id,
394                         p_comp_operation_seq_id => p_bom_comp_ops_unexp_rec.comp_operation_seq_id,
395                     p_Rowid              => p_bom_comp_ops_unexp_rec.rowid,
396                     p_Operation_Seq_Num => l_Additional_Op_Seq_Number) THEN
397 
398   l_token_tbl(1).token_name := 'COMPONENT_ITEM_NAME';
399   l_token_tbl(1).token_value := p_bom_comp_ops_rec.component_item_name;
400   l_token_tbl(2).token_name := 'OPERATION_SEQ_NUM';
401   l_token_tbl(2).token_value := p_bom_comp_ops_rec.additional_operation_seq_num;
402   Error_Handler.Add_Error_Token
403   (  x_Mesg_Token_tbl => l_Mesg_Token_tbl
404    , p_Mesg_Token_Tbl => l_Mesg_Token_Tbl
405          , p_message_name => 'BOM_COPS_DATES_OVERLAP'
406          , p_token_tbl    => l_token_tbl
407    );
408 
409         RAISE FND_API.G_EXC_ERROR;
410     END IF;
411 
412   ELSE
413 
414     IF Check_Overlap_Numbers ( p_From_End_Item_Number => p_bom_comp_ops_rec.from_end_item_unit_number,
415                     p_To_End_Item_Number     => p_bom_comp_ops_rec.to_end_item_unit_number,
416                     p_Component_Item_Id  =>p_bom_comp_ops_unexp_rec.component_item_id,
417                     p_Bill_Sequence_Id   => p_bom_comp_ops_unexp_rec.bill_sequence_id,
418                         p_comp_operation_seq_id => p_bom_comp_ops_unexp_rec.comp_operation_seq_id,
419                     p_Rowid              => p_bom_comp_ops_unexp_rec.rowid,
420                     p_Operation_Seq_Num => l_Additional_Op_Seq_Number) THEN
421 
422   l_token_tbl(1).token_name := 'COMPONENT_ITEM_NAME';
423   l_token_tbl(1).token_value := p_bom_comp_ops_rec.component_item_name;
424   l_token_tbl(2).token_name := 'OPERATION_SEQ_NUM';
425   l_token_tbl(2).token_value := p_bom_comp_ops_rec.additional_operation_seq_num;
426   Error_Handler.Add_Error_Token
427   (  x_Mesg_Token_tbl => l_Mesg_Token_tbl
428    , p_Mesg_Token_Tbl => l_Mesg_Token_Tbl
429          , p_message_name => 'BOM_COPS_NUMBERS_OVERLAP'
430          , p_token_tbl    => l_token_tbl
431    );
432         RAISE FND_API.G_EXC_ERROR;
433 
434     END IF;
435 
436     x_Mesg_Token_Tbl := l_Mesg_Token_Tbl;
437     x_return_status  := FND_API.G_RET_STS_SUCCESS;
438 
439   END IF;
440 
441 /* When the component operation is updated with new Component operation, It should be checked that
442  the New Component operation does not exists already */
443 
444      IF ( p_bom_comp_ops_rec.new_additional_op_seq_num is not null
445          and  p_bom_comp_ops_rec.new_additional_op_seq_num <> FND_API.G_MISS_NUM
446             and p_bom_comp_ops_rec.transaction_type = Bom_Globals.G_OPR_UPDATE) THEN
447 
448         select count(*) into l_temp_var
449           FROM    BOM_COMPONENT_OPERATIONS
450           WHERE   OPERATION_SEQ_NUM = p_bom_comp_ops_rec.new_additional_op_seq_num
451           AND     COMPONENT_SEQUENCE_ID = p_bom_Comp_ops_Unexp_Rec.component_sequence_id;
452 
453         IF (l_temp_var <>0) then
454         l_Token_Tbl(1).Token_Name  := 'OPERATION_SEQUENCE_NUMBER';
455         l_Token_Tbl(1).Token_Value :=
456                         p_bom_comp_ops_rec.new_additional_op_seq_num;
457         l_token_tbl(2).token_name  := 'REVISED_COMPONENT_NAME';
458         l_token_tbl(2).token_value := p_bom_comp_ops_rec.component_item_name;
459 
460                 Error_Handler.Add_Error_Token
461                 (  x_Mesg_token_tbl => l_Mesg_Token_Tbl
462                  , p_Mesg_Token_Tbl => l_Mesg_Token_Tbl
463                  , p_message_name  => 'BOM_COMP_OPS_ALREADY_EXISTS'
464                  , p_token_tbl     => l_token_tbl
465                  );
466 
467           RAISE FND_API.G_EXC_ERROR;
468         END IF;
469     END IF;
470 
471 IF BOm_GlobalS.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Verified New addtional Component operation ...  '); END IF;
472 
473 IF Bom_GlobalS.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Verifying Operation Seq Num in Editable common Bills ...  '); END IF;
474    --The op seq num being used must be valid for the editable common bills commoning this bill.
475     IF NOT BOMPCMBM.Check_Op_Seq_In_Ref_Boms(p_src_bill_seq_id => p_bom_comp_ops_unexp_rec.bill_sequence_id,
476                                              p_op_seq => nvl(p_bom_comp_ops_rec.new_additional_op_seq_num,
477                                                               p_bom_comp_ops_rec.additional_operation_seq_num)
478                                             )
479     THEN
480          Error_Handler.Add_Error_Token
481         (  p_Message_Name   => 'BOM_COMMON_OP_SEQ_INVALID'
482          , p_Mesg_Token_Tbl => l_Mesg_Token_Tbl
483          , x_Mesg_Token_Tbl => l_Mesg_Token_Tbl
484          , p_Token_Tbl      => l_Token_Tbl
485          );
486          RAISE FND_API.G_EXC_ERROR;
487     END IF;
488 
489 
490 
491 
492   EXCEPTION
493 
494     WHEN FND_API.G_EXC_ERROR THEN
495 
496 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Expected Error in Comp Operations. Entity Validation '); END IF;
497 
498   x_Mesg_Token_Tbl := l_Mesg_Token_Tbl;
499         x_return_status  := FND_API.G_RET_STS_ERROR;
500 
501     WHEN FND_API.G_EXC_UNEXPECTED_ERROR THEN
502 
503 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('UNExpected Error in Comp. Operations Entity Validation '); END IF;
504   x_Mesg_Token_Tbl := l_Mesg_Token_Tbl;
505         x_return_status := FND_API.G_RET_STS_UNEXP_ERROR;
506 
507     WHEN OTHERS THEN
508   x_Mesg_Token_Tbl := l_Mesg_Token_Tbl;
509         x_return_status := FND_API.G_RET_STS_UNEXP_ERROR;
510 
511 END Check_Entity;
512 
513 /********************************************************************
514 *
515 * Procedure     : Check_Attributes
516 * Parameters IN : Component Operation Record as given by the User
517 * Parameters OUT: Return_Status - Indicating success or faliure
518 *                 Mesg_Token_Tbl - Filled with any errors or warnings
519 * Purpose       : Attribute validation will validate individual attributes
520 *     and any errors will be populated in the Mesg_Token_Tbl
521 *     and returned with a return_status.
522 ********************************************************************/
523 
524 PROCEDURE Check_Attributes
525 (   x_return_status             IN OUT NOCOPY VARCHAR2
526 ,   x_Mesg_Token_Tbl    IN OUT NOCOPY Error_Handler.Mesg_Token_Tbl_Type
527 ,   p_bom_comp_ops_rec           IN Bom_Bo_Pub.Bom_Comp_Ops_Rec_Type
528 ,   p_bom_comp_ops_unexp_rec     IN Bom_Bo_Pub.Bom_Comp_Ops_Unexp_Rec_Type
529 )
530 IS
531 
532 l_original_routing      VARCHAR2(1) := 'N';
533 l_valid                 Number := 0;
534 l_token_tbl   Error_Handler.Token_tbl_Type;
535 l_Mesg_token_Tbl  Error_Handler.Mesg_Token_Tbl_Type;
536 l_err_text              VARCHAR2(240);
537 
538 CURSOR OpSeq_In_Original IS
539  SELECT operation_seq_num
540   FROM bom_operation_sequences bos
541   WHERE routing_sequence_id =
542       (SELECT common_routing_sequence_id
543          FROM bom_operational_routings bor
544          WHERE assembly_item_id = p_bom_comp_ops_unexp_rec.assembly_item_id
545           and organization_id = p_bom_comp_ops_unexp_rec.organization_id
546           and nvl(alternate_routing_designator,'NONE') =
547                  nvl(p_bom_comp_ops_rec.alternate_bom_code, 'NONE')
548         )
549    and nvl(trunc(disable_date), trunc(sysdate)+1) > trunc(sysdate) and nvl(operation_type,1) = 1;
550 
551 CURSOR Opseq_In_Primary IS
552  SELECT operation_seq_num
553   FROM bom_operation_sequences bos
554   WHERE routing_sequence_id =
555       (SELECT common_routing_sequence_id
556          FROM bom_operational_routings bor
557          WHERE assembly_item_id = p_bom_comp_ops_unexp_rec.assembly_item_id
558           and organization_id = p_bom_comp_ops_unexp_rec.organization_id
559           and alternate_routing_designator IS NULL
560        )
561    and nvl(trunc(disable_date), trunc(sysdate)+1) > trunc(sysdate) and nvl(operation_type,1) = 1;
562 
563 BEGIN
564 
565     x_return_status := FND_API.G_RET_STS_SUCCESS;
566 
567 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Attribute Validation Starts . . . '); END IF;
568 
569 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Additional Operation Sequence Number is '||to_char(p_bom_comp_ops_rec.additional_operation_seq_num)); END IF;
570 
571     /* Check for the existence of OpSeq in the original routing which is defined for this item */
572 
573     FOR r1 IN OpSeq_In_Original
574     LOOP
575       l_original_routing := 'Y';
576 
577       IF r1.operation_seq_num = p_bom_comp_ops_rec.additional_operation_seq_num THEN
578         l_valid := 1;
579         Exit;
580       END IF;
581     END LOOP;
582 
583     /* If there is no original routing, then check in the primary routing */
584 
585     IF l_original_routing = 'N' THEN
586       FOR r2 IN OpSeq_In_Primary
587       LOOP
588 
589         IF r2.operation_seq_num = p_bom_comp_ops_rec.additional_operation_seq_num THEN
590           l_valid := 1;
591           Exit;
592         END IF;
593 
594       END LOOP;
595     END IF;
596 
597     IF l_valid = 0 THEN
598         IF FND_MSG_PUB.Check_Msg_Level(FND_MSG_PUB.G_MSG_LVL_ERROR)
599         THEN
600     l_token_tbl(1).token_name := 'OPERATION_SEQ_NUM';
601     l_token_tbl(1).token_value := p_bom_comp_ops_rec.additional_operation_seq_num;
602 
603     Error_Handler.Add_Error_Token
604     (  x_Mesg_Token_tbl => l_Mesg_Token_tbl
605      , p_Mesg_Token_Tbl => l_Mesg_Token_Tbl
606                  , p_message_name => 'BOM_COPS_OPSEQ_INVALID'
607                  , p_token_tbl    => l_token_tbl
608      );
609         END IF;
610         x_return_status := FND_API.G_RET_STS_ERROR;
611     END IF;
612 
613     x_Mesg_Token_Tbl := l_Mesg_Token_Tbl;
614 
615 
616 EXCEPTION
617 
618     WHEN OTHERS THEN
619         IF FND_MSG_PUB.Check_Msg_Level(FND_MSG_PUB.G_MSG_LVL_UNEXP_ERROR)
620         THEN
621                 l_err_text := G_PKG_NAME ||
622                               'Attribute Validate (Component Operation)' ||
623                               SUBSTR(SQLERRM, 1, 100);
624 
625                 Error_Handler.Add_Error_Token
626                 (  p_Message_Name       => NULL
627                  , p_Message_Text       => l_err_text
628                  , p_Mesg_Token_Tbl     => l_Mesg_Token_Tbl
629                  , x_Mesg_Token_Tbl  => l_Mesg_Token_Tbl
630                 );
631         END IF;
632   x_Mesg_Token_Tbl := l_Mesg_Token_Tbl;
633         x_return_status  := FND_API.G_RET_STS_UNEXP_ERROR;
634 
635 END Check_Attributes;
636 
637 /*****************************************************************************
638 * Procedure     : Check_Existence
639 * Parameters IN : Component Operation exposed column record
640 *                 Component Operation unexposed column record
641 * Parameters OUT: Old Component Operation exposed column record
642 *                 Old Component Operation unexposed column record
643 *                 Mesg Token Table
644 *                 Return Status
645 * Purpose       : Check_Existence will perform a query using the primary key
646 *                 information and will return a success if the operation is
647 *                 CREATE and the record EXISTS or will return an
648 *                 error if the operation is UPDATE and the record DOES NOT
649 *                 EXIST.
650 *                 In case of UPDATE if the record exists then the procedure
651 *                 will return the old record in the old entity parameters
652 *                 with a success status.
653 ****************************************************************************/
654 PROCEDURE Check_Existence
655 (  p_bom_comp_ops_rec            IN  Bom_Bo_Pub.Bom_Comp_Ops_Rec_Type
656  , p_bom_comp_ops_unexp_rec      IN  Bom_Bo_Pub.Bom_Comp_Ops_Unexp_Rec_Type
657  , x_old_bom_comp_ops_rec        IN OUT NOCOPY Bom_Bo_Pub.Bom_Comp_Ops_Rec_Type
658  , x_old_bom_comp_ops_unexp_rec  IN OUT NOCOPY Bom_Bo_Pub.Bom_Comp_Ops_Unexp_Rec_Type
659  , x_Mesg_Token_Tbl              IN OUT NOCOPY Error_Handler.Mesg_Token_Tbl_Type
660  , x_Return_Status               IN OUT NOCOPY VARCHAR2
661 )
662 IS
663   l_Mesg_Token_Tbl  Error_Handler.Mesg_Token_Tbl_Type;
664   l_Return_Status   VARCHAR2(1);
665   l_Token_Tbl   Error_Handler.Token_Tbl_Type;
666 BEGIN
667         l_Token_Tbl(1).Token_Name  := 'OPERATION_SEQUENCE_NUMBER';
668         l_Token_Tbl(1).Token_Value :=
669       p_bom_comp_ops_rec.additional_operation_seq_num;
670   l_token_tbl(2).token_name  := 'REVISED_COMPONENT_NAME';
671   l_token_tbl(2).token_value := p_bom_comp_ops_rec.component_item_name;
672 
673         BOM_Comp_Operation_Util.Query_Row
674   (   p_component_sequence_id=>
675         p_bom_comp_ops_unexp_rec.component_sequence_id
676 ,p_additional_operation_seq_num =>p_bom_comp_ops_rec.additional_operation_seq_num
677   ,   x_bom_comp_ops_rec    => x_old_bom_comp_ops_rec
678   ,   x_bom_comp_ops_unexp_rec  => x_old_bom_comp_ops_unexp_rec
679   ,   x_Return_Status   => l_return_status
680   );
681 
682         IF l_return_status = Bom_Globals.G_RECORD_FOUND AND
683            p_bom_comp_ops_rec.transaction_type = Bom_Globals.G_OPR_CREATE
684         THEN
685                 Error_Handler.Add_Error_Token
686                 (  x_Mesg_token_tbl => l_Mesg_Token_Tbl
687                  , p_Mesg_Token_Tbl => l_Mesg_Token_Tbl
688                  , p_message_name  => 'BOM_COMP_OPS_ALREADY_EXISTS'
689                  , p_token_tbl     => l_token_tbl
690                  );
691                  l_return_status := FND_API.G_RET_STS_ERROR;
692         ELSIF l_return_status = Bom_Globals.G_RECORD_NOT_FOUND AND
693               p_bom_comp_ops_rec.transaction_type IN
694                  (Bom_Globals.G_OPR_UPDATE, Bom_Globals.G_OPR_DELETE)
695         THEN
696                 Error_Handler.Add_Error_Token
697                 (  x_Mesg_token_tbl => l_Mesg_Token_Tbl
698                  , p_Mesg_Token_Tbl => l_Mesg_Token_Tbl
699                  , p_message_name  => 'BOM_COMP_OPS_DOESNOT_EXIST'
700                  , p_token_tbl     => l_token_tbl
701                  );
702                  l_return_status := FND_API.G_RET_STS_ERROR;
703         ELSIF l_Return_status = FND_API.G_RET_STS_UNEXP_ERROR
704         THEN
705                 Error_Handler.Add_Error_Token
706                 (  x_Mesg_token_tbl     => l_Mesg_Token_Tbl
707                  , p_Mesg_Token_Tbl     => l_Mesg_Token_Tbl
708                  , p_message_name       => NULL
709                  , p_message_text       =>
710                    'Unexpected error while existence verification of ' ||
711                    'Component Operation '||
712                    p_bom_comp_ops_rec.operation_sequence_number
713                  , p_token_tbl          => l_token_tbl
714                  );
715         ELSE
716 
717                  /* Assign the relevant transaction type for SYNC operations */
718 
719                  IF p_bom_comp_ops_rec.transaction_type = 'SYNC' THEN
720                    IF l_return_status = Bom_Globals.G_RECORD_FOUND THEN
721                      x_old_bom_comp_ops_rec.transaction_type :=
722                                                    Bom_Globals.G_OPR_UPDATE;
723                    ELSE
724                      x_old_bom_comp_ops_rec.transaction_type :=
725                                                    Bom_Globals.G_OPR_CREATE;
726                    END IF;
727                  END IF;
728                  l_return_status := FND_API.G_RET_STS_SUCCESS;
729 
730         END IF;
731 
732         x_return_status := l_return_status;
733         x_Mesg_Token_Tbl := l_Mesg_Token_Tbl;
734 
735 END Check_Existence;
736 
737 PROCEDURE Check_Lineage
738 (  p_bom_comp_ops_rec           IN  Bom_Bo_Pub.Bom_Comp_Ops_Rec_Type
739  , p_bom_comp_ops_unexp_rec     IN  Bom_Bo_Pub.Bom_Comp_Ops_Unexp_Rec_Type
740  , x_Mesg_Token_Tbl             IN OUT NOCOPY Error_Handler.Mesg_Token_Tbl_Type
741  , x_Return_Status              IN OUT NOCOPY VARCHAR2
742 )
743 IS
744   l_token_tbl     Error_Handler.Token_Tbl_Type;
745   l_Mesg_Token_Tbl  Error_Handler.Mesg_Token_Tbl_Type;
746 
747   CURSOR c_GetComponent IS
748   SELECT component_sequence_id
749     FROM bom_inventory_components
750    WHERE component_item_id= p_bom_comp_ops_unexp_rec.component_item_id
751      AND operation_seq_num=p_bom_comp_ops_rec.operation_sequence_number
752      AND effectivity_date = p_bom_comp_ops_rec.start_effective_date
753      AND bill_sequence_id = p_bom_comp_ops_unexp_rec.bill_sequence_id;
754 BEGIN
755   x_return_status := FND_API.G_RET_STS_SUCCESS;
756 
757   FOR Component IN c_GetComponent LOOP
758     IF Component.component_sequence_id <>
759       p_bom_comp_ops_unexp_rec.component_sequence_id
760     THEN
761                                 l_Token_Tbl(1).token_name  :=
762           'REVISED_COMPONENT_NAME';
763                                 l_Token_Tbl(1).token_value :=
764                                      p_bom_comp_ops_rec.component_item_name;
765                                 l_Token_Tbl(2).token_name  :=
766           'OPERATION_SEQUENCE_NUMBER';
767                                 l_Token_Tbl(2).token_value :=
768                                  p_bom_comp_ops_rec.operation_sequence_number;
769          l_Token_Tbl(3).token_name  :=
770                                         'ASSEMBLY_ITEM_NAME';
771                                 l_Token_Tbl(3).token_value :=
772                                  p_bom_comp_ops_rec.assembly_item_name;
773 
774                                 Error_Handler.Add_Error_Token
775                                 (  p_Message_Name => 'BOM_COPS_REV_ITEM_MISMATCH'
776                                  , p_Mesg_Token_Tbl => l_Mesg_Token_Tbl
777                                  , x_Mesg_Token_Tbl => l_Mesg_Token_Tbl
778                                  , p_Token_Tbl      => l_Token_Tbl
779                                  );
780                                 x_return_status := FND_API.G_RET_STS_ERROR;
781     END IF;
782   END LOOP;
783 
784   x_Mesg_Token_Tbl := l_Mesg_Token_Tbl;
785 
786 END CHECK_LINEAGE;
787 
788 
789 
790 END BOM_Validate_Comp_Operation;