DBA Data[Home] [Help]

PACKAGE BODY: APPS.BOM_RTG_PVT

Source


1 PACKAGE BODY Bom_Rtg_Pvt  AS
2 /* $Header: BOMRPVTB.pls 120.3 2006/05/23 05:01:57 bbpatel noship $*/
3 --
4 --  Copyright (c) 2000 Oracle Corporation, Redwood Shores, CA, USA
5 --  All rights reserved.
6 --
7 --  FILENAME
8 --
9 --    BOMRPVTB.pls
10 --
11 --  DESCRIPTION
12 --
13 --      Body of package Bom_Rtg_Pvt
14 --
15 --  NOTES
16 --
17 --  HISTORY
18 --
19 --  02-AUG-1999 Biao Zhang      Initial Creation
20 --
21 --  Global constant holding the package name
22 
23 G_PKG_NAME              CONSTANT VARCHAR2(30) := 'Bom_Rtg_Pvt';
24 G_EXC_QUIT_IMPORT       EXCEPTION;
25 
26 EXC_SEV_QUIT_RECORD     EXCEPTION;
27 EXC_SEV_QUIT_BRANCH     EXCEPTION;
28 EXC_SEV_SKIP_BRANCH     EXCEPTION;
29 EXC_FAT_QUIT_OBJECT     EXCEPTION;
30 EXC_SEV_QUIT_OBJECT     EXCEPTION;
31 EXC_UNEXP_SKIP_OBJECT   EXCEPTION;
32 EXC_SEV_QUIT_SIBLINGS   EXCEPTION;
33 EXC_FAT_QUIT_SIBLINGS   EXCEPTION;
34 EXC_FAT_QUIT_BRANCH     EXCEPTION;
35 
36 --  Operation_Resources
37 
38 /****************************************************************************
39 * Procedure : Operation_Resources
40 * Parameters IN   : Operation Resources Table and all the other sibiling entities
41 * Parameters OUT  : Operatin Resources and all the other sibiling entities
42 * Purpose   : This procedure will process all the Operation Resources records.
43 *
44 *****************************************************************************/
45 
46 PROCEDURE Operation_Resources
47 (   p_validation_level        IN  NUMBER
48 ,   p_organization_id         IN  NUMBER
49 ,   p_assembly_item_name      IN  VARCHAR2
50 ,   p_alternate_routing_code  IN  VARCHAR2
51 ,   p_operation_seq_num       IN  NUMBER
52 ,   p_effectivity_date        IN  DATE
53 ,   p_operation_type          IN  NUMBER
54 ,   p_op_resource_tbl         IN  Bom_Rtg_Pub.Op_Resource_Tbl_Type
55 ,   p_sub_resource_tbl        IN  Bom_Rtg_Pub.Sub_Resource_Tbl_Type
56 ,   x_op_resource_tbl         IN OUT NOCOPY Bom_Rtg_Pub.Op_Resource_Tbl_Type
57 ,   x_sub_resource_tbl        IN OUT NOCOPY Bom_Rtg_Pub.Sub_Resource_Tbl_Type
58 ,   x_mesg_token_tbl          IN OUT NOCOPY Error_Handler.Mesg_Token_Tbl_Type
59 ,   x_return_status           IN OUT NOCOPY VARCHAR2
60 )
61 
62 IS
63 
64 /* Exposed and Unexposed record */
65 l_op_resource_rec         Bom_Rtg_Pub.Op_Resource_Rec_Type ;
66 l_op_res_unexp_rec        Bom_Rtg_Pub.Op_Res_Unexposed_Rec_Type ;
67 l_op_resource_tbl         Bom_Rtg_Pub.Op_Resource_Tbl_Type ;
68 l_old_op_resource_rec     Bom_Rtg_Pub.Op_Resource_Rec_Type ;
69 l_old_op_res_unexp_rec    Bom_Rtg_Pub.Op_Res_Unexposed_Rec_Type ;
70 
71 /* Other Entities */
72 l_rtg_header_rec        Bom_Rtg_Pub.Rtg_Header_Rec_Type ;
73 l_rtg_revision_tbl      Bom_Rtg_Pub.Rtg_Revision_Tbl_Type ;
74 l_operation_tbl         Bom_Rtg_Pub.Operation_Tbl_Type ;
75 l_sub_resource_tbl      Bom_Rtg_Pub.Sub_Resource_Tbl_Type  := p_sub_resource_tbl ;
76 l_op_network_tbl        Bom_Rtg_Pub.Op_Network_Tbl_Type ;
77 
78 /* Error Handling Variables */
79 l_token_tbl             Error_Handler.Token_Tbl_Type ;
80 l_mesg_token_tbl        Error_Handler.Mesg_Token_Tbl_Type ;
81 l_other_token_tbl       Error_Handler.Token_Tbl_Type;
82 l_other_message         VARCHAR2(2000);
83 l_err_text              VARCHAR2(2000);
84 
85 
86 /* Others */
87 l_return_status         VARCHAR2(1);
88 l_bo_return_status      VARCHAR2(1);
89 l_op_parent_exists      BOOLEAN := FALSE ;
90 l_rtg_parent_exists     BOOLEAN := FALSE ;
91 l_process_children      BOOLEAN := TRUE ;
92 l_valid                 BOOLEAN := TRUE;
93 l_temp_op_rec		BOM_RTG_Globals.Temp_Op_Rec_Type;
94 
95 BEGIN
96 
97    --  Init local table variables.
98    l_return_status    := 'S';
99    l_bo_return_status := 'S';
100    l_op_resource_tbl  := p_op_resource_tbl ;
101    l_op_res_unexp_rec.organization_id := BOM_Rtg_Globals.Get_Org_Id ;
102    FOR I IN 1..l_op_resource_tbl.COUNT LOOP
103    BEGIN
104 
105       --  Load local records
106       l_op_resource_rec := l_op_resource_tbl(I) ;
107 
108       l_op_resource_rec.transaction_type :=
109          UPPER(l_op_resource_rec.transaction_type) ;
110 
111       --
112       -- make sure to set process_children to false at the start of
113       -- every iteration
114       --
115       l_process_children := FALSE;
116 
117       --
118       -- Initialize the Unexposed Record for every iteration of the Loop
119       -- so that sequence numbers get generated for every new row.
120       --
121       l_op_res_unexp_rec.Operation_Sequence_Id   := NULL ;
122       l_op_res_unexp_rec.Substitute_Group_Number := l_op_resource_rec.Substitute_Group_Number ;
123       l_op_res_unexp_rec.Resource_Id             := NULL ;
124       l_op_res_unexp_rec.Activity_Id             := NULL ;
125       l_op_res_unexp_rec.Setup_Id                := NULL ;
126 
127 
128       IF p_operation_seq_num  IS NOT NULL AND
129          p_assembly_item_name IS NOT NULL AND
130          p_effectivity_date   IS NOT NULL AND
131          p_organization_id    IS NOT NULL
132       THEN
133          -- Revised Operation or Operation Sequence parent exists
134          l_op_parent_exists  := TRUE ;
135 
136       ELSIF p_assembly_item_name IS NOT NULL AND
137             p_organization_id    IS NOT NULL
138       THEN
139          -- Revised Item or Routing parent exists
140          l_rtg_parent_exists := TRUE ;
141       END IF ;
142 
143 	 -- If effectivity/op seq num of the parent operation has changed, update the child resource record
144       IF BOM_RTG_Globals.G_Init_Eff_Date_Op_Num_Flag
145       AND BOM_RTG_Globals.Get_Temp_Op_Rec1
146           ( l_op_resource_rec.operation_sequence_number
147 	  , p_effectivity_date -- this cannot be null as this check is done only when the op has children
148 	  , l_temp_op_rec) THEN
149 	 l_op_resource_rec.operation_sequence_number := l_temp_op_rec.new_op_seq_num;
150 	 l_op_resource_rec.op_start_effective_Date := l_temp_op_rec.new_start_eff_date;
151 /*
152 		Bom_Default_Op_Res.Init_Eff_Date_Op_Seq_Num
153 		( p_op_seq_num	=> p_operation_seq_num
154 		, p_eff_date	=> p_effectivity_date
155 		, p_op_res_rec	=> l_op_resource_rec
156 		, x_op_res_rec	=> l_op_resource_rec
157 		);
158 */
159       END IF;
160 
161 
162       -- Process Flow Step 2: Check if record has not yet been processed and
163       -- that it is the child of the parent that called this procedure
164       --
165 
166       IF (l_op_resource_rec.return_status IS NULL OR
167           l_op_resource_rec.return_status  = FND_API.G_MISS_CHAR)
168          AND
169          (
170             -- Did Op_Seq call this procedure, that is,
171             -- if revised operation(operation sequence) exists, then is this record a child ?
172             (l_op_parent_exists AND
173                (l_op_resource_rec.assembly_item_name = p_assembly_item_name AND
174                 l_op_res_unexp_rec.organization_id = p_organization_id      AND
175                 NVL(l_op_resource_rec.alternate_routing_code, FND_API.G_MISS_CHAR)
176                            = NVL(p_alternate_routing_code, FND_API.G_MISS_CHAR) AND
177                 l_op_resource_rec.operation_sequence_number
178                                                       = p_operation_seq_num AND
179                 l_op_resource_rec.op_start_effective_date
180                                                       = p_effectivity_date  AND
181                 NVL(l_op_resource_rec.operation_type, 1)
182                                                       = NVL(p_operation_type, 1)
183                )
184             )
185             OR
186             -- Did Rtg_Header call this procedure, that is,
187             -- if revised item or routing header exists, then is this record a child ?
188             (l_rtg_parent_exists AND
189                (l_op_resource_rec.assembly_item_name = p_assembly_item_name AND
190                l_op_res_unexp_rec.organization_id    = p_organization_id    AND
191                NVL(l_op_resource_rec.alternate_routing_code, FND_API.G_MISS_CHAR)
192                                = NVL(p_alternate_routing_code, FND_API.G_MISS_CHAR)
193                )
194             )
195            OR
196            (NOT l_rtg_parent_exists AND NOT l_op_parent_exists)
197          )
198       THEN
199          l_return_status := FND_API.G_RET_STS_SUCCESS;
200          l_op_resource_rec.return_status := FND_API.G_RET_STS_SUCCESS;
201 
202          --
203          -- Process Flow step 3 :Check if transaction_type is valid
204          -- Transaction_Type must be CRATE, UPDATE, DELETE or CANCEL(in only ECO for Rrg)
205          -- Call the BOM_Rtg_Globals.Transaction_Type_Validity
206          --
207          BOM_Rtg_Globals.Transaction_Type_Validity
208          (   p_transaction_type => l_op_resource_rec.transaction_type
209          ,   p_entity           => 'Op_Res'
210          ,   p_entity_id        => l_op_resource_rec.resource_sequence_number
211          ,   x_valid            => l_valid
212          ,   x_mesg_token_tbl   => l_mesg_token_tbl
213          ) ;
214 
215          IF NOT l_valid
216          THEN
217                 l_return_status := Error_Handler.G_STATUS_ERROR;
218                 RAISE EXC_SEV_QUIT_RECORD ;
219          END IF ;
220 
221          --
222          -- Process Flow step 4(a): Convert user unique index to unique
223          -- index I
224          -- Call BOM_Rtg_Val_To_Id.Op_Resource_UUI_To_UI Shared Utility Package
225          --
226 	 BOM_Rtg_Val_To_Id.Op_Resource_UUI_To_UI
227          ( p_op_resource_rec    => l_op_resource_rec
228          , p_op_res_unexp_rec   => l_op_res_unexp_rec
229          , x_op_res_unexp_rec   => l_op_res_unexp_rec
230          , x_mesg_token_tbl     => l_mesg_token_tbl
231          , x_return_status      => l_return_status
232          ) ;
233 
234          IF BOM_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
235          ('Convert to User Unique Index to Index1 completed with return_status: ' || l_return_status) ;
236          END IF;
237 
238          IF l_return_status = Error_Handler.G_STATUS_ERROR
239          THEN
240             l_other_message := 'BOM_RES_UUI_SEV_ERROR';
241             l_other_token_tbl(1).token_name := 'RES_SEQ_NUMBER';
242             l_other_token_tbl(1).token_value :=
243                         l_op_resource_rec.resource_sequence_number ;
244             RAISE EXC_SEV_QUIT_BRANCH ;
245 
246          ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
247          THEN
248             l_other_message := 'BOM_RES_UUI_UNEXP_SKIP';
249             l_other_token_tbl(1).token_name := 'RES_SEQ_NUMBER';
250             l_other_token_tbl(1).token_value :=
251                         l_op_resource_rec.resource_sequence_number ;
252             RAISE EXC_UNEXP_SKIP_OBJECT;
253          END IF ;
254 
255 /*       --
256          -- Process Flow step 4(b): Convert user unique index to unique
257          -- index II
258          -- Call the BOM_Rtg_Val_To_Id.Operation_UUI_To_UI2
259          --
260 
261          BOM_Rtg_Val_To_Id.Op_Resource_UUI_To_UI2
262          ( p_op_resource_rec    => l_op_resource_rec
263          , p_op_res_unexp_rec   => l_op_res_unexp_rec
264          , x_op_res_unexp_rec   => l_op_res_unexp_rec
265          , x_mesg_token_tbl     => l_mesg_token_tbl
266          , x_other_message      => l_other_message
267          , x_other_token_tbl    => l_other_token_tbl
268          , x_return_status      => l_return_status
269          ) ;
270 
271          IF BOM_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
272          ('Convert to User Unique Index to Index2 completed with return_status: ' || l_return_status) ;
273          END IF;
274 
275          IF l_return_status = Error_Handler.G_STATUS_ERROR
276          THEN
277             RAISE EXC_SEV_QUIT_SIBLINGS ;
278          ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
279          THEN
280             l_other_message := 'BOM_RES_UUI_UNEXP_SKIP';
281             l_other_token_tbl(1).token_name := 'RES_SEQ_NUMBER';
282             l_other_token_tbl(1).token_value :=
283                    l_op_resource_rec.resource_sequence_number ;
284             RAISE EXC_UNEXP_SKIP_OBJECT;
285          END IF ;
286 */
287          --
288          -- Process Flow step 5: Verify Operation Resource's existence
289          -- Call the Bom_Validate_Op_Seq.Check_Existence
290          --
291          --
292          Bom_Validate_Op_Res.Check_Existence
293          (  p_op_resource_rec        => l_op_resource_rec
294          ,  p_op_res_unexp_rec       => l_op_res_unexp_rec
295          ,  x_old_op_resource_rec    => l_old_op_resource_rec
296          ,  x_old_op_res_unexp_rec   => l_old_op_res_unexp_rec
297          ,  x_mesg_token_tbl         => l_mesg_token_tbl
298          ,  x_return_status          => l_return_status
299          ) ;
300 
301 
302          IF BOM_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
303          ('Check Existence completed with return_status: ' || l_return_status) ;
304          END IF ;
305 
306          IF l_return_status = Error_Handler.G_STATUS_ERROR
307          THEN
308             l_other_message := 'BOM_RES_EXS_SEV_SKIP';
309             l_other_token_tbl(1).token_name := 'RES_SEQ_NUMBER';
310             l_other_token_tbl(1).token_value :=
311                           l_op_resource_rec.resource_sequence_number ;
312             l_other_token_tbl(2).token_name := 'REVISED_ITEM_NAME';
313             l_other_token_tbl(2).token_value :=
314                           l_op_resource_rec.assembly_item_name ;
315             RAISE EXC_SEV_QUIT_BRANCH;
316          ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
317          THEN
318             l_other_message := 'BOM_RES_EXS_UNEXP_SKIP';
319             l_other_token_tbl(1).token_name := 'RES_SEQ_NUMBER';
320             l_other_token_tbl(1).token_value :=
321                           l_op_resource_rec.resource_sequence_number ;
322             l_other_token_tbl(2).token_name := 'REVISED_ITEM_NAME';
323             l_other_token_tbl(2).token_value :=
324                           l_op_resource_rec.assembly_item_name ;
325             RAISE EXC_UNEXP_SKIP_OBJECT;
326          END IF;
327 
328          --
329          -- Process Flow step 6: Is Operation Resource record an orphan ?
330          --
331 
332          IF NOT l_op_parent_exists
333          THEN
334 
335             --
336             -- Process Flow step 7 : Check Assembly Item Operability for Routing
337             -- Call Bom_Validate_Rtg_Header.Check_Access
338             --
339 
340             Bom_Validate_Rtg_Header.Check_Access
341             ( p_assembly_item_name => l_op_resource_rec.assembly_item_name
342             , p_assembly_item_id   => l_op_res_unexp_rec.assembly_item_id
343             , p_organization_id    => l_op_res_unexp_rec.organization_id
344             , p_mesg_token_tbl     => Error_Handler.G_MISS_MESG_TOKEN_TBL
345             , p_alternate_rtg_code => l_op_resource_rec.alternate_routing_code
346             , x_mesg_token_tbl     => l_mesg_token_tbl
347             , x_return_status      => l_return_status
348             ) ;
349 
350             IF BOM_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
351             ('Check Assembly Item Operability completed with return_status: ' || l_return_status) ;
352             END IF ;
353 
354             IF l_return_status = Error_Handler.G_STATUS_ERROR
355             THEN
356                l_other_message := 'BOM_RES_RITACC_FAT_FATAL';
357                l_other_token_tbl(1).token_name := 'RES_SEQ_NUMBER';
358                l_other_token_tbl(1).token_value :=
359                           l_op_resource_rec.resource_sequence_number ;
360                l_return_status := 'F' ;
361                RAISE EXC_FAT_QUIT_SIBLINGS ;
362             ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
363             THEN
364                l_other_message := 'BOM_RES_RITACC_UNEXP_SKIP';
365                l_other_token_tbl(1).token_name := 'RES_SEQ_NUMBER';
366                l_other_token_tbl(1).token_value :=
367                           l_op_resource_rec.resource_sequence_number ;
368                RAISE EXC_UNEXP_SKIP_OBJECT;
369             END IF;
370 
371          END IF; -- l_op_parent_exists
372 
373          --
374          -- Process Flow step 8 : Check if the parent operation is
375          -- non-referencing operation of type: Event
376          --
377          Bom_Validate_Op_Res.Check_NonRefEvent
378          (   p_operation_sequence_id => l_op_res_unexp_rec.operation_sequence_id
379           ,  p_operation_type      => l_op_resource_rec.operation_type
380           ,  p_entity_processed    => 'RES'
381           ,  x_mesg_token_tbl      => l_mesg_token_tbl
382           ,  x_return_status       => l_return_status
383          ) ;
384 
385          IF BOM_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
386             ('Check non-ref operation completed with return_status: ' || l_return_status) ;
387          END IF ;
388 
389          IF l_return_status = Error_Handler.G_STATUS_ERROR
390          THEN
391                IF l_op_resource_rec.operation_type IN (2 , 3) -- Process or Line Op
392                THEN
393 
394                   l_token_tbl(1).token_name := 'RES_SEQ_NUMBER';
395                   l_token_tbl(1).token_value :=
396                           l_op_resource_rec.resource_sequence_number ;
397                   l_token_tbl(2).token_name := 'OP_SEQ_NUMBER';
398                   l_token_tbl(2).token_value :=
399                           l_op_resource_rec.operation_sequence_number ;
400 
401                   Error_Handler.Add_Error_Token
402                         ( p_Message_Name   => 'BOM_RES_OPTYPE_NOT_EVENT'
403                         , p_mesg_token_tbl => l_mesg_token_tbl
404                         , x_mesg_token_tbl => l_mesg_token_tbl
405                         , p_Token_Tbl      => l_token_tbl
406                         ) ;
407                ELSIF nvl(BOM_Globals.Get_Caller_Type, '') <> 'MIGRATION' THEN
408                   l_token_tbl(1).token_name := 'RES_SEQ_NUMBER';
409                   l_token_tbl(1).token_value :=
410                           l_op_resource_rec.resource_sequence_number ;
411                   l_token_tbl(2).token_name := 'OP_SEQ_NUMBER';
412                   l_token_tbl(2).token_value :=
413                           l_op_resource_rec.operation_sequence_number ;
414 
415                   Error_Handler.Add_Error_Token
416                         ( p_Message_Name   => 'BOM_RES_MUST_NONREF'
417                         , p_mesg_token_tbl => l_mesg_token_tbl
418                         , x_mesg_token_tbl => l_mesg_token_tbl
419                         , p_Token_Tbl      => l_token_tbl
420                         ) ;
421 
422                END IF ;
423 
424                l_return_status := 'F';
425                l_other_message := 'BOM_RES_ACCESS_FAT_FATAL';
426                l_other_token_tbl(1).token_name := 'RES_SEQ_NUMBER';
427                l_other_token_tbl(1).token_value :=
428                           l_op_resource_rec.resource_sequence_number ;
429                RAISE EXC_FAT_QUIT_SIBLINGS ;
430 
431          ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
432          THEN
433                l_other_message := 'BOM_RES_ACCESS_UNEXP_SKIP';
434                l_other_token_tbl(1).token_name := 'RES_SEQ_NUMBER';
435                l_other_token_tbl(1).token_value :=
436                           l_op_resource_rec.resource_sequence_number ;
437                RAISE EXC_UNEXP_SKIP_OBJECT;
438          END IF;
439 
440 
441          --
442          -- Process Flow step 9: Value to Id conversions
443          -- Call BOM_Rtg_Val_To_Id.Op_Resource_VID
444          --
445 
446          BOM_Rtg_Val_To_Id.Op_Resource_VID
447          (  p_op_resource_rec        => l_op_resource_rec
448          ,  p_op_res_unexp_rec       => l_op_res_unexp_rec
449          ,  x_op_res_unexp_rec       => l_op_res_unexp_rec
450          ,  x_mesg_token_tbl         => l_mesg_token_tbl
451          ,  x_return_status          => l_return_status
452          );
453 
454          IF BOM_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
455          ('Value-id conversions completed with return_status: ' || l_return_status) ;
456          END IF ;
457 
458          IF l_return_status = Error_Handler.G_STATUS_ERROR
459          THEN
460             IF l_op_resource_rec.transaction_type = 'CREATE'
461             THEN
462                l_other_message := 'BOM_RES_VID_CSEV_SKIP';
463                l_other_token_tbl(1).token_name := 'RES_SEQ_NUMBER';
464                l_other_token_tbl(1).token_value :=
465                           l_op_resource_rec.resource_sequence_number ;
466                RAISE EXC_SEV_SKIP_BRANCH;
467             ELSE
468                RAISE EXC_SEV_QUIT_RECORD ;
469             END IF ;
470 
471          ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
472          THEN
473             l_other_message := 'BOM_RES_VID_UNEXP_SKIP';
474             l_other_token_tbl(1).token_name := 'RES_SEQ_NUMBER';
475             l_other_token_tbl(1).token_value :=
476                           l_op_resource_rec.resource_sequence_number ;
477             RAISE EXC_UNEXP_SKIP_OBJECT;
478 
479          ELSIF l_return_status ='S' AND l_mesg_token_tbl .COUNT <>0
480          THEN
481 /*
482             p_rtg_header_rec      => Bom_Rtg_Pub.G_MISS_RTG_HEADER_REC
483          ,  p_rtg_revision_tbl    => Bom_Rtg_Pub.G_MISS_RTG_REVISION_TBL
484          ,  p_op_resource_tbl     => Bom_Rtg_Pub.G_MISS_OP_RESOURCE_TBL
485          ,  p_sub_resource_tbl    => Bom_Rtg_Pub.G_MISS_SUB_RESOURCE_TBL
486          ,  p_operation_tbl       => Bom_Rtg_Pub.G_MISS_OPERATION_TBL
487          ,  p_op_network_tbl      => Bom_Rtg_Pub.G_MISS_OP_NETWORK_TBL
488 */
489 
490             Bom_Rtg_Error_Handler.Log_Error
491             (
492                p_rtg_header_rec      => Bom_Rtg_Pub.G_MISS_RTG_HEADER_REC
493             ,  p_rtg_revision_tbl    => Bom_Rtg_Pub.G_MISS_RTG_REVISION_TBL
494             ,  p_operation_tbl       => Bom_Rtg_Pub.G_MISS_OPERATION_TBL
495             ,  p_op_resource_tbl     => l_op_resource_tbl
496             ,  p_sub_resource_tbl    => l_sub_resource_tbl
497             ,  p_op_network_tbl      => Bom_Rtg_Pub.G_MISS_OP_NETWORK_TBL
498             ,  p_mesg_token_tbl      => l_mesg_token_tbl
499             ,  p_error_status        => 'W'
500             ,  p_error_scope         => NULL
501             ,  p_error_level         => Error_Handler.G_RES_LEVEL
502             ,  p_entity_index        => I
503             ,  p_other_message       => NULL
504             ,  p_other_mesg_appid    => 'BOM'
505             ,  p_other_status        => NULL
506             ,  p_other_token_tbl     => Error_Handler.G_MISS_TOKEN_TBL
507             ,  x_rtg_header_rec      => l_rtg_header_rec
508             ,  x_rtg_revision_tbl    => l_rtg_revision_tbl
509             ,  x_op_network_tbl      => l_op_network_tbl
510             ,  x_operation_tbl       => l_operation_tbl
511             ,  x_op_resource_tbl     => l_op_resource_tbl
512             ,  x_sub_resource_tbl    => l_sub_resource_tbl
513             ) ;
514          END IF;
515 
516          --
517          -- Process Flow step 10 : Check required fields exist
518          -- (also includes a part of conditionally required fields)
519          --
520 
521 /*
522          Bom_Validate_Op_Res.Check_Required
523          ( p_op_resource_rec            => l_op_resource_rec
524          , x_return_status              => l_return_status
525          , x_mesg_token_tbl             => l_mesg_token_tbl
526          ) ;
527 
528 
529 
530          IF BOM_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
531          ('Check required completed with return_status: ' || l_return_status) ;
532          END IF ;
533 
534          IF l_return_status = Error_Handler.G_STATUS_ERROR
535          THEN
536             IF l_op_resource_rec.transaction_type = BOM_Rtg_Globals.G_OPR_CREATE
537             THEN
538                l_other_message := 'BOM_RES_REQ_CSEV_SKIP';
539                l_other_token_tbl(1).token_name := 'RES_SEQ_NUMBER';
540                l_other_token_tbl(1).token_value :=
541                           l_op_resource_rec.resource_sequence_number ;
542                RAISE EXC_SEV_SKIP_BRANCH ;
543             ELSE
544                RAISE EXC_SEV_QUIT_RECORD ;
545             END IF;
546          ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
547          THEN
548             l_other_message := 'BOM_RES_REQ_UNEXP_SKIP';
549             l_other_token_tbl(1).token_name := 'RES_SEQ_NUMBER';
550             l_other_token_tbl(1).token_value :=
551                           l_op_resource_rec.resource_sequence_number ;
552             RAISE EXC_UNEXP_SKIP_OBJECT ;
553          END IF;
554 */
555 
556          --
557          -- Process Flow step 11 : Attribute Validation for CREATE and UPDATE
558          -- Call Bom_Validate_Op_Res.Check_Attributes
559          --
560 
561          IF l_op_resource_rec.transaction_type IN
562             (BOM_Rtg_Globals.G_OPR_CREATE, BOM_Rtg_Globals.G_OPR_UPDATE)
563          THEN
564             Bom_Validate_Op_Res.Check_Attributes
565             ( p_op_resource_rec   => l_op_resource_rec
566             , p_op_res_unexp_rec  => l_op_res_unexp_rec
567             , x_return_status     => l_return_status
568             , x_mesg_token_tbl    => l_mesg_token_tbl
569             ) ;
570 
571             IF BOM_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
572             ('Attribute validation completed with return_status: ' || l_return_status) ;
573             END IF ;
574 
575 
576             IF l_return_status = Error_Handler.G_STATUS_ERROR
577             THEN
578                IF l_op_resource_rec.transaction_type = BOM_Rtg_Globals.G_OPR_CREATE
579                THEN
580                   l_other_message := 'BOM_RES_ATTVAL_CSEV_SKIP';
581                   l_other_token_tbl(1).token_name := 'RES_SEQ_NUMBER';
582                   l_other_token_tbl(1).token_value :=
583                            l_op_resource_rec.resource_sequence_number ;
584                      RAISE EXC_SEV_SKIP_BRANCH ;
585                   ELSE
586                      RAISE EXC_SEV_QUIT_RECORD ;
587                END IF;
588             ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
589             THEN
590                l_other_message := 'BOM_RES_ATTVAL_UNEXP_SKIP';
591                l_other_token_tbl(1).token_name := 'RES_SEQ_NUMBER';
592                l_other_token_tbl(1).token_value :=
593                            l_op_resource_rec.resource_sequence_number ;
594                RAISE EXC_UNEXP_SKIP_OBJECT ;
595             ELSIF l_return_status ='S' AND l_mesg_token_tbl .COUNT <> 0
596             THEN
597                Bom_Rtg_Error_Handler.Log_Error
598                (
599                   p_rtg_header_rec      => Bom_Rtg_Pub.G_MISS_RTG_HEADER_REC
600                ,  p_rtg_revision_tbl    => Bom_Rtg_Pub.G_MISS_RTG_REVISION_TBL
601                ,  p_operation_tbl       => Bom_Rtg_Pub.G_MISS_OPERATION_TBL
602                ,  p_op_resource_tbl     => l_op_resource_tbl
603                ,  p_sub_resource_tbl    => l_sub_resource_tbl
604                ,  p_op_network_tbl      => Bom_Rtg_Pub.G_MISS_OP_NETWORK_TBL
605                ,  p_mesg_token_tbl      => l_mesg_token_tbl
606                ,  p_error_status        => 'W'
607                ,  p_error_scope         => NULL
608                ,  p_other_message       => NULL
609                ,  p_other_mesg_appid    => 'BOM'
610                ,  p_other_status        => NULL
611                ,  p_other_token_tbl     => Error_Handler.G_MISS_TOKEN_TBL
612                ,  p_error_level         => Error_Handler.G_RES_LEVEL
613                ,  p_entity_index        => I
614                ,  x_rtg_header_rec      => l_rtg_header_rec
615                ,  x_rtg_revision_tbl    => l_rtg_revision_tbl
616                ,  x_op_network_tbl      => l_op_network_tbl
617                ,  x_operation_tbl       => l_operation_tbl
618                ,  x_op_resource_tbl     => l_op_resource_tbl
619                ,  x_sub_resource_tbl    => l_sub_resource_tbl
620                ) ;
621            END IF;
622         END IF;
623 
624 
625 
626         IF l_op_resource_rec.transaction_type IN
627            (BOM_Rtg_Globals.G_OPR_UPDATE, BOM_Rtg_Globals.G_OPR_DELETE)
628         THEN
629 
630         --
631         -- Process flow step 12: Populate NULL columns for Update and Delete
632         -- Call Bom_Default_Op_Res.Populate_Null_Columns
633         --
634 
635            IF BOM_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Populate NULL columns') ;
636            END IF ;
637 
638              Bom_Default_Op_Res.Populate_Null_Columns
639              (   p_op_resource_rec       => l_op_resource_rec
640              ,   p_old_op_resource_rec   => l_old_op_resource_rec
641              ,   p_op_res_unexp_rec      => l_op_res_unexp_rec
642              ,   p_old_op_res_unexp_rec  => l_old_op_res_unexp_rec
643              ,   x_op_resource_rec       => l_op_resource_rec
644              ,   x_op_res_unexp_rec      => l_op_res_unexp_rec
645              ) ;
646 
647         ELSIF l_op_resource_rec.transaction_type = BOM_Rtg_Globals.G_OPR_CREATE
648         THEN
649         --
650         -- Process Flow step 13 : Default missing values for Op Resource (CREATE)
651         -- Call Bom_Default_Op_Res.Attribute_Defaulting
652         --
653 
654            IF BOM_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Attribute Defaulting') ;
655            END IF ;
656 
657              Bom_Default_Op_Res.Attribute_Defaulting
658              (   p_op_resource_rec     => l_op_resource_rec
659              ,   p_op_res_unexp_rec    => l_op_res_unexp_rec
660              ,   x_op_resource_rec     => l_op_resource_rec
661              ,   x_op_res_unexp_rec    => l_op_res_unexp_rec
662              ,   x_mesg_token_tbl      => l_mesg_token_tbl
663              ,   x_return_status       => l_return_status
664              ) ;
665 
666 
667            IF BOM_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
668            ('Attribute Defaulting completed with return_status: ' || l_return_status) ;
669            END IF ;
670 
671            IF l_return_status = Error_Handler.G_STATUS_ERROR
672            THEN
673               l_other_message := 'BOM_RES_ATTDEF_CSEV_SKIP';
674               l_other_token_tbl(1).token_name := 'RES_SEQ_NUMBER';
675               l_other_token_tbl(1).token_value :=
676                           l_op_resource_rec.resource_sequence_number ;
677               RAISE EXC_SEV_SKIP_BRANCH ;
678 
679            ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
680            THEN
681               l_other_message := 'BOM_RES_ATTDEF_UNEXP_SKIP';
682               l_other_token_tbl(1).token_name := 'RES_SEQ_NUMBER';
683               l_other_token_tbl(1).token_value :=
684                            l_op_resource_rec.resource_sequence_number ;
685               RAISE EXC_UNEXP_SKIP_OBJECT ;
686            ELSIF l_return_status ='S' AND l_mesg_token_tbl .COUNT <> 0
687            THEN
688                Bom_Rtg_Error_Handler.Log_Error
689                (
690                   p_rtg_header_rec      => Bom_Rtg_Pub.G_MISS_RTG_HEADER_REC
691                ,  p_rtg_revision_tbl    => Bom_Rtg_Pub.G_MISS_RTG_REVISION_TBL
692                ,  p_operation_tbl       => Bom_Rtg_Pub.G_MISS_OPERATION_TBL
693                ,  p_op_resource_tbl     => l_op_resource_tbl
694                ,  p_op_network_tbl      => Bom_Rtg_Pub.G_MISS_OP_NETWORK_TBL
695                ,  p_sub_resource_tbl    => l_sub_resource_tbl
696                ,  p_mesg_token_tbl      => l_mesg_token_tbl
697                ,  p_error_status        => 'W'
698                ,  p_error_scope         => NULL
699                ,  p_other_message       => NULL
700                ,  p_other_mesg_appid    => 'BOM'
701                ,  p_other_status        => NULL
702                ,  p_other_token_tbl     => Error_Handler.G_MISS_TOKEN_TBL
703                ,  p_error_level         => Error_Handler.G_RES_LEVEL
704                ,  p_entity_index        => I
705                ,  x_rtg_header_rec      => l_rtg_header_rec
706                ,  x_rtg_revision_tbl    => l_rtg_revision_tbl
707                ,  x_op_network_tbl      => l_op_network_tbl
708                ,  x_operation_tbl       => l_operation_tbl
709                ,  x_op_resource_tbl     => l_op_resource_tbl
710                ,  x_sub_resource_tbl    => l_sub_resource_tbl
711                ) ;
712           END IF;
713        END IF;
714 
715        --
716        -- Process Flow step 14: Conditionally Required Attributes
717        --
718        --
719        /*
720        IF l_op_resource_rec.transaction_type IN ( BOM_Rtg_Globals.G_OPR_CREATE
721                                                 , BOM_Rtg_Globals.G_OPR_UPDATE )
722        THEN
723           Bom_Validate_Op_Seq.Check_Conditionally_Required
724           ( p_op_resource_rec       => l_op_resource_rec
725           , p_op_res_unexp_rec      => l_op_res_unexp_rec
726           , x_return_status         => l_return_status
727           , x_mesg_token_tbl        => l_mesg_token_tbl
728           ) ;
729 
730 
731           IF BOM_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
732           ('Check Conditionally Required Attr. completed with return_status: ' || l_return_status) ;
733           END IF ;
734 
735 
736           IF l_return_status = Error_Handler.G_STATUS_ERROR
737           THEN
738              IF l_op_resource_rec.transaction_type = BOM_Rtg_Globals.G_OPR_CREATE
739              THEN
740                 l_other_message := 'BOM_RES_CONREQ_CSEV_SKIP';
741                 l_other_token_tbl(1).token_name := 'RES_SEQ_NUMBER';
742                 l_other_token_tbl(1).token_value :=
743                           l_op_resource_rec.resource_sequence_number ;
744                 RAISE EXC_SEV_SKIP_BRANCH ;
745              ELSE
746                 RAISE EXC_SEV_QUIT_RECORD ;
747              END IF;
748           ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
749           THEN
750              l_other_message := 'BOM_RES_CONREQ_UNEXP_SKIP';
751              l_other_token_tbl(1).token_name := 'RES_SEQ_NUMBER';
752              l_other_token_tbl(1).token_value :=
753                           l_op_resource_rec.resource_sequence_number ;
754              RAISE EXC_UNEXP_SKIP_OBJECT ;
755           ELSIF l_return_status ='S' AND l_mesg_token_tbl .COUNT <> 0
756           THEN
757              Bom_Rtg_Error_Handler.Log_Error
758              (    p_rtg_header_rec      => Bom_Rtg_Pub.G_MISS_RTG_HEADER_REC
759                ,  p_rtg_revision_tbl    => Bom_Rtg_Pub.G_MISS_RTG_REVISION_TBL
760                ,  p_operation_tbl       => Bom_Rtg_Pub.G_MISS_OPERATION_TBL
761                ,  p_op_resource_tbl     => l_op_resource_tbl
762                ,  p_op_network_tbl      => Bom_Rtg_Pub.G_MISS_OP_NETWORK_TBL
763                ,  p_sub_resource_tbl    => l_sub_resource_tbl
764                ,  p_mesg_token_tbl      => l_mesg_token_tbl
765                ,  p_error_status        => 'W'
766                ,  p_error_scope         => NULL
767                ,  p_other_message       => NULL
768                ,  p_other_mesg_appid    => 'BOM'
769                ,  p_other_status        => NULL
770                ,  p_other_token_tbl     => Error_Handler.G_MISS_TOKEN_TBL
771                ,  p_error_level         => Error_Handler.G_RES_LEVEL
772                ,  p_entity_index        => I
773                ,  x_rtg_header_rec      => l_rtg_header_rec
774                ,  x_rtg_revision_tbl    => l_rtg_revision_tbl
775                ,  x_op_network_tbl      => l_op_network_tbl
776                ,  x_operation_tbl       => l_operation_tbl
777                ,  x_op_resource_tbl     => l_op_resource_tbl
778                ,  x_sub_resource_tbl    => l_sub_resource_tbl
779              ) ;
780           END IF;
781        END IF;
782        */
783 
784        --
785        -- Process Flow step 15: Entity defaulting for CREATE and UPDATE
786        --
787        IF l_op_resource_rec.transaction_type IN ( BOM_Rtg_Globals.G_OPR_CREATE
788                                                 , BOM_Rtg_Globals.G_OPR_UPDATE )
789 
790        THEN
791           Bom_Default_Op_Res.Entity_Defaulting
792               (   p_op_resource_rec   => l_op_resource_rec
793               ,   p_op_res_unexp_rec  => l_op_res_unexp_rec
794               ,   x_op_resource_rec   => l_op_resource_rec
795               ,   x_op_res_unexp_rec  => l_op_res_unexp_rec
796               ,   x_mesg_token_tbl    => l_mesg_token_tbl
797               ,   x_return_status     => l_return_status
798               ) ;
799 
800           IF BOM_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
801           ('Entity defaulting completed with return_status: ' || l_return_status) ;
802           END IF ;
803 
804           IF l_return_status = Error_Handler.G_STATUS_ERROR
805           THEN
806              IF l_op_resource_rec.transaction_type = BOM_Rtg_Globals.G_OPR_CREATE
807              THEN
808                 l_other_message := 'BOM_RES_ENTDEF_CSEV_SKIP';
809                 l_other_token_tbl(1).token_name  := 'RES_SEQ_NUMBER';
810                 l_other_token_tbl(1).token_value :=
811                           l_op_resource_rec.operation_sequence_number ;
812                 RAISE EXC_SEV_SKIP_BRANCH ;
813              ELSE
814                 RAISE EXC_SEV_QUIT_RECORD ;
815              END IF;
816           ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
817           THEN
818              l_other_message := 'BOM_RES_ENTDEF_UNEXP_SKIP';
819              l_other_token_tbl(1).token_name  := 'RES_SEQ_NUMBER';
820              l_other_token_tbl(1).token_value :=
821                           l_op_resource_rec.resource_sequence_number ;
822              RAISE EXC_UNEXP_SKIP_OBJECT ;
823           ELSIF l_return_status ='S' AND l_mesg_token_tbl .COUNT <> 0
824           THEN
825              Bom_Rtg_Error_Handler.Log_Error
826              (
827                   p_rtg_header_rec      => Bom_Rtg_Pub.G_MISS_RTG_HEADER_REC
828                ,  p_rtg_revision_tbl    => Bom_Rtg_Pub.G_MISS_RTG_REVISION_TBL
829                ,  p_operation_tbl       => Bom_Rtg_Pub.G_MISS_OPERATION_TBL
830                ,  p_op_resource_tbl     => l_op_resource_tbl
831                ,  p_op_network_tbl      => Bom_Rtg_Pub.G_MISS_OP_NETWORK_TBL
832                ,  p_sub_resource_tbl    => l_sub_resource_tbl
833                ,  p_mesg_token_tbl      => l_mesg_token_tbl
834                ,  p_error_status        => 'W'
835                ,  p_error_scope         => NULL
836                ,  p_other_message       => NULL
837                ,  p_other_mesg_appid    => 'BOM'
838                ,  p_other_status        => NULL
839                ,  p_other_token_tbl     => Error_Handler.G_MISS_TOKEN_TBL
840                ,  p_error_level         => Error_Handler.G_RES_LEVEL
841                ,  p_entity_index        => I
842                ,  x_rtg_header_rec      => l_rtg_header_rec
843                ,  x_rtg_revision_tbl    => l_rtg_revision_tbl
844                ,  x_op_network_tbl      => l_op_network_tbl
845                ,  x_operation_tbl       => l_operation_tbl
846                ,  x_op_resource_tbl     => l_op_resource_tbl
847                ,  x_sub_resource_tbl    => l_sub_resource_tbl
848              ) ;
849           END IF ;
850        END IF ;
851 
852 
853        --
854        -- Process Flow step 16 - Entity Level Validation
855        -- Call Bom_Validate_Op_Res.Check_Entity
856        --
857        Bom_Validate_Op_Res.Check_Entity
858           (  p_op_resource_rec       => l_op_resource_rec
859           ,  p_op_res_unexp_rec      => l_op_res_unexp_rec
860           ,  p_old_op_resource_rec   => l_old_op_resource_rec
861           ,  p_old_op_res_unexp_rec  => l_old_op_res_unexp_rec
862           ,  x_op_resource_rec       => l_op_resource_rec
863           ,  x_op_res_unexp_rec      => l_op_res_unexp_rec
864           ,  x_mesg_token_tbl        => l_mesg_token_tbl
865           ,  x_return_status         => l_return_status
866           ) ;
867 
868 
869        IF l_return_status = Error_Handler.G_STATUS_ERROR
870        THEN
871           IF l_op_resource_rec.transaction_type = BOM_Rtg_Globals.G_OPR_CREATE
872           THEN
873              l_other_message := 'BOM_RES_ENTVAL_CSEV_SKIP';
874              l_other_token_tbl(1).token_name  := 'RES_SEQ_NUMBER';
875              l_other_token_tbl(1).token_value :=
876                            l_op_resource_rec.resource_sequence_number ;
877              RAISE EXC_SEV_SKIP_BRANCH ;
878           ELSE
879              RAISE EXC_SEV_QUIT_RECORD ;
880           END IF;
881        ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
882        THEN
883           l_other_message := 'BOM_RES_ENTVAL_UNEXP_SKIP';
884           l_other_token_tbl(1).token_name := 'RES_SEQ_NUMBER';
885           l_other_token_tbl(1).token_value :=
886                         l_op_resource_rec.resource_sequence_number ;
887           RAISE EXC_UNEXP_SKIP_OBJECT ;
888        ELSIF l_return_status ='S' AND l_mesg_token_tbl .COUNT <> 0
889        THEN
890           Bom_Rtg_Error_Handler.Log_Error
891           (  p_rtg_header_rec      => Bom_Rtg_Pub.G_MISS_RTG_HEADER_REC
892           ,  p_rtg_revision_tbl    => Bom_Rtg_Pub.G_MISS_RTG_REVISION_TBL
893           ,  p_operation_tbl       => Bom_Rtg_Pub.G_MISS_OPERATION_TBL
894           ,  p_op_resource_tbl     => l_op_resource_tbl
895           ,  p_op_network_tbl      => Bom_Rtg_Pub.G_MISS_OP_NETWORK_TBL
896 	      ,  p_sub_resource_tbl    => l_sub_resource_tbl
897 	      ,  p_mesg_token_tbl      => l_mesg_token_tbl
898 	      ,  p_error_status        => 'W'
899           ,  p_error_scope         => NULL
900           ,  p_other_message       => NULL
901           ,  p_other_mesg_appid    => 'BOM'
902           ,  p_other_status        => NULL
903           ,  p_other_token_tbl     => Error_Handler.G_MISS_TOKEN_TBL
904           ,  p_error_level         => Error_Handler.G_RES_LEVEL
905           ,  p_entity_index        => I
906           ,  x_rtg_header_rec      => l_rtg_header_rec
907           ,  x_rtg_revision_tbl    => l_rtg_revision_tbl
908           ,  x_op_network_tbl      => l_op_network_tbl
909           ,  x_operation_tbl       => l_operation_tbl
910           ,  x_op_resource_tbl     => l_op_resource_tbl
911           ,  x_sub_resource_tbl    => l_sub_resource_tbl
912           ) ;
913        END IF;
914 
915 IF BOM_Rtg_Globals.Get_Debug = 'Y' THEN
916     Error_Handler.Write_Debug('Entity validation completed with '
917              || l_return_Status || ' proceeding for database writes . . . ') ;
918 END IF;
919 
920        --
921        -- Process Flow step 17: Database Writes
922        --
923           SAVEPOINT validate_sgn;
924           Bom_Op_Res_Util.Perform_Writes
925           (   p_op_resource_rec     => l_op_resource_rec
926           ,   p_op_res_unexp_rec    => l_op_res_unexp_rec
927           ,   x_mesg_token_tbl      => l_mesg_token_tbl
928           ,   x_return_status       => l_return_status
929           ) ;
930 
931        IF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
932        THEN
933           l_other_message := 'BOM_RES_WRITES_UNEXP_SKIP';
934           l_other_token_tbl(1).token_name := 'RES_SEQ_NUMBER';
935           l_other_token_tbl(1).token_value :=
936                           l_op_resource_rec.resource_sequence_number ;
937           RAISE EXC_UNEXP_SKIP_OBJECT ;
938        ELSIF l_return_status ='S' AND
939           l_mesg_token_tbl .COUNT <>0
940        THEN
941           Bom_Rtg_Error_Handler.Log_Error
942           (  p_rtg_header_rec      => Bom_Rtg_Pub.G_MISS_RTG_HEADER_REC
943           ,  p_rtg_revision_tbl    => Bom_Rtg_Pub.G_MISS_RTG_REVISION_TBL
944           ,  p_operation_tbl       => Bom_Rtg_Pub.G_MISS_OPERATION_TBL
945           ,  p_op_resource_tbl     => l_op_resource_tbl
946           ,  p_op_network_tbl      => Bom_Rtg_Pub.G_MISS_OP_NETWORK_TBL
947           ,  p_sub_resource_tbl    => l_sub_resource_tbl
948           ,  p_mesg_token_tbl      => l_mesg_token_tbl
949           ,  p_error_status        => 'W'
950           ,  p_error_scope         => NULL
951           ,  p_other_message       => NULL
952           ,  p_other_mesg_appid    => 'BOM'
953           ,  p_other_status        => NULL
954           ,  p_other_token_tbl     => Error_Handler.G_MISS_TOKEN_TBL
955           ,  p_error_level         => Error_Handler.G_RES_LEVEL
956           ,  p_entity_index        => I
957           ,  x_rtg_header_rec      => l_rtg_header_rec
958           ,  x_rtg_revision_tbl    => l_rtg_revision_tbl
959           ,  x_op_network_tbl      => l_op_network_tbl
960           ,  x_operation_tbl       => l_operation_tbl
961           ,  x_op_resource_tbl     => l_op_resource_tbl
962           ,  x_sub_resource_tbl    => l_sub_resource_tbl
963           ) ;
964        END IF;
965 
966        IF BOM_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Res Database writes completed with status  ' || l_return_status);
967        END IF;
968        --
969        -- Process Flow Step 18: Validate SGN order
970        --
971 
972        Bom_Validate_Op_Res.Val_SGN_Order
973        ( p_op_seq_id      => l_op_res_unexp_rec.operation_sequence_id
974        , x_mesg_token_tbl => l_mesg_token_tbl
975        , x_return_status  => l_return_status);
976 
977        IF l_return_status = Error_Handler.G_STATUS_ERROR
978        THEN
979           ROLLBACK TO validate_sgn;
980           RAISE EXC_SEV_QUIT_SIBLINGS;
981        END IF;
982 
983        IF BOM_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('validate SGN order completed with status  ' || l_return_status);
984        END IF;
985 
986     END IF; -- END IF statement that checks RETURN STATUS
987 
988     --  Load tables.
989     l_op_resource_tbl(I)          := l_op_resource_rec;
990 
991 
992     --  For loop exception handler.
993 
994     EXCEPTION
995        WHEN EXC_SEV_QUIT_RECORD THEN
996           Bom_Rtg_Error_Handler.Log_Error
997           (  p_rtg_header_rec      => Bom_Rtg_Pub.G_MISS_RTG_HEADER_REC
998           ,  p_rtg_revision_tbl    => Bom_Rtg_Pub.G_MISS_RTG_REVISION_TBL
999           ,  p_operation_tbl       => Bom_Rtg_Pub.G_MISS_OPERATION_TBL
1000           ,  p_op_resource_tbl     => l_op_resource_tbl
1001           ,  p_op_network_tbl      => Bom_Rtg_Pub.G_MISS_OP_NETWORK_TBL
1002           ,  p_sub_resource_tbl    => l_sub_resource_tbl
1003           ,  p_mesg_token_tbl      => l_mesg_token_tbl
1004           ,  p_error_status        => Error_Handler.G_STATUS_ERROR
1005           ,  p_error_scope         => Error_Handler.G_SCOPE_RECORD
1006           ,  p_other_message       => NULL
1007           ,  p_other_mesg_appid    => 'BOM'
1008           ,  p_other_status        => NULL
1009           ,  p_other_token_tbl     => Error_Handler.G_MISS_TOKEN_TBL
1010           ,  p_error_level         => Error_Handler.G_RES_LEVEL
1011           ,  p_entity_index        => I
1012           ,  x_rtg_header_rec      => l_rtg_header_rec
1013           ,  x_rtg_revision_tbl    => l_rtg_revision_tbl
1014           ,  x_op_network_tbl      => l_op_network_tbl
1015           ,  x_operation_tbl       => l_operation_tbl
1016           ,  x_op_resource_tbl     => l_op_resource_tbl
1017           ,  x_sub_resource_tbl    => l_sub_resource_tbl
1018           ) ;
1019 
1020 
1021          IF l_bo_return_status = 'S'
1022          THEN
1023             l_bo_return_status := l_return_status ;
1024          END IF;
1025 
1026          x_return_status       := l_bo_return_status;
1027          x_mesg_token_tbl      := l_mesg_token_tbl ;
1028          x_op_resource_tbl     := l_op_resource_tbl ;
1029          x_sub_resource_tbl    := l_sub_resource_tbl ;
1030 
1031 
1032       WHEN EXC_SEV_QUIT_BRANCH THEN
1033 
1034          Bom_Rtg_Error_Handler.Log_Error
1035          (
1036             p_rtg_header_rec      => Bom_Rtg_Pub.G_MISS_RTG_HEADER_REC
1037          ,  p_rtg_revision_tbl    => Bom_Rtg_Pub.G_MISS_RTG_REVISION_TBL
1038          ,  p_operation_tbl       => Bom_Rtg_Pub.G_MISS_OPERATION_TBL
1039          ,  p_op_resource_tbl     => l_op_resource_tbl
1040          ,  p_op_network_tbl      => Bom_Rtg_Pub.G_MISS_OP_NETWORK_TBL
1041          ,  p_sub_resource_tbl    => l_sub_resource_tbl
1042          ,  p_mesg_token_tbl      => l_mesg_token_tbl
1043          ,  p_error_status        => Error_Handler.G_STATUS_ERROR
1044          ,  p_error_scope         => Error_Handler.G_SCOPE_CHILDREN
1045          ,  p_other_status        => Error_Handler.G_STATUS_ERROR
1046          ,  p_other_message       => l_other_message
1047          ,  p_other_token_tbl     => l_other_token_tbl
1048          ,  p_error_level         => Error_Handler.G_RES_LEVEL
1049          ,  p_entity_index        => I
1050          ,  p_other_mesg_appid    => 'BOM'
1051          ,  x_rtg_header_rec      => l_rtg_header_rec
1052          ,  x_rtg_revision_tbl    => l_rtg_revision_tbl
1053          ,  x_op_network_tbl      => l_op_network_tbl
1054          ,  x_operation_tbl       => l_operation_tbl
1055          ,  x_op_resource_tbl     => l_op_resource_tbl
1056          ,  x_sub_resource_tbl    => l_sub_resource_tbl
1057          ) ;
1058 
1059 
1060          IF l_bo_return_status = 'S'
1061          THEN
1062             l_bo_return_status  := l_return_status;
1063          END IF;
1064 
1065          x_return_status       := l_bo_return_status;
1066          x_mesg_token_tbl      := l_mesg_token_tbl ;
1067          x_op_resource_tbl     := l_op_resource_tbl ;
1068          x_sub_resource_tbl := l_sub_resource_tbl ;
1069 
1070       WHEN EXC_SEV_SKIP_BRANCH THEN
1071          Bom_Rtg_Error_Handler.Log_Error
1072          (
1073             p_rtg_header_rec      => Bom_Rtg_Pub.G_MISS_RTG_HEADER_REC
1074          ,  p_rtg_revision_tbl    => Bom_Rtg_Pub.G_MISS_RTG_REVISION_TBL
1075          ,  p_operation_tbl       => Bom_Rtg_Pub.G_MISS_OPERATION_TBL
1076          ,  p_op_resource_tbl     => l_op_resource_tbl
1077          ,  p_op_network_tbl      => Bom_Rtg_Pub.G_MISS_OP_NETWORK_TBL
1078          ,  p_sub_resource_tbl    => l_sub_resource_tbl
1079          ,  p_mesg_token_tbl      => l_mesg_token_tbl
1080          ,  p_error_status        => Error_Handler.G_STATUS_ERROR
1081          ,  p_error_scope         => Error_Handler.G_SCOPE_CHILDREN
1082          ,  p_other_status        => Error_Handler.G_STATUS_NOT_PICKED
1083          ,  p_other_message       => l_other_message
1084          ,  p_other_token_tbl     => l_other_token_tbl
1085          ,  p_error_level         => Error_Handler.G_RES_LEVEL
1086          ,  p_entity_index        => I
1087          ,  p_other_mesg_appid    => 'BOM'
1088          ,  x_rtg_header_rec      => l_rtg_header_rec
1089          ,  x_rtg_revision_tbl    => l_rtg_revision_tbl
1090          ,  x_op_network_tbl      => l_op_network_tbl
1091          ,  x_operation_tbl       => l_operation_tbl
1092          ,  x_op_resource_tbl     => l_op_resource_tbl
1093          ,  x_sub_resource_tbl    => l_sub_resource_tbl
1094          ) ;
1095 
1096         IF l_bo_return_status = 'S'
1097         THEN
1098            l_bo_return_status  := l_return_status ;
1099         END IF;
1100         x_return_status       := l_bo_return_status;
1101         x_mesg_token_tbl      := l_mesg_token_tbl ;
1102         x_op_resource_tbl     := l_op_resource_tbl ;
1103         x_sub_resource_tbl    := l_sub_resource_tbl ;
1104 
1105       WHEN EXC_SEV_QUIT_SIBLINGS THEN
1106          Bom_Rtg_Error_Handler.Log_Error
1107          (
1108             p_rtg_header_rec      => Bom_Rtg_Pub.G_MISS_RTG_HEADER_REC
1109          ,  p_rtg_revision_tbl    => Bom_Rtg_Pub.G_MISS_RTG_REVISION_TBL
1110          ,  p_operation_tbl       => Bom_Rtg_Pub.G_MISS_OPERATION_TBL
1111          ,  p_op_resource_tbl     => l_op_resource_tbl
1112          ,  p_op_network_tbl      => Bom_Rtg_Pub.G_MISS_OP_NETWORK_TBL
1113          ,  p_sub_resource_tbl    => l_sub_resource_tbl
1114          ,  p_mesg_token_tbl      => l_mesg_token_tbl
1115          ,  p_error_status        => Error_Handler.G_STATUS_ERROR
1116          ,  p_error_scope         => Error_Handler.G_SCOPE_SIBLINGS
1117          ,  p_other_status        => Error_Handler.G_STATUS_ERROR
1118          ,  p_other_message       => l_other_message
1119          ,  p_other_token_tbl     => l_other_token_tbl
1120          ,  p_error_level         => Error_Handler.G_RES_LEVEL
1121          ,  p_entity_index        => I
1122          ,  p_other_mesg_appid    => 'BOM'
1123          ,  x_rtg_header_rec      => l_rtg_header_rec
1124          ,  x_rtg_revision_tbl    => l_rtg_revision_tbl
1125          ,  x_op_network_tbl      => l_op_network_tbl
1126          ,  x_operation_tbl       => l_operation_tbl
1127          ,  x_op_resource_tbl     => l_op_resource_tbl
1128          ,  x_sub_resource_tbl    => l_sub_resource_tbl
1129          ) ;
1130 
1131          IF l_bo_return_status = 'S'
1132          THEN
1133            l_bo_return_status  := l_return_status ;
1134          END IF;
1135          x_return_status       := l_bo_return_status;
1136          x_mesg_token_tbl      := l_mesg_token_tbl ;
1137          x_op_resource_tbl     := l_op_resource_tbl ;
1138          x_sub_resource_tbl := l_sub_resource_tbl ;
1139 
1140 
1141       WHEN EXC_FAT_QUIT_BRANCH THEN
1142          Bom_Rtg_Error_Handler.Log_Error
1143          (
1144             p_rtg_header_rec      => Bom_Rtg_Pub.G_MISS_RTG_HEADER_REC
1145          ,  p_rtg_revision_tbl    => Bom_Rtg_Pub.G_MISS_RTG_REVISION_TBL
1146          ,  p_operation_tbl       => Bom_Rtg_Pub.G_MISS_OPERATION_TBL
1147          ,  p_op_resource_tbl     => l_op_resource_tbl
1148          ,  p_op_network_tbl      => Bom_Rtg_Pub.G_MISS_OP_NETWORK_TBL
1149          ,  p_sub_resource_tbl    => l_sub_resource_tbl
1150          ,  p_mesg_token_tbl      => l_mesg_token_tbl
1151          ,  p_error_status        => Error_Handler.G_STATUS_FATAL
1152          ,  p_error_scope         => Error_Handler.G_SCOPE_CHILDREN
1153          ,  p_other_status        => Error_Handler.G_STATUS_FATAL
1154          ,  p_other_message       => l_other_message
1155          ,  p_other_token_tbl     => l_other_token_tbl
1156          ,  p_error_level         => Error_Handler.G_RES_LEVEL
1157          ,  p_entity_index        => I
1158          ,  p_other_mesg_appid    => 'BOM'
1159          ,  x_rtg_header_rec      => l_rtg_header_rec
1160          ,  x_rtg_revision_tbl    => l_rtg_revision_tbl
1161          ,  x_op_network_tbl      => l_op_network_tbl
1162          ,  x_operation_tbl       => l_operation_tbl
1163          ,  x_op_resource_tbl     => l_op_resource_tbl
1164          ,  x_sub_resource_tbl    => l_sub_resource_tbl
1165          ) ;
1166 
1167          x_return_status       := Error_Handler.G_STATUS_FATAL;
1168          x_mesg_token_tbl      := l_mesg_token_tbl ;
1169          x_op_resource_tbl     := l_op_resource_tbl ;
1170          x_sub_resource_tbl    := l_sub_resource_tbl ;
1171 
1172 
1173       WHEN EXC_FAT_QUIT_SIBLINGS THEN
1174          Bom_Rtg_Error_Handler.Log_Error
1175          (
1176              p_rtg_header_rec      => Bom_Rtg_Pub.G_MISS_RTG_HEADER_REC
1177          ,  p_rtg_revision_tbl    => Bom_Rtg_Pub.G_MISS_RTG_REVISION_TBL
1178          ,  p_operation_tbl       => Bom_Rtg_Pub.G_MISS_OPERATION_TBL
1179          ,  p_op_resource_tbl     => l_op_resource_tbl
1180          ,  p_op_network_tbl      => Bom_Rtg_Pub.G_MISS_OP_NETWORK_TBL
1181          ,  p_sub_resource_tbl    => l_sub_resource_tbl
1182          ,  p_mesg_token_tbl      => l_mesg_token_tbl
1183          ,  p_error_status        => Error_Handler.G_STATUS_FATAL
1184          ,  p_error_scope         => Error_Handler.G_SCOPE_SIBLINGS
1185          ,  p_other_status        => Error_Handler.G_STATUS_FATAL
1186          ,  p_other_message       => l_other_message
1187          ,  p_other_token_tbl     => l_other_token_tbl
1188          ,  p_error_level         => Error_Handler.G_RES_LEVEL
1189          ,  p_entity_index        => I
1190          ,  p_other_mesg_appid    => 'BOM'
1191          ,  x_rtg_header_rec      => l_rtg_header_rec
1192          ,  x_rtg_revision_tbl    => l_rtg_revision_tbl
1193          ,  x_op_network_tbl      => l_op_network_tbl
1194          ,  x_operation_tbl       => l_operation_tbl
1195          ,  x_op_resource_tbl     => l_op_resource_tbl
1196          ,  x_sub_resource_tbl    => l_sub_resource_tbl
1197          ) ;
1198 
1199         x_return_status       := Error_Handler.G_STATUS_FATAL;
1200         x_mesg_token_tbl      := l_mesg_token_tbl ;
1201         x_op_resource_tbl     := l_op_resource_tbl ;
1202         x_sub_resource_tbl    := l_sub_resource_tbl ;
1203 
1204 /*
1205     WHEN EXC_FAT_QUIT_OBJECT THEN
1206          Bom_Rtg_Error_Handler.Log_Error
1207          (  p_op_resource_tbl     => l_op_resource_tbl
1208          ,  p_sub_resource_tbl    => l_sub_resource_tbl
1209          ,  p_mesg_token_tbl      => l_mesg_token_tbl
1210          ,  p_error_status        => Error_Handler.G_STATUS_FATAL
1211          ,  p_error_scope         => Error_Handler.G_SCOPE_ALL
1212          ,  p_other_status        => Error_Handler.G_STATUS_FATAL
1213          ,  p_other_message       => l_other_message
1214          ,  p_other_token_tbl     => l_other_token_tbl
1215          ,  p_error_level         => Error_Handler.G_RES_LEVEL
1216          ,  p_entity_index        => I
1217          ,  x_rtg_header_rec      => l_rtg_header_rec
1218          ,  x_rtg_revision_tbl    => l_rtg_revision_tbl
1219          ,  x_op_network_tbl      => l_op_network_tbl
1220          ,  x_operation_tbl       => l_operation_tbl
1221          ,  x_op_resource_tbl     => l_op_resource_tbl
1222          ,  x_sub_resource_tbl    => l_sub_resource_tbl
1223          ) ;
1224 
1225          l_return_status       := 'Q';
1226          x_mesg_token_tbl      := l_mesg_token_tbl ;
1227          x_op_resource_tbl     := l_op_resource_tbl ;
1228          x_sub_resource_tbl    := l_sub_resource_tbl ;
1229 */
1230 
1231       WHEN EXC_UNEXP_SKIP_OBJECT THEN
1232          Bom_Rtg_Error_Handler.Log_Error
1233          (
1234             p_rtg_header_rec      => Bom_Rtg_Pub.G_MISS_RTG_HEADER_REC
1235          ,  p_rtg_revision_tbl    => Bom_Rtg_Pub.G_MISS_RTG_REVISION_TBL
1236          ,  p_operation_tbl       => Bom_Rtg_Pub.G_MISS_OPERATION_TBL
1237          ,  p_op_resource_tbl     => l_op_resource_tbl
1238          ,  p_op_network_tbl      => Bom_Rtg_Pub.G_MISS_OP_NETWORK_TBL
1239          ,  p_sub_resource_tbl    => l_sub_resource_tbl
1240          ,  p_mesg_token_tbl      => l_mesg_token_tbl
1241          ,  p_error_status        => Error_Handler.G_STATUS_UNEXPECTED
1242          ,  p_error_scope         => NULL
1243          ,  p_other_status        => Error_Handler.G_STATUS_NOT_PICKED
1244          ,  p_other_message       => l_other_message
1245          ,  p_other_mesg_appid    => 'BOM'
1246          ,  p_other_token_tbl     => l_other_token_tbl
1247          ,  p_error_level         => Error_Handler.G_RES_LEVEL
1248          ,  p_entity_index        => I
1249          ,  x_rtg_header_rec      => l_rtg_header_rec
1250          ,  x_rtg_revision_tbl    => l_rtg_revision_tbl
1251          ,  x_op_network_tbl      => l_op_network_tbl
1252          ,  x_operation_tbl       => l_operation_tbl
1253          ,  x_op_resource_tbl     => l_op_resource_tbl
1254          ,  x_sub_resource_tbl    => l_sub_resource_tbl
1255          ) ;
1256 
1257          l_return_status       := 'U';
1258          x_mesg_token_tbl      := l_mesg_token_tbl ;
1259          x_op_resource_tbl     := l_op_resource_tbl ;
1260          x_sub_resource_tbl    := l_sub_resource_tbl ;
1261 
1262    END ; -- END block
1263 
1264 
1265    IF l_return_status in ('Q', 'U')
1266    THEN
1267       x_return_status := l_return_status;
1268       RETURN ;
1269    END IF;
1270 
1271    END LOOP; -- END Operation Resources processing loop
1272 
1273    --  Load OUT parameters
1274    IF NVL(l_return_status, 'S') <> 'S'
1275    THEN
1276       x_return_status    := l_return_status;
1277    END IF;
1278 
1279    x_mesg_token_tbl      := l_mesg_token_tbl ;
1280    x_op_resource_tbl     := l_op_resource_tbl ;
1281    x_sub_resource_tbl    := l_sub_resource_tbl ;
1282    x_mesg_token_tbl      := l_mesg_token_tbl ;
1283 
1284 END Operation_Resources ;
1285 
1286 
1287 --  Sub_Operation_Resources
1288 
1289 /****************************************************************************
1290 * Procedure : Sub_Operation_Resources
1291 * Parameters IN   : Sub Operation Resources Table and all the other sibiling entities
1292 * Parameters OUT  : Sub Operatin Resources and all the other sibiling entities
1293 * Purpose   : This procedure will process all the Sub Operation Resources records.
1294 *
1295 *****************************************************************************/
1296 
1297 PROCEDURE Sub_Operation_Resources
1298 (   p_validation_level        IN  NUMBER
1299 ,   p_organization_id         IN  NUMBER   := NULL
1300 ,   p_assembly_item_name      IN  VARCHAR2 := NULL
1301 ,   p_alternate_routing_code  IN  VARCHAR2 := NULL
1302 ,   p_operation_seq_num       IN  NUMBER   := NULL
1303 ,   p_effectivity_date        IN  DATE     := NULL
1304 ,   p_operation_type          IN  NUMBER   := NULL
1305 ,   p_sub_resource_tbl        IN  Bom_Rtg_Pub.Sub_Resource_Tbl_Type
1306 ,   x_sub_resource_tbl        IN OUT NOCOPY Bom_Rtg_Pub.Sub_Resource_Tbl_Type
1307 ,   x_mesg_token_tbl          IN OUT NOCOPY Error_Handler.Mesg_Token_Tbl_Type
1308 ,   x_return_status           IN OUT NOCOPY VARCHAR2
1309 )
1310 
1311 IS
1312 
1313 /* Exposed and Unexposed record */
1314 l_sub_resource_rec         Bom_Rtg_Pub.Sub_Resource_Rec_Type ;
1315 l_sub_res_unexp_rec        Bom_Rtg_Pub.Sub_Res_Unexposed_Rec_Type ;
1316 l_old_sub_resource_rec     Bom_Rtg_Pub.Sub_Resource_Rec_Type ;
1317 l_old_sub_res_unexp_rec    Bom_Rtg_Pub.Sub_Res_Unexposed_Rec_Type ;
1318 
1319 l_sub_resource_tbl         Bom_Rtg_Pub.Sub_Resource_Tbl_Type ;
1320 
1321 /* Other Entities */
1322 l_rtg_header_rec        Bom_Rtg_Pub.Rtg_Header_Rec_Type ;
1323 l_rtg_revision_tbl      Bom_Rtg_Pub.Rtg_Revision_Tbl_Type ;
1324 l_operation_tbl         Bom_Rtg_Pub.Operation_Tbl_Type ;
1325 l_op_resource_tbl       Bom_Rtg_Pub.Op_Resource_Tbl_Type ;
1326 l_op_network_tbl        Bom_Rtg_Pub.Op_Network_Tbl_Type ;
1327 
1328 /* Error Handling Variables */
1329 l_token_tbl             Error_Handler.Token_Tbl_Type ;
1330 l_mesg_token_tbl        Error_Handler.Mesg_Token_Tbl_Type ;
1331 l_other_token_tbl       Error_Handler.Token_Tbl_Type;
1332 l_other_message         VARCHAR2(2000);
1333 l_err_text              VARCHAR2(2000);
1334 
1335 
1336 /* Others */
1337 l_return_status         VARCHAR2(3);
1338 l_bo_return_status      VARCHAR2(1);
1339 l_op_parent_exists      BOOLEAN := FALSE ;
1340 l_rtg_parent_exists     BOOLEAN := FALSE ;
1341 l_process_children      BOOLEAN := TRUE ;
1342 l_valid                 BOOLEAN := TRUE;
1343 l_temp_op_rec		BOM_RTG_Globals.Temp_Op_Rec_Type;
1344 
1345 BEGIN
1346 
1347    --  Init local table variables.
1348    l_return_status    := 'S';
1349    l_bo_return_status := 'S';
1350    l_sub_resource_tbl  := p_sub_resource_tbl ;
1351    l_sub_res_unexp_rec.organization_id := BOM_Rtg_Globals.Get_Org_Id ;
1352 
1353 
1354    FOR I IN 1..l_sub_resource_tbl.COUNT LOOP
1355    BEGIN
1356 
1357       --  Load local records
1358       l_sub_resource_rec := l_sub_resource_tbl(I) ;
1359 
1360       l_sub_resource_rec.transaction_type :=
1361          UPPER(l_sub_resource_rec.transaction_type) ;
1362 
1363       --
1364       -- Initialize the Unexposed Record for every iteration of the Loop
1365       -- so that sequence numbers get generated for every new row.
1366       --
1367       l_sub_res_unexp_rec.Operation_Sequence_Id   := NULL ;
1368       l_sub_res_unexp_rec.Substitute_Group_Number := l_sub_resource_rec.Substitute_Group_Number ;
1369       l_sub_res_unexp_rec.Resource_Id             := NULL ;
1370       l_sub_res_unexp_rec.New_Resource_Id         := NULL ;
1371       l_sub_res_unexp_rec.Activity_Id             := NULL ;
1372       l_sub_res_unexp_rec.Setup_Id                := NULL ;
1373 
1374       IF p_operation_seq_num  IS NOT NULL AND
1375          p_assembly_item_name IS NOT NULL AND
1376          p_effectivity_date   IS NOT NULL AND
1377          p_organization_id    IS NOT NULL
1378       THEN
1379          -- Revised Operation or Operation Sequence parent exists
1380          l_op_parent_exists  := TRUE ;
1381 
1382       ELSIF p_assembly_item_name IS NOT NULL AND
1383             p_organization_id    IS NOT NULL
1384       THEN
1385          -- Revised Item or Routing parent exists
1386          l_rtg_parent_exists := TRUE ;
1387       END IF ;
1388 
1389       -- If effectivity/op seq num of the parent operation has changed, update the child resource record
1390       IF BOM_RTG_Globals.G_Init_Eff_Date_Op_Num_Flag
1391       AND BOM_RTG_Globals.Get_Temp_Op_Rec1
1392           ( l_sub_resource_rec.operation_sequence_number
1393 	  , p_effectivity_date -- this cannot be null as this check is done only when the op has children
1394 	  , l_temp_op_rec)
1395       THEN
1396 	 l_sub_resource_rec.operation_sequence_number := l_temp_op_rec.new_op_seq_num;
1397 	 l_sub_resource_rec.op_start_effective_Date := l_temp_op_rec.new_start_eff_date;
1398 /*
1399 		Bom_Default_Sub_Op_Res.Init_Eff_Date_Op_Seq_Num
1400 		( p_op_seq_num	=> p_operation_seq_num
1401 		, p_eff_date	=> p_effectivity_date
1402 		, p_sub_res_rec	=> l_sub_resource_rec
1403 		, x_sub_res_rec	=> l_sub_resource_rec
1404 		);
1405 */
1406       END IF;
1407 
1408 
1409       -- Process Flow Step 2: Check if record has not yet been processed and
1410       -- that it is the child of the parent that called this procedure
1411       --
1412 
1413       IF (l_sub_resource_rec.return_status IS NULL OR
1414           l_sub_resource_rec.return_status  = FND_API.G_MISS_CHAR)
1415          AND
1416          (
1417             -- Did Op_Seq call this procedure, that is,
1418             -- if revised operation(operation sequence) exists, then is this record a child ?
1419             (l_op_parent_exists AND
1420                (l_sub_resource_rec.assembly_item_name = p_assembly_item_name AND
1421                 l_sub_res_unexp_rec.organization_id   = p_organization_id    AND
1422                 NVL(l_sub_resource_rec.alternate_routing_code, FND_API.G_MISS_CHAR)
1423                                  = NVL(p_alternate_routing_code, FND_API.G_MISS_CHAR) AND
1424                 l_sub_resource_rec.operation_sequence_number
1425                                                        = p_operation_seq_num AND
1426                 l_sub_resource_rec.op_start_effective_date
1427                                                        = p_effectivity_date  AND
1428                 NVL(l_sub_resource_rec.operation_type, 1) = NVL(p_operation_type, 1)
1429                )
1430             )
1431             OR
1432             -- Did Rtg_Header call this procedure, that is,
1433             -- if revised item or routing header exists, then is this record a child ?
1434             (l_rtg_parent_exists AND
1435                (l_sub_resource_rec.assembly_item_name = p_assembly_item_name AND
1436                 l_sub_res_unexp_rec.organization_id   = p_organization_id    AND
1437                 NVL(l_sub_resource_rec.alternate_routing_code, FND_API.G_MISS_CHAR)
1438                                  = NVL(p_alternate_routing_code, FND_API.G_MISS_CHAR)
1439                )
1440             )
1441            OR
1442            (NOT l_rtg_parent_exists AND NOT l_op_parent_exists)
1443          )
1444       THEN
1445          l_return_status := FND_API.G_RET_STS_SUCCESS;
1446          l_sub_resource_rec.return_status := FND_API.G_RET_STS_SUCCESS;
1447 
1448          --
1449          -- Process Flow step 3 :Check if transaction_type is valid
1450          -- Transaction_Type must be CRATE, UPDATE, DELETE or CANCEL(in only ECO for Rrg)
1451          -- Call the BOM_Rtg_Globals.Transaction_Type_Validity
1452          --
1453 
1454          BOM_Rtg_Globals.Transaction_Type_Validity
1455          (   p_transaction_type => l_sub_resource_rec.transaction_type
1456          ,   p_entity           => 'Sub_Res'
1457          ,   p_entity_id        => nvl(l_sub_resource_rec.substitute_group_number, l_sub_res_unexp_rec.substitute_group_number)
1458          ,   x_valid            => l_valid
1459          ,   x_mesg_token_tbl   => l_mesg_token_tbl
1460          ) ;
1461 
1462          IF NOT l_valid
1463          THEN
1464              l_return_status := Error_Handler.G_STATUS_ERROR;
1465              RAISE EXC_SEV_QUIT_RECORD ;
1466          END IF ;
1467 
1468          --
1469          -- Process Flow step 4(a): Convert user unique index to unique
1470          -- index I
1471          -- Call BOM_Rtg_Val_To_Id.Op_Resource_UUI_To_UI Shared Utility Package
1472          --
1473 	 BOM_Rtg_Val_To_Id.Sub_Resource_UUI_To_UI
1474          ( p_sub_resource_rec    => l_sub_resource_rec
1475          , p_sub_res_unexp_rec   => l_sub_res_unexp_rec
1476          , x_sub_res_unexp_rec   => l_sub_res_unexp_rec
1477          , x_mesg_token_tbl      => l_mesg_token_tbl
1478          , x_return_status       => l_return_status
1479          ) ;
1480 
1481          IF BOM_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
1482          ('Convert to User Unique Index to Index1 completed with return_status: ' || l_return_status) ;
1483          END IF;
1484 
1485          IF l_return_status = Error_Handler.G_STATUS_ERROR
1486          THEN
1487             l_other_message := 'BOM_SUB_RES_UUI_SEV_ERROR';
1488             l_other_token_tbl(1).token_name := 'SUB_RESOURCE_CODE';
1489             l_other_token_tbl(1).token_value :=
1490                         l_sub_resource_rec.sub_resource_code ;
1491             l_other_token_tbl(2).token_name := 'SCHEDULE_SEQ_NUMBER';
1492             l_other_token_tbl(2).token_value :=
1493                         nvl(l_sub_resource_rec.substitute_group_number, l_sub_res_unexp_rec.substitute_group_number) ;
1494             RAISE EXC_SEV_QUIT_SIBLINGS ;
1495 
1496          ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
1497          THEN
1498             l_other_message := 'BOM_SUB_RES_UUI_UNEXP_SKIP';
1499             l_other_token_tbl(1).token_name := 'SUB_RESOURCE_CODE';
1500             l_other_token_tbl(1).token_value :=
1501                         l_sub_resource_rec.sub_resource_code ;
1502             l_other_token_tbl(2).token_name := 'SCHEDULE_SEQ_NUMBER';
1503             l_other_token_tbl(2).token_value :=
1504                         nvl(l_sub_resource_rec.substitute_group_number, l_sub_res_unexp_rec.substitute_group_number) ;
1505             RAISE EXC_UNEXP_SKIP_OBJECT;
1506          END IF ;
1507 /*
1508          --
1509          -- Process Flow step 4(b): Convert user unique index to unique
1510          -- index II
1511          -- Call the BOM_Rtg_Val_To_Id.Operation_UUI_To_UI2
1512          --
1513 
1514          BOM_Rtg_Val_To_Id.Sub_Resource_UUI_To_UI2
1515          ( p_sub_resource_rec   => l_sub_resource_rec
1516          , p_sub_res_unexp_rec  => l_sub_res_unexp_rec
1517          , x_sub_res_unexp_rec  => l_sub_res_unexp_rec
1518          , x_mesg_token_tbl     => l_mesg_token_tbl
1519          , x_other_message      => l_other_message
1520          , x_other_token_tbl    => l_other_token_tbl
1521          , x_return_status      => l_return_status
1522          ) ;
1523 
1524          IF BOM_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
1525          ('Convert to User Unique Index to Index2 completed with return_status: ' || l_return_status) ;
1526          END IF;
1527 
1528          IF l_return_status = Error_Handler.G_STATUS_ERROR
1529          THEN
1530             RAISE EXC_SEV_QUIT_SIBLINGS ;
1531          ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
1532          THEN
1533             l_other_message := 'BOM_SUB_RES_UUI_UNEXP_SKIP';
1534             l_other_token_tbl(1).token_name := 'SUB_RESOURCE_CODE';
1535             l_other_token_tbl(1).token_value :=
1536                         l_sub_resource_rec.sub_resource_code ;
1537             l_other_token_tbl(2).token_name := 'SCHEDULE_SEQ_NUMBER';
1538             l_other_token_tbl(2).token_value :=
1539                         l_sub_resource_rec.schedule_sequence_number ;
1540             RAISE EXC_UNEXP_SKIP_OBJECT;
1541          END IF ;
1542 */
1543          --
1544          -- Process Flow step 5: Verify Operation Resource's existence
1545          -- Call the Bom_Validate_Op_Seq.Check_Existence
1546          --
1547          --
1548 
1549          Bom_Validate_Sub_Op_Res.Check_Existence
1550          (  p_sub_resource_rec        => l_sub_resource_rec
1551          ,  p_sub_res_unexp_rec       => l_sub_res_unexp_rec
1552          ,  x_old_sub_resource_rec    => l_old_sub_resource_rec
1553          ,  x_old_sub_res_unexp_rec   => l_old_sub_res_unexp_rec
1554          ,  x_mesg_token_tbl          => l_mesg_token_tbl
1555          ,  x_return_status           => l_return_status
1556          ) ;
1557 
1558 
1559          IF BOM_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
1560          ('Check Existence completed with return_status: ' || l_return_status) ;
1561          END IF ;
1562 
1563          IF l_return_status = Error_Handler.G_STATUS_ERROR
1564          THEN
1565             l_other_message := 'BOM_SUB_RES_EXS_SEV_SKIP';
1566             l_other_token_tbl(1).token_name := 'SUB_RESOURCE_CODE';
1567             l_other_token_tbl(1).token_value :=
1568                         l_sub_resource_rec.sub_resource_code ;
1569             l_other_token_tbl(2).token_name := 'SCHEDULE_SEQ_NUMBER';
1570             l_other_token_tbl(2).token_value :=
1571                         nvl(l_sub_resource_rec.substitute_group_number, l_sub_res_unexp_rec.substitute_group_number) ;
1572             -- l_other_token_tbl(3).token_name := 'REVISED_ITEM_NAME';
1573             -- l_other_token_tbl(3).token_value :=
1574             --           l_sub_resource_rec.assembly_item_name ;
1575             RAISE EXC_SEV_QUIT_BRANCH;
1576          ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
1577          THEN
1578             l_other_message := 'BOM_SUB_RES_EXS_UNEXP_SKIP';
1579             l_other_token_tbl(1).token_name := 'SUB_RESOURCE_CODE';
1580             l_other_token_tbl(1).token_value :=
1581                         l_sub_resource_rec.sub_resource_code ;
1582             l_other_token_tbl(2).token_name := 'SCHEDULE_SEQ_NUMBER';
1583             l_other_token_tbl(2).token_value :=
1584                         nvl(l_sub_resource_rec.substitute_group_number, l_sub_res_unexp_rec.substitute_group_number) ;
1585             -- l_other_token_tbl(3).token_name := 'REVISED_ITEM_NAME';
1586             -- l_other_token_tbl(3).token_value :=
1587             --            l_sub_resource_rec.assembly_item_name ;
1588             RAISE EXC_UNEXP_SKIP_OBJECT;
1589          END IF;
1590 
1591          --
1592          -- Process Flow step 6: Is Operation Resource record an orphan ?
1593          --
1594 
1595          IF NOT l_op_parent_exists
1596          THEN
1597 
1598             --
1599             -- Process Flow step 7 : Check Assembly Item Operability for Routing
1600             -- Call Bom_Validate_Rtg_Header.Check_Access
1601             --
1602 
1603             Bom_Validate_Rtg_Header.Check_Access
1604             ( p_assembly_item_name => l_sub_resource_rec.assembly_item_name
1605             , p_assembly_item_id   => l_sub_res_unexp_rec.assembly_item_id
1606             , p_organization_id    => l_sub_res_unexp_rec.organization_id
1607             , p_alternate_rtg_code => l_sub_resource_rec.alternate_routing_code
1608             , p_mesg_token_tbl     => Error_Handler.G_MISS_MESG_TOKEN_TBL
1609             , x_mesg_token_tbl     => l_mesg_token_tbl
1610             , x_return_status      => l_return_status
1611             ) ;
1612 
1613             IF BOM_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
1614             ('Check Assembly Item Operability completed with return_status: ' || l_return_status) ;
1615             END IF ;
1616 
1617             IF l_return_status = Error_Handler.G_STATUS_ERROR
1618             THEN
1619                l_other_message := 'BOM_SUB_RES_RITACC_FAT_FATAL';
1620                l_other_token_tbl(1).token_name := 'SUB_RESOURCE_CODE';
1621                l_other_token_tbl(1).token_value :=
1622                         l_sub_resource_rec.sub_resource_code ;
1623                l_other_token_tbl(2).token_name := 'SCHEDULE_SEQ_NUMBER';
1624                l_other_token_tbl(2).token_value :=
1625                         nvl(l_sub_resource_rec.substitute_group_number, l_sub_res_unexp_rec.substitute_group_number) ;
1626                l_return_status := 'F' ;
1627                RAISE EXC_FAT_QUIT_SIBLINGS ;
1628             ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
1629             THEN
1630                l_other_message := 'BOM_SUB_RES_RITACC_UNEXP_SKIP';
1631                l_other_token_tbl(1).token_name := 'SUB_RESOURCE_CODE';
1632                l_other_token_tbl(1).token_value :=
1633                         l_sub_resource_rec.sub_resource_code ;
1634                l_other_token_tbl(2).token_name := 'SCHEDULE_SEQ_NUMBER';
1635                l_other_token_tbl(2).token_value :=
1636                         nvl(l_sub_resource_rec.substitute_group_number, l_sub_res_unexp_rec.substitute_group_number) ;
1637                RAISE EXC_UNEXP_SKIP_OBJECT;
1638             END IF;
1639 
1640             --
1641             -- Process Flow step 8 : Check if the parent operation is
1642             -- non-referencing operation of type: Event
1643             -- Call Bom_Validate_Op_Seq.Check_NonRefEvent
1644             --
1645             Bom_Validate_Op_Res.Check_NonRefEvent
1646             (  p_operation_sequence_id      =>
1647                                       l_sub_res_unexp_rec.operation_sequence_id
1648             ,  p_operation_type            => l_sub_resource_rec.operation_type
1649             ,  p_entity_processed          => 'SR'
1650             ,  x_mesg_token_tbl            => l_mesg_token_tbl
1651             ,  x_return_status             => l_return_status
1652             ) ;
1653 
1654             IF BOM_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
1655             ('Check non-ref operation completed with return_status: ' || l_return_status) ;
1656             END IF ;
1657 
1658             IF l_return_status = Error_Handler.G_STATUS_ERROR
1659             THEN
1660                IF l_sub_resource_rec.operation_type IN (2 , 3) -- Process or Line Op
1661                THEN
1662 
1663 
1664                   l_token_tbl(1).token_name := 'SUB_RESOURCE_CODE';
1665                   l_token_tbl(1).token_value :=
1666                           l_sub_resource_rec.sub_resource_code ;
1667                   l_token_tbl(2).token_name := 'SCHEDULE_SEQ_NUMBER';
1668                   l_token_tbl(2).token_value :=
1669                           nvl(l_sub_resource_rec.substitute_group_number, l_sub_res_unexp_rec.substitute_group_number) ;
1670                   l_token_tbl(3).token_name := 'OP_SEQ_NUMBER';
1671                   l_token_tbl(3).token_value :=
1672                           l_sub_resource_rec.operation_sequence_number ;
1673 
1674                   Error_Handler.Add_Error_Token
1675                         ( p_Message_Name   => 'BOM_SUB_RES_OPTYPE_NOT_EVENT'
1676                         , p_mesg_token_tbl => l_mesg_token_tbl
1677                         , x_mesg_token_tbl => l_mesg_token_tbl
1678                         , p_Token_Tbl      => l_token_tbl
1679                         ) ;
1680 
1681                ELSE
1682 
1683                   l_token_tbl(1).token_name := 'SUB_RESOURCE_CODE';
1684                   l_token_tbl(1).token_value :=
1685                           l_sub_resource_rec.sub_resource_code ;
1686                   l_token_tbl(2).token_name := 'SCHEDULE_SEQ_NUMBER';
1687                   l_token_tbl(2).token_value :=
1688                           nvl(l_sub_resource_rec.substitute_group_number, l_sub_res_unexp_rec.substitute_group_number) ;
1689                   l_token_tbl(3).token_name := 'OP_SEQ_NUMBER';
1690                   l_token_tbl(3).token_value :=
1691                           l_sub_resource_rec.operation_sequence_number ;
1692 
1693                   Error_Handler.Add_Error_Token
1694                         ( p_Message_Name   => 'BOM_SUB_RES_MUST_NONREF'
1695                         , p_mesg_token_tbl => l_mesg_token_tbl
1696                         , x_mesg_token_tbl => l_mesg_token_tbl
1697                         , p_Token_Tbl      => l_token_tbl
1698                         ) ;
1699 
1700 
1701 
1702                END IF ;
1703 
1704                l_other_message := 'BOM_SUB_RES_ACCESS_FAT_FATAL';
1705                l_other_token_tbl(1).token_name := 'SUB_RESOURCE_CODE';
1706                l_other_token_tbl(1).token_value :=
1707                         l_sub_resource_rec.sub_resource_code ;
1708                l_other_token_tbl(2).token_name := 'SCHEDULE_SEQ_NUMBER';
1709                l_other_token_tbl(2).token_value :=
1710                         nvl(l_sub_resource_rec.substitute_group_number, l_sub_res_unexp_rec.substitute_group_number) ;
1711 
1712 
1713                l_return_status := 'F';
1714                RAISE EXC_FAT_QUIT_SIBLINGS ;
1715 
1716             -- For eAM enhancement, maintenace routings do not support
1717             -- sub resource currently
1718             ELSIF l_return_status = 'EAM'  THEN
1719 
1720                   l_return_status := FND_API.G_RET_STS_ERROR ;
1721 
1722                   l_token_tbl(1).token_name := 'SUB_RESOURCE_CODE';
1723                   l_token_tbl(1).token_value :=
1724                           l_sub_resource_rec.sub_resource_code ;
1725                   l_token_tbl(2).token_name := 'SCHEDULE_SEQ_NUMBER';
1726                   l_token_tbl(2).token_value :=
1727                           nvl(l_sub_resource_rec.substitute_group_number, l_sub_res_unexp_rec.substitute_group_number) ;
1728                   l_token_tbl(3).token_name := 'OP_SEQ_NUMBER';
1729                   l_token_tbl(3).token_value :=
1730                           l_sub_resource_rec.operation_sequence_number ;
1731 
1732                   Error_Handler.Add_Error_Token
1733                         ( p_Message_Name   => 'BOM_EAM_SUB_RES_NOT_ACCESS'
1734                         , p_mesg_token_tbl => l_mesg_token_tbl
1735                         , x_mesg_token_tbl => l_mesg_token_tbl
1736                         , p_Token_Tbl      => l_token_tbl
1737                         ) ;
1738 
1739 
1740 
1741                   l_other_message := 'BOM_SUB_RES_ACCESS_FAT_FATAL';
1742                   l_other_token_tbl(1).token_name := 'SUB_RESOURCE_CODE';
1743                   l_other_token_tbl(1).token_value :=
1744                         l_sub_resource_rec.sub_resource_code ;
1745                   l_other_token_tbl(2).token_name := 'SCHEDULE_SEQ_NUMBER';
1746                   l_other_token_tbl(2).token_value :=
1747                         nvl(l_sub_resource_rec.substitute_group_number, l_sub_res_unexp_rec.substitute_group_number) ;
1748 
1749                   l_return_status := 'F';
1750                   RAISE EXC_FAT_QUIT_SIBLINGS ;
1751 
1752 
1753             ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
1754             THEN
1755                l_other_message := 'BOM_SUB_RES_ACCESS_UNEXP_SKIP';
1756                l_other_token_tbl(1).token_name := 'SUB_RESOURCE_CODE';
1757                l_other_token_tbl(1).token_value :=
1758                         l_sub_resource_rec.sub_resource_code ;
1759                l_other_token_tbl(2).token_name := 'SCHEDULE_SEQ_NUMBER';
1760                l_other_token_tbl(2).token_value :=
1761                         nvl(l_sub_resource_rec.substitute_group_number, l_sub_res_unexp_rec.substitute_group_number) ;
1762                RAISE EXC_UNEXP_SKIP_OBJECT;
1763             END IF;
1764 
1765          END IF;
1766 
1767          --
1768          -- Process Flow step 9: Value to Id conversions
1769          -- Call BOM_Rtg_Val_To_Id.Sub_Resource_VID
1770          --
1771          BOM_Rtg_Val_To_Id.Sub_Resource_VID
1772          (  p_sub_resource_rec       => l_sub_resource_rec
1773          ,  p_sub_res_unexp_rec      => l_sub_res_unexp_rec
1774          ,  x_sub_res_unexp_rec      => l_sub_res_unexp_rec
1775          ,  x_mesg_token_tbl         => l_mesg_token_tbl
1776          ,  x_return_status          => l_return_status
1777          );
1778 
1779          IF BOM_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
1780          ('Value-id conversions completed with return_status: ' || l_return_status) ;
1781          END IF ;
1782 
1783          IF l_return_status = Error_Handler.G_STATUS_ERROR
1784          THEN
1785             IF l_sub_resource_rec.transaction_type = 'CREATE'
1786             THEN
1787                l_other_message := 'BOM_SUB_RES_VID_CSEV_SKIP';
1788                l_other_token_tbl(1).token_name := 'SUB_RESOURCE_CODE';
1789                l_other_token_tbl(1).token_value :=
1790                         l_sub_resource_rec.sub_resource_code ;
1791                l_other_token_tbl(2).token_name := 'SCHEDULE_SEQ_NUMBER';
1792                l_other_token_tbl(2).token_value :=
1793                         nvl(l_sub_resource_rec.substitute_group_number, l_sub_res_unexp_rec.substitute_group_number) ;
1794                RAISE EXC_SEV_SKIP_BRANCH;
1795             ELSE
1796                RAISE EXC_SEV_QUIT_RECORD ;
1797             END IF ;
1798 
1799          ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
1800          THEN
1801             l_other_message := 'BOM_SUB_RES_VID_UNEXP_SKIP';
1802             l_other_token_tbl(1).token_name := 'SUB_RESOURCE_CODE';
1803             l_other_token_tbl(1).token_value :=
1804                      l_sub_resource_rec.sub_resource_code ;
1805             l_other_token_tbl(2).token_name := 'SCHEDULE_SEQ_NUMBER';
1806             l_other_token_tbl(2).token_value :=
1807                      nvl(l_sub_resource_rec.substitute_group_number, l_sub_res_unexp_rec.substitute_group_number) ;
1808             RAISE EXC_UNEXP_SKIP_OBJECT;
1809 
1810          ELSIF l_return_status ='S' AND l_mesg_token_tbl .COUNT <>0
1811          THEN
1812             Bom_Rtg_Error_Handler.Log_Error
1813             (
1814                p_sub_resource_tbl    => l_sub_resource_tbl
1815             ,  p_rtg_header_rec      =>Bom_Rtg_Pub.G_MISS_RTG_HEADER_REC
1816             ,  p_rtg_revision_tbl    =>Bom_Rtg_Pub.G_MISS_RTG_REVISION_TBL
1817             ,  p_operation_tbl       =>Bom_Rtg_Pub.G_MISS_OPERATION_TBL
1818             ,  p_op_resource_tbl     =>Bom_Rtg_Pub.G_MISS_OP_RESOURCE_TBL
1819             ,  p_op_network_tbl      =>Bom_Rtg_Pub.G_MISS_OP_NETWORK_TBL
1820             ,  p_mesg_token_tbl      => l_mesg_token_tbl
1821             ,  p_error_status        => 'W'
1822             ,  p_error_level         => Error_Handler.G_SR_LEVEL
1823             ,  p_entity_index        => I
1824             ,  p_error_scope         => NULL
1825             ,  p_other_message       => NULL
1826             ,  p_other_mesg_appid    => 'BOM'
1827             ,  p_other_status        => NULL
1828             ,  p_other_token_tbl     => Error_Handler.G_MISS_TOKEN_TBL
1829             ,  x_rtg_header_rec      => l_rtg_header_rec
1830             ,  x_rtg_revision_tbl    => l_rtg_revision_tbl
1831             ,  x_op_network_tbl      => l_op_network_tbl
1832             ,  x_operation_tbl       => l_operation_tbl
1833             ,  x_op_resource_tbl     => l_op_resource_tbl
1834             ,  x_sub_resource_tbl    => l_sub_resource_tbl
1835             ) ;
1836          END IF;
1837 
1838          --
1839          -- Process Flow step 10 : Check required fields exist
1840          -- (also includes a part of conditionally required fields)
1841          --
1842 
1843 /*
1844          Bom_Validate_Op_Res.Check_Required
1845          ( p_sub_resource_rec           => l_sub_resource_rec
1846          , x_return_status              => l_return_status
1847          , x_mesg_token_tbl             => l_mesg_token_tbl
1848          ) ;
1849 
1850 
1851 
1852          IF BOM_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
1853          ('Check required completed with return_status: ' || l_return_status) ;
1854          END IF ;
1855 
1856          IF l_return_status = Error_Handler.G_STATUS_ERROR
1857          THEN
1858             IF l_sub_resource_rec.transaction_type = BOM_Rtg_Globals.G_OPR_CREATE
1859             THEN
1860                l_other_message := 'BOM_SUB_RES_REQ_CSEV_SKIP';
1861                l_other_token_tbl(1).token_name := 'SUB_RESOURCE_CODE';
1862                l_other_token_tbl(1).token_value :=
1863                         l_sub_resource_rec.sub_resource_code ;
1864                l_other_token_tbl(2).token_name := 'SCHEDULE_SEQ_NUMBER';
1865                l_other_token_tbl(2).token_value :=
1866                         l_sub_resource_rec.schedule_sequence_number ;
1867                RAISE EXC_SEV_SKIP_BRANCH ;
1868             ELSE
1869                RAISE EXC_SEV_QUIT_RECORD ;
1870             END IF;
1871          ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
1872          THEN
1873             l_other_message := 'BOM_SUB_RES_REQ_UNEXP_SKIP';
1874             l_other_token_tbl(1).token_name := 'SUB_RESOURCE_CODE';
1875             l_other_token_tbl(1).token_value :=
1876                      l_sub_resource_rec.sub_resource_code ;
1877             l_other_token_tbl(2).token_name := 'SCHEDULE_SEQ_NUMBER';
1878             l_other_token_tbl(2).token_value :=
1879                      l_sub_resource_rec.schedule_sequence_number ;
1880             RAISE EXC_UNEXP_SKIP_OBJECT ;
1881          END IF;
1882 */
1883 
1884          --
1885          -- Process Flow step 11 : Attribute Validation for CREATE and UPDATE
1886          -- Call Bom_Validate_Sub_Op_Res.Check_Attributes
1887          --
1888 
1889          IF l_sub_resource_rec.transaction_type IN
1890             (BOM_Rtg_Globals.G_OPR_CREATE, BOM_Rtg_Globals.G_OPR_UPDATE)
1891          THEN
1892             Bom_Validate_Sub_Op_Res.Check_Attributes
1893             ( p_sub_resource_rec   => l_sub_resource_rec
1894             , p_sub_res_unexp_rec  => l_sub_res_unexp_rec
1895             , x_return_status      => l_return_status
1896             , x_mesg_token_tbl     => l_mesg_token_tbl
1897             ) ;
1898 
1899             IF BOM_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
1900             ('Attribute validation completed with return_status: ' || l_return_status) ;
1901             END IF ;
1902 
1903 
1904             IF l_return_status = Error_Handler.G_STATUS_ERROR
1905             THEN
1906                IF l_sub_resource_rec.transaction_type = BOM_Rtg_Globals.G_OPR_CREATE
1907                THEN
1908                   l_other_message := 'BOM_SUB_RES_ATTVAL_CSEV_SKIP';
1909                   l_other_token_tbl(1).token_name := 'SUB_RESOURCE_CODE';
1910                   l_other_token_tbl(1).token_value :=
1911                         l_sub_resource_rec.sub_resource_code ;
1912                   l_other_token_tbl(2).token_name := 'SCHEDULE_SEQ_NUMBER';
1913                   l_other_token_tbl(2).token_value :=
1914                         nvl(l_sub_resource_rec.substitute_group_number, l_sub_res_unexp_rec.substitute_group_number) ;
1915                   RAISE EXC_SEV_SKIP_BRANCH ;
1916                ELSE
1917                   RAISE EXC_SEV_QUIT_RECORD ;
1918                END IF;
1919             ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
1920             THEN
1921                l_other_message := 'BOM_SUB_RES_ATTVAL_UNEXP_SKIP';
1922                l_other_token_tbl(1).token_name := 'SUB_RESOURCE_CODE';
1923                l_other_token_tbl(1).token_value :=
1924                         l_sub_resource_rec.sub_resource_code ;
1925                l_other_token_tbl(2).token_name := 'SCHEDULE_SEQ_NUMBER';
1926                l_other_token_tbl(2).token_value :=
1927                         nvl(l_sub_resource_rec.substitute_group_number, l_sub_res_unexp_rec.substitute_group_number) ;
1928                RAISE EXC_UNEXP_SKIP_OBJECT ;
1929             ELSIF l_return_status ='S' AND l_mesg_token_tbl .COUNT <> 0
1930             THEN
1931                Bom_Rtg_Error_Handler.Log_Error
1932                (  p_sub_resource_tbl    => l_sub_resource_tbl
1933                ,  p_rtg_header_rec      => Bom_Rtg_Pub.G_MISS_RTG_HEADER_REC
1934                ,  p_rtg_revision_tbl    => Bom_Rtg_Pub.G_MISS_RTG_REVISION_TBL
1935                ,  p_operation_tbl       => Bom_Rtg_Pub.G_MISS_OPERATION_TBL
1936                ,  p_op_resource_tbl     => Bom_Rtg_Pub.G_MISS_OP_RESOURCE_TBL
1937                ,  p_op_network_tbl      => Bom_Rtg_Pub.G_MISS_OP_NETWORK_TBL
1938                ,  p_mesg_token_tbl      => l_mesg_token_tbl
1939                ,  p_error_status        => 'W'
1940                ,  p_error_level         => Error_Handler.G_SR_LEVEL
1941                ,  p_entity_index        => I
1942                ,  p_error_scope         => NULL
1943                ,  p_other_message       => NULL
1944                ,  p_other_mesg_appid    => 'BOM'
1945                ,  p_other_status        => NULL
1946                ,  p_other_token_tbl     => Error_Handler.G_MISS_TOKEN_TBL
1947                ,  x_rtg_header_rec      => l_rtg_header_rec
1948                ,  x_rtg_revision_tbl    => l_rtg_revision_tbl
1949                ,  x_op_network_tbl      => l_op_network_tbl
1950                ,  x_operation_tbl       => l_operation_tbl
1951                ,  x_op_resource_tbl     => l_op_resource_tbl
1952                ,  x_sub_resource_tbl    => l_sub_resource_tbl
1953                ) ;
1954            END IF;
1955         END IF;
1956 
1957 
1958 
1959         IF l_sub_resource_rec.transaction_type IN
1960            (BOM_Rtg_Globals.G_OPR_UPDATE, BOM_Rtg_Globals.G_OPR_DELETE)
1961         THEN
1962 
1963         --
1964         -- Process flow step 12: Populate NULL columns for Update and Delete
1965         -- Call Bom_Default_Op_Res.Populate_Null_Columns
1966         --
1967 
1968            IF BOM_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Populate NULL columns') ;
1969            END IF ;
1970 
1971              Bom_Default_Sub_Op_Res.Populate_Null_Columns
1972              (   p_sub_resource_rec       => l_sub_resource_rec
1973              ,   p_old_sub_resource_rec   => l_old_sub_resource_rec
1974              ,   p_sub_res_unexp_rec      => l_sub_res_unexp_rec
1975              ,   p_old_sub_res_unexp_rec  => l_old_sub_res_unexp_rec
1976              ,   x_sub_resource_rec       => l_sub_resource_rec
1977              ,   x_sub_res_unexp_rec      => l_sub_res_unexp_rec
1978              ) ;
1979 
1980         ELSIF l_sub_resource_rec.transaction_type = BOM_Rtg_Globals.G_OPR_CREATE
1981         THEN
1982         --
1983         -- Process Flow step 13 : Default missing values for Op Resource (CREATE)
1984         -- Call Bom_Default_Op_Res.Attribute_Defaulting
1985         --
1986              Bom_Default_Sub_Op_Res.Attribute_Defaulting
1987              (   p_sub_resource_rec     => l_sub_resource_rec
1988              ,   p_sub_res_unexp_rec    => l_sub_res_unexp_rec
1989              ,   x_sub_resource_rec     => l_sub_resource_rec
1990              ,   x_sub_res_unexp_rec    => l_sub_res_unexp_rec
1991              ,   x_mesg_token_tbl       => l_mesg_token_tbl
1992              ,   x_return_status        => l_return_status
1993              ) ;
1994 
1995            IF BOM_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
1996            ('Attribute Defaulting completed with return_status: ' || l_return_status) ;
1997            END IF ;
1998 
1999            IF l_return_status = Error_Handler.G_STATUS_ERROR
2000            THEN
2001               l_other_message := 'BOM_SUB_RES_ATTDEF_CSEV_SKIP';
2002               l_other_token_tbl(1).token_name := 'SUB_RESOURCE_CODE';
2003               l_other_token_tbl(1).token_value :=
2004                         l_sub_resource_rec.sub_resource_code ;
2005               l_other_token_tbl(2).token_name := 'SCHEDULE_SEQ_NUMBER';
2006               l_other_token_tbl(2).token_value :=
2007                         nvl(l_sub_resource_rec.substitute_group_number, l_sub_res_unexp_rec.substitute_group_number) ;
2008               RAISE EXC_SEV_SKIP_BRANCH ;
2009 
2010            ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
2011            THEN
2012               l_other_message := 'BOM_SUB_RES_ATTDEF_UNEXP_SKIP';
2013               l_other_token_tbl(1).token_name := 'SUB_RESOURCE_CODE';
2014               l_other_token_tbl(1).token_value :=
2015                         l_sub_resource_rec.sub_resource_code ;
2016               l_other_token_tbl(2).token_name := 'SCHEDULE_SEQ_NUMBER';
2017               l_other_token_tbl(2).token_value :=
2018                         nvl(l_sub_resource_rec.substitute_group_number, l_sub_res_unexp_rec.substitute_group_number) ;
2019               RAISE EXC_UNEXP_SKIP_OBJECT ;
2020            ELSIF l_return_status ='S' AND l_mesg_token_tbl .COUNT <> 0
2021            THEN
2022                Bom_Rtg_Error_Handler.Log_Error
2023                (  p_sub_resource_tbl    => l_sub_resource_tbl
2024                ,  p_rtg_header_rec      => Bom_Rtg_Pub.G_MISS_RTG_HEADER_REC
2025                ,  p_rtg_revision_tbl    => Bom_Rtg_Pub.G_MISS_RTG_REVISION_TBL
2026                ,  p_operation_tbl       => Bom_Rtg_Pub.G_MISS_OPERATION_TBL
2027                ,  p_op_resource_tbl     => Bom_Rtg_Pub.G_MISS_OP_RESOURCE_TBL
2028                ,  p_op_network_tbl      => Bom_Rtg_Pub.G_MISS_OP_NETWORK_TBL
2029                ,  p_mesg_token_tbl      => l_mesg_token_tbl
2030                ,  p_error_status        => 'W'
2031                ,  p_error_level         => Error_Handler.G_SR_LEVEL
2032                ,  p_entity_index        => I
2033                ,  p_error_scope         => NULL
2034                ,  p_other_message       => NULL
2035                ,  p_other_mesg_appid    => 'BOM'
2036                ,  p_other_status        => NULL
2037                ,  p_other_token_tbl     => Error_Handler.G_MISS_TOKEN_TBL
2038                ,  x_rtg_header_rec      => l_rtg_header_rec
2039                ,  x_rtg_revision_tbl    => l_rtg_revision_tbl
2040                ,  x_op_network_tbl      => l_op_network_tbl
2041                ,  x_operation_tbl       => l_operation_tbl
2042                ,  x_op_resource_tbl     => l_op_resource_tbl
2043                ,  x_sub_resource_tbl    => l_sub_resource_tbl
2044                ) ;
2045           END IF;
2046        END IF;
2047 
2048        --
2049        -- Process Flow step 14: Conditionally Required Attributes
2050        --
2051        --
2052 /*
2053        IF l_sub_resource_rec.transaction_type IN ( BOM_Rtg_Globals.G_OPR_CREATE
2054                                                  , BOM_Rtg_Globals.G_OPR_UPDATE )
2055        THEN
2056 
2057           Bom_Validate_Sub_Op_Seq.Check_Conditionally_Required
2058           ( p_sub_resource_rec       => l_sub_resource_rec
2059           , p_sub_res_unexp_rec      => l_sub_res_unexp_rec
2060           , x_return_status          => l_return_status
2061           , x_mesg_token_tbl         => l_mesg_token_tbl
2062           ) ;
2063 
2064 
2065           IF BOM_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
2066           ('Check Conditionally Required Attr. completed with return_status: ' || l_return_status) ;
2067           END IF ;
2068 
2069 
2070           IF l_return_status = Error_Handler.G_STATUS_ERROR
2071           THEN
2072              IF l_sub_resource_rec.transaction_type = BOM_Rtg_Globals.G_OPR_CREATE
2073              THEN
2074                 l_other_message := 'BOM_SUB_RES_CONREQ_CSEV_SKIP';
2075                 l_other_token_tbl(1).token_name := 'SUB_RESOURCE_CODE';
2076                 l_other_token_tbl(1).token_value :=
2077                          l_sub_resource_rec.sub_resource_code ;
2078                 l_other_token_tbl(2).token_name := 'SCHEDULE_SEQ_NUMBER';
2079                 l_other_token_tbl(2).token_value :=
2080                         l_sub_resource_rec.schedule_sequence_number ;
2081                 RAISE EXC_SEV_SKIP_BRANCH ;
2082              ELSE
2083                 RAISE EXC_SEV_QUIT_RECORD ;
2084              END IF;
2085           ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
2086           THEN
2087              l_other_message := 'BOM_SUB_RES_CONREQ_UNEXP_SKIP';
2088              l_other_token_tbl(1).token_name := 'SUB_RESOURCE_CODE';
2089              l_other_token_tbl(1).token_value :=
2090                         l_sub_resource_rec.sub_resource_code ;
2091              l_other_token_tbl(2).token_name := 'SCHEDULE_SEQ_NUMBER';
2092              l_other_token_tbl(2).token_value :=
2093                         l_sub_resource_rec.schedule_sequence_number ;
2094              RAISE EXC_UNEXP_SKIP_OBJECT ;
2095           ELSIF l_return_status ='S' AND l_mesg_token_tbl .COUNT <> 0
2096           THEN
2097              Bom_Rtg_Error_Handler.Log_Error
2098              (  p_sub_resource_tbl    => l_sub_resource_tbl
2099              ,  p_rtg_header_rec      =>Bom_Rtg_Pub.G_MISS_RTG_HEADER_REC
2100              ,  p_rtg_revision_tbl    =>Bom_Rtg_Pub.G_MISS_RTG_REVISION_TBL
2101              ,  p_operation_tbl       =>Bom_Rtg_Pub.G_MISS_OPERATION_TBL
2102              ,  p_op_resource_tbl     =>Bom_Rtg_Pub.G_MISS_OP_RESOURCE_TBL
2103              ,  p_op_network_tbl      =>Bom_Rtg_Pub.G_MISS_OP_NETWORK_TBL
2104              ,  p_mesg_token_tbl      => l_mesg_token_tbl
2105              ,  p_error_status        => 'W'
2106              ,  p_error_level         => Error_Handler.G_SR_LEVEL
2107              ,  p_entity_index        => I
2108              ,  p_error_scope         => NULL
2109              ,  p_other_message       => NULL
2110              ,  p_other_mesg_appid    => 'BOM'
2111              ,  p_other_status        => NULL
2112              ,  p_other_token_tbl     => Error_Handler.G_MISS_TOKEN_TBL
2113              ,  x_rtg_header_rec      => l_rtg_header_rec
2114              ,  x_rtg_revision_tbl    => l_rtg_revision_tbl
2115              ,  x_op_network_tbl      => l_op_network_tbl
2116              ,  x_operation_tbl       => l_operation_tbl
2117              ,  x_op_resource_tbl     => l_op_resource_tbl
2118              ,  x_sub_resource_tbl    => l_sub_resource_tbl
2119              ) ;
2120           END IF;
2121        END IF;
2122   */
2123 
2124        --
2125        -- Process Flow step 15: Entity defaulting for CREATE and UPDATE
2126        --
2127        IF l_sub_resource_rec.transaction_type IN ( BOM_Rtg_Globals.G_OPR_CREATE
2128                                                  , BOM_Rtg_Globals.G_OPR_UPDATE )
2129 
2130        THEN
2131           Bom_Default_Sub_Op_Res.Entity_Defaulting
2132               (   p_sub_resource_rec   => l_sub_resource_rec
2133               ,   p_sub_res_unexp_rec  => l_sub_res_unexp_rec
2134               ,   x_sub_resource_rec   => l_sub_resource_rec
2135               ,   x_sub_res_unexp_rec  => l_sub_res_unexp_rec
2136               ,   x_mesg_token_tbl     => l_mesg_token_tbl
2137               ,   x_return_status      => l_return_status
2138               ) ;
2139 
2140           IF BOM_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
2141           ('Entity defaulting completed with return_status: ' || l_return_status) ;
2142           END IF ;
2143 
2144           IF l_return_status = Error_Handler.G_STATUS_ERROR
2145           THEN
2146              IF l_sub_resource_rec.transaction_type = BOM_Rtg_Globals.G_OPR_CREATE
2147              THEN
2148                 l_other_message := 'BOM_SUB_RES_ENTDEF_CSEV_SKIP';
2149                 l_other_token_tbl(1).token_name := 'SUB_RESOURCE_CODE';
2150                 l_other_token_tbl(1).token_value :=
2151                         l_sub_resource_rec.sub_resource_code ;
2152                 l_other_token_tbl(2).token_name := 'SCHEDULE_SEQ_NUMBER';
2153                 l_other_token_tbl(2).token_value :=
2154                         nvl(l_sub_resource_rec.substitute_group_number, l_sub_res_unexp_rec.substitute_group_number) ;
2155                 RAISE EXC_SEV_SKIP_BRANCH ;
2156              ELSE
2157                 RAISE EXC_SEV_QUIT_RECORD ;
2158              END IF;
2159           ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
2160           THEN
2161              l_other_message := 'BOM_SUB_RES_ENTDEF_UNEXP_SKIP';
2162              l_other_token_tbl(1).token_name := 'SUB_RESOURCE_CODE';
2163              l_other_token_tbl(1).token_value :=
2164                         l_sub_resource_rec.sub_resource_code ;
2165              l_other_token_tbl(2).token_name := 'SCHEDULE_SEQ_NUMBER';
2166              l_other_token_tbl(2).token_value :=
2167                         nvl(l_sub_resource_rec.substitute_group_number, l_sub_res_unexp_rec.substitute_group_number) ;
2168              RAISE EXC_UNEXP_SKIP_OBJECT ;
2169           ELSIF l_return_status ='S' AND l_mesg_token_tbl .COUNT <> 0
2170           THEN
2171              Bom_Rtg_Error_Handler.Log_Error
2172              (  p_sub_resource_tbl    => l_sub_resource_tbl
2173              ,  p_rtg_header_rec      => Bom_Rtg_Pub.G_MISS_RTG_HEADER_REC
2174              ,  p_rtg_revision_tbl    => Bom_Rtg_Pub.G_MISS_RTG_REVISION_TBL
2175              ,  p_operation_tbl       => Bom_Rtg_Pub.G_MISS_OPERATION_TBL
2176              ,  p_op_resource_tbl     => Bom_Rtg_Pub.G_MISS_OP_RESOURCE_TBL
2177              ,  p_op_network_tbl      => Bom_Rtg_Pub.G_MISS_OP_NETWORK_TBL
2178              ,  p_mesg_token_tbl      => l_mesg_token_tbl
2179              ,  p_error_status        => 'W'
2180              ,  p_error_level         => Error_Handler.G_SR_LEVEL
2181              ,  p_entity_index        => I
2182              ,  p_error_scope         => NULL
2183              ,  p_other_message       => NULL
2184              ,  p_other_mesg_appid    => 'BOM'
2185              ,  p_other_status        => NULL
2186              ,  p_other_token_tbl     => Error_Handler.G_MISS_TOKEN_TBL
2187              ,  x_rtg_header_rec      => l_rtg_header_rec
2188              ,  x_rtg_revision_tbl    => l_rtg_revision_tbl
2189              ,  x_op_network_tbl      => l_op_network_tbl
2190              ,  x_operation_tbl       => l_operation_tbl
2191              ,  x_op_resource_tbl     => l_op_resource_tbl
2192              ,  x_sub_resource_tbl    => l_sub_resource_tbl
2193              ) ;
2194           END IF ;
2195        END IF ;
2196 
2197 
2198        --
2199        -- Process Flow step 16 - Entity Level Validation
2200        -- Call Bom_Validate_Op_Res.Check_Entity
2201        --
2202        Bom_Validate_Sub_Op_Res.Check_Entity
2203           (  p_sub_resource_rec       => l_sub_resource_rec
2204           ,  p_sub_res_unexp_rec      => l_sub_res_unexp_rec
2205           ,  p_old_sub_resource_rec   => l_old_sub_resource_rec
2206           ,  p_old_sub_res_unexp_rec  => l_old_sub_res_unexp_rec
2207           ,  x_sub_resource_rec       => l_sub_resource_rec
2208           ,  x_sub_res_unexp_rec      => l_sub_res_unexp_rec
2209           ,  x_mesg_token_tbl         => l_mesg_token_tbl
2210           ,  x_return_status          => l_return_status
2211           ) ;
2212 
2213 
2214        IF l_return_status = Error_Handler.G_STATUS_ERROR
2215        THEN
2216           IF l_sub_resource_rec.transaction_type = BOM_Rtg_Globals.G_OPR_CREATE
2217           THEN
2218              l_other_message := 'BOM_SUB_RES_ENTVAL_CSEV_SKIP';
2219              l_other_token_tbl(1).token_name := 'SUB_RESOURCE_CODE';
2220              l_other_token_tbl(1).token_value :=
2221                         l_sub_resource_rec.sub_resource_code ;
2222              l_other_token_tbl(2).token_name := 'SCHEDULE_SEQ_NUMBER';
2223              l_other_token_tbl(2).token_value :=
2224                         nvl(l_sub_resource_rec.substitute_group_number, l_sub_res_unexp_rec.substitute_group_number) ;
2225              RAISE EXC_SEV_SKIP_BRANCH ;
2226           ELSE
2227              RAISE EXC_SEV_QUIT_RECORD ;
2228           END IF;
2229        ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
2230        THEN
2231           l_other_message := 'BOM_SUB_RES_ENTVAL_UNEXP_SKIP';
2232           l_other_token_tbl(1).token_name := 'SUB_RESOURCE_CODE';
2233           l_other_token_tbl(1).token_value :=
2234                         l_sub_resource_rec.sub_resource_code ;
2235           l_other_token_tbl(2).token_name := 'SCHEDULE_SEQ_NUMBER';
2236           l_other_token_tbl(2).token_value :=
2237                         nvl(l_sub_resource_rec.substitute_group_number, l_sub_res_unexp_rec.substitute_group_number) ;
2238           RAISE EXC_UNEXP_SKIP_OBJECT ;
2239        ELSIF l_return_status ='S' AND l_mesg_token_tbl .COUNT <> 0
2240        THEN
2241           Bom_Rtg_Error_Handler.Log_Error
2242           (    p_sub_resource_tbl    => l_sub_resource_tbl
2243             ,  p_rtg_header_rec      =>Bom_Rtg_Pub.G_MISS_RTG_HEADER_REC
2244             ,  p_rtg_revision_tbl    =>Bom_Rtg_Pub.G_MISS_RTG_REVISION_TBL
2245             ,  p_operation_tbl       =>Bom_Rtg_Pub.G_MISS_OPERATION_TBL
2246             ,  p_op_resource_tbl     =>Bom_Rtg_Pub.G_MISS_OP_RESOURCE_TBL
2247             ,  p_op_network_tbl      =>Bom_Rtg_Pub.G_MISS_OP_NETWORK_TBL
2248             ,  p_mesg_token_tbl      => l_mesg_token_tbl
2249             ,  p_error_status        => 'W'
2250             ,  p_error_level         => Error_Handler.G_SR_LEVEL
2251             ,  p_entity_index        => I
2252             ,  p_error_scope         => NULL
2253             ,  p_other_message       => NULL
2254             ,  p_other_mesg_appid    => 'BOM'
2255             ,  p_other_status        => NULL
2256             ,  p_other_token_tbl     => Error_Handler.G_MISS_TOKEN_TBL
2257             ,  x_rtg_header_rec      => l_rtg_header_rec
2258             ,  x_rtg_revision_tbl    => l_rtg_revision_tbl
2259             ,  x_op_network_tbl      => l_op_network_tbl
2260             ,  x_operation_tbl       => l_operation_tbl
2261             ,  x_op_resource_tbl     => l_op_resource_tbl
2262             ,  x_sub_resource_tbl    => l_sub_resource_tbl
2263           ) ;
2264        END IF;
2265 
2266        IF BOM_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Entity validation completed with '
2267              || l_return_Status || ' proceeding for database writes . . . ') ;
2268        END IF;
2269 
2270        --
2271        -- Process Flow step 16 : Database Writes
2272        --
2273           SAVEPOINT validate_sgn; -- Bug 3798362
2274           Bom_Sub_Op_Res_Util.Perform_Writes
2275           (   p_sub_resource_rec     => l_sub_resource_rec
2276           ,   p_sub_res_unexp_rec    => l_sub_res_unexp_rec
2277           ,   x_mesg_token_tbl       => l_mesg_token_tbl
2278           ,   x_return_status        => l_return_status
2279           ) ;
2280 
2281        IF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
2282        THEN
2283           l_other_message := 'BOM_SUB_RES_WRITES_UNEXP_SKIP';
2284           l_other_token_tbl(1).token_name := 'SUB_RESOURCE_CODE';
2285           l_other_token_tbl(1).token_value :=
2286                         l_sub_resource_rec.sub_resource_code ;
2287           l_other_token_tbl(2).token_name := 'SCHEDULE_SEQ_NUMBER';
2288           l_other_token_tbl(2).token_value :=
2289                         nvl(l_sub_resource_rec.substitute_group_number, l_sub_res_unexp_rec.substitute_group_number) ;
2290           RAISE EXC_UNEXP_SKIP_OBJECT ;
2291        ELSIF l_return_status ='S' AND
2292           l_mesg_token_tbl .COUNT <>0
2293        THEN
2294           Bom_Rtg_Error_Handler.Log_Error
2295           (  p_sub_resource_tbl    => l_sub_resource_tbl
2296             ,  p_rtg_header_rec      =>Bom_Rtg_Pub.G_MISS_RTG_HEADER_REC
2297             ,  p_rtg_revision_tbl    =>Bom_Rtg_Pub.G_MISS_RTG_REVISION_TBL
2298             ,  p_operation_tbl       =>Bom_Rtg_Pub.G_MISS_OPERATION_TBL
2299             ,  p_op_resource_tbl     =>Bom_Rtg_Pub.G_MISS_OP_RESOURCE_TBL
2300             ,  p_op_network_tbl      =>Bom_Rtg_Pub.G_MISS_OP_NETWORK_TBL
2301             ,  p_mesg_token_tbl      => l_mesg_token_tbl
2302             ,  p_error_status        => 'W'
2303             ,  p_error_level         => Error_Handler.G_SR_LEVEL
2304             ,  p_entity_index        => I
2305             ,  p_error_scope         => NULL
2306             ,  p_other_message       => NULL
2307             ,  p_other_mesg_appid    => 'BOM'
2308             ,  p_other_status        => NULL
2309             ,  p_other_token_tbl     => Error_Handler.G_MISS_TOKEN_TBL
2310             ,  x_rtg_header_rec      => l_rtg_header_rec
2311             ,  x_rtg_revision_tbl    => l_rtg_revision_tbl
2312             ,  x_op_network_tbl      => l_op_network_tbl
2313             ,  x_operation_tbl       => l_operation_tbl
2314             ,  x_op_resource_tbl     => l_op_resource_tbl
2315             ,  x_sub_resource_tbl    => l_sub_resource_tbl
2316           ) ;
2317        END IF;
2318 
2319        IF BOM_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Sub Res Database writes completed with status  ' || l_return_status);
2320        END IF;
2321 
2322 
2323        --
2324        -- Process Flow Step 17: Validate SGN order -- Bug 3798362
2325        --
2326 
2327        Bom_Validate_Op_Res.Val_SGN_Order
2328        ( p_op_seq_id      => l_sub_res_unexp_rec.operation_sequence_id
2329        , x_mesg_token_tbl => l_mesg_token_tbl
2330        , x_return_status  => l_return_status);
2331 
2332        IF l_return_status = Error_Handler.G_STATUS_ERROR
2333        THEN
2334           ROLLBACK TO validate_sgn;
2335           RAISE EXC_SEV_QUIT_SIBLINGS;
2336        END IF;
2337 
2338        IF BOM_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Sub Res validate SGN order completed with status  ' || l_return_status);
2339        END IF;
2340     END IF; -- END IF statement that checks RETURN STATUS
2341 
2342     --  Load tables.
2343     l_sub_resource_tbl(I)          := l_sub_resource_rec;
2344 
2345 
2346     --  For loop exception handler.
2347 
2348     EXCEPTION
2349        WHEN EXC_SEV_QUIT_RECORD THEN
2350           Bom_Rtg_Error_Handler.Log_Error
2351           (  p_sub_resource_tbl    => l_sub_resource_tbl
2352             ,  p_rtg_header_rec      =>Bom_Rtg_Pub.G_MISS_RTG_HEADER_REC
2353             ,  p_rtg_revision_tbl    =>Bom_Rtg_Pub.G_MISS_RTG_REVISION_TBL
2354             ,  p_operation_tbl       =>Bom_Rtg_Pub.G_MISS_OPERATION_TBL
2355             ,  p_op_resource_tbl     =>Bom_Rtg_Pub.G_MISS_OP_RESOURCE_TBL
2356             ,  p_op_network_tbl      =>Bom_Rtg_Pub.G_MISS_OP_NETWORK_TBL
2357             ,  p_mesg_token_tbl      => l_mesg_token_tbl
2358             ,  p_error_status        => Error_Handler.G_STATUS_ERROR
2359             ,  p_error_scope         => Error_Handler.G_SCOPE_RECORD
2360             ,  p_error_level         => Error_Handler.G_SR_LEVEL
2361             ,  p_entity_index        => I
2362             ,  p_other_message       => NULL
2363             ,  p_other_mesg_appid    => 'BOM'
2364             ,  p_other_status        => NULL
2365             ,  p_other_token_tbl     => Error_Handler.G_MISS_TOKEN_TBL
2366             ,  x_rtg_header_rec      => l_rtg_header_rec
2367             ,  x_rtg_revision_tbl    => l_rtg_revision_tbl
2368             ,  x_op_network_tbl      => l_op_network_tbl
2369             ,  x_operation_tbl       => l_operation_tbl
2370             ,  x_op_resource_tbl     => l_op_resource_tbl
2371             ,  x_sub_resource_tbl    => l_sub_resource_tbl
2372           ) ;
2373 
2374 
2375          IF l_bo_return_status = 'S'
2376          THEN
2377             l_bo_return_status := l_return_status ;
2378          END IF;
2379 
2380          x_return_status       := l_bo_return_status;
2381          x_mesg_token_tbl      := l_mesg_token_tbl ;
2382          x_sub_resource_tbl    := l_sub_resource_tbl ;
2383 
2384 
2385       WHEN EXC_SEV_QUIT_BRANCH THEN
2386 
2387          Bom_Rtg_Error_Handler.Log_Error
2388          (     p_sub_resource_tbl    => l_sub_resource_tbl
2389             ,  p_rtg_header_rec      => Bom_Rtg_Pub.G_MISS_RTG_HEADER_REC
2390             ,  p_rtg_revision_tbl    => Bom_Rtg_Pub.G_MISS_RTG_REVISION_TBL
2391             ,  p_operation_tbl       => Bom_Rtg_Pub.G_MISS_OPERATION_TBL
2392             ,  p_op_resource_tbl     => Bom_Rtg_Pub.G_MISS_OP_RESOURCE_TBL
2393             ,  p_op_network_tbl      => Bom_Rtg_Pub.G_MISS_OP_NETWORK_TBL
2394             ,  p_mesg_token_tbl      => l_mesg_token_tbl
2395             ,  p_error_status        => Error_Handler.G_STATUS_ERROR
2396             ,  p_error_scope         => Error_Handler.G_SCOPE_CHILDREN
2397             ,  p_other_status        => Error_Handler.G_STATUS_ERROR
2398             ,  p_other_message       => l_other_message
2399             ,  p_other_token_tbl     => l_other_token_tbl
2400             ,  p_error_level         => Error_Handler.G_SR_LEVEL
2401             ,  p_entity_index        => I
2402             ,  p_other_mesg_appid    => 'BOM'
2403             ,  x_rtg_header_rec      => l_rtg_header_rec
2404             ,  x_rtg_revision_tbl    => l_rtg_revision_tbl
2405             ,  x_op_network_tbl      => l_op_network_tbl
2406             ,  x_operation_tbl       => l_operation_tbl
2407             ,  x_op_resource_tbl     => l_op_resource_tbl
2408             ,  x_sub_resource_tbl    => l_sub_resource_tbl
2409           ) ;
2410 
2411 
2412          IF l_bo_return_status = 'S'
2413          THEN
2414             l_bo_return_status  := l_return_status;
2415          END IF;
2416 
2417          x_return_status       := l_bo_return_status;
2418          x_mesg_token_tbl      := l_mesg_token_tbl ;
2419          x_sub_resource_tbl    := l_sub_resource_tbl ;
2420 
2421       WHEN EXC_SEV_SKIP_BRANCH THEN
2422          Bom_Rtg_Error_Handler.Log_Error
2423          (  p_sub_resource_tbl    => l_sub_resource_tbl
2424             ,  p_rtg_header_rec      =>Bom_Rtg_Pub.G_MISS_RTG_HEADER_REC
2425             ,  p_rtg_revision_tbl    =>Bom_Rtg_Pub.G_MISS_RTG_REVISION_TBL
2426             ,  p_operation_tbl       =>Bom_Rtg_Pub.G_MISS_OPERATION_TBL
2427             ,  p_op_resource_tbl     =>Bom_Rtg_Pub.G_MISS_OP_RESOURCE_TBL
2428             ,  p_op_network_tbl      =>Bom_Rtg_Pub.G_MISS_OP_NETWORK_TBL
2429             ,  p_mesg_token_tbl      => l_mesg_token_tbl
2430             ,  p_error_status        => Error_Handler.G_STATUS_ERROR
2431             ,  p_error_scope         => Error_Handler.G_SCOPE_CHILDREN
2432             ,  p_other_status        => Error_Handler.G_STATUS_NOT_PICKED
2433             ,  p_other_message       => l_other_message
2434             ,  p_other_token_tbl     => l_other_token_tbl
2435             ,  p_error_level         => Error_Handler.G_SR_LEVEL
2436             ,  p_entity_index        => I
2437             ,  p_other_mesg_appid    => 'BOM'
2438             ,  x_rtg_header_rec      => l_rtg_header_rec
2439             ,  x_rtg_revision_tbl    => l_rtg_revision_tbl
2440             ,  x_op_network_tbl      => l_op_network_tbl
2441             ,  x_operation_tbl       => l_operation_tbl
2442             ,  x_op_resource_tbl     => l_op_resource_tbl
2443             ,  x_sub_resource_tbl    => l_sub_resource_tbl
2444          ) ;
2445 
2446         IF l_bo_return_status = 'S'
2447         THEN
2448            l_bo_return_status  := l_return_status ;
2449         END IF;
2450         x_return_status       := l_bo_return_status;
2451         x_mesg_token_tbl      := l_mesg_token_tbl ;
2452         x_sub_resource_tbl    := l_sub_resource_tbl ;
2453 
2454       WHEN EXC_SEV_QUIT_SIBLINGS THEN
2455          Bom_Rtg_Error_Handler.Log_Error
2456          (     p_sub_resource_tbl    => l_sub_resource_tbl
2457             ,  p_rtg_header_rec      => Bom_Rtg_Pub.G_MISS_RTG_HEADER_REC
2458             ,  p_rtg_revision_tbl    => Bom_Rtg_Pub.G_MISS_RTG_REVISION_TBL
2459             ,  p_operation_tbl       => Bom_Rtg_Pub.G_MISS_OPERATION_TBL
2460             ,  p_op_resource_tbl     => Bom_Rtg_Pub.G_MISS_OP_RESOURCE_TBL
2461             ,  p_op_network_tbl      => Bom_Rtg_Pub.G_MISS_OP_NETWORK_TBL
2462             ,  p_mesg_token_tbl      => l_mesg_token_tbl
2463             ,  p_error_status        => Error_Handler.G_STATUS_ERROR
2464             ,  p_error_scope         => Error_Handler.G_SCOPE_SIBLINGS
2465             ,  p_other_status        => Error_Handler.G_STATUS_ERROR
2466             ,  p_other_message       => l_other_message
2467             ,  p_other_token_tbl     => l_other_token_tbl
2468             ,  p_error_level         => Error_Handler.G_SR_LEVEL
2469             ,  p_entity_index        => I
2470             ,  p_other_mesg_appid    => 'BOM'
2471             ,  x_rtg_header_rec      => l_rtg_header_rec
2472             ,  x_rtg_revision_tbl    => l_rtg_revision_tbl
2473             ,  x_op_network_tbl      => l_op_network_tbl
2474             ,  x_operation_tbl       => l_operation_tbl
2475             ,  x_op_resource_tbl     => l_op_resource_tbl
2476             ,  x_sub_resource_tbl    => l_sub_resource_tbl
2477          ) ;
2478 
2479          IF l_bo_return_status = 'S'
2480          THEN
2481            l_bo_return_status  := l_return_status ;
2482          END IF;
2483          x_return_status       := l_bo_return_status;
2484          x_mesg_token_tbl      := l_mesg_token_tbl ;
2485          x_sub_resource_tbl    := l_sub_resource_tbl ;
2486 
2487 
2488       WHEN EXC_FAT_QUIT_BRANCH THEN
2489          Bom_Rtg_Error_Handler.Log_Error
2490          (     p_sub_resource_tbl    => l_sub_resource_tbl
2491             ,  p_rtg_header_rec      =>Bom_Rtg_Pub.G_MISS_RTG_HEADER_REC
2492             ,  p_rtg_revision_tbl    =>Bom_Rtg_Pub.G_MISS_RTG_REVISION_TBL
2493             ,  p_operation_tbl       =>Bom_Rtg_Pub.G_MISS_OPERATION_TBL
2494             ,  p_op_resource_tbl     =>Bom_Rtg_Pub.G_MISS_OP_RESOURCE_TBL
2495             ,  p_op_network_tbl      =>Bom_Rtg_Pub.G_MISS_OP_NETWORK_TBL
2496             ,  p_mesg_token_tbl      => l_mesg_token_tbl
2497             ,  p_error_status        => Error_Handler.G_STATUS_FATAL
2498             ,  p_error_scope         => Error_Handler.G_SCOPE_CHILDREN
2499             ,  p_other_status        => Error_Handler.G_STATUS_FATAL
2500             ,  p_other_message       => l_other_message
2501             ,  p_other_token_tbl     => l_other_token_tbl
2502             ,  p_error_level         => Error_Handler.G_SR_LEVEL
2503             ,  p_entity_index        => I
2504             ,  p_other_mesg_appid    => 'BOM'
2505             ,  x_rtg_header_rec      => l_rtg_header_rec
2506             ,  x_rtg_revision_tbl    => l_rtg_revision_tbl
2507             ,  x_op_network_tbl      => l_op_network_tbl
2508             ,  x_operation_tbl       => l_operation_tbl
2509             ,  x_op_resource_tbl     => l_op_resource_tbl
2510             ,  x_sub_resource_tbl    => l_sub_resource_tbl
2511          ) ;
2512 
2513          x_return_status       := Error_Handler.G_STATUS_FATAL;
2514          x_mesg_token_tbl      := l_mesg_token_tbl ;
2515          x_sub_resource_tbl    := l_sub_resource_tbl ;
2516 
2517 
2518       WHEN EXC_FAT_QUIT_SIBLINGS THEN
2519          Bom_Rtg_Error_Handler.Log_Error
2520          (     p_sub_resource_tbl    => l_sub_resource_tbl
2521             ,  p_rtg_header_rec      =>Bom_Rtg_Pub.G_MISS_RTG_HEADER_REC
2522             ,  p_rtg_revision_tbl    =>Bom_Rtg_Pub.G_MISS_RTG_REVISION_TBL
2523             ,  p_operation_tbl       =>Bom_Rtg_Pub.G_MISS_OPERATION_TBL
2524             ,  p_op_resource_tbl     =>Bom_Rtg_Pub.G_MISS_OP_RESOURCE_TBL
2525             ,  p_op_network_tbl      =>Bom_Rtg_Pub.G_MISS_OP_NETWORK_TBL
2526             ,  p_mesg_token_tbl      => l_mesg_token_tbl
2527             ,  p_error_status        => Error_Handler.G_STATUS_FATAL
2528             ,  p_error_scope         => Error_Handler.G_SCOPE_SIBLINGS
2529             ,  p_other_status        => Error_Handler.G_STATUS_FATAL
2530             ,  p_other_message       => l_other_message
2531             ,  p_other_token_tbl     => l_other_token_tbl
2532             ,  p_error_level         => Error_Handler.G_SR_LEVEL
2533             ,  p_entity_index        => I
2534             ,  p_other_mesg_appid    => 'BOM'
2535             ,  x_rtg_header_rec      => l_rtg_header_rec
2536             ,  x_rtg_revision_tbl    => l_rtg_revision_tbl
2537             ,  x_op_network_tbl      => l_op_network_tbl
2538             ,  x_operation_tbl       => l_operation_tbl
2539             ,  x_op_resource_tbl     => l_op_resource_tbl
2540             ,  x_sub_resource_tbl    => l_sub_resource_tbl
2541          ) ;
2542 
2543         x_return_status       := Error_Handler.G_STATUS_FATAL;
2544         x_mesg_token_tbl      := l_mesg_token_tbl ;
2545         x_sub_resource_tbl    := l_sub_resource_tbl ;
2546 
2547 /*
2548     WHEN EXC_FAT_QUIT_OBJECT THEN
2549          Bom_Rtg_Error_Handler.Log_Error
2550          (  p_sub_resource_tbl    => l_sub_resource_tbl
2551          ,  p_mesg_token_tbl      => l_mesg_token_tbl
2552          ,  p_error_status        => Error_Handler.G_STATUS_FATAL
2553          ,  p_error_scope         => Error_Handler.G_SCOPE_ALL
2554          ,  p_other_status        => Error_Handler.G_STATUS_FATAL
2555          ,  p_other_message       => l_other_message
2556          ,  p_other_token_tbl     => l_other_token_tbl
2557          ,  p_error_level         => Error_Handler.G_SR_LEVEL
2558          ,  p_entity_index        => I
2559          ,  x_rtg_header_rec      => l_rtg_header_rec
2560          ,  x_rtg_revision_tbl    => l_rtg_revision_tbl
2561          ,  x_op_network_tbl      => l_op_network_tbl
2562          ,  x_operation_tbl       => l_operation_tbl
2563          ,  x_op_resource_tbl     => l_op_resource_tbl
2564          ,  x_sub_resource_tbl    => l_sub_resource_tbl
2565          ) ;
2566 
2567          l_return_status       := 'Q';
2568          x_mesg_token_tbl      := l_mesg_token_tbl ;
2569          x_sub_resource_tbl    := l_sub_resource_tbl ;
2570 */
2571 
2572       WHEN EXC_UNEXP_SKIP_OBJECT THEN
2573          Bom_Rtg_Error_Handler.Log_Error
2574          (  p_sub_resource_tbl    => l_sub_resource_tbl
2575          ,  p_rtg_header_rec      => Bom_Rtg_Pub.G_MISS_RTG_HEADER_REC
2576          ,  p_rtg_revision_tbl    => Bom_Rtg_Pub.G_MISS_RTG_REVISION_TBL
2577          ,  p_operation_tbl       => Bom_Rtg_Pub.G_MISS_OPERATION_TBL
2578          ,  p_op_resource_tbl     => Bom_Rtg_Pub.G_MISS_OP_RESOURCE_TBL
2579          ,  p_op_network_tbl      => Bom_Rtg_Pub.G_MISS_OP_NETWORK_TBL
2580          ,  p_mesg_token_tbl      => l_mesg_token_tbl
2581          ,  p_error_status        => Error_Handler.G_STATUS_UNEXPECTED
2582          ,  p_other_status        => Error_Handler.G_STATUS_NOT_PICKED
2583          ,  p_other_message       => l_other_message
2584          ,  p_other_token_tbl     => l_other_token_tbl
2585          ,  p_error_level         => Error_Handler.G_SR_LEVEL
2586          ,  p_other_mesg_appid    => 'BOM'
2587          ,  p_entity_index         => I
2588          ,  p_error_scope          => NULL
2589          ,  x_rtg_header_rec      => l_rtg_header_rec
2590          ,  x_rtg_revision_tbl    => l_rtg_revision_tbl
2591          ,  x_op_network_tbl      => l_op_network_tbl
2592          ,  x_operation_tbl       => l_operation_tbl
2593          ,  x_op_resource_tbl     => l_op_resource_tbl
2594          ,  x_sub_resource_tbl    => l_sub_resource_tbl
2595          ) ;
2596 
2597          l_return_status       := 'U';
2598          x_mesg_token_tbl      := l_mesg_token_tbl ;
2599          x_sub_resource_tbl    := l_sub_resource_tbl ;
2600 
2601    END ; -- END block
2602 
2603 
2604    IF l_return_status in ('Q', 'U')
2605    THEN
2606       x_return_status := l_return_status;
2607       RETURN ;
2608    END IF;
2609 
2610    END LOOP; -- END Substitute Operation Resources processing loop
2611 
2612    --  Load OUT parameters
2613    IF NVL(l_return_status, 'S') <> 'S'
2614    THEN
2615       x_return_status     := l_return_status;
2616    END IF;
2617 
2618    x_mesg_token_tbl      := l_mesg_token_tbl ;
2619    x_sub_resource_tbl    := l_sub_resource_tbl ;
2620    x_mesg_token_tbl      := l_mesg_token_tbl ;
2621 
2622 END Sub_Operation_Resources ;
2623 
2624 /****************************************************************************
2625 * Procedure     : Op_Network
2626 * Parameters IN : Op Network Table and all the other entities
2627 * Parameters OUT: Op Network Table and all the other entities
2628 * Purpose       : This procedure will process all the network records.
2629 *                 Although the other entities are not children of this entity
2630 *                 the are taken as parameters so that the error handler could
2631 *                 set the records to appropriate status if a fatal or severity
2632 *                 1 error occurs.
2633 *****************************************************************************/
2634 
2635 PROCEDURE Op_Networks
2636 (   p_validation_level           IN  NUMBER
2637  ,  p_assembly_item_name         IN  VARCHAR2   := NULL
2638  ,  p_assembly_item_id           IN  NUMBER     := NULL
2639  ,  p_organization_id            IN  NUMBER     := NULL
2640  ,  p_alternate_rtg_code         IN  VARCHAR2   := NULL
2641  ,  p_op_network_tbl             IN  Bom_Rtg_Pub.Op_Network_Tbl_Type
2642  ,  x_op_network_tbl             IN OUT NOCOPY Bom_Rtg_Pub.Op_Network_Tbl_Type
2643  ,  x_Mesg_Token_Tbl             IN OUT NOCOPY Error_Handler.Mesg_Token_Tbl_Type
2644  ,  x_return_status              IN OUT NOCOPY VARCHAR2
2645  )
2646 IS
2647 
2648 /* Error Handling Variables */
2649 l_token_tbl             Error_Handler.Token_Tbl_Type ;
2650 l_mesg_token_tbl        Error_Handler.Mesg_Token_Tbl_Type ;
2651 l_other_token_tbl       Error_Handler.Token_Tbl_Type;
2652 l_other_message         VARCHAR2(2000);
2653 l_err_text              VARCHAR2(2000);
2654 
2655 
2656 l_valid                 BOOLEAN := TRUE;
2657 l_return_status         VARCHAR2(1) := FND_API.G_RET_STS_SUCCESS;
2658 l_bo_return_status      VARCHAR2(1) := 'S';
2659 l_rtg_parent_exists     BOOLEAN := FALSE;
2660 
2661 l_rtg_header_rec        Bom_Rtg_Pub.rtg_header_Rec_Type;
2662 l_rtg_header_unexp_rec  Bom_Rtg_Pub.rtg_header_unexposed_Rec_Type;
2663 l_old_rtg_header_rec    Bom_Rtg_Pub.rtg_header_Rec_Type;
2664 l_old_rtg_header_unexp_rec Bom_Rtg_Pub.rtg_Header_Unexposed_Rec_Type;
2665 l_op_network_rec        Bom_Rtg_Pub.op_network_Rec_Type;
2666 l_op_network_unexp_rec  Bom_Rtg_Pub.op_network_Unexposed_Rec_Type;
2667 l_op_network_tbl        Bom_Rtg_Pub.op_network_Tbl_Type := p_op_network_tbl;
2668 l_old_op_network_rec    Bom_Rtg_Pub.op_network_Rec_Type := NULL;
2669 l_old_op_network_unexp_rec
2670                         Bom_Rtg_Pub.op_network_Unexposed_Rec_Type := NULL;
2671 l_rtg_revision_tbl      Bom_Rtg_Pub.Rtg_Revision_Tbl_Type ;
2672 l_operation_tbl         Bom_Rtg_Pub.operation_tbl_type;
2673 l_op_resource_tbl       Bom_Rtg_Pub.op_resource_tbl_type;
2674 l_sub_resource_tbl      Bom_Rtg_Pub.sub_resource_tbl_type;
2675 
2676 l_return_value          NUMBER;
2677   /*below change for RBO support for OSFM*/
2678 l_common_routing_sequence_id   NUMBER;
2679 l_prev_start_id                NUMBER:=0;
2680 l_prev_end_id                  NUMBER:=0;
2681 l_temp_rtg_id                  NUMBER:=0;
2682 
2683 l_line_op		BOOLEAN := FALSE; -- Added for calc_cynp
2684 l_process_op		BOOLEAN := FALSE;
2685 l_dummy			VARCHAR2(1) := 'S';
2686 --l_temp_op_rec_tbl_test   BOM_RTG_Globals.Temp_Op_Rec_Tbl_Type;
2687 
2688 BEGIN
2689   IF BOM_Rtg_Globals.Get_Debug = 'Y'
2690   THEN Error_Handler.Write_Debug
2691     ('Within Operation Network procedure call. . . ');
2692   END IF;
2693 
2694     l_return_status := 'S';
2695     l_bo_return_status := 'S';
2696 
2697     --  Init local table variables.
2698     l_op_network_tbl := p_op_network_tbl;
2699 
2700     l_op_network_unexp_rec.organization_id := BOM_Rtg_Globals.Get_org_id;
2701     FOR I IN 1..l_op_network_tbl.COUNT LOOP
2702     BEGIN
2703 
2704         --  Load local records.
2705         l_op_network_rec := l_op_network_tbl(I);
2706 
2707         --
2708         -- Process Flow Step 2: Check if return status is NULL
2709         --
2710 
2711         l_op_network_rec.transaction_type :=
2712                 UPPER(l_op_network_rec.transaction_type);
2713 
2714         IF p_assembly_item_name IS NOT NULL AND
2715            p_organization_id IS NOT NULL
2716         THEN
2717                 l_rtg_parent_exists := TRUE;
2718         END IF;
2719 
2720         --
2721         -- Initialize the Unexposed Record for every iteration of the Loop
2722         -- so that sequence numbers get generated for every new row.
2723         --
2724         l_op_network_unexp_rec.From_Op_Seq_Id := NULL ;
2725         l_op_network_unexp_rec.To_Op_Seq_Id := NULL ;
2726         l_op_network_unexp_rec.new_from_op_seq_id := NULL;
2727         l_op_network_unexp_rec.new_to_op_seq_id := NULL;
2728 
2729         --
2730         -- Process Flow Step 2.5: Check if record has not yet been processed and
2731         -- that it is the child of the parent that called this procedure
2732         --
2733         IF (l_op_network_rec.return_status IS NULL OR
2734             l_op_network_rec.return_status = FND_API.G_MISS_CHAR)
2735            AND
2736            (NOT l_rtg_parent_exists
2737            OR
2738            (l_rtg_parent_exists AND
2739               ( l_op_network_rec.assembly_item_name = p_assembly_item_name AND
2740                 l_op_network_unexp_rec.organization_id = p_organization_id AND
2741                 NVL(l_op_network_rec.alternate_routing_code, FND_API.G_MISS_CHAR) =
2742                     NVL(p_alternate_rtg_code, FND_API.G_MISS_CHAR)
2743               )
2744              )
2745             )
2746         THEN
2747 
2748            l_return_status := FND_API.G_RET_STS_SUCCESS;
2749            l_op_network_rec.return_status := FND_API.G_RET_STS_SUCCESS;
2750 
2751            --
2752            -- Step 3: Check if transaction_type is valid
2753            --
2754            BOM_Rtg_Globals.Transaction_Type_Validity
2755            (   p_transaction_type       => l_op_network_rec.transaction_type
2756            ,   p_entity                 => 'Op_Network'
2757            ,   p_entity_id              => l_op_network_rec.assembly_item_name
2758            ,   x_valid                  => l_valid
2759            ,   x_Mesg_Token_Tbl         => l_Mesg_Token_Tbl
2760            );
2761 
2762            IF NOT l_valid
2763            THEN
2764                 l_return_status := Error_Handler.G_STATUS_ERROR;
2765                 RAISE EXC_SEV_QUIT_RECORD;
2766            END IF;
2767 
2768            --
2769            -- Process Flow Step: 4 Convert User Unique Index
2770            --l_temp_op_rec_tbl	BOM_RTG_Globals.Temp_Op_Rec_Tbl_Type;
2771 --	   BOM_RTG_Globals.Set_Temp_Op_Tbl(l_temp_op_rec_tbl_test);
2772            BOM_Rtg_Val_To_Id.Op_Network_UUI_To_UI
2773            (  p_op_network_rec          => l_op_network_rec
2774             , p_op_network_unexp_rec    => l_op_network_unexp_rec
2775             , x_op_network_unexp_rec    => l_op_network_unexp_rec
2776             , x_mesg_token_tbl          => l_mesg_token_tbl
2777             , x_return_status           => l_return_status
2778             );
2779 
2780            IF  l_return_status = Error_Handler.G_STATUS_ERROR
2781            THEN
2782                 l_other_message := 'BOM_OP_NWK_UUI_SEV_ERROR';
2783                 l_other_token_tbl(1).token_name := 'FROM_OP_SEQ_NUMBER';
2784                 l_other_token_tbl(1).token_value :=
2785                                     l_op_network_rec.from_op_seq_number;
2786                 l_other_token_tbl(2).token_name := 'TO_OP_SEQ_NUMBER';
2787                 l_other_token_tbl(2).token_value :=
2788                                     l_op_network_rec.to_op_seq_number;
2789                 RAISE EXC_SEV_QUIT_OBJECT;
2790            ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
2791            THEN
2792                 l_other_message := 'BOM_OP_NWK_UUI_UNEXP_SKIP';
2793                 l_other_token_tbl(1).token_name := 'FROM_OP_SEQ_NUMBER';
2794                 l_other_token_tbl(1).token_value :=
2795                                     l_op_network_rec.from_op_seq_number;
2796                 l_other_token_tbl(2).token_name := 'TO_OP_SEQ_NUMBER';
2797                 l_other_token_tbl(2).token_value :=
2798                                     l_op_network_rec.to_op_seq_number;
2799                 RAISE EXC_UNEXP_SKIP_OBJECT;
2800            END IF;
2801 
2802   /*below change for RBO support for OSFM*/
2803   /**************************************************************************
2804    * 1. If its update of OSFM Network, then we store the start operation id *
2805    * at the start. Then at the end of the network transactions, we check    *
2806    * that this start operation is the same as the one at the end of update. *
2807    * If its not(user changed start) we should error out!                    *
2808    * 2. Same for the End operation.                                         *
2809    * 3. We are also adding logic to default the subinventory and locator.   *
2810    * Since the original logic as in OSFM forms trigger, depends on the end  *
2811    * operation sub inv and locator, we have put the logic here. So that we  *
2812    * can get the end operation at the end of saving all the network links.  *
2813    * 4. Also, we cannot ask user to decide for following 2 cases as forms   *
2814    * does , so we are going to give user instruction to do so by going to   *
2815    * the form.But we will not assume any thing and let the data be as it is!*
2816    * Cases in question :                                                    *
2817    * a. When the end operation has sub inv and loc; also it matches with the*
2818    *    routing sub inv => we will not change data and tell user that if    *
2819    *    he/she wwants they can change this in form.                         *
2820    * b. When sub inv also match , then we will not change the locator =>    *
2821    *    we will tell user that the sub inv matches and locators are not the *
2822    *    same, and that they can change this in form if they wish!           *
2823    **************************************************************************/
2824    l_temp_rtg_id := BOM_RTG_Globals.Get_Routing_Sequence_Id();
2825    IF( l_temp_rtg_id  IS NULL OR l_temp_rtg_id = 0 ) OR
2826      ( BOM_RTG_Globals.Is_Osfm_NW_Calc_Flag = FALSE) THEN
2827 
2828      BOM_RTG_Globals.Set_Routing_Sequence_Id(
2829      l_op_network_unexp_rec.routing_sequence_id);
2830      BOM_RTG_Globals.Set_Osfm_NW_Calc_Flag(TRUE);
2831      IF BOM_Rtg_Globals.Get_Debug = 'Y'
2832      THEN Error_Handler.Write_Debug
2833       ('Op Network: Calling BOM_Op_Network_UTIL.Get_WSM_Netowrk_Attribs....');
2834      END IF;
2835 
2836       BOM_Op_Network_UTIL.Get_WSM_Netowrk_Attribs  (
2837       p_routing_sequence_id =>l_op_network_unexp_rec.routing_sequence_id
2838     , x_prev_start_id      => l_prev_start_id
2839     , x_prev_end_id        => l_prev_end_id
2840     , x_mesg_token_tbl     => l_mesg_token_tbl
2841     , x_Return_status      => l_return_status
2842      );
2843      IF BOM_Rtg_Globals.Get_Debug = 'Y'
2844      THEN Error_Handler.Write_Debug
2845       ('Op Network: Get_WSM_Netowrk_Attribs returned with Status '||
2846       l_return_status);
2847      END IF;
2848 
2849      IF l_return_status = Error_Handler.G_STATUS_ERROR
2850      THEN
2851        l_other_message := 'BOM_WSM_NWK_NO_START_OR_END';
2852        RAISE EXC_SEV_QUIT_OBJECT ;
2853      END IF;
2854 
2855    END IF;
2856   /*above change for RBO support for OSFM*/
2857 
2858            /* No longer Used
2859            -- Step 5: Verify routing header's existence in database.
2860            -- If  routing header record is being created and the business object
2861            -- does not carry the Rtg header, then it is imperative to check
2862            -- for the Rtg Header's existence.
2863 
2864            IF l_op_network_rec.transaction_type = BOM_Rtg_Globals.G_OPR_CREATE
2865               AND NOT l_rtg_parent_exists
2866            THEN
2867                 l_rtg_header_rec.alternate_routing_code :=
2868                                                p_alternate_rtg_code;
2869                 l_rtg_header_unexp_rec.organization_id := p_organization_id;
2870                 l_rtg_header_unexp_rec.assembly_item_id := p_assembly_item_id;
2871                 l_rtg_header_rec.transaction_type := 'XXX';
2872 
2873                 Bom_Validate_rtg_header.Check_Existence
2874                 ( p_rtg_header_rec        => l_rtg_header_rec
2875                 , p_rtg_header_unexp_rec  => l_rtg_header_unexp_rec
2876                 , x_old_rtg_header_rec    => l_old_rtg_header_rec
2877                 , x_old_rtg_header_unexp_rec => l_old_rtg_header_unexp_rec
2878                 , x_Mesg_Token_Tbl           => l_Mesg_Token_Tbl
2879                 , x_return_status            => l_return_status
2880                 );
2881                 IF l_return_status = Error_Handler.G_STATUS_ERROR
2882                 THEN
2883                    l_other_message := 'BOM_RTG_HEADER_NOT_EXIST';
2884                    l_other_token_tbl(1).token_name := 'ASSEMBLY_ITEM_NAME';
2885                    l_other_token_tbl(1).token_value :=
2886                                         l_op_network_rec.assembly_item_name;
2887                    l_other_token_tbl(2).token_name := 'ORGANIZATION_CODE';
2888                    l_other_token_tbl(2).token_value :=
2889                                         l_op_network_rec.organization_code;
2890                    RAISE EXC_SEV_QUIT_OBJECT;
2891                 ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
2892                 THEN
2893                    l_other_message := 'BOM_RTG_REV_LIN_UNEXP_SKIP';
2894                    l_other_token_tbl(1).token_name :='ASSEMBLY_ITEM_NAME';
2895                    l_other_token_tbl(1).token_value :=
2896                                      l_op_network_rec.assembly_item_name;
2897                    RAISE EXC_UNEXP_SKIP_OBJECT;
2898                 END IF;
2899           END IF;
2900           */
2901 
2902 
2903            --
2904            -- Process Flow step 5: Verify operation network's existence
2905            --
2906            Bom_Validate_Op_Network.Check_Existence
2907                 (  p_op_network_rec             => l_op_network_rec
2908                 ,  p_op_network_unexp_rec       => l_op_network_unexp_rec
2909                 ,  x_old_op_network_rec         => l_old_op_network_rec
2910                 ,  x_old_op_network_unexp_rec   => l_old_op_network_unexp_rec
2911                 ,  x_Mesg_Token_Tbl             => l_Mesg_Token_Tbl
2912                 ,  x_return_status              => l_return_status
2913                 );
2914 
2915            IF l_return_status = Error_Handler.G_STATUS_ERROR
2916            THEN
2917                 /*  No longer used
2918                 l_other_message := 'BOM_OP_NWK_EXS_SEV_SKIP';
2919                 l_other_token_tbl(1).token_name := 'FROM_OP_SEQ_NUMBER';
2920                 l_other_token_tbl(1).token_value :=
2921                                     l_op_network_rec.from_op_seq_number;
2922                 l_other_token_tbl(2).token_name := 'TO_OP_SEQ_NUMBER';
2923                 l_other_token_tbl(2).token_value :=
2924                                     l_op_network_rec.to_op_seq_number;
2925                 l_other_token_tbl(3).token_name := 'ASSEMBLY_ITEM_NAME';
2926                 l_other_token_tbl(3).token_value :=
2927                              l_op_network_rec.assembly_item_name ;
2928                 */
2929                 RAISE EXC_SEV_QUIT_RECORD;
2930            ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
2931            THEN
2932                 l_other_message := 'BOM_OP_NWK_EXS_UNEXP_SKIP';
2933                 l_other_token_tbl(1).token_name := 'FROM_OP_SEQ_NUMBER';
2934                 l_other_token_tbl(1).token_value :=
2935                                     l_op_network_rec.from_op_seq_number;
2936                 l_other_token_tbl(2).token_name := 'TO_OP_SEQ_NUMBER';
2937                 l_other_token_tbl(2).token_value :=
2938                                     l_op_network_rec.to_op_seq_number;
2939                 -- l_other_token_tbl(3).token_name := 'ASSEMBLY_ITEM_NAME';
2940                 -- l_other_token_tbl(3).token_value :=
2941                 --           l_op_network_rec.assembly_item_name ;
2942                 RAISE EXC_UNEXP_SKIP_OBJECT;
2943            END IF;
2944 
2945            --
2946            -- Process Flow step 7:
2947            -- Check assembly item's operability for routing
2948            --
2949            IF NOT l_rtg_parent_exists
2950            THEN
2951 
2952                 Bom_Validate_Rtg_Header.Check_Access
2953                 ( p_assembly_item_name => l_op_network_rec.assembly_item_name
2954                 , p_assembly_item_id   => l_op_network_unexp_rec.assembly_item_id
2955                 , p_organization_id    => l_op_network_unexp_rec.organization_id
2956                 , p_alternate_rtg_code => l_op_network_rec.alternate_routing_code
2957                 , p_mesg_token_tbl     => Error_Handler.G_MISS_MESG_TOKEN_TBL
2958 
2959                 , x_Mesg_Token_Tbl     => l_Mesg_Token_Tbl
2960                 , x_Return_Status      => l_return_status
2961                 );
2962 
2963                 IF l_return_status = Error_Handler.G_STATUS_ERROR
2964                 THEN
2965                         l_other_message := 'BOM_OP_NWK_RITACC_FAT_FATAL';
2966                         l_other_token_tbl(1).token_name := 'FROM_OP_SEQ_NUMBER';
2967                         l_other_token_tbl(1).token_value :=
2968                                     l_op_network_rec.from_op_seq_number;
2969                         l_other_token_tbl(2).token_name := 'TO_OP_SEQ_NUMBER';
2970                         l_other_token_tbl(2).token_value :=
2971                                     l_op_network_rec.to_op_seq_number;
2972                         l_return_status := 'F';
2973                         RAISE EXC_FAT_QUIT_OBJECT;
2974                 ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
2975                 THEN
2976                         l_other_message := 'BOM_OP_NWK_RITACC_UNEXP_ERROR';
2977                         l_other_token_tbl(1).token_name := 'FROM_OP_SEQ_NUMBER';
2978                         l_other_token_tbl(1).token_value :=
2979                                     l_op_network_rec.from_op_seq_number;
2980                         l_other_token_tbl(2).token_name := 'TO_OP_SEQ_NUMBER';
2981                         l_other_token_tbl(2).token_value :=
2982                                     l_op_network_rec.to_op_seq_number;
2983                         RAISE EXC_UNEXP_SKIP_OBJECT;
2984                 END IF;
2985 
2986            END IF;
2987 
2988            --
2989            -- Process Flow step 9: Attribute Validation for Create and Update
2990            --
2991            IF l_op_network_rec.transaction_type IN
2992                 (BOM_Rtg_Globals.G_OPR_UPDATE, BOM_Rtg_Globals.G_OPR_CREATE)
2993            THEN
2994                Bom_Validate_Op_Network.Check_Access
2995                 (   p_op_network_rec           => l_op_network_rec
2996                 ,   p_op_network_unexp_rec     => l_op_network_unexp_rec
2997                 ,   x_return_status            => l_return_status
2998                 ,   x_Mesg_Token_Tbl           => l_Mesg_Token_Tbl
2999                 );
3000 
3001 IF BOM_Rtg_Globals.Get_Debug = 'Y'  THEN
3002     Error_Handler.Write_Debug
3003     ('Op Network: Check Access is completed with status '|| l_return_status );
3004 END IF;
3005 
3006                 IF l_return_status = Error_Handler.G_STATUS_ERROR
3007                 THEN
3008                         RAISE EXC_SEV_QUIT_RECORD;
3009                 ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
3010                 THEN
3011                         l_other_message := 'BOM_OP_NWK_ACCESS_UNEXP_SKIP';
3012                         l_other_token_tbl(1).token_name := 'FROM_OP_SEQ_NUMBER';
3013                         l_other_token_tbl(1).token_value :=
3014                                     l_op_network_rec.from_op_seq_number;
3015                         l_other_token_tbl(2).token_name := 'TO_OP_SEQ_NUMBER';
3016                         l_other_token_tbl(2).token_value :=
3017                                     l_op_network_rec.to_op_seq_number;
3018 
3019                         RAISE EXC_UNEXP_SKIP_OBJECT;
3020                 END IF;
3021            END IF;
3022 
3023 
3024            --
3025            -- Process Flow step 9: Attribute Validation for Create and Update
3026            --
3027            IF l_op_network_rec.transaction_type IN
3028                 (BOM_Rtg_Globals.G_OPR_UPDATE, BOM_Rtg_Globals.G_OPR_CREATE)
3029            THEN
3030                Bom_Validate_Op_Network.Check_Attributes
3031                 (   x_return_status            => l_return_status
3032                 ,   x_Mesg_Token_Tbl           => l_Mesg_Token_Tbl
3033                 ,   p_op_network_rec           => l_op_network_rec
3034                 ,   p_op_network_unexp_rec     => l_op_network_unexp_rec
3035                 ,   p_old_op_network_rec       => l_Old_op_network_rec
3036                 ,   p_old_op_network_unexp_rec => l_Old_op_network_unexp_rec
3037                 );
3038 
3039 IF BOM_Rtg_Globals.Get_Debug = 'Y'  THEN
3040     Error_Handler.Write_Debug
3041     ('Op Network: Check Attributes is completed with status '|| l_return_status );
3042 END IF;
3043 
3044                 IF l_return_status = Error_Handler.G_STATUS_ERROR
3045                 THEN
3046                         RAISE EXC_SEV_QUIT_RECORD;
3047 
3048                         /* No linger used
3049                         IF l_op_network_rec.transaction_type = 'CREATE'
3050                         THEN
3051                            l_other_message :='BOM_OP_NWK_ATTVAL_CSEV_ERROR';
3052                            l_other_token_tbl(1).token_name := 'FROM_OP_SEQ_NUMBER';
3053                            l_other_token_tbl(1).token_value :=
3054                                     l_op_network_rec.from_op_seq_number;
3055                            l_other_token_tbl(2).token_name := 'TO_OP_SEQ_NUMBER';
3056                            l_other_token_tbl(2).token_value :=
3057                                     l_op_network_rec.to_op_seq_number;
3058                            RAISE EXC_SEV_SKIP_BRANCH;
3059                         ELSE
3060                            RAISE EXC_SEV_QUIT_RECORD;
3061                         END IF;
3062                         */
3063                 ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
3064                 THEN
3065                         l_other_message := 'BOM_OP_NWK_ATTVAL_UNEXP_SKIP';
3066                         l_other_token_tbl(1).token_name := 'FROM_OP_SEQ_NUMBER';
3067                         l_other_token_tbl(1).token_value :=
3068                                     l_op_network_rec.from_op_seq_number;
3069                         l_other_token_tbl(2).token_name := 'TO_OP_SEQ_NUMBER';
3070                         l_other_token_tbl(2).token_value :=
3071                                     l_op_network_rec.to_op_seq_number;
3072 
3073                         RAISE EXC_UNEXP_SKIP_OBJECT;
3074                 END IF;
3075            END IF;
3076 
3077 
3078            IF l_op_network_rec.Transaction_Type IN
3079                 (BOM_Rtg_Globals.G_OPR_UPDATE, BOM_Rtg_Globals.G_OPR_DELETE)
3080            THEN
3081 
3082                 -- Process flow  - Populate NULL columns for Update and
3083                 -- Delete.
3084 
3085                 Bom_Default_Op_Network.Populate_NULL_Columns
3086                 (   p_op_network_rec            => l_op_network_rec
3087                 ,   p_op_network_unexp_rec      => l_op_network_unexp_rec
3088                 ,   p_old_op_network_rec        => l_old_op_network_rec
3089                 ,   p_old_op_network_unexp_rec  => l_old_op_network_unexp_rec
3090                 ,   x_op_network_rec            => l_op_network_rec
3091                 ,   x_op_network_unexp_rec      => l_op_network_unexp_rec
3092                 );
3093 
3094 IF BOM_Rtg_Globals.Get_Debug = 'Y'  THEN
3095     Error_Handler.Write_Debug
3096     ('Op Network: Populate Null columns is completed with status '|| l_return_status );
3097 END IF;
3098 
3099 
3100            ELSIF l_op_network_rec.Transaction_Type = BOM_Rtg_Globals.G_OPR_CREATE
3101            THEN
3102                 --
3103                 --  Default missing values for Operation network record creation
3104                 --
3105                 Bom_Default_Op_Network.Attribute_Defaulting
3106                 (   p_op_network_rec       => l_op_network_rec
3107                 ,   p_op_network_unexp_rec => l_op_network_unexp_rec
3108                 ,   x_op_network_rec       => l_op_network_rec
3109                 ,   x_op_network_unexp_rec => l_op_network_unexp_rec
3110                 ,   x_mesg_token_tbl       => l_mesg_token_tbl
3111                 ,   x_return_status        => l_return_status
3112                 );
3113 
3114 IF BOM_Rtg_Globals.Get_Debug = 'Y'  THEN
3115     Error_Handler.Write_Debug
3116     ('Op Network: Attribute Defaulting is completed with status '|| l_return_status );
3117 END IF;
3118 
3119 
3120 
3121                IF l_return_status = Error_Handler.G_STATUS_ERROR
3122                THEN
3123                    RAISE EXC_SEV_QUIT_RECORD;
3124 
3125                    /* No longer used
3126                    IF l_op_network_rec.transaction_type = 'CREATE'
3127                    THEN
3128                        l_other_message := 'BOM_OP_NWK_ATTDEF_CSEV_SKIP';
3129                        l_other_token_tbl(1).token_name := 'FROM_OP_SEQ_NUMBER';
3130                        l_other_token_tbl(1).token_value :=
3131                                     l_op_network_rec.from_op_seq_number;
3132                        l_other_token_tbl(2).token_name := 'TO_OP_SEQ_NUMBER';
3133                        l_other_token_tbl(2).token_value :=
3134                                     l_op_network_rec.to_op_seq_number;
3135                        RAISE EXC_SEV_SKIP_BRANCH;
3136                    ELSE
3137                        RAISE EXC_SEV_QUIT_RECORD;
3138                    END IF;
3139                    */
3140 
3141                ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
3142                THEN
3143                     l_other_message := 'BOM_OP_NWK_ATTDEF_UNEXP_SKIP';
3144                     l_other_token_tbl(1).token_name  := 'FROM_OP_SEQ_NUMBER';
3145                     l_other_token_tbl(1).token_value :=
3146                                     l_op_network_rec.from_op_seq_number;
3147                     l_other_token_tbl(2).token_name  := 'TO_OP_SEQ_NUMBER';
3148                     l_other_token_tbl(2).token_value :=
3149                                     l_op_network_rec.to_op_seq_number;
3150                     RAISE EXC_UNEXP_SKIP_OBJECT;
3151                END IF;
3152 
3153            END IF;
3154 
3155 
3156            --
3157            --  Default missing values for Operation network record creation
3158            --
3159            Bom_Default_Op_Network.Entity_Attribute_Defaulting
3160            (   p_op_network_rec       => l_op_network_rec
3161            ,   p_op_network_unexp_rec => l_op_network_unexp_rec
3162            ,   x_op_network_rec       => l_op_network_rec
3163            ,   x_op_network_unexp_rec => l_op_network_unexp_rec
3164            ,   x_mesg_token_tbl       => l_mesg_token_tbl
3165            ,   x_return_status        => l_return_status
3166            );
3167 
3168            IF l_return_status = Error_Handler.G_STATUS_ERROR
3169            THEN
3170                    RAISE EXC_SEV_QUIT_RECORD;
3171 
3172            ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
3173            THEN
3174                     l_other_message := 'BOM_OP_NWK_ATTDEF_UNEXP_SKIP';
3175                     l_other_token_tbl(1).token_name  := 'FROM_OP_SEQ_NUMBER';
3176                     l_other_token_tbl(1).token_value :=
3177                                     l_op_network_rec.from_op_seq_number;
3178                     l_other_token_tbl(2).token_name  := 'TO_OP_SEQ_NUMBER';
3179                     l_other_token_tbl(2).token_value :=
3180                                     l_op_network_rec.to_op_seq_number;
3181                     RAISE EXC_UNEXP_SKIP_OBJECT;
3182 
3183 
3184            -- Added for eAM enhancement. Entity_Attribute_Defaulting
3185            -- may return a warning message.
3186            ELSIF l_return_status ='S' AND l_mesg_token_tbl .COUNT <> 0
3187            THEN
3188               Bom_Rtg_Error_Handler.Log_Error
3189               (  p_rtg_header_rec      => l_rtg_header_rec
3190               ,  p_op_network_tbl      => l_op_network_tbl
3191               ,  p_rtg_revision_tbl    => Bom_Rtg_Pub.G_MISS_RTG_REVISION_TBL
3192               ,  p_operation_tbl       => Bom_Rtg_Pub.G_MISS_OPERATION_TBL
3193               ,  p_op_resource_tbl     => Bom_Rtg_Pub.G_MISS_OP_RESOURCE_TBL
3194               ,  p_sub_resource_tbl    => Bom_Rtg_Pub.G_MISS_SUB_RESOURCE_TBL
3195               ,  p_mesg_token_tbl      => l_mesg_token_tbl
3196               ,  p_error_status        => 'W'
3197               ,  p_error_level         => Error_Handler.G_NWK_LEVEL
3198               ,  p_entity_index        => I
3199               ,  p_error_scope         => NULL
3200               ,  p_other_message       => NULL
3201               ,  p_other_mesg_appid    => 'BOM'
3202               ,  p_other_status        => NULL
3203               ,  p_other_token_tbl     => Error_Handler.G_MISS_TOKEN_TBL
3204               ,  x_rtg_header_rec      => l_rtg_header_rec
3205               ,  x_rtg_revision_tbl    => l_rtg_revision_tbl
3206               ,  x_op_network_tbl      => l_op_network_tbl
3207               ,  x_operation_tbl       => l_operation_tbl
3208               ,  x_op_resource_tbl     => l_op_resource_tbl
3209               ,  x_sub_resource_tbl    => l_sub_resource_tbl
3210               ) ;
3211            END IF;
3212 
3213 
3214 
3215            --
3216            -- Process Flow step 13: Entity level Validation for Create and Update
3217            --
3218            Bom_Validate_Op_Network.Check_Entity1
3219            (  x_return_status           => l_return_status
3220            ,  x_Mesg_Token_Tbl          => l_Mesg_Token_Tbl
3221            ,  p_op_network_rec          => l_op_network_rec
3222            ,  p_op_network_unexp_rec    => l_op_network_unexp_rec
3223            ,  p_old_op_network_rec      => l_old_op_network_rec
3224            ,  p_old_op_network_unexp_rec=> l_old_op_network_unexp_rec
3225            );
3226 
3227 IF BOM_Rtg_Globals.Get_Debug = 'Y'  THEN
3228     Error_Handler.Write_Debug
3229     ('Op Network: Check Entity1 is completed with status '|| l_return_status );
3230 END IF;
3231 
3232 
3233            IF l_return_status = Error_Handler.G_STATUS_ERROR
3234            THEN
3235                 /* No longer used
3236                 l_other_message := 'BOM_OP_NWK_ENTVAL_CSEV_ERROR';
3237                 l_other_token_tbl(1).token_name  := 'FROM_OP_SEQ_NUMBER';
3238                 l_other_token_tbl(1).token_value :=
3239                                     l_op_network_rec.from_op_seq_number;
3240                 l_other_token_tbl(2).token_name  := 'TO_OP_SEQ_NUMBER';
3241                 l_other_token_tbl(2).token_value :=
3242                                     l_op_network_rec.to_op_seq_number;
3243                 */
3244 
3245                 RAISE EXC_SEV_QUIT_RECORD;
3246            ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
3247            THEN
3248                 l_other_message := 'BOM_OP_NWK_ENTVAL_UNEXP_ERROR';
3249                 l_other_token_tbl(1).token_name  := 'FROM_OP_SEQ_NUMBER';
3250                 l_other_token_tbl(1).token_value :=
3251                                     l_op_network_rec.from_op_seq_number;
3252                 l_other_token_tbl(2).token_name  := 'TO_OP_SEQ_NUMBER';
3253                 l_other_token_tbl(2).token_value :=
3254                                     l_op_network_rec.to_op_seq_number;
3255                 RAISE EXC_UNEXP_SKIP_OBJECT;
3256            END IF;
3257 
3258            --
3259            -- Process Flow step 14 : Database Writes
3260            --
3261            Bom_Op_Network_Util.Perform_Writes
3262                 (   p_op_network_rec            => l_op_network_rec
3263                 ,   p_op_network_unexp_rec      => l_op_network_unexp_rec
3264                 ,   x_Mesg_Token_Tbl            => l_Mesg_Token_Tbl
3265                 ,   x_return_status             => l_return_status
3266                 );
3267 
3268 IF BOM_Rtg_Globals.Get_Debug = 'Y'  THEN
3269     Error_Handler.Write_Debug
3270     ('Op Network: Perform Writes is completed with status '|| l_return_status );
3271 END IF;
3272 
3273 
3274            IF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
3275            THEN
3276                 l_other_message := 'BOM_OP_NWK_WRITES_UNEXP_SKIP';
3277                 l_other_token_tbl(1).token_name  := 'FROM_OP_SEQ_NUMBER';
3278                 l_other_token_tbl(1).token_value :=
3279                                     l_op_network_rec.from_op_seq_number;
3280                 l_other_token_tbl(2).token_name  := 'TO_OP_SEQ_NUMBER';
3281                 l_other_token_tbl(2).token_value :=
3282                                     l_op_network_rec.to_op_seq_number;
3283                 RAISE EXC_UNEXP_SKIP_OBJECT;
3284            END IF;
3285 
3286 
3287            --
3288            -- Process Flow step 15 : Entity level2 validation
3289            --
3290            --
3291              Bom_Validate_Op_Network.Check_Entity2
3292              (  x_return_status           => l_return_status
3293              ,  x_Mesg_Token_Tbl          => l_Mesg_Token_Tbl
3294              ,  p_op_network_rec          => l_op_network_rec
3295              ,  p_op_network_unexp_rec    => l_op_network_unexp_rec
3296              ,  p_old_op_network_rec      => l_old_op_network_rec
3297              ,  p_old_op_network_unexp_rec=> l_old_op_network_unexp_rec
3298              );
3299 
3300 IF BOM_Rtg_Globals.Get_Debug = 'Y'  THEN
3301     Error_Handler.Write_Debug
3302     ('Op Network: Check Entity2 is completed with status '|| l_return_status );
3303 END IF;
3304 
3305      /* below is OSFM change */
3306      BOM_RTG_Globals.Add_Osfm_NW_Count(1);
3307      /* above is OSFM change */
3308 
3309              IF l_return_status = Error_Handler.G_STATUS_ERROR
3310              THEN
3311                 l_other_message := 'BOM_OP_NWK_ENTVAL_CSEV_ERROR';
3312                 l_other_token_tbl(1).token_name  := 'FROM_OP_SEQ_NUMBER';
3313                 l_other_token_tbl(1).token_value :=
3314                                     l_op_network_rec.from_op_seq_number;
3315                 l_other_token_tbl(2).token_name  := 'TO_OP_SEQ_NUMBER';
3316                 l_other_token_tbl(2).token_value :=
3317                                     l_op_network_rec.to_op_seq_number;
3318 
3319                 RAISE EXC_SEV_QUIT_OBJECT ;
3320              ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
3321              THEN
3322                 l_other_message := 'BOM_OP_NWK_ENTVAL_UNEXP_ERROR';
3323                 l_other_token_tbl(1).token_name  := 'FROM_OP_SEQ_NUMBER';
3324                 l_other_token_tbl(1).token_value :=
3325                                     l_op_network_rec.from_op_seq_number;
3326                 l_other_token_tbl(2).token_name  := 'TO_OP_SEQ_NUMBER';
3327                 l_other_token_tbl(2).token_value :=
3328                                     l_op_network_rec.to_op_seq_number;
3329                 RAISE EXC_UNEXP_SKIP_OBJECT;
3330              ELSIF l_return_status ='S' AND l_mesg_token_tbl .COUNT <> 0
3331              THEN
3332               Bom_Rtg_Error_Handler.Log_Error
3333               (  p_rtg_header_rec      => l_rtg_header_rec
3334               ,  p_op_network_tbl      => l_op_network_tbl
3335               ,  p_rtg_revision_tbl    => Bom_Rtg_Pub.G_MISS_RTG_REVISION_TBL
3336               ,  p_operation_tbl       => Bom_Rtg_Pub.G_MISS_OPERATION_TBL
3337               ,  p_op_resource_tbl     => Bom_Rtg_Pub.G_MISS_OP_RESOURCE_TBL
3338               ,  p_sub_resource_tbl    => Bom_Rtg_Pub.G_MISS_SUB_RESOURCE_TBL
3339               ,  p_mesg_token_tbl      => l_mesg_token_tbl
3340               ,  p_error_status        => 'W'
3341               ,  p_error_level         => Error_Handler.G_NWK_LEVEL
3342               ,  p_entity_index        => I
3343               ,  p_error_scope         => NULL
3344               ,  p_other_message       => NULL
3345               ,  p_other_mesg_appid    => 'BOM'
3346               ,  p_other_status        => NULL
3347               ,  p_other_token_tbl     => Error_Handler.G_MISS_TOKEN_TBL
3348               ,  x_rtg_header_rec      => l_rtg_header_rec
3349               ,  x_rtg_revision_tbl    => l_rtg_revision_tbl
3350               ,  x_op_network_tbl      => l_op_network_tbl
3351               ,  x_operation_tbl       => l_operation_tbl
3352               ,  x_op_resource_tbl     => l_op_resource_tbl
3353               ,  x_sub_resource_tbl    => l_sub_resource_tbl
3354               ) ;
3355             END IF;
3356 
3357         END IF;
3358 
3359         --  Load tables.
3360         l_op_network_tbl(I)          := l_op_network_rec;
3361 
3362 	-- Initialize variables for calc_cynp
3363 	IF l_op_network_rec.Operation_Type = Bom_Rtg_Globals.G_LINE_OP THEN
3364 		l_line_op := TRUE;
3365 	ELSIF l_op_network_rec.Operation_Type = Bom_Rtg_Globals.G_PROCESS_OP THEN
3366 		l_process_op := TRUE;
3367 	END IF;
3368 
3369         --  For loop exception handler.
3370 
3371      EXCEPTION
3372 
3373         WHEN EXC_SEV_QUIT_RECORD THEN
3374              Bom_Rtg_Error_Handler.Log_Error
3375              (  p_rtg_header_rec       => l_rtg_header_rec
3376              ,  p_op_network_tbl       => l_op_network_tbl
3377              ,  p_rtg_revision_tbl     => Bom_Rtg_Pub.G_MISS_RTG_REVISION_TBL
3378              ,  p_operation_tbl        => Bom_Rtg_Pub.G_MISS_OPERATION_TBL
3379              ,  p_op_resource_tbl      => Bom_Rtg_Pub.G_MISS_OP_RESOURCE_TBL
3380              ,  p_sub_resource_tbl     => Bom_Rtg_Pub.G_MISS_SUB_RESOURCE_TBL
3381              ,  p_mesg_token_tbl       => l_mesg_token_tbl
3382              ,  p_error_status         => Error_Handler.G_STATUS_ERROR
3383              ,  p_error_scope          => Error_Handler.G_SCOPE_RECORD
3384              ,  p_error_level          => Error_Handler.G_NWK_LEVEL
3385              ,  p_entity_index         => I
3386              ,  p_other_message        => NULL
3387              ,  p_other_mesg_appid     => 'BOM'
3388              ,  p_other_status         => NULL
3389              ,  p_other_token_tbl      => Error_Handler.G_MISS_TOKEN_TBL
3390              ,  x_rtg_header_rec       => l_rtg_header_rec
3391              ,  x_rtg_revision_tbl     => l_rtg_revision_tbl
3392              ,  x_operation_tbl        => l_operation_tbl
3393              ,  x_op_resource_tbl      => l_op_resource_tbl
3394              ,  x_sub_resource_tbl     => l_sub_resource_tbl
3395              ,  x_op_network_tbl       => l_op_network_tbl
3396              );
3397 
3398         IF l_bo_return_status = 'S'
3399         THEN
3400                 l_bo_return_status     := l_return_status;
3401         END IF;
3402 
3403         x_return_status                := l_bo_return_status;
3404         x_Mesg_Token_Tbl               := l_Mesg_Token_Tbl;
3405    --   x_rtg_header_rec               := l_rtg_header_rec;
3406    --   x_rtg_revision_tbl             := l_rtg_revision_tbl;
3407    --   x_operation_tbl                := l_operation_tbl;
3408    --   x_op_resource_tbl              := l_op_resource_tbl;
3409    --   x_sub_resource_tbl             := l_sub_resource_tbl;
3410         x_op_network_tbl               := l_op_network_tbl;
3411 
3412 
3413         WHEN EXC_SEV_QUIT_OBJECT THEN
3414             Bom_Rtg_Error_Handler.Log_Error
3415             ( p_rtg_header_rec        => l_rtg_header_rec
3416             , p_op_network_tbl        => l_op_network_tbl
3417             , p_rtg_revision_tbl      => Bom_Rtg_Pub.G_MISS_RTG_REVISION_TBL
3418             , p_operation_tbl         => Bom_Rtg_Pub.G_MISS_OPERATION_TBL
3419             , p_op_resource_tbl       => Bom_Rtg_Pub.G_MISS_OP_RESOURCE_TBL
3420             , p_sub_resource_tbl      => Bom_Rtg_Pub.G_MISS_SUB_RESOURCE_TBL
3421             , p_mesg_token_tbl        => l_mesg_token_tbl
3422             , p_error_status          => Error_Handler.G_STATUS_ERROR
3423             , p_error_scope           => Error_Handler.G_SCOPE_ALL
3424             , p_error_level           => Error_Handler.G_NWK_LEVEL
3425             , p_other_message         => l_other_message
3426             , p_other_status          => Error_Handler.G_STATUS_ERROR
3427             , p_other_token_tbl       => l_other_token_tbl
3428             , p_other_mesg_appid      => 'BOM'
3429             , p_entity_index          => I
3430             , x_rtg_header_rec        => l_rtg_header_rec
3431             , x_rtg_revision_tbl      => l_rtg_revision_tbl
3432             , x_operation_tbl         => l_operation_tbl
3433             , x_op_resource_tbl       => l_op_resource_tbl
3434             , x_sub_resource_tbl      => l_sub_resource_tbl
3435             , x_op_network_tbl        => l_op_network_tbl
3436             );
3437 
3438         IF l_bo_return_status = 'S'
3439         THEN
3440                 l_bo_return_status     := l_return_status;
3441         END IF;
3442 
3443         x_return_status                := l_return_status;
3444         x_Mesg_Token_Tbl               := l_Mesg_Token_Tbl;
3445    --   x_rtg_header_rec               := l_rtg_header_rec;
3446    --   x_rtg_revision_tbl             := l_rtg_revision_tbl;
3447    --   x_operation_tbl                := l_operation_tbl;
3448    --   x_op_resource_tbl              := l_op_resource_tbl;
3449    --   x_sub_resource_tbl             := l_sub_resource_tbl;
3450         x_op_network_tbl               := l_op_network_tbl;
3451 
3452         WHEN EXC_FAT_QUIT_OBJECT THEN
3453 
3454           Bom_Rtg_Error_Handler.Log_Error
3455             (  p_op_network_tbl       => l_op_network_tbl
3456             ,  p_rtg_header_rec       => Bom_Rtg_Pub.G_MISS_RTG_HEADER_REC
3457             ,  p_rtg_revision_tbl     => Bom_Rtg_Pub.G_MISS_RTG_REVISION_TBL
3458             ,  p_operation_tbl        => Bom_Rtg_Pub.G_MISS_OPERATION_TBL
3459             ,  p_op_resource_tbl      => Bom_Rtg_Pub.G_MISS_OP_RESOURCE_TBL
3460             ,  p_sub_resource_tbl     => Bom_Rtg_Pub.G_MISS_SUB_RESOURCE_TBL
3461             ,  p_mesg_token_tbl       => l_mesg_token_tbl
3462             ,  p_error_status         => Error_Handler.G_STATUS_FATAL
3463             ,  p_error_scope          => Error_Handler.G_SCOPE_ALL
3464             ,  p_error_level          => Error_Handler.G_NWK_LEVEL
3465             ,  p_other_message        => l_other_message
3466             ,  p_other_status         => Error_Handler.G_STATUS_FATAL
3467             ,  p_other_token_tbl      => l_other_token_tbl
3468             ,  p_other_mesg_appid     => 'BOM'
3469             ,  p_entity_index         => 1
3470             ,  x_rtg_header_rec       => l_rtg_header_rec
3471             ,  x_rtg_revision_tbl     => l_rtg_revision_tbl
3472             ,  x_operation_tbl        => l_operation_tbl
3473             ,  x_op_resource_tbl      => l_op_resource_tbl
3474             ,  x_sub_resource_tbl     => l_sub_resource_tbl
3475             ,  x_op_network_tbl       => l_op_network_tbl
3476             );
3477         x_return_status                := l_return_status;
3478         x_Mesg_Token_Tbl               := l_Mesg_Token_Tbl;
3479    --   x_rtg_header_rec               := l_rtg_header_rec;
3480    --   x_rtg_revision_tbl             := l_rtg_revision_tbl;
3481    --   x_operation_tbl                := l_operation_tbl;
3482    --   x_op_resource_tbl              := l_op_resource_tbl;
3483    --   x_sub_resource_tbl             := l_sub_resource_tbl;
3484         x_op_network_tbl               := l_op_network_tbl;
3485 
3486         l_return_status := 'Q';
3487 
3488        WHEN EXC_UNEXP_SKIP_OBJECT THEN
3489 
3490             Bom_Rtg_Error_Handler.Log_Error
3491             ( p_op_network_tbl       => l_op_network_tbl
3492             , p_rtg_header_rec       =>Bom_Rtg_Pub.G_MISS_RTG_HEADER_REC
3493             , p_rtg_revision_tbl     =>Bom_Rtg_Pub.G_MISS_RTG_REVISION_TBL
3494             , p_operation_tbl        =>Bom_Rtg_Pub.G_MISS_OPERATION_TBL
3495             , p_op_resource_tbl      =>Bom_Rtg_Pub.G_MISS_OP_RESOURCE_TBL
3496             , p_sub_resource_tbl     =>Bom_Rtg_Pub.G_MISS_SUB_RESOURCE_TBL
3497             , p_mesg_token_tbl       => l_mesg_token_tbl
3498             , p_error_status         => Error_Handler.G_STATUS_UNEXPECTED
3499             , p_error_scope          => Error_Handler.G_SCOPE_ALL
3500             , p_error_level          => Error_Handler.G_NWK_LEVEL
3501             , p_other_message        => l_other_message
3502             , p_other_status         => Error_Handler.G_STATUS_NOT_PICKED
3503             , p_other_token_tbl      => l_other_token_tbl
3504             , p_other_mesg_appid     => 'BOM'
3505             , p_entity_index         => I
3506             , x_rtg_header_rec       => l_rtg_header_rec
3507             , x_rtg_revision_tbl     => l_rtg_revision_tbl
3508             , x_operation_tbl        => l_operation_tbl
3509             , x_op_resource_tbl      => l_op_resource_tbl
3510             , x_sub_resource_tbl     => l_sub_resource_tbl
3511             , x_op_network_tbl       => l_op_network_tbl
3512             );
3513 
3514         IF l_bo_return_status = 'S'
3515         THEN
3516                 l_bo_return_status     := l_return_status;
3517         END IF;
3518 
3519         x_return_status                := l_bo_return_status;
3520         x_Mesg_Token_Tbl               := l_Mesg_Token_Tbl;
3521    --   x_rtg_header_rec               := l_rtg_header_rec;
3522    --   x_rtg_revision_tbl             := l_rtg_revision_tbl;
3523    --   x_operation_tbl                := l_operation_tbl;
3524    --   x_op_resource_tbl              := l_op_resource_tbl;
3525    --   x_sub_resource_tbl             := l_sub_resource_tbl;
3526         x_op_network_tbl               := l_op_network_tbl;
3527         l_return_status := 'U';
3528 
3529         END; -- END block
3530 
3531     END LOOP; -- END Revisions processing loop
3532     IF l_return_status in ('Q', 'U')
3533     THEN
3534         x_return_status := l_return_status;
3535         --RETURN;
3536     END IF;
3537     /** Following for Rouitng Network Level validations that cannot be
3538         done only after the whole network is defined ,
3539         So cannot fit into link level validation code */
3540   -- Commented to make use of bom_calc_cynp.calc_cynp (bug 2689249)
3541 /*
3542     FOR I IN 1..l_op_network_tbl.COUNT LOOP
3543     BEGIN
3544 
3545       IF    l_op_network_rec.connection_type <> 3  -- Not Rework
3546       AND   BOM_Rtg_Globals.Get_Eam_Item_Type <>
3547             BOM_Rtg_Globals.G_ASSET_ACTIVITY THEN
3548       bom_rtg_network_validate_api.validate_routing_network
3549       ( p_rtg_sequence_id => l_op_network_unexp_rec.routing_sequence_id
3550       , p_assy_item_id    => l_op_network_unexp_rec.assembly_item_id
3551       , p_org_id          => l_op_network_unexp_rec.organization_id
3552       , p_alt_rtg_desig   => l_op_network_rec.alternate_routing_code
3553       , p_operation_type  => l_op_network_rec.operation_type
3554       , x_status          => l_return_status
3555       , x_message         => l_other_message
3556       ) ;
3557      IF BOM_Rtg_Globals.Get_Debug = 'Y'
3558      THEN Error_Handler.Write_Debug
3559       ('After calling Rtg Network Validate API. Retrun status is '|| l_return_status);
3560      END IF;
3561 --dbms_output.put_line('returned from nwk validate');
3562      IF  l_return_status = 'F' AND l_other_message IS NOT NULL THEN
3563 
3564         IF  UPPER( RTRIM(l_other_message) ) =
3565           UPPER('A loop has been detected in this Routing Network.')
3566         THEN
3567           Error_Handler.Add_Error_Token
3568           (  p_message_name       => 'BOM_OP_NWK_LOOP_EXIT'
3569           , p_token_tbl          => l_token_tbl
3570           , p_mesg_token_tbl     => l_mesg_token_tbl
3571           , x_mesg_token_tbl     => l_mesg_token_tbl
3572           );
3573           x_return_status := FND_API.G_RET_STS_ERROR;
3574         ELSIF  UPPER( RTRIM(l_other_message) ) =
3575           UPPER('A broken link exists in this routing Network.')
3576         THEN
3577 
3578           Error_Handler.Add_Error_Token
3579           (  p_message_name       => 'BOM_RTG_NTWK_BROKEN_LINK_EXIST'
3580            , p_token_tbl          => l_token_tbl
3581            , p_mesg_token_tbl     => l_mesg_token_tbl
3582            , x_mesg_token_tbl     => l_mesg_token_tbl
3583           );
3584 
3585           x_return_status := FND_API.G_RET_STS_ERROR;
3586         ELSE
3587 
3588           Error_Handler.Add_Error_Token
3589           (  p_message_name       => 'BOM_OP_NWK_VLDN_ERROR'
3590            , p_token_tbl          => l_token_tbl
3591            , p_mesg_token_tbl     => l_mesg_token_tbl
3592            , x_mesg_token_tbl     => l_mesg_token_tbl
3593           );
3594 
3595           x_return_status := FND_API.G_RET_STS_ERROR;
3596         END IF;
3597 --dbms_output.put_line('before raising excptn');
3598 	RAISE EXC_SEV_QUIT_OBJECT ;
3599       END IF;
3600     END IF;
3601 
3602     END;
3603     END LOOP; -- END
3604 */
3605 
3606     l_temp_rtg_id := BOM_RTG_Globals.Get_Routing_Sequence_Id();
3607     IF l_process_op THEN
3608          bom_calc_cynp.calc_cynp_rbo(p_routing_sequence_id => l_temp_rtg_id,
3609 			             p_operation_type      => BOM_Rtg_Globals.G_PROCESS_OP,
3610 				     p_update_events       => 0,
3611 				     x_token_tbl => l_token_tbl,
3612 				     x_err_msg => l_other_message,
3613 				     x_return_status => l_dummy);
3614 
3615 	IF l_dummy = 'E' THEN
3616 	 IF FND_MSG_PUB.Check_Msg_Level(FND_MSG_PUB.G_MSG_LVL_ERROR)
3617          THEN
3618           Error_Handler.Add_Error_Token
3619           (  p_message_name       => l_other_message
3620            , p_token_tbl          => l_token_tbl
3621            , p_mesg_token_tbl     => l_mesg_token_tbl
3622            , x_mesg_token_tbl     => l_mesg_token_tbl
3623           );
3624           l_return_status := FND_API.G_RET_STS_ERROR;
3625 	  RAISE EXC_SEV_QUIT_OBJECT ;
3626 	 END IF;
3627 	END IF;
3628     END IF;
3629     IF l_line_op THEN
3630 	 bom_calc_cynp.calc_cynp_rbo(p_routing_sequence_id => l_temp_rtg_id,
3631 			             p_operation_type      => BOM_Rtg_Globals.G_LINE_OP,
3632 				     p_update_events       => 0,
3633 				     x_token_tbl => l_token_tbl,
3634 				     x_err_msg => l_other_message,
3635 				     x_return_status => l_dummy);
3636 
3637 	IF l_dummy = 'E' THEN
3638 	 IF FND_MSG_PUB.Check_Msg_Level(FND_MSG_PUB.G_MSG_LVL_ERROR)
3639          THEN
3640           Error_Handler.Add_Error_Token
3641           (  p_message_name       => l_other_message
3642            , p_token_tbl          => l_token_tbl
3643            , p_mesg_token_tbl     => l_mesg_token_tbl
3644            , x_mesg_token_tbl     => l_mesg_token_tbl
3645           );
3646           l_return_status := FND_API.G_RET_STS_ERROR;
3647 	  RAISE EXC_SEV_QUIT_OBJECT ;
3648 	 END IF;
3649 	END IF;
3650 
3651     END IF;
3652 
3653   /* end of the whole network validation */
3654 
3655   /*below change for RBO support for OSFM*/
3656    IF ( l_op_network_tbl.COUNT = BOM_RTG_Globals.Get_Osfm_NW_Count() )
3657    AND( l_op_network_tbl.COUNT <> 0  )
3658    AND ( l_temp_rtg_id IS NOT NULL AND l_temp_rtg_id <>0 )THEN
3659      IF BOM_Rtg_Globals.Get_Debug = 'Y'
3660      THEN Error_Handler.Write_Debug
3661       ('Op Network: Calling BOM_Validate_Op_Network.Check_WSM_Netowrk_Attribs....');
3662      END IF;
3663 
3664      BOM_Validate_Op_Network.Check_WSM_Netowrk_Attribs  (
3665       p_routing_sequence_id =>l_temp_rtg_id
3666     , p_prev_start_id      => l_prev_start_id
3667     , p_prev_end_id        => l_prev_end_id
3668     , x_mesg_token_tbl     => l_mesg_token_tbl
3669     , x_Return_status      => l_return_status
3670      );
3671 
3672      IF BOM_Rtg_Globals.Get_Debug = 'Y'
3673      THEN Error_Handler.Write_Debug
3674       ('Op Network: Check_WSM_Netowrk_Attribs comleted with Status '||
3675       l_return_status);
3676      END IF;
3677 
3678 
3679      IF l_return_status = Error_Handler.G_STATUS_ERROR
3680      THEN
3681        RAISE EXC_SEV_QUIT_OBJECT ;
3682      END IF;
3683      IF BOM_Rtg_Globals.Get_Debug = 'Y'
3684      THEN Error_Handler.Write_Debug
3685       ('Op Network: Calling BOM_Op_Network_UTIL.Set_WSM_Network_Sub_Loc...');
3686      END IF;
3687 
3688      BOM_Op_Network_UTIL.Set_WSM_Network_Sub_Loc(
3689       p_routing_sequence_id =>l_temp_rtg_id
3690     , p_end_id             => l_prev_end_id
3691     , x_mesg_token_tbl     => l_mesg_token_tbl
3692     , x_Return_status      => l_return_status
3693      );
3694 
3695      IF BOM_Rtg_Globals.Get_Debug = 'Y'
3696      THEN Error_Handler.Write_Debug
3697       ('Op Network: Set_WSM_Network_Sub_Loc comleted with Status '||
3698       l_return_status);
3699      END IF;
3700 
3701      IF l_return_status = Error_Handler.G_STATUS_ERROR
3702      THEN
3703        RAISE EXC_SEV_QUIT_OBJECT ;
3704      END IF;
3705    END IF;
3706   /*above change for RBO support for OSFM*/
3707 
3708     -- bug:5235684 SSOS is required for standard/network routing for serial controlled item
3709     -- and it should be present on primary path.
3710     IF (    ( l_return_status = FND_API.G_RET_STS_SUCCESS )
3711         AND ( BOM_RTG_Globals.Get_Routing_Sequence_Id() IS NOT NULL )  )
3712     THEN
3713       Bom_Validate_Rtg_Header.Validate_SSOS
3714           (  p_routing_sequence_id  => BOM_RTG_Globals.Get_Routing_Sequence_Id()
3715            , p_ser_start_op_seq     => NULL
3716            , p_validate_from_table  => TRUE
3717            , x_mesg_token_tbl       => l_Mesg_Token_Tbl
3718            , x_return_status        => l_return_status );
3719 
3720       IF ( l_return_status <> FND_API.G_RET_STS_SUCCESS ) THEN
3721         RAISE EXC_SEV_QUIT_OBJECT;
3722       END IF;
3723     END IF; -- end if ( l_return_status = FND_API.G_RET_STS_SUCCESS )
3724 
3725     --bug:5060186 Copy the first or last operation of the network if disabled.
3726     IF ( BOM_RTG_Globals.Get_Routing_Sequence_Id() IS NOT NULL ) THEN
3727       Bom_Op_Network_Util.Copy_First_Last_Dis_Op(
3728                                                   p_routing_sequence_id => BOM_RTG_Globals.Get_Routing_Sequence_Id()
3729                                                 , x_mesg_token_tbl     => l_mesg_token_tbl
3730                                                 , x_return_status      => l_return_status );
3731 
3732       IF BOM_Rtg_Globals.Get_Debug = 'Y'  THEN
3733           Error_Handler.Write_Debug
3734             ( 'Op Network: Copy First/Last Disabled Operation completed with status ' ||
3735               l_return_status );
3736       END IF;
3737     END IF;
3738 
3739      --  Load OUT parameters
3740 
3741     IF l_return_status in ('Q', 'U')
3742     THEN
3743         x_return_status := l_return_status;
3744         RETURN;
3745     END IF;
3746 
3747      x_return_status            := l_bo_return_status;
3748      x_op_network_tbl           := l_op_network_tbl;
3749      x_Mesg_Token_Tbl           := l_Mesg_Token_Tbl;
3750 
3751   EXCEPTION
3752         WHEN EXC_SEV_QUIT_OBJECT THEN
3753             Bom_Rtg_Error_Handler.Log_Error
3754             ( p_rtg_header_rec         => l_rtg_header_rec
3755             , p_op_network_tbl         => l_op_network_tbl
3756             , p_rtg_revision_tbl       => Bom_Rtg_Pub.G_MISS_RTG_REVISION_TBL
3757             , p_operation_tbl          => Bom_Rtg_Pub.G_MISS_OPERATION_TBL
3758             , p_op_resource_tbl        => Bom_Rtg_Pub.G_MISS_OP_RESOURCE_TBL
3759             , p_sub_resource_tbl       => Bom_Rtg_Pub.G_MISS_SUB_RESOURCE_TBL
3760             , p_mesg_token_tbl         => l_mesg_token_tbl
3761             , p_error_status           => Error_Handler.G_STATUS_ERROR
3762             , p_error_scope            => Error_Handler.G_SCOPE_ALL
3763             , p_error_level            => Error_Handler.G_NWK_LEVEL
3764             , p_other_message          => l_other_message
3765             , p_other_status           => Error_Handler.G_STATUS_ERROR
3766             , p_other_token_tbl        => l_other_token_tbl
3767             , p_other_mesg_appid       => 'BOM'
3768             , p_entity_index           => 1
3769             , x_rtg_header_rec         => l_rtg_header_rec
3770             , x_rtg_revision_tbl       => l_rtg_revision_tbl
3771             , x_operation_tbl          => l_operation_tbl
3772             , x_op_resource_tbl        => l_op_resource_tbl
3773             , x_sub_resource_tbl       => l_sub_resource_tbl
3774             , x_op_network_tbl         => l_op_network_tbl
3775             );
3776         IF l_bo_return_status = 'S'
3777         THEN
3778                 l_bo_return_status     := l_return_status;
3779         END IF;
3780 
3781 	x_op_network_tbl:= l_op_network_tbl;
3782 	x_return_status	:= l_return_status;
3783 	x_Mesg_Token_Tbl:= l_Mesg_Token_Tbl;
3784 
3785 END Op_Networks;
3786 
3787 --  Operation_Sequences
3788 
3789 /****************************************************************************
3790 * Procedure : Operation_Sequences
3791 * Parameters IN   : Operation Sequences Table and all the other sibiling and
3792 *                   child entities
3793 * Parameters OUT  : Operatin Sequences and all the other sibiling and
3794 *                   child entities entities
3795 * Purpose   : This procedure will process all the Operation Seuqence records.
3796 *             It will process the entities that are children of operation
3797 *             sequences.
3798 *****************************************************************************/
3799 
3800 PROCEDURE Operation_Sequences
3801 (   p_validation_level        IN  NUMBER
3802 ,   p_organization_id         IN  NUMBER   := NULL
3803 ,   p_assembly_item_name      IN  VARCHAR2 := NULL
3804 ,   p_alternate_routing_code  IN  VARCHAR2 := NULL
3805 ,   p_operation_tbl           IN  Bom_Rtg_Pub.Operation_Tbl_Type
3806 ,   p_op_resource_tbl         IN  Bom_Rtg_Pub.Op_Resource_Tbl_Type
3807 ,   p_sub_resource_tbl        IN  Bom_Rtg_Pub.Sub_Resource_Tbl_Type
3808 ,   p_op_network_tbl          IN  Bom_Rtg_Pub.Op_Network_Tbl_Type
3809 ,   x_operation_tbl           IN OUT NOCOPY Bom_Rtg_Pub.Operation_Tbl_Type
3810 ,   x_op_resource_tbl         IN OUT NOCOPY Bom_Rtg_Pub.Op_Resource_Tbl_Type
3811 ,   x_sub_resource_tbl        IN OUT NOCOPY Bom_Rtg_Pub.Sub_Resource_Tbl_Type
3812 ,   x_op_network_tbl          IN OUT NOCOPY Bom_Rtg_Pub.Op_Network_Tbl_Type
3813 ,   x_mesg_token_tbl          IN OUT NOCOPY Error_Handler.Mesg_Token_Tbl_Type
3814 ,   x_return_status           IN OUT NOCOPY VARCHAR2
3815 )
3816 
3817 IS
3818 
3819 /* Exposed and Unexposed record */
3820 l_operation_rec         Bom_Rtg_Pub.Operation_Rec_Type ;
3821 l_operation_tbl         Bom_Rtg_Pub.Operation_Tbl_Type ;
3822 l_op_unexp_rec          Bom_Rtg_Pub.Op_Unexposed_Rec_Type ;
3823 l_old_operation_rec     Bom_Rtg_Pub.Operation_Rec_Type ;
3824 l_old_op_unexp_rec      Bom_Rtg_Pub.Op_Unexposed_Rec_Type ;
3825 
3826 /* Other Entities */
3827 l_rtg_header_rec        Bom_Rtg_Pub.Rtg_Header_Rec_Type ;
3828 l_rtg_revision_tbl      Bom_Rtg_Pub.Rtg_Revision_Tbl_Type ;
3829 l_op_resource_tbl       Bom_Rtg_Pub.Op_Resource_Tbl_Type   := p_op_resource_tbl ;
3830 l_sub_resource_tbl      Bom_Rtg_Pub.Sub_Resource_Tbl_Type  := p_sub_resource_tbl ;
3831 l_op_network_tbl        Bom_Rtg_Pub.Op_Network_Tbl_Type    := p_op_network_tbl ;
3832 
3833 /* Error Handling Variables */
3834 l_token_tbl             Error_Handler.Token_Tbl_Type ;
3835 l_mesg_token_tbl        Error_Handler.Mesg_Token_Tbl_Type;
3836 l_other_token_tbl       Error_Handler.Token_Tbl_Type ;
3837 l_other_message         VARCHAR2(2000);
3838 l_err_text              VARCHAR2(2000);
3839 
3840 
3841 /* Others */
3842 l_return_status         VARCHAR2(1) ;
3843 l_bo_return_status      VARCHAR2(1) ;
3844 l_process_children      BOOLEAN := TRUE ;
3845 l_parent_exists         BOOLEAN := FALSE ;
3846 l_valid                 BOOLEAN := TRUE ;
3847 
3848 l_op_seq_num		NUMBER;
3849 l_strt_eff_date		DATE;
3850 l_tmp_cnt		NUMBER := 1;
3851 l_dummy_cnt		NUMBER;
3852 l_temp_op_rec_tbl	BOM_RTG_Globals.Temp_Op_Rec_Tbl_Type;
3853 
3854 l_cfm_routing_flag    BOM_OPERATIONAL_ROUTINGS.CFM_ROUTING_FLAG%TYPE;
3855 l_routing_sequence_id NUMBER;
3856 
3857 BEGIN
3858 
3859    --  Init local table variables.
3860    l_return_status    := 'S' ;
3861    l_bo_return_status := 'S' ;
3862    l_operation_tbl    := p_operation_tbl ;
3863    l_op_unexp_rec.organization_id := BOM_Rtg_Globals.Get_Org_Id ;
3864    l_temp_op_rec_tbl.DELETE;
3865    l_tmp_cnt := 1;
3866    FOR I IN 1..l_operation_tbl.COUNT LOOP
3867    BEGIN
3868 
3869       --  Load local records.
3870       l_operation_rec := l_operation_tbl(I);
3871 
3872       l_operation_rec.transaction_type :=
3873          UPPER(l_operation_rec.transaction_type);
3874 
3875 
3876       --
3877       -- make sure to set process_children to false at the start of
3878       -- every iteration
3879       --
3880       l_process_children := FALSE;
3881 
3882       -- Initialize the init_eff_date_op_num flag to false for every operation (bug 2767019)
3883       BOM_RTG_Globals.G_Init_Eff_Date_Op_Num_Flag := FALSE;
3884 
3885       --
3886       -- Initialize the Unexposed Record for every iteration of the Loop
3887       -- so that sequence numbers get generated for every new row.
3888       --
3889       l_op_unexp_rec.Operation_Sequence_Id   := NULL ;
3890       l_op_unexp_rec.Standard_Operation_Id   := NULL ;
3891       l_op_unexp_rec.Department_Id           := NULL ;
3892       l_op_unexp_rec.Process_Op_Seq_Id       := NULL ;
3893       l_op_unexp_rec.Line_Op_Seq_Id          := NULL ;
3894       l_op_unexp_rec.DG_Sequence_Id          := NULL ;
3895       l_op_unexp_rec.User_Elapsed_Time       := NULL ;
3896       l_op_unexp_rec.DG_Description          := NULL ;
3897       l_op_unexp_rec.DG_New                  := NULL ;
3898       l_op_unexp_rec.Lowest_acceptable_yield := NULL ;	-- Added for MES Enhancement
3899       l_op_unexp_rec.Use_org_settings	     := NULL ;
3900       l_op_unexp_rec.Queue_mandatory_flag    := NULL ;
3901       l_op_unexp_rec.Run_mandatory_flag	     := NULL ;
3902       l_op_unexp_rec.To_move_mandatory_flag  := NULL ;
3903       l_op_unexp_rec.Show_next_op_by_default := NULL ;
3904       l_op_unexp_rec.Show_scrap_code	     := NULL ;
3905       l_op_unexp_rec.Show_lot_attrib	     := NULL ;
3906       l_op_unexp_rec.Track_multiple_res_usage_dates := NULL ;  -- End of MES Changes
3907 
3908       IF p_assembly_item_name IS NOT NULL AND
3909          p_organization_id IS NOT NULL
3910       THEN
3911          -- Revised Item or Routing parent exists
3912          l_parent_exists := TRUE ;
3913       END IF ;
3914 
3915       -- Process Flow Step 2: Check if record has not yet been processed and
3916       -- that it is the child of the parent that called this procedure
3917       --
3918 
3919       IF (l_operation_rec.return_status IS NULL OR
3920          l_operation_rec.return_status = FND_API.G_MISS_CHAR)
3921          AND
3922 
3923          -- Did Rtg Header call this procedure, that is,
3924          -- if revised item or routing header exists,
3925          -- then is this record a child ?
3926          (NOT l_parent_exists
3927           OR
3928           (l_parent_exists AND
3929             (l_operation_rec.assembly_item_name = p_assembly_item_name AND
3930              l_op_unexp_rec.organization_id = p_organization_id        AND
3931              NVL(l_operation_rec.alternate_routing_code, FND_API.G_MISS_CHAR)
3932                                   = NVL(p_alternate_routing_code, FND_API.G_MISS_CHAR)
3933              )
3934           )
3935          )
3936       THEN
3937 
3938          l_return_status := FND_API.G_RET_STS_SUCCESS;
3939          l_operation_rec.return_status := FND_API.G_RET_STS_SUCCESS;
3940 
3941          --
3942          -- Process Flow step 3 :Check if transaction_type is valid
3943          -- Transaction_Type must be CRATE, UPDATE, DELETE
3944          -- Call the BOM_Rtg_Globals.Transaction_Type_Validity
3945          --
3946 
3947          BOM_Rtg_Globals.Transaction_Type_Validity
3948          (   p_transaction_type => l_operation_rec.transaction_type
3949          ,   p_entity           => 'Op_Seq'
3950          ,   p_entity_id        => l_operation_rec.operation_sequence_number
3951          ,   x_valid            => l_valid
3952          ,   x_mesg_token_tbl   => l_mesg_token_tbl
3953          ) ;
3954 
3955          IF NOT l_valid
3956          THEN
3957              l_return_status := Error_Handler.G_STATUS_ERROR;
3958              RAISE EXC_SEV_QUIT_RECORD ;
3959          END IF ;
3960 
3961          --
3962          -- Process Flow step 4(a): Convert user unique index to unique
3963          -- index I
3964          -- Call BOM_Rtg_Val_To_Id.Operation_UUI_To_UI Shared Utility Package
3965          --
3966 
3967          BOM_Rtg_Val_To_Id.Operation_UUI_To_UI
3968          ( p_operation_rec         => l_operation_rec
3969          , p_op_unexp_rec          => l_op_unexp_rec
3970          , x_op_unexp_rec          => l_op_unexp_rec
3971          , x_mesg_token_tbl        => l_mesg_token_tbl
3972          , x_return_status         => l_return_status
3973          ) ;
3974 
3975          IF BOM_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
3976          ('Convert to User Unique Index to Index1 completed with return_status: ' || l_return_status) ;
3977          END IF;
3978 
3979          IF l_return_status = Error_Handler.G_STATUS_ERROR
3980          THEN
3981             l_other_message := 'BOM_OP_UUI_SEV_ERROR';
3982             l_other_token_tbl(1).token_name := 'OP_SEQ_NUMBER';
3983             l_other_token_tbl(1).token_value :=
3984                         l_operation_rec.operation_sequence_number ;
3985             RAISE EXC_SEV_QUIT_BRANCH ;
3986 
3987          ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
3988          THEN
3989             l_other_message := 'BOM_OP_UUI_UNEXP_SKIP';
3990             l_other_token_tbl(1).token_name := 'OP_SEQ_NUMBER';
3991             l_other_token_tbl(1).token_value :=
3992                         l_operation_rec.operation_sequence_number ;
3993             RAISE EXC_UNEXP_SKIP_OBJECT;
3994          IF BOM_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
3995              ('Convert to User Unique Index to Index2 completed
3996                 with return_status: ' || l_return_status) ;
3997          END IF ;
3998 
3999          END IF;
4000 
4001      /*
4002          --
4003          -- Process Flow step 4(b): Convert user unique index to unique
4004          -- index II
4005          -- Call the BOM_Rtg_Val_To_Id.Operation_UUI_To_UI2
4006          --
4007 
4008          BOM_Rtg_Val_To_Id.Operation_UUI_To_UI2
4009          ( p_operation_rec      => l_operation_rec
4010          , p_op_unexp_rec       => l_op_unexp_rec
4011          , x_op_unexp_rec       => l_op_unexp_rec
4012          , x_mesg_token_tbl     => l_mesg_token_tbl
4013          , x_other_message      => l_other_message
4014          , x_other_token_tbl    => l_other_token_tbl
4015          , x_return_status      => l_return_status
4016          ) ;
4017 
4018          IF BOM_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
4019          ('Convert to User Unique Index to Index2 completed with return_status:
4020             ' || l_return_status) ;
4021          END IF;
4022 
4023          IF l_return_status = Error_Handler.G_STATUS_ERROR
4024          THEN
4025             RAISE EXC_SEV_QUIT_SIBLINGS ;
4026          ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
4027          THEN
4028             l_other_message := 'BOM_OP_UUI_UNEXP_SKIP';
4029             l_other_token_tbl(1).token_name := 'OP_SEQ_NUMBER';
4030             l_other_token_tbl(1).token_value :=
4031                    l_operation_rec.operation_sequence_number ;
4032             RAISE EXC_UNEXP_SKIP_OBJECT;
4033          END IF ;
4034      */
4035          --
4036          -- Process Flow step 5: Verify Operation Sequence's existence
4037          -- Call the Bom_Validate_Op_Seq.Check_Existence
4038          --
4039          --
4040          Bom_Validate_Op_Seq.Check_Existence
4041          (  p_operation_rec          => l_operation_rec
4042          ,  p_op_unexp_rec           => l_op_unexp_rec
4043          ,  x_old_operation_rec      => l_old_operation_rec
4044          ,  x_old_op_unexp_rec       => l_old_op_unexp_rec
4045          ,  x_mesg_token_tbl         => l_mesg_token_tbl
4046          ,  x_return_status          => l_return_status
4047          ) ;
4048 
4049          IF BOM_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
4050          ('Check Existence completed with return_status: ' || l_return_status) ;
4051          END IF ;
4052 
4053          IF l_return_status = Error_Handler.G_STATUS_ERROR
4054          THEN
4055             l_other_message := 'BOM_OP_EXS_SEV_SKIP';
4056             l_other_token_tbl(1).token_name := 'OP_SEQ_NUMBER';
4057             l_other_token_tbl(1).token_value :=
4058                           l_operation_rec.operation_sequence_number ;
4059             l_other_token_tbl(2).token_name := 'REVISED_ITEM_NAME';
4060             l_other_token_tbl(2).token_value :=
4061                           l_operation_rec.assembly_item_name ;
4062 	    RAISE EXC_SEV_QUIT_BRANCH;
4063          ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
4064          THEN
4065             l_other_message := 'BOM_OP_EXS_UNEXP_SKIP';
4066             l_other_token_tbl(1).token_name := 'OP_SEQ_NUMBER';
4067             l_other_token_tbl(1).token_value :=
4068                           l_operation_rec.operation_sequence_number ;
4069             l_other_token_tbl(2).token_name := 'REVISED_ITEM_NAME';
4070             l_other_token_tbl(2).token_value :=
4071                           l_operation_rec.assembly_item_name ;
4072             RAISE EXC_UNEXP_SKIP_OBJECT;
4073          END IF;
4074 
4075          --
4076          -- Process Flow step 6: Is Operation Sequence record an orphan ?
4077          --
4078 
4079          IF NOT l_parent_exists
4080          THEN
4081 
4082             --
4083             -- Process Flow step 7 : Check Assembly Item Operability for Routing
4084             -- Call Bom_Validate_Rtg_Header.Check_Access
4085             --
4086             Bom_Validate_Rtg_Header.Check_Access
4087             ( p_assembly_item_name => l_operation_rec.assembly_item_name
4088             , p_assembly_item_id   => l_op_unexp_rec.assembly_item_id
4089             , p_organization_id    => l_op_unexp_rec.organization_id
4090             , p_alternate_rtg_code => l_operation_rec.alternate_routing_code
4091             , p_mesg_token_tbl     => Error_Handler.G_MISS_MESG_TOKEN_TBL
4092             , x_mesg_token_tbl     => l_mesg_token_tbl
4093             , x_return_status      => l_return_status
4094             ) ;
4095 
4096          IF BOM_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
4097          ('Check Assembly Item Operability completed with return_status: ' || l_return_status) ;
4098          END IF ;
4099 
4100 
4101             IF l_return_status = Error_Handler.G_STATUS_ERROR
4102             THEN
4103                l_other_message := 'BOM_OP_RITACC_FAT_FATAL';
4104                l_other_token_tbl(1).token_name := 'OP_SEQ_NUMBER';
4105                l_other_token_tbl(1).token_value :=
4106                           l_operation_rec.operation_sequence_number ;
4107                l_return_status := 'F' ;
4108                RAISE EXC_FAT_QUIT_SIBLINGS ;
4109             ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
4110             THEN
4111                l_other_message := 'BOM_OP_RITACC_UNEXP_SKIP';
4112                l_other_token_tbl(1).token_name := 'OP_SEQ_NUMBER';
4113                l_other_token_tbl(1).token_value :=
4114                           l_operation_rec.operation_sequence_number ;
4115                RAISE EXC_UNEXP_SKIP_OBJECT;
4116             END IF;
4117 
4118             --
4119             -- Process Flow step 8 : Check the routing does not have a common
4120             --
4121             --
4122 
4123             Bom_Validate_Op_Seq.Check_CommonRtg
4124             (  p_routing_sequence_id   => l_op_unexp_rec.routing_sequence_id
4125             ,  x_mesg_token_tbl       => l_mesg_token_tbl
4126             ,  x_return_status        => l_return_status
4127             ) ;
4128 
4129          IF BOM_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
4130          ('Check the routing non-referenced common completed with return_status: ' || l_return_status) ;
4131          END IF ;
4132 
4133             IF l_return_status = Error_Handler.G_STATUS_ERROR
4134             THEN
4135 
4136               l_token_tbl(1).token_name  := 'OP_SEQ_NUMBER';
4137               l_token_tbl(1).token_value := l_operation_rec.operation_sequence_number ;
4138               l_token_tbl(2).token_name  := 'REVISED_ITEM_NAME';
4139               l_token_tbl(2).token_value := l_operation_rec.assembly_item_name ;
4140 
4141               Error_Handler.Add_Error_Token
4142               ( p_Message_Name   => 'BOM_OP_RTG_HAVECOMMON'
4143               , p_mesg_token_tbl => l_mesg_token_tbl
4144               , x_mesg_token_tbl => l_mesg_token_tbl
4145               , p_Token_Tbl      => l_token_tbl
4146               ) ;
4147 
4148                l_return_status := 'F';
4149                RAISE EXC_FAT_QUIT_SIBLINGS ;
4150 
4151             ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
4152             THEN
4153                l_other_message := 'BOM_OP_ACCESS_UNEXP_SKIP';
4154                l_other_token_tbl(1).token_name := 'OP_SEQ_NUMBER';
4155                l_other_token_tbl(1).token_value :=
4156                           l_operation_rec.operation_sequence_number ;
4157                RAISE EXC_UNEXP_SKIP_OBJECT;
4158             END IF;
4159 
4160          END IF;  -- Parent not exists
4161 
4162 
4163          -- Process Flow Step  : Check parent CFM Routing Flag
4164          -- Validate Non-Operated Columns using CFM Routing Flag
4165          -- Standard Routing, Flow Routing, Lot Based Routing.
4166          -- If a non-operated column is not null, the procedure set it to null
4167          -- and occur Warning.
4168          --
4169          BOM_Validate_Op_Seq.Check_NonOperated_Attribute
4170          ( p_operation_rec        => l_operation_rec
4171          , p_op_unexp_rec         => l_op_unexp_rec
4172          , x_operation_rec        => l_operation_rec
4173          , x_op_unexp_rec         => l_op_unexp_rec
4174          , x_mesg_token_tbl       => l_mesg_token_tbl
4175          , x_return_status        => l_return_status
4176          ) ;
4177 
4178 
4179          IF BOM_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
4180          ('Check non-operating columns completed with return_status: ' || l_return_status) ;
4181          END IF ;
4182 
4183          IF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
4184          THEN
4185 	    l_other_message := 'BOM_OP_NONOPERATED_UNEXP_SKIP';
4186             l_other_token_tbl(1).token_name := 'OP_SEQ_NUMBER';
4187             l_other_token_tbl(1).token_value :=
4188                           l_operation_rec.operation_sequence_number ;
4189             RAISE EXC_UNEXP_SKIP_OBJECT;
4190 
4191          ELSIF l_return_status ='S' AND l_mesg_token_tbl .COUNT <>0
4192          THEN
4193             Bom_Rtg_Error_Handler.Log_Error
4194             (  p_operation_tbl       => l_operation_tbl
4195             ,  p_op_resource_tbl     => l_op_resource_tbl
4196             ,  p_sub_resource_tbl    => l_sub_resource_tbl
4197             ,  p_op_network_tbl      => l_op_network_tbl
4198             ,  p_rtg_revision_tbl    => Bom_Rtg_Pub.G_MISS_RTG_REVISION_TBL
4199             ,  p_rtg_header_rec      => Bom_Rtg_Pub.G_MISS_RTG_HEADER_REC
4200             ,  p_mesg_token_tbl      => l_mesg_token_tbl
4201             ,  p_error_status        => 'W'
4202             ,  p_error_level         => Error_Handler.G_OP_LEVEL
4203             ,  p_entity_index        => I
4204             ,  p_error_scope         => NULL
4205             ,  p_other_message       => NULL
4206             ,  p_other_mesg_appid    => 'BOM'
4207             ,  p_other_status        => NULL
4208             ,  p_other_token_tbl     => Error_Handler.G_MISS_TOKEN_TBL
4209             ,  x_rtg_header_rec      => l_rtg_header_rec
4210             ,  x_rtg_revision_tbl    => l_rtg_revision_tbl
4211             ,  x_op_network_tbl      => l_op_network_tbl
4212             ,  x_operation_tbl       => l_operation_tbl
4213             ,  x_op_resource_tbl     => l_op_resource_tbl
4214             ,  x_sub_resource_tbl    => l_sub_resource_tbl
4215             ) ;
4216          END IF;
4217 
4218 
4219          --
4220          -- Process Flow step 9: Value to Id conversions
4221          -- Call BOM_Rtg_Val_To_Id.Operation_VID
4222          --
4223          BOM_Rtg_Val_To_Id.Operation_VID
4224          (  p_operation_rec          => l_operation_rec
4225          ,  p_op_unexp_rec           => l_op_unexp_rec
4226          ,  x_op_unexp_rec           => l_op_unexp_rec
4227          ,  x_mesg_token_tbl         => l_mesg_token_tbl
4228          ,  x_return_status          => l_return_status
4229          );
4230 
4231          IF BOM_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
4232          ('Value-id conversions completed with return_status: ' || l_return_status) ;
4233          END IF ;
4234 
4235          IF l_return_status = Error_Handler.G_STATUS_ERROR
4236          THEN
4237             IF l_operation_rec.transaction_type = 'CREATE'
4238             THEN
4239                l_other_message := 'BOM_OP_VID_CSEV_SKIP';
4240                l_other_token_tbl(1).token_name := 'OP_SEQ_NUMBER';
4241                l_other_token_tbl(1).token_value :=
4242                           l_operation_rec.operation_sequence_number ;
4243                RAISE EXC_SEV_SKIP_BRANCH;
4244             ELSE
4245                RAISE EXC_SEV_QUIT_RECORD ;
4246             END IF ;
4247 
4248          ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
4249          THEN
4250             l_other_message := 'BOM_OP_VID_UNEXP_SKIP';
4251             l_other_token_tbl(1).token_name := 'OP_SEQ_NUMBER';
4252             l_other_token_tbl(1).token_value :=
4253                           l_operation_rec.operation_sequence_number ;
4254             RAISE EXC_UNEXP_SKIP_OBJECT;
4255 
4256          ELSIF l_return_status ='S' AND l_mesg_token_tbl .COUNT <>0
4257          THEN
4258             Bom_Rtg_Error_Handler.Log_Error
4259             (  p_operation_tbl       => l_operation_tbl
4260             ,  p_op_resource_tbl     => l_op_resource_tbl
4261             ,  p_sub_resource_tbl    => l_sub_resource_tbl
4262             ,  p_rtg_header_rec      => Bom_Rtg_Pub.G_MISS_RTG_HEADER_REC
4263             ,  p_rtg_revision_tbl    => Bom_Rtg_Pub.G_MISS_RTG_REVISION_TBL
4264             ,  p_op_network_tbl      => Bom_Rtg_Pub.G_MISS_OP_NETWORK_TBL
4265             ,  p_mesg_token_tbl      => l_mesg_token_tbl
4266             ,  p_error_status        => 'W'
4267             ,  p_error_level         => Error_Handler.G_OP_LEVEL
4268             ,  p_entity_index        => I
4269             ,  p_error_scope         => NULL
4270             ,  p_other_message       => NULL
4271             ,  p_other_mesg_appid    => 'BOM'
4272             ,  p_other_status        => NULL
4273             ,  p_other_token_tbl     => Error_Handler.G_MISS_TOKEN_TBL
4274             ,  x_rtg_header_rec      => l_rtg_header_rec
4275             ,  x_rtg_revision_tbl    => l_rtg_revision_tbl
4276             ,  x_op_network_tbl      => l_op_network_tbl
4277             ,  x_operation_tbl       => l_operation_tbl
4278             ,  x_op_resource_tbl     => l_op_resource_tbl
4279             ,  x_sub_resource_tbl    => l_sub_resource_tbl
4280             ) ;
4281          END IF;
4282 
4283          --copy the routing sequence id, since all the operation will belong to same routing
4284          l_routing_sequence_id := l_op_unexp_rec.Routing_Sequence_Id;
4285          --
4286          -- Process Flow step 10 : Check required fields exist
4287          -- (also includes a part of conditionally required fields)
4288          --
4289 
4290          Bom_Validate_Op_Seq.Check_Required
4291          ( p_operation_rec              => l_operation_rec
4292          , x_return_status              => l_return_status
4293          , x_mesg_token_tbl             => l_mesg_token_tbl
4294          ) ;
4295 
4296 
4297          IF BOM_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
4298          ('Check required completed with return_status: ' || l_return_status) ;
4299          END IF ;
4300 
4301 
4302          IF l_return_status = Error_Handler.G_STATUS_ERROR
4303          THEN
4304             IF l_operation_rec.transaction_type = BOM_Rtg_Globals.G_OPR_CREATE
4305             THEN
4306                l_other_message := 'BOM_OP_REQ_CSEV_SKIP';
4307                l_other_token_tbl(1).token_name := 'OP_SEQ_NUMBER';
4308                l_other_token_tbl(1).token_value :=
4309                           l_operation_rec.operation_sequence_number ;
4310                RAISE EXC_SEV_SKIP_BRANCH ;
4311             ELSE
4312                RAISE EXC_SEV_QUIT_RECORD ;
4313             END IF;
4314          ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
4315          THEN
4316             l_other_message := 'BOM_OP_REQ_UNEXP_SKIP';
4317             l_other_token_tbl(1).token_name := 'OP_SEQ_NUMBER';
4318             l_other_token_tbl(1).token_value :=
4319                           l_operation_rec.operation_sequence_number ;
4320             RAISE EXC_UNEXP_SKIP_OBJECT ;
4321          END IF;
4322 
4323          --
4324          -- Process Flow step 11 : Attribute Validation for CREATE and UPDATE
4325          --
4326          --
4327 
4328          IF l_operation_rec.transaction_type IN
4329             (BOM_Rtg_Globals.G_OPR_CREATE, BOM_Rtg_Globals.G_OPR_UPDATE)
4330          THEN
4331             Bom_Validate_Op_Seq.Check_Attributes
4332             ( p_operation_rec     => l_operation_rec
4333             , p_op_unexp_rec      => l_op_unexp_rec
4334             , x_return_status     => l_return_status
4335             , x_mesg_token_tbl    => l_mesg_token_tbl
4336             ) ;
4337             IF BOM_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
4338             ('Attribute validation completed with return_status: ' || l_return_status) ;
4339             END IF ;
4340 
4341             IF BOM_RTG_Globals.G_Init_Eff_Date_Op_Num_Flag -- Added for bug 2767019
4342 	    THEN
4343 		-- This flag is set only for Create transactions and
4344 		--   if the date is in the past wrt time, but on the same day
4345 		-- Initialize the date which will be used for this operation
4346 		l_operation_rec.Start_Effective_Date := sysdate;
4347 	    END IF;
4348 	    IF l_return_status = Error_Handler.G_STATUS_ERROR
4349             THEN
4350                IF l_operation_rec.transaction_type = BOM_Rtg_Globals.G_OPR_CREATE
4351                THEN
4352                   l_other_message := 'BOM_OP_ATTVAL_CSEV_SKIP';
4353                   l_other_token_tbl(1).token_name := 'OP_SEQ_NUMBER';
4354                   l_other_token_tbl(1).token_value :=
4355                            l_operation_rec.operation_sequence_number ;
4356                   RAISE EXC_SEV_SKIP_BRANCH ;
4357                   ELSE
4358                      RAISE EXC_SEV_QUIT_RECORD ;
4359                END IF;
4360             ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
4361             THEN
4362                l_other_message := 'BOM_OP_ATTVAL_UNEXP_SKIP';
4363                l_other_token_tbl(1).token_name := 'OP_SEQ_NUMBER';
4364                l_other_token_tbl(1).token_value :=
4365                            l_operation_rec.operation_sequence_number ;
4366                RAISE EXC_UNEXP_SKIP_OBJECT ;
4367             ELSIF l_return_status ='S' AND l_mesg_token_tbl .COUNT <> 0
4368             THEN
4369                Bom_Rtg_Error_Handler.Log_Error
4370                (  p_operation_tbl       => l_operation_tbl
4371                ,  p_op_resource_tbl     => l_op_resource_tbl
4372                ,  p_sub_resource_tbl    => l_sub_resource_tbl
4373                ,  p_rtg_header_rec      => Bom_Rtg_Pub.G_MISS_RTG_HEADER_REC
4374                ,  p_rtg_revision_tbl    => Bom_Rtg_Pub.G_MISS_RTG_REVISION_TBL
4375                ,  p_op_network_tbl      => Bom_Rtg_Pub.G_MISS_OP_NETWORK_TBL
4376                ,  p_mesg_token_tbl      => l_mesg_token_tbl
4377                ,  p_error_status        => 'W'
4378                ,  p_error_level         => Error_Handler.G_OP_LEVEL
4379                ,  p_entity_index        => I
4380                ,  p_error_scope         => NULL
4381                ,  p_other_message       => NULL
4382                ,  p_other_mesg_appid    => 'BOM'
4383                ,  p_other_status        => NULL
4384                ,  p_other_token_tbl     => Error_Handler.G_MISS_TOKEN_TBL
4385                ,  x_rtg_header_rec      => l_rtg_header_rec
4386                ,  x_rtg_revision_tbl    => l_rtg_revision_tbl
4387                ,  x_op_network_tbl      => l_op_network_tbl
4388                ,  x_operation_tbl       => l_operation_tbl
4389                ,  x_op_resource_tbl     => l_op_resource_tbl
4390                ,  x_sub_resource_tbl    => l_sub_resource_tbl
4391                ) ;
4392            END IF;
4393         END IF;
4394 
4395 
4396         IF l_operation_rec.transaction_type IN
4397            (BOM_Rtg_Globals.G_OPR_UPDATE, BOM_Rtg_Globals.G_OPR_DELETE)
4398         THEN
4399 
4400         --
4401         -- Process flow step 12: Populate NULL columns for Update and Delete
4402         -- Call Bom_Default_Op_Seq.Populate_Null_Columns
4403         --
4404 
4405            IF BOM_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Populate NULL columns') ;
4406            END IF ;
4407 
4408            Bom_Default_Op_Seq.Populate_Null_Columns
4409            (   p_operation_rec     => l_operation_rec
4410            ,   p_old_operation_Rec => l_old_operation_rec
4411            ,   p_op_unexp_rec      => l_op_unexp_rec
4412            ,   p_old_op_unexp_rec  => l_old_op_unexp_rec
4413            ,   x_operation_Rec     => l_operation_rec
4414            ,   x_op_unexp_rec      => l_op_unexp_rec
4415            ) ;
4416 
4417 
4418         ELSIF l_operation_rec.transaction_type = BOM_Rtg_Globals.G_OPR_CREATE
4419         THEN
4420         --
4421         -- Process Flow step 13 : Default missing values for Operation (CREATE)
4422         -- (also includes Entity Defaulting)
4423         -- Call Bom_Default_Op_Seq.Attribute_Defaulting
4424         --
4425 
4426            Bom_Default_Op_Seq.Attribute_Defaulting
4427            (   p_operation_rec   => l_operation_rec
4428            ,   p_op_unexp_rec    => l_op_unexp_rec
4429            ,   x_operation_rec   => l_operation_rec
4430            ,   x_op_unexp_rec    => l_op_unexp_rec
4431            ,   x_mesg_token_tbl  => l_mesg_token_tbl
4432            ,   x_return_status   => l_return_status
4433            ) ;
4434 
4435            IF BOM_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
4436            ('Attribute Defaulting completed with return_status: ' || l_return_status) ;
4437            END IF ;
4438 
4439 
4440            IF l_return_status = Error_Handler.G_STATUS_ERROR
4441            THEN
4442               l_other_message := 'BOM_OP_ATTDEF_CSEV_SKIP';
4443               l_other_token_tbl(1).token_name := 'OP_SEQ_NUMBER';
4444               l_other_token_tbl(1).token_value :=
4445                           l_operation_rec.operation_sequence_number ;
4446               RAISE EXC_SEV_SKIP_BRANCH ;
4447 
4448            ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
4449            THEN
4450               l_other_message := 'BOM_OP_ATTDEF_UNEXP_SKIP';
4451               l_other_token_tbl(1).token_name := 'OP_SEQ_NUMBER';
4452               l_other_token_tbl(1).token_value :=
4453                            l_operation_rec.operation_sequence_number ;
4454               RAISE EXC_UNEXP_SKIP_OBJECT ;
4455            ELSIF l_return_status ='S' AND l_mesg_token_tbl .COUNT <> 0
4456            THEN
4457                Bom_Rtg_Error_Handler.Log_Error
4458                (  p_operation_tbl       => l_operation_tbl
4459                ,  p_op_resource_tbl     => l_op_resource_tbl
4460                ,  p_sub_resource_tbl    => l_sub_resource_tbl
4461                ,  p_rtg_header_rec      => Bom_Rtg_Pub.G_MISS_RTG_HEADER_REC
4462                ,  p_rtg_revision_tbl    => Bom_Rtg_Pub.G_MISS_RTG_REVISION_TBL
4463                ,  p_op_network_tbl      => Bom_Rtg_Pub.G_MISS_OP_NETWORK_TBL
4464                ,  p_mesg_token_tbl      => l_mesg_token_tbl
4465                ,  p_error_status        => 'W'
4466                ,  p_error_level         => Error_Handler.G_OP_LEVEL
4467                ,  p_entity_index        => I
4468                ,  p_error_scope         => NULL
4469                ,  p_other_message       => NULL
4470                ,  p_other_mesg_appid    => 'BOM'
4471                ,  p_other_status        => NULL
4472                ,  p_other_token_tbl     => Error_Handler.G_MISS_TOKEN_TBL
4473                ,  x_rtg_header_rec      => l_rtg_header_rec
4474                ,  x_rtg_revision_tbl    => l_rtg_revision_tbl
4475                ,  x_op_network_tbl      => l_op_network_tbl
4476                ,  x_operation_tbl       => l_operation_tbl
4477                ,  x_op_resource_tbl     => l_op_resource_tbl
4478                ,  x_sub_resource_tbl    => l_sub_resource_tbl
4479                ) ;
4480           END IF;
4481        END IF;
4482 
4483        --
4484        -- Process Flow step 14: Conditionally Required Attributes
4485        --
4486        --
4487        IF l_operation_rec.transaction_type IN ( BOM_Rtg_Globals.G_OPR_CREATE
4488                                               , BOM_Rtg_Globals.G_OPR_UPDATE )
4489        THEN
4490           Bom_Validate_Op_Seq.Check_Conditionally_Required
4491           ( p_operation_rec              => l_operation_rec
4492           , p_op_unexp_rec               => l_op_unexp_rec
4493           , x_return_status              => l_return_status
4494           , x_mesg_token_tbl             => l_mesg_token_tbl
4495           ) ;
4496 
4497           IF BOM_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
4498           ('Check Conditionally Required Attr. completed with return_status: ' || l_return_status) ;
4499           END IF ;
4500 
4501           IF l_return_status = Error_Handler.G_STATUS_ERROR
4502           THEN
4503              IF l_operation_rec.transaction_type = BOM_Rtg_Globals.G_OPR_CREATE
4504              THEN
4505                 l_other_message := 'BOM_OP_CONREQ_CSEV_SKIP';
4506                 l_other_token_tbl(1).token_name := 'OP_SEQ_NUMBER';
4507                 l_other_token_tbl(1).token_value :=
4508                           l_operation_rec.operation_sequence_number ;
4509                 RAISE EXC_SEV_SKIP_BRANCH ;
4510              ELSE
4511                 RAISE EXC_SEV_QUIT_RECORD ;
4512              END IF;
4513           ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
4514           THEN
4515              l_other_message := 'BOM_OP_CONREQ_UNEXP_SKIP';
4516              l_other_token_tbl(1).token_name := 'OP_SEQ_NUMBER';
4517              l_other_token_tbl(1).token_value :=
4518                           l_operation_rec.operation_sequence_number ;
4519              RAISE EXC_UNEXP_SKIP_OBJECT ;
4520           ELSIF l_return_status ='S' AND l_mesg_token_tbl .COUNT <> 0
4521           THEN
4522              Bom_Rtg_Error_Handler.Log_Error
4523              (  p_operation_tbl       => l_operation_tbl
4524              ,  p_op_resource_tbl     => l_op_resource_tbl
4525              ,  p_sub_resource_tbl    => l_sub_resource_tbl
4526              ,  p_rtg_header_rec      => Bom_Rtg_Pub.G_MISS_RTG_HEADER_REC
4527              ,  p_rtg_revision_tbl    => Bom_Rtg_Pub.G_MISS_RTG_REVISION_TBL
4528              ,  p_op_network_tbl      => Bom_Rtg_Pub.G_MISS_OP_NETWORK_TBL
4529              ,  p_mesg_token_tbl      => l_mesg_token_tbl
4530              ,  p_error_status        => 'W'
4531              ,  p_error_level         => Error_Handler.G_OP_LEVEL
4532              ,  p_entity_index        => I
4533              ,  p_error_scope         => NULL
4534              ,  p_other_message       => NULL
4535              ,  p_other_mesg_appid    => 'BOM'
4536              ,  p_other_status        => NULL
4537              ,  p_other_token_tbl     => Error_Handler.G_MISS_TOKEN_TBL
4538              ,  x_rtg_header_rec      => l_rtg_header_rec
4539              ,  x_rtg_revision_tbl    => l_rtg_revision_tbl
4540              ,  x_op_network_tbl      => l_op_network_tbl
4541              ,  x_operation_tbl       => l_operation_tbl
4542              ,  x_op_resource_tbl     => l_op_resource_tbl
4543              ,  x_sub_resource_tbl    => l_sub_resource_tbl
4544              ) ;
4545           END IF;
4546        END IF;
4547 
4548        --
4549        -- Process Flow step 15: Entity defaulting for CREATE and UPDATE
4550        -- Merged into Process Flow step 13 : Default missing values
4551        --
4552 
4553        IF l_operation_rec.transaction_type IN ( BOM_Rtg_Globals.G_OPR_CREATE
4554                                               , BOM_Rtg_Globals.G_OPR_UPDATE )
4555        THEN
4556           Bom_Default_Op_Seq.Entity_Defaulting
4557               (   p_operation_rec   => l_operation_rec
4558               ,   p_op_unexp_rec    => l_op_unexp_rec
4559               ,   x_operation_rec   => l_operation_rec
4560               ,   x_op_unexp_rec    => l_op_unexp_rec
4561               ,   x_mesg_token_tbl  => l_mesg_token_tbl
4562               ,   x_return_status   => l_return_status
4563               ) ;
4564 
4565           IF BOM_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
4566           ('Entity defaulting completed with return_status: ' || l_return_status) ;
4567           END IF ;
4568 
4569           IF l_return_status = Error_Handler.G_STATUS_ERROR
4570           THEN
4571              IF l_operation_rec.transaction_type = BOM_Rtg_Globals.G_OPR_CREATE
4572              THEN
4573                 l_other_message := 'BOM_OP_ENTDEF_CSEV_SKIP';
4574                 l_other_token_tbl(1).token_name := 'OP_SEQ_NUMBER';
4575                 l_other_token_tbl(1).token_value :=
4576                           l_operation_rec.operation_sequence_number ;
4577                 RAISE EXC_SEV_SKIP_BRANCH ;
4578              ELSE
4579                 RAISE EXC_SEV_QUIT_RECORD ;
4580              END IF;
4581           ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
4582           THEN
4583              l_other_message := 'BOM_OP_ENTDEF_UNEXP_SKIP';
4584              l_other_token_tbl(1).token_name := 'OP_SEQ_NUMBER';
4585              l_other_token_tbl(1).token_value :=
4586                           l_operation_rec.operation_sequence_number ;
4587              RAISE EXC_UNEXP_SKIP_OBJECT ;
4588           ELSIF l_return_status ='S' AND l_mesg_token_tbl .COUNT <> 0
4589           THEN
4590              Bom_Rtg_Error_Handler.Log_Error
4591              (  p_operation_tbl       => l_operation_tbl
4592              ,  p_op_resource_tbl     => l_op_resource_tbl
4593              ,  p_sub_resource_tbl    => l_sub_resource_tbl
4594              ,  p_rtg_header_rec      => Bom_Rtg_Pub.G_MISS_RTG_HEADER_REC
4595              ,  p_rtg_revision_tbl    => Bom_Rtg_Pub.G_MISS_RTG_REVISION_TBL
4596              ,  p_op_network_tbl      => Bom_Rtg_Pub.G_MISS_OP_NETWORK_TBL
4597              ,  p_mesg_token_tbl      => l_mesg_token_tbl
4598              ,  p_error_status        => 'W'
4599              ,  p_error_level         => Error_Handler.G_OP_LEVEL
4600              ,  p_entity_index        => I
4601              ,  p_error_scope         => NULL
4602              ,  p_other_message       => NULL
4603              ,  p_other_mesg_appid    => 'BOM'
4604              ,  p_other_status        => NULL
4605              ,  p_other_token_tbl     => Error_Handler.G_MISS_TOKEN_TBL
4606              ,  x_rtg_header_rec      => l_rtg_header_rec
4607              ,  x_rtg_revision_tbl    => l_rtg_revision_tbl
4608              ,  x_op_network_tbl      => l_op_network_tbl
4609              ,  x_operation_tbl       => l_operation_tbl
4610              ,  x_op_resource_tbl     => l_op_resource_tbl
4611              ,  x_sub_resource_tbl    => l_sub_resource_tbl
4612              ) ;
4613           END IF ;
4614        END IF ;
4615 
4616 
4617        --
4618        -- Process Flow step 16 - Entity Level Validation
4619        -- Call Bom_Validate_Op_Seq.Check_Entity
4620        --
4621        Bom_Validate_Op_Seq.Check_Entity
4622           (  p_operation_rec     => l_operation_rec
4623           ,  p_op_unexp_rec      => l_op_unexp_rec
4624           ,  p_old_operation_rec => l_old_operation_rec
4625           ,  p_old_op_unexp_rec  => l_old_op_unexp_rec
4626           ,  x_operation_rec     => l_operation_rec
4627           ,  x_op_unexp_rec      => l_op_unexp_rec
4628           ,  x_mesg_token_tbl    => l_mesg_token_tbl
4629           ,  x_return_status     => l_return_status
4630           ) ;
4631 
4632 
4633        IF l_return_status = Error_Handler.G_STATUS_ERROR
4634        THEN
4635           IF l_operation_rec.transaction_type = BOM_Rtg_Globals.G_OPR_CREATE
4636           THEN
4637              l_other_message := 'BOM_OP_ENTVAL_CSEV_SKIP';
4638              l_other_token_tbl(1).token_name := 'OP_SEQ_NUMBER';
4639              l_other_token_tbl(1).token_value :=
4640                            l_operation_rec.operation_sequence_number ;
4641              RAISE EXC_SEV_SKIP_BRANCH ;
4642           ELSE
4643              RAISE EXC_SEV_QUIT_RECORD ;
4644           END IF;
4645        ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
4646        THEN
4647           l_other_message := 'BOM_OP_ENTVAL_UNEXP_SKIP';
4648           l_other_token_tbl(1).token_name := 'OP_SEQ_NUMBER';
4649           l_other_token_tbl(1).token_value :=
4650                         l_operation_rec.operation_sequence_number ;
4651           RAISE EXC_UNEXP_SKIP_OBJECT ;
4652        ELSIF l_return_status ='S' AND l_mesg_token_tbl .COUNT <> 0
4653        THEN
4654           Bom_Rtg_Error_Handler.Log_Error
4655           (  p_operation_tbl       => l_operation_tbl
4656           ,  p_op_resource_tbl     => l_op_resource_tbl
4657           ,  p_sub_resource_tbl    => l_sub_resource_tbl
4658           ,  p_rtg_header_rec      => Bom_Rtg_Pub.G_MISS_RTG_HEADER_REC
4659           ,  p_rtg_revision_tbl    => Bom_Rtg_Pub.G_MISS_RTG_REVISION_TBL
4660           ,  p_op_network_tbl      => Bom_Rtg_Pub.G_MISS_OP_NETWORK_TBL
4661           ,  p_mesg_token_tbl      => l_mesg_token_tbl
4662           ,  p_error_status        => 'W'
4663           ,  p_error_level         => Error_Handler.G_OP_LEVEL
4664           ,  p_entity_index        => I
4665           ,  p_error_scope         => NULL
4666           ,  p_other_message       => NULL
4667           ,  p_other_mesg_appid    => 'BOM'
4668           ,  p_other_status        => NULL
4669           ,  p_other_token_tbl     => Error_Handler.G_MISS_TOKEN_TBL
4670           ,  x_rtg_header_rec      => l_rtg_header_rec
4671           ,  x_rtg_revision_tbl    => l_rtg_revision_tbl
4672           ,  x_op_network_tbl      => l_op_network_tbl
4673           ,  x_operation_tbl       => l_operation_tbl
4674           ,  x_op_resource_tbl     => l_op_resource_tbl
4675           ,  x_sub_resource_tbl    => l_sub_resource_tbl
4676           ) ;
4677        END IF;
4678 
4679        IF BOM_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Entity validation completed with '
4680              || l_return_Status || ' proceeding for database writes . . . ') ;
4681        END IF;
4682 
4683        --
4684        -- Process Flow step 16 : Database Writes
4685        --
4686           Bom_Op_Seq_Util.Perform_Writes
4687           (   p_operation_rec       => l_operation_rec
4688           ,   p_op_unexp_rec        => l_op_unexp_rec
4689           ,   x_mesg_token_tbl      => l_mesg_token_tbl
4690           ,   x_return_status       => l_return_status
4691           ) ;
4692 
4693        IF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
4694        THEN
4695           l_other_message := 'BOM_OP_WRITES_UNEXP_SKIP';
4696           l_other_token_tbl(1).token_name := 'OP_SEQ_NUMBER';
4697           l_other_token_tbl(1).token_value :=
4698                           l_operation_rec.operation_sequence_number ;
4699           RAISE EXC_UNEXP_SKIP_OBJECT ;
4700        ELSIF l_return_status ='S' AND
4701           l_mesg_token_tbl .COUNT <>0
4702        THEN
4703           Bom_Rtg_Error_Handler.Log_Error
4704           (  p_operation_tbl       => l_operation_tbl
4705           ,  p_op_resource_tbl     => l_op_resource_tbl
4706           ,  p_sub_resource_tbl    => l_sub_resource_tbl
4707           ,  p_rtg_header_rec      => Bom_Rtg_Pub.G_MISS_RTG_HEADER_REC
4708           ,  p_rtg_revision_tbl    => Bom_Rtg_Pub.G_MISS_RTG_REVISION_TBL
4709           ,  p_op_network_tbl      => Bom_Rtg_Pub.G_MISS_OP_NETWORK_TBL
4710           ,  p_mesg_token_tbl      => l_mesg_token_tbl
4711           ,  p_error_status        => 'W'
4712           ,  p_error_level         => Error_Handler.G_OP_LEVEL
4713           ,  p_entity_index        => I
4714           ,  p_error_scope         => NULL
4715           ,  p_other_message       => NULL
4716           ,  p_other_mesg_appid    => 'BOM'
4717           ,  p_other_status        => NULL
4718           ,  p_other_token_tbl     => Error_Handler.G_MISS_TOKEN_TBL
4719           ,  x_rtg_header_rec      => l_rtg_header_rec
4720           ,  x_rtg_revision_tbl    => l_rtg_revision_tbl
4721           ,  x_op_network_tbl      => l_op_network_tbl
4722           ,  x_operation_tbl       => l_operation_tbl
4723           ,  x_op_resource_tbl     => l_op_resource_tbl
4724           ,  x_sub_resource_tbl    => l_sub_resource_tbl
4725           ) ;
4726        END IF;
4727 
4728        IF BOM_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Op Database writes completed with status  ' || l_return_status);
4729        END IF;
4730 
4731     END IF; -- END IF statement that checks RETURN STATUS
4732 
4733     --  Load tables.
4734     l_operation_tbl(I)          := l_operation_rec;
4735 
4736 
4737     -- Indicate that children need to be processed
4738     -- l_process_children := TRUE;
4739    IF l_operation_rec.reference_flag = 1 AND nvl(BOM_Globals.Get_Caller_Type,'') = 'MIGRATION' THEN --for iSetup issue
4740        FOR J IN 1..l_op_resource_tbl.COUNT LOOP
4741 
4742          IF l_operation_rec.Assembly_Item_Name = l_op_resource_tbl(J).Assembly_Item_Name AND
4743             l_operation_rec.Organization_Code = l_op_resource_tbl(J).Organization_Code AND
4744             l_operation_rec.Operation_Sequence_Number = l_op_resource_tbl(J).Operation_Sequence_Number AND
4745             l_operation_rec.Start_Effective_Date = l_op_resource_tbl(J).Op_Start_Effective_Date AND
4746             nvl(l_operation_rec.Alternate_Routing_Code,'@#$%^') = nvl(l_op_resource_tbl(J).Alternate_Routing_Code,'@#$%^') THEN
4747          l_op_resource_tbl(J).return_status := nvl(l_return_status,'S');
4748          END IF;
4749        END LOOP;
4750        FOR K IN 1..l_sub_resource_tbl.COUNT LOOP
4751          IF l_operation_rec.Assembly_Item_Name = l_sub_resource_tbl(K).Assembly_Item_Name AND
4752             l_operation_rec.Organization_Code = l_sub_resource_tbl(K).Organization_Code AND
4753             l_operation_rec.Operation_Sequence_Number = l_sub_resource_tbl(K).Operation_Sequence_Number AND
4754             l_operation_rec.Start_Effective_Date = l_sub_resource_tbl(K).Op_Start_Effective_Date AND
4755             nvl(l_operation_rec.Alternate_Routing_Code,'@#$%^') = nvl(l_sub_resource_tbl(K).Alternate_Routing_Code,'@#$%^') THEN
4756          l_sub_resource_tbl(K).return_status := nvl(l_return_status,'S');
4757          END IF;
4758        END LOOP;
4759        l_process_children := FALSE;
4760    ELSE
4761      l_process_children := TRUE;
4762    END IF;
4763 
4764 
4765 
4766     --  For loop exception handler.
4767 
4768     EXCEPTION
4769        WHEN EXC_SEV_QUIT_RECORD THEN
4770           Bom_Rtg_Error_Handler.Log_Error
4771           (  p_operation_tbl       => l_operation_tbl
4772           ,  p_op_resource_tbl     => l_op_resource_tbl
4773           ,  p_sub_resource_tbl    => l_sub_resource_tbl
4774           ,  p_rtg_header_rec      => Bom_Rtg_Pub.G_MISS_RTG_HEADER_REC
4775           ,  p_rtg_revision_tbl    => Bom_Rtg_Pub.G_MISS_RTG_REVISION_TBL
4776           ,  p_op_network_tbl      => Bom_Rtg_Pub.G_MISS_OP_NETWORK_TBL
4777           ,  p_mesg_token_tbl      => l_mesg_token_tbl
4778           ,  p_error_status        => Error_Handler.G_STATUS_ERROR
4779           ,  p_error_scope         => Error_Handler.G_SCOPE_RECORD
4780           ,  p_error_level         => Error_Handler.G_OP_LEVEL
4781           ,  p_entity_index        => I
4782           ,  p_other_message       => NULL
4783           ,  p_other_mesg_appid    => 'BOM'
4784           ,  p_other_status        => NULL
4785           ,  p_other_token_tbl     => Error_Handler.G_MISS_TOKEN_TBL
4786           ,  x_rtg_header_rec      => l_rtg_header_rec
4787           ,  x_rtg_revision_tbl    => l_rtg_revision_tbl
4788           ,  x_op_network_tbl      => l_op_network_tbl
4789           ,  x_operation_tbl       => l_operation_tbl
4790           ,  x_op_resource_tbl     => l_op_resource_tbl
4791           ,  x_sub_resource_tbl    => l_sub_resource_tbl
4792           ) ;
4793 
4794 
4795          l_process_children := TRUE;
4796 
4797          IF l_bo_return_status = 'S'
4798          THEN
4799             l_bo_return_status := l_return_status ;
4800          END IF;
4801 
4802          x_return_status       := l_bo_return_status;
4803          x_mesg_token_tbl      := l_mesg_token_tbl ;
4804          x_operation_tbl       := l_operation_tbl ;
4805          x_op_resource_tbl     := l_op_resource_tbl ;
4806          x_sub_resource_tbl    := l_sub_resource_tbl ;
4807          x_op_network_tbl      := l_op_network_tbl ;
4808 
4809 
4810       WHEN EXC_SEV_QUIT_BRANCH THEN
4811 
4812          Bom_Rtg_Error_Handler.Log_Error
4813          (  p_operation_tbl       => l_operation_tbl
4814          ,  p_op_resource_tbl     => l_op_resource_tbl
4815          ,  p_sub_resource_tbl    => l_sub_resource_tbl
4816          ,  p_rtg_header_rec      => Bom_Rtg_Pub.G_MISS_RTG_HEADER_REC
4817          ,  p_rtg_revision_tbl    => Bom_Rtg_Pub.G_MISS_RTG_REVISION_TBL
4818          ,  p_op_network_tbl      => Bom_Rtg_Pub.G_MISS_OP_NETWORK_TBL
4819          ,  p_mesg_token_tbl      => l_mesg_token_tbl
4820          ,  p_error_status        => Error_Handler.G_STATUS_ERROR
4821          ,  p_error_scope         => Error_Handler.G_SCOPE_CHILDREN
4822          ,  p_other_status        => Error_Handler.G_STATUS_ERROR
4823          ,  p_other_message       => l_other_message
4824          ,  p_other_token_tbl     => l_other_token_tbl
4825          ,  p_error_level         => Error_Handler.G_OP_LEVEL
4826          ,  p_entity_index        => I
4827          ,  p_other_mesg_appid    => 'BOM'
4828          ,  x_rtg_header_rec      => l_rtg_header_rec
4829          ,  x_rtg_revision_tbl    => l_rtg_revision_tbl
4830          ,  x_op_network_tbl      => l_op_network_tbl
4831          ,  x_operation_tbl       => l_operation_tbl
4832          ,  x_op_resource_tbl     => l_op_resource_tbl
4833          ,  x_sub_resource_tbl    => l_sub_resource_tbl
4834          ) ;
4835 
4836 
4837 
4838          l_process_children := FALSE;
4839 
4840          IF l_bo_return_status = 'S'
4841          THEN
4842             l_bo_return_status  := l_return_status;
4843          END IF;
4844 
4845          x_return_status       := l_bo_return_status;
4846          x_mesg_token_tbl      := l_mesg_token_tbl ;
4847          x_operation_tbl       := l_operation_tbl ;
4848          x_op_resource_tbl     := l_op_resource_tbl ;
4849          x_sub_resource_tbl    := l_sub_resource_tbl ;
4850          x_op_network_tbl      := l_op_network_tbl ;
4851 
4852 
4853       WHEN EXC_SEV_SKIP_BRANCH THEN
4854          Bom_Rtg_Error_Handler.Log_Error
4855          (  p_operation_tbl       => l_operation_tbl
4856          ,  p_op_resource_tbl     => l_op_resource_tbl
4857          ,  p_sub_resource_tbl    => l_sub_resource_tbl
4858          ,  p_rtg_header_rec      => Bom_Rtg_Pub.G_MISS_RTG_HEADER_REC
4859          ,  p_rtg_revision_tbl    => Bom_Rtg_Pub.G_MISS_RTG_REVISION_TBL
4860          ,  p_op_network_tbl      => Bom_Rtg_Pub.G_MISS_OP_NETWORK_TBL
4861          ,  p_mesg_token_tbl      => l_mesg_token_tbl
4862          ,  p_error_status        => Error_Handler.G_STATUS_ERROR
4863          ,  p_error_scope         => Error_Handler.G_SCOPE_CHILDREN
4864          ,  p_other_status        => Error_Handler.G_STATUS_NOT_PICKED
4865          ,  p_other_message       => l_other_message
4866          ,  p_other_token_tbl     => l_other_token_tbl
4867          ,  p_error_level         => Error_Handler.G_OP_LEVEL
4868          ,  p_entity_index        => I
4869          ,  p_other_mesg_appid    => 'BOM'
4870          ,  x_rtg_header_rec      => l_rtg_header_rec
4871          ,  x_rtg_revision_tbl    => l_rtg_revision_tbl
4872          ,  x_op_network_tbl      => l_op_network_tbl
4873          ,  x_operation_tbl       => l_operation_tbl
4874          ,  x_op_resource_tbl     => l_op_resource_tbl
4875          ,  x_sub_resource_tbl    => l_sub_resource_tbl
4876          ) ;
4877 
4878         l_process_children    := FALSE ;
4879         IF l_bo_return_status = 'S'
4880         THEN
4881            l_bo_return_status := l_return_status ;
4882         END IF;
4883         x_return_status       := l_bo_return_status;
4884         x_mesg_token_tbl      := l_mesg_token_tbl ;
4885         x_operation_tbl       := l_operation_tbl ;
4886         x_op_resource_tbl     := l_op_resource_tbl ;
4887         x_sub_resource_tbl := l_sub_resource_tbl ;
4888         x_op_network_tbl      := l_op_network_tbl ;
4889 
4890       WHEN EXC_SEV_QUIT_SIBLINGS THEN
4891          Bom_Rtg_Error_Handler.Log_Error
4892          (  p_operation_tbl       => l_operation_tbl
4893          ,  p_op_resource_tbl     => l_op_resource_tbl
4894          ,  p_sub_resource_tbl    => l_sub_resource_tbl
4895          ,  p_rtg_header_rec      => Bom_Rtg_Pub.G_MISS_RTG_HEADER_REC
4896          ,  p_rtg_revision_tbl    => Bom_Rtg_Pub.G_MISS_RTG_REVISION_TBL
4897          ,  p_op_network_tbl      => Bom_Rtg_Pub.G_MISS_OP_NETWORK_TBL
4898          ,  p_mesg_token_tbl      => l_mesg_token_tbl
4899          ,  p_error_status        => Error_Handler.G_STATUS_ERROR
4900          ,  p_error_scope         => Error_Handler.G_SCOPE_SIBLINGS
4901          ,  p_other_status        => Error_Handler.G_STATUS_ERROR
4902          ,  p_other_message       => l_other_message
4903          ,  p_other_token_tbl     => l_other_token_tbl
4904          ,  p_error_level         => Error_Handler.G_OP_LEVEL
4905          ,  p_entity_index        => I
4906          ,  p_other_mesg_appid    => 'BOM'
4907          ,  x_rtg_header_rec      => l_rtg_header_rec
4908          ,  x_rtg_revision_tbl    => l_rtg_revision_tbl
4909          ,  x_op_network_tbl      => l_op_network_tbl
4910          ,  x_operation_tbl       => l_operation_tbl
4911          ,  x_op_resource_tbl     => l_op_resource_tbl
4912          ,  x_sub_resource_tbl    => l_sub_resource_tbl
4913          ) ;
4914 
4915          l_process_children    := FALSE ;
4916          IF l_bo_return_status = 'S'
4917          THEN
4918            l_bo_return_status  := l_return_status ;
4919          END IF;
4920          x_return_status       := l_bo_return_status;
4921          x_mesg_token_tbl      := l_mesg_token_tbl ;
4922          x_operation_tbl       := l_operation_tbl ;
4923          x_op_resource_tbl     := l_op_resource_tbl ;
4924          x_sub_resource_tbl    := l_sub_resource_tbl ;
4925          x_op_network_tbl      := l_op_network_tbl ;
4926 
4927 
4928       WHEN EXC_FAT_QUIT_BRANCH THEN
4929          Bom_Rtg_Error_Handler.Log_Error
4930          (  p_operation_tbl       => l_operation_tbl
4931          ,  p_op_resource_tbl     => l_op_resource_tbl
4932          ,  p_sub_resource_tbl    => l_sub_resource_tbl
4933          ,  p_rtg_header_rec      => Bom_Rtg_Pub.G_MISS_RTG_HEADER_REC
4934          ,  p_rtg_revision_tbl    => Bom_Rtg_Pub.G_MISS_RTG_REVISION_TBL
4935          ,  p_op_network_tbl      => Bom_Rtg_Pub.G_MISS_OP_NETWORK_TBL
4936          ,  p_mesg_token_tbl      => l_mesg_token_tbl
4937          ,  p_error_status        => Error_Handler.G_STATUS_FATAL
4938          ,  p_error_scope         => Error_Handler.G_SCOPE_CHILDREN
4939          ,  p_other_status        => Error_Handler.G_STATUS_FATAL
4940          ,  p_other_message       => l_other_message
4941          ,  p_other_token_tbl     => l_other_token_tbl
4942          ,  p_error_level         => Error_Handler.G_OP_LEVEL
4943          ,  p_entity_index        => I
4944          ,  p_other_mesg_appid    => 'BOM'
4945          ,  x_rtg_header_rec      => l_rtg_header_rec
4946          ,  x_rtg_revision_tbl    => l_rtg_revision_tbl
4947          ,  x_op_network_tbl      => l_op_network_tbl
4948          ,  x_operation_tbl       => l_operation_tbl
4949          ,  x_op_resource_tbl     => l_op_resource_tbl
4950          ,  x_sub_resource_tbl    => l_sub_resource_tbl
4951          ) ;
4952 
4953          l_process_children    := FALSE ;
4954          x_return_status       := Error_Handler.G_STATUS_FATAL;
4955          x_mesg_token_tbl      := l_mesg_token_tbl ;
4956          x_operation_tbl       := l_operation_tbl ;
4957          x_op_resource_tbl     := l_op_resource_tbl ;
4958          x_sub_resource_tbl    := l_sub_resource_tbl ;
4959          x_op_network_tbl      := l_op_network_tbl ;
4960 
4961 
4962       WHEN EXC_FAT_QUIT_SIBLINGS THEN
4963          Bom_Rtg_Error_Handler.Log_Error
4964          (  p_operation_tbl       => l_operation_tbl
4965          ,  p_op_resource_tbl     => l_op_resource_tbl
4966          ,  p_sub_resource_tbl    => l_sub_resource_tbl
4967          ,  p_rtg_header_rec      => Bom_Rtg_Pub.G_MISS_RTG_HEADER_REC
4968          ,  p_rtg_revision_tbl    => Bom_Rtg_Pub.G_MISS_RTG_REVISION_TBL
4969          ,  p_op_network_tbl      => Bom_Rtg_Pub.G_MISS_OP_NETWORK_TBL
4970          ,  p_mesg_token_tbl      => l_mesg_token_tbl
4971          ,  p_error_status        => Error_Handler.G_STATUS_FATAL
4972          ,  p_error_scope         => Error_Handler.G_SCOPE_SIBLINGS
4973          ,  p_other_status        => Error_Handler.G_STATUS_FATAL
4974          ,  p_other_message       => l_other_message
4975          ,  p_other_token_tbl     => l_other_token_tbl
4976          ,  p_error_level         => Error_Handler.G_OP_LEVEL
4977          ,  p_entity_index        => I
4978          ,  p_other_mesg_appid    => 'BOM'
4979          ,  x_rtg_header_rec      => l_rtg_header_rec
4980          ,  x_rtg_revision_tbl    => l_rtg_revision_tbl
4981          ,  x_op_network_tbl      => l_op_network_tbl
4982          ,  x_operation_tbl       => l_operation_tbl
4983          ,  x_op_resource_tbl     => l_op_resource_tbl
4984          ,  x_sub_resource_tbl    => l_sub_resource_tbl
4985          ) ;
4986 
4987 	l_process_children    := FALSE ;
4988         x_return_status       := Error_Handler.G_STATUS_FATAL;
4989         x_mesg_token_tbl      := l_mesg_token_tbl ;
4990         x_operation_tbl       := l_operation_tbl ;
4991         x_op_resource_tbl     := l_op_resource_tbl ;
4992         x_sub_resource_tbl    := l_sub_resource_tbl ;
4993         x_op_network_tbl      := l_op_network_tbl ;
4994 
4995 /*
4996     WHEN EXC_FAT_QUIT_OBJECT THEN
4997          Bom_Rtg_Error_Handler.Log_Error
4998          (  p_operation_tbl       => l_operation_tbl
4999          ,  p_op_resource_tbl     => l_op_resource_tbl
5000          ,  p_sub_resource_tbl    => l_sub_resource_tbl
5001          ,  p_mesg_token_tbl      => l_mesg_token_tbl
5002          ,  p_error_status        => Error_Handler.G_STATUS_FATAL
5003          ,  p_error_scope         => Error_Handler.G_SCOPE_ALL
5004          ,  p_other_status        => Error_Handler.G_STATUS_FATAL
5005          ,  p_other_message       => l_other_message
5006          ,  p_other_token_tbl     => l_other_token_tbl
5007          ,  p_error_level         => Error_Handler.G_OP_LEVEL
5008          ,  p_entity_index        => I
5009             , p_other_mesg_appid     => 'BOM'
5010          ,  x_rtg_header_rec      => l_rtg_header_rec
5011          ,  x_rtg_revision_tbl    => l_rtg_revision_tbl
5012          ,  x_op_network_tbl      => l_op_network_tbl
5013          ,  x_operation_tbl       => l_operation_tbl
5014          ,  x_op_resource_tbl     => l_op_resource_tbl
5015          ,  x_sub_resource_tbl    => l_sub_resource_tbl
5016          ) ;
5017 
5018          l_return_status       := 'Q';
5019          x_mesg_token_tbl      := l_mesg_token_tbl ;
5020          x_operation_tbl       := l_operation_tbl ;
5021          x_op_resource_tbl     := l_op_resource_tbl ;
5022          x_sub_resource_tbl    := l_sub_resource_tbl ;
5023          x_op_network_tbl      := l_op_network_tbl ;
5024 */
5025 
5026       WHEN EXC_UNEXP_SKIP_OBJECT THEN
5027          Bom_Rtg_Error_Handler.Log_Error
5028          (  p_operation_tbl       => l_operation_tbl
5029          ,  p_op_resource_tbl     => l_op_resource_tbl
5030          ,  p_sub_resource_tbl    => l_sub_resource_tbl
5031          ,  p_rtg_header_rec      => Bom_Rtg_Pub.G_MISS_RTG_HEADER_REC
5032          ,  p_rtg_revision_tbl    => Bom_Rtg_Pub.G_MISS_RTG_REVISION_TBL
5033          ,  p_op_network_tbl      => Bom_Rtg_Pub.G_MISS_OP_NETWORK_TBL
5034          ,  p_mesg_token_tbl      => l_mesg_token_tbl
5035          ,  p_error_status        => Error_Handler.G_STATUS_UNEXPECTED
5036          ,  p_other_status        => Error_Handler.G_STATUS_NOT_PICKED
5037          ,  p_other_message       => l_other_message
5038          ,  p_other_token_tbl     => l_other_token_tbl
5039          ,  p_error_level         => Error_Handler.G_OP_LEVEL
5040          ,  p_error_scope         => NULL
5041          ,  p_other_mesg_appid    => 'BOM'
5042          ,  p_entity_index        => I
5043          ,  x_rtg_header_rec      => l_rtg_header_rec
5044          ,  x_rtg_revision_tbl    => l_rtg_revision_tbl
5045          ,  x_op_network_tbl      => l_op_network_tbl
5046          ,  x_operation_tbl       => l_operation_tbl
5047          ,  x_op_resource_tbl     => l_op_resource_tbl
5048          ,  x_sub_resource_tbl    => l_sub_resource_tbl
5049          ) ;
5050 
5051          l_return_status       := 'U';
5052          x_mesg_token_tbl      := l_mesg_token_tbl ;
5053          x_operation_tbl       := l_operation_tbl ;
5054          x_op_resource_tbl     := l_op_resource_tbl ;
5055          x_sub_resource_tbl    := l_sub_resource_tbl ;
5056          x_op_network_tbl      := l_op_network_tbl ;
5057 
5058    END ; -- END block
5059 
5060    IF l_return_status in ('Q', 'U')
5061    THEN
5062       x_return_status := l_return_status;
5063       RETURN ;
5064    END IF;
5065 
5066 
5067    IF l_process_children
5068    THEN
5069       -- Process Operation Resources that are direct children of this
5070       -- Operation
5071 
5072 	   l_op_seq_num := nvl(l_operation_rec.New_Operation_Sequence_Number, l_operation_rec.operation_sequence_number);
5073 	   l_strt_eff_date := nvl(l_operation_rec.New_Start_Effective_Date, l_operation_rec.start_effective_date);
5074 
5075 	IF l_operation_rec.New_Operation_Sequence_Number IS NOT NULL -- populate the temp_op_rec_tbl to be used later by networks
5076 	  OR l_operation_rec.New_Start_Effective_Date IS NOT NULL
5077 	  OR BOM_RTG_Globals.G_Init_Eff_Date_Op_Num_Flag THEN -- added for bug 2767019
5078 
5079 	   l_temp_op_rec_tbl(l_tmp_cnt).old_op_seq_num := l_operation_rec.operation_sequence_number;
5080 	   l_temp_op_rec_tbl(l_tmp_cnt).new_op_seq_num := l_op_seq_num;
5081 
5082 	   l_temp_op_rec_tbl(l_tmp_cnt).old_start_eff_date := l_operation_rec.start_effective_date;
5083 	   l_temp_op_rec_tbl(l_tmp_cnt).new_start_eff_date := l_strt_eff_date;
5084 
5085 	   l_tmp_cnt := l_tmp_cnt + 1;
5086 	   BOM_RTG_Globals.G_Init_Eff_Date_Op_Num_Flag := TRUE;
5087 
5088 	   -- Set the temp_op_rec_tbl to be used by the children(res and sub res) and network (for OSFM)
5089 	   BOM_RTG_Globals.Set_Temp_Op_Tbl(l_temp_op_rec_tbl);
5090 	END IF;
5091 
5092       Operation_Resources
5093       (   p_validation_level        => p_validation_level
5094       ,   p_organization_id         => l_op_unexp_rec.organization_id
5095       ,   p_assembly_item_name      => l_operation_rec.assembly_item_name
5096       ,   p_alternate_routing_code  => l_operation_rec.alternate_routing_code
5097 --    ,   p_operation_seq_num       => l_operation_rec.operation_sequence_number
5098 --    ,   p_effectivity_date        => l_operation_rec.start_effective_date
5099       ,   p_operation_seq_num       => l_op_seq_num
5100       ,   p_effectivity_date        => l_strt_eff_date
5101       ,   p_operation_type          => l_operation_rec.operation_type
5102       ,   p_op_resource_tbl         => l_op_resource_tbl
5103       ,   p_sub_resource_tbl        => l_sub_resource_tbl
5104       ,   x_op_resource_tbl         => l_op_resource_tbl
5105       ,   x_sub_resource_tbl        => l_sub_resource_tbl
5106       ,   x_mesg_token_tbl          => l_mesg_token_tbl
5107       ,   x_return_status           => l_return_status
5108       ) ;
5109 
5110    IF l_return_status in ('Q', 'U')
5111    THEN
5112       x_return_status := l_return_status;
5113       RETURN ;
5114    ELSIF NVL(l_return_status, 'S') <> 'S'
5115    THEN
5116       x_return_status     := l_return_status;
5117    END IF;
5118 
5119       -- Process Substitute Operation Resources that are direct children of this
5120       -- operation
5121 
5122       Sub_Operation_Resources
5123       (   p_validation_level         => p_validation_level
5124       ,   p_organization_id          => l_op_unexp_rec.organization_id
5125       ,   p_assembly_item_name       => l_operation_rec.assembly_item_name
5126       ,   p_alternate_routing_code   => l_operation_rec.alternate_routing_code
5127       ,   p_operation_seq_num       => l_op_seq_num
5128       ,   p_effectivity_date        => l_strt_eff_date
5129       ,   p_operation_type           => l_operation_rec.operation_type
5130       ,   p_sub_resource_tbl         => l_sub_resource_tbl
5131       ,   x_sub_resource_tbl         => l_sub_resource_tbl
5132       ,   x_mesg_token_tbl           => l_mesg_token_tbl
5133       ,   x_return_status            => l_return_status
5134       ) ;
5135 
5136    IF l_return_status in ('Q', 'U')
5137    THEN
5138       x_return_status := l_return_status;
5139       RETURN ;
5140    ELSIF NVL(l_return_status, 'S') <> 'S'
5141    THEN
5142       x_return_status     := l_return_status;
5143    END IF;
5144 
5145 
5146    END IF;   -- Process children
5147    END LOOP; -- END Operation Sequences processing loop
5148    -- Reset the Init_Eff_Date_Op_Num flag so that this affects only it's children
5149    BOM_RTG_Globals.G_Init_Eff_Date_Op_Num_Flag := FALSE;
5150 
5151 
5152     -- bug:5060186 Copy the first or last operation of the network routing if disabled.
5153     IF ( l_routing_sequence_id IS NOT NULL ) THEN
5154       SELECT  CFM_ROUTING_FLAG
5155       INTO    l_cfm_routing_flag
5156       FROM    BOM_OPERATIONAL_ROUTINGS
5157       WHERE   ROUTING_SEQUENCE_ID = l_routing_sequence_id;
5158 
5159       IF ( l_cfm_routing_flag = 3 ) THEN -- check if the routing is network routing
5160         Bom_Op_Network_Util.Copy_First_Last_Dis_Op(
5161                                                     p_routing_sequence_id => l_routing_sequence_id
5162                                                   , x_mesg_token_tbl     => l_mesg_token_tbl
5163                                                   , x_return_status      => l_return_status );
5164 
5165         IF BOM_Rtg_Globals.Get_Debug = 'Y'  THEN
5166             Error_Handler.Write_Debug
5167               ( 'Op Sequences: Copy First/Last Disabled Operation completed with status ' ||
5168                 l_return_status );
5169         END IF; -- end if BOM_Rtg_Globals.Get_Debug = 'Y'
5170       END IF; -- end if l_cfm_routing_flag = 3
5171     END IF; -- end if l_routing_sequence_id IS NOT NULL
5172 
5173    --  Load OUT parameters
5174    IF NVL(l_return_status, 'S') <> 'S'
5175    THEN
5176       x_return_status     := l_return_status;
5177    END IF;
5178 
5179    x_mesg_token_tbl      := l_mesg_token_tbl ;
5180    x_operation_tbl       := l_operation_tbl ;
5181    x_op_resource_tbl     := l_op_resource_tbl ;
5182    x_sub_resource_tbl    := l_sub_resource_tbl ;
5183    x_op_network_tbl      := l_op_network_tbl ;
5184 
5185 END Operation_Sequences ;
5186 
5187 
5188 /****************************************************************************
5189 * Procedure     : Rtg_Revisions
5190 * Parameters IN : Rtg Revision Table and all the other entities
5191 * Parameters OUT: Rtg Revision Table and all the other entities
5192 * Purpose       : This procedure will process all the Rtg revision records.
5193 *                 Although the other entities are not children of this entity
5194 *                 the are taken as parameters so that the error handler could
5195 *                 set the records to appropriate status if a fatal or severity
5196 *                 1 error occurs.
5197 *****************************************************************************/
5198 
5199 PROCEDURE Rtg_Revisions
5200 (   p_validation_level           IN  NUMBER
5201  ,  p_assembly_item_name         IN  VARCHAR2   := NULL
5202  ,  p_assembly_item_id           IN  NUMBER     := NULL
5203  ,  p_organization_id            IN  NUMBER     := NULL
5204  ,  p_alternate_rtg_code         IN  VARCHAR2   := NULL
5205  ,  p_rtg_revision_tbl           IN  Bom_Rtg_Pub.rtg_Revision_Tbl_Type
5206  ,  p_operation_tbl              IN  Bom_Rtg_Pub.Operation_Tbl_Type
5207  ,  p_op_resource_tbl            IN  Bom_Rtg_Pub.Op_Resource_Tbl_Type
5208  ,  p_sub_resource_tbl           IN  Bom_Rtg_Pub.Sub_Resource_Tbl_Type
5209  ,  p_op_network_tbl             IN  Bom_Rtg_Pub.Op_Network_Tbl_Type
5210  ,  x_rtg_revision_tbl           IN OUT NOCOPY Bom_Rtg_Pub.rtg_Revision_Tbl_Type
5211  ,  x_operation_tbl              IN OUT NOCOPY Bom_Rtg_Pub.Operation_Tbl_Type
5212  ,  x_op_resource_tbl            IN OUT NOCOPY Bom_Rtg_Pub.Op_Resource_Tbl_Type
5213  ,  x_sub_resource_tbl           IN OUT NOCOPY Bom_Rtg_Pub.Sub_Resource_Tbl_Type
5214  ,  x_op_network_tbl             IN OUT NOCOPY Bom_Rtg_Pub.Op_Network_Tbl_Type
5215  ,  x_Mesg_Token_Tbl             IN OUT NOCOPY Error_Handler.Mesg_Token_Tbl_Type
5216  ,  x_return_status              IN OUT NOCOPY VARCHAR2
5217  )
5218 IS
5219 l_Mesg_Token_Tbl        Error_Handler.Mesg_Token_Tbl_Type;
5220 l_other_token_tbl       Error_Handler.Token_Tbl_Type;
5221 l_other_message         VARCHAR2(50);
5222 l_err_text              VARCHAR2(2000);
5223 l_valid                 BOOLEAN := TRUE;
5224 l_return_status         VARCHAR2(1) := FND_API.G_RET_STS_SUCCESS;
5225 l_bo_return_status      VARCHAR2(1) := 'S';
5226 l_bom_parent_exists     BOOLEAN := FALSE;
5227 l_rtg_header_rec        Bom_Rtg_Pub.rtg_Header_Rec_Type;
5228 l_rtg_header_unexp_rec  Bom_Rtg_Pub.rtg_Header_unexposed_Rec_Type;
5229 l_old_rtg_header_rec    Bom_Rtg_Pub.rtg_Header_Rec_Type;
5230 l_old_rtg_header_unexp_rec Bom_Rtg_Pub.rtg_Header_Unexposed_Rec_Type;
5231 l_rtg_revision_rec      Bom_Rtg_Pub.Rtg_Revision_Rec_Type;
5232 l_rtg_rev_unexp_rec     Bom_Rtg_Pub.Rtg_Rev_Unexposed_Rec_Type;
5233 l_rtg_revision_tbl      Bom_Rtg_Pub.rtg_Revision_Tbl_Type := p_rtg_revision_tbl;
5234 l_old_rtg_revision_rec  Bom_Rtg_Pub.Rtg_Revision_Rec_Type := NULL;
5235 l_old_rtg_rev_unexp_rec Bom_Rtg_Pub.Rtg_Rev_Unexposed_Rec_Type := NULL;
5236 l_operation_tbl         Bom_Rtg_Pub.operation_tbl_Type := p_operation_tbl;
5237 l_op_resource_tbl       Bom_Rtg_Pub.op_resource_tbl_Type := p_op_resource_tbl;
5238 l_sub_resource_tbl      Bom_Rtg_Pub.sub_resource_tbl_Type :=
5239                                 p_sub_resource_tbl;
5240 l_op_network_tbl        Bom_Rtg_Pub.op_network_tbl_Type :=
5241                                 p_op_network_tbl;
5242 l_return_value          NUMBER;
5243 l_rtg_parent_exists     BOOLEAN := FALSE ;
5244 l_Token_Tbl             Error_Handler.Token_Tbl_Type;
5245 
5246 BEGIN
5247 
5248     l_return_status := 'S';
5249     l_bo_return_status := 'S';
5250 
5251     --  Init local table variables.
5252 
5253     l_rtg_revision_tbl := p_rtg_revision_tbl;
5254     l_rtg_rev_unexp_rec.organization_id := BOM_Rtg_Globals.Get_org_id;
5255 
5256     FOR I IN 1..l_rtg_revision_tbl.COUNT LOOP
5257     BEGIN
5258 
5259         --  Load local records.
5260 
5261         l_rtg_revision_rec := l_rtg_revision_tbl(I);
5262 
5263         l_rtg_revision_rec.transaction_type :=
5264                 UPPER(l_rtg_revision_rec.transaction_type);
5265 
5266         IF p_assembly_item_name IS NOT NULL AND
5267            p_organization_id IS NOT NULL
5268         THEN
5269                 l_rtg_parent_exists := TRUE;
5270         END IF;
5271 
5272         --
5273         -- Process Flow Step 2: Check if record has not yet been processed and
5274         -- that it is the child of the parent that called this procedure
5275         --
5276 
5277         IF (l_rtg_revision_rec.return_status IS NULL OR
5278             l_rtg_revision_rec.return_status = FND_API.G_MISS_CHAR)
5279            AND
5280            (NOT l_rtg_parent_exists
5281            OR
5282            (l_rtg_parent_exists AND
5283               ( l_rtg_revision_rec.assembly_item_name = p_assembly_item_name AND
5284                 l_rtg_rev_unexp_rec.organization_id =   p_organization_id AND
5285                 NVL(l_rtg_revision_rec.alternate_routing_code, FND_API.G_MISS_CHAR) =
5286                                   NVL(p_alternate_rtg_code, FND_API.G_MISS_CHAR)
5287               )
5288              )
5289             )
5290         THEN
5291 
5292            l_return_status := FND_API.G_RET_STS_SUCCESS;
5293            l_rtg_revision_rec.return_status := FND_API.G_RET_STS_SUCCESS;
5294 
5295            --
5296            -- Check if transaction_type is valid
5297            --
5298            BOM_Rtg_Globals.Transaction_Type_Validity
5299            (   p_transaction_type       => l_rtg_revision_rec.transaction_type
5300            ,   p_entity                 => 'Routing_Revision'
5301            ,   p_entity_id              => l_rtg_revision_rec.revision
5302            ,   x_valid                  => l_valid
5303            ,   x_Mesg_Token_Tbl         => l_Mesg_Token_Tbl
5304            );
5305 
5306            IF NOT l_valid
5307            THEN
5308                 l_return_status := Error_Handler.G_STATUS_ERROR;
5309                 RAISE EXC_SEV_QUIT_RECORD;
5310            END IF;
5311 
5312            --
5313            -- Process Flow step 4: Verify that Revision is not NULL or MISSING
5314            --
5315 
5316            IF l_rtg_revision_rec.revision is NULL OR
5317               l_rtg_revision_rec.revision =  FND_API.G_MISS_CHAR
5318            THEN
5319                 l_other_message := 'BOM_RTG_REV_KEYCOL_NULL';
5320                 l_return_status := Error_Handler.G_STATUS_ERROR;
5321                 RAISE EXC_UNEXP_SKIP_OBJECT;
5322            END IF;
5323 
5324            --
5325            -- Process Flow Step: 5 Convert User Unique Index
5326            --
5327            BOM_Rtg_Val_To_Id.Rtg_Revision_UUI_To_UI
5328            (  p_rtg_revision_rec        => l_rtg_revision_rec
5329             , p_rtg_rev_unexp_rec       => l_rtg_rev_unexp_rec
5330             , x_rtg_rev_unexp_rec       => l_rtg_rev_unexp_rec
5331             , x_mesg_token_tbl          => l_mesg_token_tbl
5332             , x_return_status           => l_return_status
5333             );
5334             IF  l_return_status = Error_Handler.G_STATUS_ERROR
5335             THEN
5336                 l_other_message := 'BOM_RTG_REV_UUI_SEV_ERROR';
5337                 l_other_token_tbl(1).token_name := 'REVISION';
5338                 l_other_token_tbl(1).token_value := l_rtg_revision_rec.revision;
5339                 RAISE EXC_SEV_QUIT_OBJECT;
5340             ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
5341             THEN
5342                 l_other_message := 'BOM_RTG_REV_UUI_UNEXP_SKIP';
5343                 l_other_token_tbl(1).token_name := 'REVISION';
5344                 l_other_token_tbl(1).token_value := l_rtg_revision_rec.revision;
5345 
5346                 RAISE EXC_UNEXP_SKIP_OBJECT;
5347             END IF;
5348 
5349 
5350            /*  BIao No Longer
5351            -- Verify Rtg Header's existence in database.
5352            -- If revision is being created and the business object does not
5353            -- carry the Rtg header, then it is imperative to check for the
5354            -- Rtg Header's existence.
5355 
5356            IF l_rtg_revision_rec.transaction_type = BOM_Rtg_Globals.G_OPR_CREATE
5357               AND
5358               NOT l_rtg_parent_exists
5359            THEN
5360                 l_rtg_header_rec.alternate_routing_code := p_alternate_rtg_code;
5361                 l_rtg_header_unexp_rec.organization_id  := p_organization_id;
5362                 l_rtg_header_unexp_rec.assembly_item_id := p_assembly_item_id;
5363                 l_rtg_header_rec.transaction_type := 'XXX';
5364 
5365                 Bom_Validate_Rtg_Header.Check_Existence
5366                 ( p_rtg_header_rec      => l_rtg_header_rec
5367                 , p_rtg_header_unexp_rec  => l_rtg_header_unexp_rec
5368                 , x_old_rtg_header_rec  => l_old_rtg_header_rec
5369                 , x_old_rtg_header_unexp_rec => l_old_rtg_header_unexp_rec
5370                 , x_Mesg_Token_Tbl         => l_Mesg_Token_Tbl
5371                 , x_return_status          => l_return_status
5372                 );
5373                 IF l_return_status = Error_Handler.G_STATUS_ERROR
5374                 THEN
5375                    l_other_message := 'BOM_RTG_HEADER_NOT_EXIST';
5376                    l_other_token_tbl(1).token_name := 'ASSEMBLY_ITEM_NAME';
5377                    l_other_token_tbl(1).token_value :=
5378                                         l_rtg_revision_rec.assembly_item_name;
5379                    l_other_token_tbl(2).token_name := 'ORGANIZATION_CODE';
5380                    l_other_token_tbl(2).token_value :=
5381                                         l_rtg_revision_rec.organization_code;
5382                    RAISE EXC_SEV_QUIT_OBJECT;
5383                 ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
5384                 THEN
5385                    l_other_message := 'BOM_RTG_REV_LIN_UNEXP_SKIP';
5386                    l_other_token_tbl(1).token_name := 'REVISION';
5387                    l_other_token_tbl(1).token_value :=
5388                                                 l_rtg_revision_rec.revision;
5389                    RAISE EXC_UNEXP_SKIP_OBJECT;
5390                 END IF;
5391            END IF;
5392 
5393            */
5394 
5395            --
5396            -- Process Flow step 5: Verify Revision's existence
5397            --
5398            Bom_Validate_Rtg_Revision.Check_Existence
5399                 (  p_rtg_revision_rec           => l_rtg_revision_rec
5400                 ,  p_rtg_rev_unexp_rec          => l_rtg_rev_unexp_rec
5401                 ,  x_old_rtg_revision_rec       => l_old_rtg_revision_rec
5402                 ,  x_old_rtg_rev_unexp_rec      => l_old_rtg_rev_unexp_rec
5403                 ,  x_Mesg_Token_Tbl             => l_Mesg_Token_Tbl
5404                 ,  x_return_status              => l_return_status
5405                 );
5406 
5407            IF l_return_status = Error_Handler.G_STATUS_ERROR
5408            THEN
5409                 l_other_message := 'BOM_RTG_REV_EXS_SEV_SKIP';
5410                 l_other_token_tbl(1).token_name := 'REVISION';
5411                 l_other_token_tbl(1).token_value := l_rtg_revision_rec.revision;
5412 --                RAISE EXC_UNEXP_SKIP_OBJECT; -- this should not stop processing of other entities, bug 2871039
5413                 RAISE EXC_SEV_QUIT_RECORD;
5414            ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
5415            THEN
5416                 l_other_message := 'BOM_RTG_REV_EXS_UNEXP_SKIP';
5417                 l_other_token_tbl(1).token_name := 'REVISION';
5418                 l_other_token_tbl(1).token_value := l_rtg_revision_rec.revision;
5419                 RAISE EXC_UNEXP_SKIP_OBJECT;
5420            END IF;
5421 
5422 
5423            -- Process Flow step 5: Is Revision record an orphan ?
5424 
5425            IF NOT l_rtg_parent_exists
5426            THEN
5427 
5428                 Bom_Validate_Rtg_Header.Check_Access
5429                 ( p_assembly_item_name  => l_rtg_revision_rec.assembly_item_name
5430                 , p_assembly_item_id    => l_rtg_rev_unexp_rec.assembly_item_id
5431                 , p_organization_id     => l_rtg_rev_unexp_rec.organization_id
5432                 , p_alternate_rtg_code  =>
5433                                      l_rtg_revision_rec.alternate_routing_code
5434                 , p_mesg_token_tbl     => Error_Handler.G_MISS_MESG_TOKEN_TBL
5435                 , x_Mesg_Token_Tbl      => l_Mesg_Token_Tbl
5436                 , x_Return_Status       => l_return_status
5437                 );
5438 
5439                 IF l_return_status = Error_Handler.G_STATUS_ERROR
5440                 THEN
5441                         l_other_message := 'BOM_RTG_REV_AITACC_FAT_FATAL';
5442                         l_other_token_tbl(1).token_name := 'REVISION';
5443                         l_other_token_tbl(1).token_value :=
5444                                                 l_rtg_revision_rec.revision;
5445                         l_return_status := 'F';
5446                         RAISE EXC_FAT_QUIT_OBJECT;
5447                 ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
5448                 THEN
5449                         l_other_message := 'BOM_RTG_REV_AITACC_UNEXP_ERROR';
5450                         l_other_token_tbl(1).token_name := 'REVISION';
5451                         l_other_token_tbl(1).token_value :=
5452                                                 l_rtg_revision_rec.revision;
5453                         RAISE EXC_UNEXP_SKIP_OBJECT;
5454                 END IF;
5455 
5456            END IF;
5457 
5458         --
5459         -- Process Flow step 9: Attribute Validation for Create and Update
5460         --
5461         IF l_rtg_revision_rec.transaction_type IN
5462                 (BOM_Rtg_Globals.G_OPR_UPDATE, BOM_Rtg_Globals.G_OPR_CREATE)
5463         THEN
5464 
5465 IF BOM_Rtg_Globals.Get_Debug = 'Y' THEN
5466     Error_Handler.Write_Debug('Rtg Revision : Check Attributes . . .');
5467 END IF;
5468 
5469                 Bom_Validate_Rtg_Revision.Check_Attributes
5470                 (   x_return_status            => l_return_status
5471                 ,   x_Mesg_Token_Tbl           => l_Mesg_Token_Tbl
5472                 ,   p_rtg_revision_rec         => l_rtg_revision_rec
5473                 ,   p_rtg_rev_unexp_rec        => l_rtg_rev_unexp_rec
5474                 ,   p_old_rtg_revision_rec     => l_old_rtg_revision_rec
5475                 ,   p_old_rtg_rev_unexp_rec    => l_old_rtg_rev_unexp_rec
5476                 );
5477 
5478                 IF l_return_status = Error_Handler.G_STATUS_ERROR
5479                 THEN
5480                         l_other_message := 'BOM_RTG_REV_ATTVAL_CSEV_SKIP';
5481                         l_other_token_tbl(1).token_name := 'REVISION';
5482                         l_other_token_tbl(1).token_value :=
5483                                                 l_rtg_revision_rec.revision;
5484                         IF l_rtg_header_rec.transaction_type = 'CREATE'
5485                         THEN
5486                                 RAISE EXC_SEV_SKIP_BRANCH;
5487                         ELSE
5488                                 RAISE EXC_SEV_QUIT_RECORD;
5489                         END IF;
5490                 ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
5491                 THEN
5492                         l_other_message := 'BOM_RTG_REV_ATTVAL_UNEXP_SKIP';
5493                         l_other_token_tbl(1).token_name := 'REVISION';
5494                         l_other_token_tbl(1).token_value :=
5495                                                 l_rtg_revision_rec.revision;
5496 
5497                         RAISE EXC_UNEXP_SKIP_OBJECT;
5498                 END IF;
5499        END IF;
5500 
5501 
5502        IF l_rtg_revision_rec.Transaction_Type IN
5503                 (BOM_Rtg_Globals.G_OPR_UPDATE, BOM_Rtg_Globals.G_OPR_DELETE)
5504        THEN
5505 
5506                 -- Process flow  - Populate NULL columns for Update and
5507                 -- Delete.
5508 
5509                 Bom_Default_Rtg_Revision.Populate_NULL_Columns
5510                 (   p_rtg_revision_rec          => l_rtg_revision_rec
5511                 ,   p_rtg_rev_unexp_rec         => l_rtg_rev_unexp_rec
5512                 ,   p_old_rtg_revision_rec      => l_old_rtg_revision_rec
5513                 ,   p_old_rtg_rev_unexp_rec     => l_old_rtg_rev_unexp_rec
5514                 ,   x_rtg_revision_rec          => l_rtg_revision_rec
5515                 ,   x_rtg_rev_unexp_rec         => l_rtg_rev_unexp_rec
5516                 );
5517 
5518       ELSIF l_rtg_revision_rec.Transaction_Type = BOM_Rtg_Globals.G_OPR_CREATE
5519       THEN
5520 
5521                 --
5522                 --  Default missing values for Operation
5523                 -- CREATE
5524                 --
5525                         NULL;
5526 
5527                 /*
5528                 ** There is not attribute defualting for RTG Revisions
5529                 */
5530 
5531 
5532 
5533       END IF;
5534 
5535         --
5536         -- Process Flow step 12: Attribute Validation for Create and Update
5537         --
5538 
5539            Bom_Validate_Rtg_Revision.Check_Entity
5540                 (  x_return_status        => l_return_status
5541                 ,  x_Mesg_Token_Tbl       => l_Mesg_Token_Tbl
5542                 ,  p_rtg_revision_rec     => l_rtg_revision_rec
5543                 ,  p_rtg_rev_unexp_rec    => l_rtg_rev_unexp_rec
5544                 ,  p_old_rtg_revision_rec => l_old_rtg_revision_rec
5545                 ,  p_old_rtg_rev_unexp_rec=> l_old_rtg_rev_unexp_rec
5546                 );
5547 
5548            IF l_return_status = Error_Handler.G_STATUS_ERROR
5549            THEN
5550                 l_other_message := 'BOM_RTG_REV_ENTVAL_CSEV_SKIP';
5551                 l_other_token_tbl(1).token_name := 'REVISION';
5552                 l_other_token_tbl(1).token_value :=
5553                                                 l_rtg_revision_rec.revision;
5554                 RAISE EXC_SEV_QUIT_RECORD;
5555            ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
5556            THEN
5557                 l_other_message := 'BOM_RTG_REV_ENTVAL_UNEXP_ERROR';
5558                 l_other_token_tbl(1).token_name := 'REVISION';
5559                 l_other_token_tbl(1).token_value := l_rtg_revision_rec.revision;
5560                 RAISE EXC_UNEXP_SKIP_OBJECT;
5561            END IF;
5562 
5563            --
5564            -- Process Flow step 13 : Database Writes
5565            --
5566            BOM_RTG_Revision_Util.Perform_Writes
5567                 (   p_rtg_revision_rec          => l_rtg_revision_rec
5568                 ,   p_rtg_rev_unexp_rec         => l_rtg_rev_unexp_rec
5569                 ,   x_Mesg_Token_Tbl            => l_Mesg_Token_Tbl
5570                 ,   x_return_status             => l_return_status
5571                 );
5572 
5573            IF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
5574            THEN
5575                 l_other_message := 'BOM_RTG_REV_WRITES_UNEXP_ERROR';
5576                 l_other_token_tbl(1).token_name := 'REVISION';
5577                 l_other_token_tbl(1).token_value := l_rtg_revision_rec.revision;
5578                 RAISE EXC_UNEXP_SKIP_OBJECT;
5579            END IF;
5580 
5581         END IF;
5582         -- End IF that checks RETURN STATUS AND PARENT-CHILD RELATIONSHIP
5583 
5584         --  Load tables.
5585 
5586         l_rtg_revision_tbl(I)          := l_rtg_revision_rec;
5587 
5588         --  For loop exception handler.
5589      EXCEPTION
5590 
5591        WHEN EXC_SEV_QUIT_RECORD THEN
5592 
5593                 Bom_Rtg_Error_Handler.Log_Error
5594                 (  p_rtg_revision_tbl   => l_rtg_revision_tbl
5595                 ,  p_operation_tbl      => l_operation_tbl
5596                 ,  p_op_resource_tbl    => l_op_resource_tbl
5597                 ,  p_sub_resource_tbl   => l_sub_resource_tbl
5598                 ,  p_op_network_tbl     => l_op_network_tbl
5599                 ,  p_rtg_header_rec     => Bom_Rtg_Pub.G_MISS_RTG_HEADER_REC
5600                 ,  p_mesg_token_tbl     => l_mesg_token_tbl
5601                 ,  p_error_status       => Error_Handler.G_STATUS_ERROR
5602                 ,  p_error_scope        => Error_Handler.G_SCOPE_RECORD
5603                 ,  p_error_level        => Error_Handler.G_REV_LEVEL
5604                 ,  p_entity_index       => I
5605                 ,  p_other_message      => NULL
5606                 ,  p_other_mesg_appid   => 'BOM'
5607                 ,  p_other_status       => NULL
5608                 ,  p_other_token_tbl    => Error_Handler.G_MISS_TOKEN_TBL
5609                 ,  x_rtg_header_rec     => l_rtg_header_rec
5610                 ,  x_rtg_revision_tbl   => l_rtg_revision_tbl
5611                 ,  x_operation_tbl      => l_operation_tbl
5612                 ,  x_op_resource_tbl    => l_op_resource_tbl
5613                 ,  x_sub_resource_tbl   => l_sub_resource_tbl
5614                 ,  x_op_network_tbl     => l_op_network_tbl
5615            );
5616 
5617         IF l_bo_return_status = 'S'
5618         THEN
5619                 l_bo_return_status     := l_return_status;
5620         END IF;
5621         x_return_status                := l_bo_return_status;
5622         x_Mesg_Token_Tbl               := l_Mesg_Token_Tbl;
5623         x_rtg_revision_tbl             := l_rtg_revision_tbl;
5624         x_operation_tbl                := l_operation_tbl;
5625         x_op_resource_tbl              := l_op_resource_tbl;
5626         x_sub_resource_tbl             := l_sub_resource_tbl;
5627         x_op_network_tbl               := l_op_network_tbl;
5628 
5629         WHEN EXC_SEV_QUIT_OBJECT THEN
5630 
5631             Bom_Rtg_Error_Handler.Log_Error
5632             (  p_rtg_revision_tbl       => l_rtg_revision_tbl
5633              , p_operation_tbl          => l_operation_tbl
5634              , p_op_resource_tbl        => l_op_resource_tbl
5635              , p_sub_resource_tbl       => l_sub_resource_tbl
5636              , p_op_network_tbl         => l_op_network_tbl
5637              , p_rtg_header_rec         => Bom_Rtg_Pub.G_MISS_RTG_HEADER_REC
5638              , p_mesg_token_tbl         => l_mesg_token_tbl
5639              , p_error_status           => Error_Handler.G_STATUS_ERROR
5640              , p_error_scope            => Error_Handler.G_SCOPE_ALL
5641              , p_error_level            => Error_Handler.G_REV_LEVEL
5642              , p_other_message          => l_other_message
5643              , p_other_status           => Error_Handler.G_STATUS_ERROR
5644              , p_other_token_tbl        => l_other_token_tbl
5645              , p_other_mesg_appid       => 'BOM'
5646              , p_entity_index           => I
5647              , x_rtg_header_rec         => l_rtg_header_rec
5648              , x_rtg_revision_tbl       => l_rtg_revision_tbl
5649              , x_operation_tbl          => l_operation_tbl
5650              , x_op_resource_tbl        => l_op_resource_tbl
5651              , x_sub_resource_tbl       => l_sub_resource_tbl
5652              , x_op_network_tbl         => l_op_network_tbl
5653              );
5654 
5655         IF l_bo_return_status = 'S'
5656         THEN
5657                 l_bo_return_status     := l_return_status;
5658         END IF;
5659         x_return_status                := l_bo_return_status;
5660         x_Mesg_Token_Tbl               := l_Mesg_Token_Tbl;
5661         x_rtg_revision_tbl             := l_rtg_revision_tbl;
5662         x_operation_tbl                := l_operation_tbl;
5663         x_op_resource_tbl              := l_op_resource_tbl;
5664         x_sub_resource_tbl             := l_sub_resource_tbl;
5665         x_op_network_tbl               := l_op_network_tbl;
5666 
5667        WHEN EXC_FAT_QUIT_OBJECT THEN
5668 
5669           Bom_Rtg_Error_Handler.Log_Error
5670             (  p_rtg_revision_tbl       => l_rtg_revision_tbl
5671              , p_operation_tbl          => l_operation_tbl
5672              , p_op_resource_tbl        => l_op_resource_tbl
5673              , p_sub_resource_tbl       => l_sub_resource_tbl
5674              , p_op_network_tbl         => l_op_network_tbl
5675              , p_rtg_header_rec         => Bom_Rtg_Pub.G_MISS_RTG_HEADER_REC
5676              , p_mesg_token_tbl         => l_mesg_token_tbl
5677              , p_error_status           => Error_Handler.G_STATUS_FATAL
5678              , p_error_scope            => Error_Handler.G_SCOPE_ALL
5679              , p_error_level            => Error_Handler.G_REV_LEVEL
5680              , p_other_message          => l_other_message
5681              , p_other_status           => Error_Handler.G_STATUS_FATAL
5682              , p_other_token_tbl        => l_other_token_tbl
5683              , p_other_mesg_appid       => 'BOM'
5684              , p_entity_index           => I
5685              , x_rtg_header_rec         => l_rtg_header_rec
5686              , x_rtg_revision_tbl       => l_rtg_revision_tbl
5687              , x_operation_tbl          => l_operation_tbl
5688              , x_op_resource_tbl        => l_op_resource_tbl
5689              , x_sub_resource_tbl       => l_sub_resource_tbl
5690              , x_op_network_tbl         => l_op_network_tbl
5691         );
5692 
5693         x_Mesg_Token_Tbl               := l_Mesg_Token_Tbl;
5694         x_rtg_revision_tbl             := l_rtg_revision_tbl;
5695         x_operation_tbl                := l_operation_tbl;
5696         x_op_resource_tbl              := l_op_resource_tbl;
5697         x_sub_resource_tbl             := l_sub_resource_tbl;
5698         x_op_network_tbl               := l_op_network_tbl;
5699 
5700         l_return_status := 'Q';
5701 
5702        WHEN EXC_UNEXP_SKIP_OBJECT THEN
5703 
5704             Bom_Rtg_Error_Handler.Log_Error
5705             (  p_rtg_revision_tbl       => l_rtg_revision_tbl
5706              , p_operation_tbl          => l_operation_tbl
5707              , p_op_resource_tbl        => l_op_resource_tbl
5708              , p_sub_resource_tbl       => l_sub_resource_tbl
5709              , p_op_network_tbl         => l_op_network_tbl
5710              , p_rtg_header_rec         => Bom_Rtg_Pub.G_MISS_RTG_HEADER_REC
5711              , p_mesg_token_tbl         => l_mesg_token_tbl
5712              , p_error_status           => Error_Handler.G_STATUS_UNEXPECTED
5713              , p_error_scope            => Error_Handler.G_SCOPE_ALL
5714              , p_error_level            => Error_Handler.G_REV_LEVEL
5715              , p_other_message          => l_other_message
5716              , p_other_status           => Error_Handler.G_STATUS_NOT_PICKED
5717              , p_other_token_tbl        => l_other_token_tbl
5718              , p_other_mesg_appid       => 'BOM'
5719              , p_entity_index           => I
5720              , x_rtg_header_rec         => l_rtg_header_rec
5721              , x_rtg_revision_tbl       => l_rtg_revision_tbl
5722              , x_operation_tbl          => l_operation_tbl
5723              , x_op_resource_tbl        => l_op_resource_tbl
5724              , x_sub_resource_tbl       => l_sub_resource_tbl
5725              , x_op_network_tbl         => l_op_network_tbl
5726              );
5727         IF l_bo_return_status = 'S'
5728         THEN
5729                 l_bo_return_status     := l_return_status;
5730         END IF;
5731         x_return_status                := l_bo_return_status;
5732         x_Mesg_Token_Tbl               := l_Mesg_Token_Tbl;
5733         x_rtg_revision_tbl             := l_rtg_revision_tbl;
5734         x_operation_tbl                := l_operation_tbl;
5735         x_op_resource_tbl              := l_op_resource_tbl;
5736         x_sub_resource_tbl             := l_sub_resource_tbl;
5737         x_op_network_tbl               := l_op_network_tbl;
5738         --l_return_status := 'U';
5739 
5740         END; -- END block
5741 
5742      END LOOP; -- END Revisions processing loop
5743 
5744     IF l_return_status in ('Q', 'U')
5745     THEN
5746         x_return_status := l_return_status;
5747         RETURN;
5748     END IF;
5749 
5750      --  Load OUT parameters
5751 
5752      x_return_status            := l_bo_return_status;
5753      x_rtg_revision_tbl         := l_rtg_revision_tbl;
5754      x_operation_tbl            := l_operation_tbl;
5755      x_op_resource_tbl          := l_op_resource_tbl;
5756      x_sub_resource_tbl         := l_sub_resource_tbl;
5757      x_op_network_tbl           := l_op_network_tbl;
5758      x_Mesg_Token_Tbl           := l_Mesg_Token_Tbl;
5759 
5760 END Rtg_Revisions;
5761 
5762 /***************************************************************************
5763 * Procedure     : Rtg_Header (Unexposed)
5764 * Parameters IN : Rtg Header Record and all the child entities
5765 * Parameters OUT: Rtg Header Record and all the child entities
5766 * Purpose       : This procedure will validate and perform the appropriate
5767 *                 action on the RTG Header record.
5768 *                 It will process the entities that are children of this header.
5769 ***************************************************************************/
5770 -- Header needs to be changed
5771 PROCEDURE Rtg_Header
5772 (   p_validation_level              IN  NUMBER
5773 ,   p_rtg_header_rec                IN  Bom_Rtg_Pub.rtg_Header_Rec_Type
5774 ,   p_rtg_revision_tbl              IN  Bom_Rtg_Pub.rtg_Revision_Tbl_Type
5775 ,   p_operation_tbl                 IN  Bom_Rtg_Pub.Operation_Tbl_Type
5776 ,   p_op_resource_tbl               IN  Bom_Rtg_Pub.Op_Resource_Tbl_Type
5777 ,   p_sub_resource_tbl              IN  Bom_Rtg_Pub.Sub_Resource_Tbl_Type
5778 ,   p_op_network_tbl                IN  Bom_Rtg_Pub.Op_Network_Tbl_Type
5779 ,   x_rtg_header_rec                IN OUT NOCOPY Bom_Rtg_Pub.rtg_Header_Rec_Type
5780 ,   x_rtg_revision_tbl              IN OUT NOCOPY Bom_Rtg_Pub.rtg_Revision_Tbl_Type
5781 ,   x_operation_tbl                 IN OUT NOCOPY Bom_Rtg_Pub.Operation_Tbl_Type
5782 ,   x_op_resource_tbl               IN OUT NOCOPY Bom_Rtg_Pub.Op_Resource_Tbl_Type
5783 ,   x_sub_resource_tbl              IN OUT NOCOPY Bom_Rtg_Pub.Sub_Resource_Tbl_Type
5784 ,   x_op_network_tbl                IN OUT NOCOPY Bom_Rtg_Pub.Op_Network_Tbl_Type
5785 ,   x_Mesg_Token_Tbl                IN OUT NOCOPY Error_Handler.Mesg_Token_Tbl_Type
5786 ,   x_return_status                 IN OUT NOCOPY VARCHAR2
5787 )
5788 IS
5789 
5790 l_Mesg_Token_Tbl        Error_Handler.Mesg_Token_Tbl_Type;
5791 l_other_token_tbl       Error_Handler.Token_Tbl_Type;
5792 l_other_message         VARCHAR2(50);
5793 l_err_text              VARCHAR2(2000);
5794 l_valid                 BOOLEAN := TRUE;
5795 l_return_status         VARCHAR2(1) := FND_API.G_RET_STS_SUCCESS;
5796 l_bo_return_status      VARCHAR2(1) := 'S';
5797 l_rtg_header_rec        Bom_Rtg_Pub.Rtg_Header_Rec_Type;
5798 l_old_rtg_header_rec    Bom_Rtg_Pub.Rtg_Header_Rec_Type;
5799 l_old_rtg_header_unexp_rec Bom_Rtg_Pub.rtg_Header_Unexposed_Rec_Type;
5800 l_rtg_header_Unexp_Rec  Bom_Rtg_Pub.Rtg_Header_Unexposed_Rec_Type;
5801 l_rtg_revision_tbl      Bom_Rtg_Pub.Rtg_Revision_Tbl_Type := p_rtg_revision_tbl;
5802 l_operation_tbl         Bom_Rtg_Pub.operation_tbl_type   := p_operation_tbl;
5803 l_op_resource_tbl       Bom_Rtg_Pub.op_resource_tbl_type := p_op_resource_tbl;
5804 l_sub_resource_tbl      Bom_Rtg_Pub.sub_resource_tbl_type :=
5805                                 p_sub_resource_tbl;
5806 l_op_network_tbl        Bom_Rtg_Pub.op_network_tbl_type :=
5807                                 p_op_network_tbl;
5808 l_return_value          NUMBER;
5809 l_Token_Tbl             Error_Handler.Token_Tbl_Type;
5810 
5811 BEGIN
5812 
5813 
5814 
5815         -- Begin block that processes header.
5816         -- This block holds the exception handlers for header errors.
5817 
5818     BEGIN
5819 
5820         --  Load entity and record-specific details into system_information
5821         --  record
5822 
5823         l_rtg_header_unexp_rec.organization_id := BOM_Rtg_Globals.Get_Org_Id;
5824 
5825 
5826         l_rtg_header_rec := p_rtg_header_rec;
5827         l_rtg_header_rec.transaction_type :=
5828                                 UPPER(l_rtg_header_rec.transaction_type);
5829 
5830 IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN
5831     Error_Handler.Write_Debug('Processing Rtg Header - Trans Type : '|| l_rtg_header_rec.transaction_type) ;
5832 End IF ;
5833         -- Process Flow Step 2: Check if record has not yet been processed
5834         --
5835 
5836         IF l_rtg_header_rec.return_status IS NOT NULL AND
5837            l_rtg_header_rec.return_status <> FND_API.G_MISS_CHAR
5838         THEN
5839                 x_return_status                := l_return_status;
5840                 x_rtg_header_rec               := l_rtg_header_rec;
5841                 x_rtg_revision_tbl             := l_rtg_revision_tbl;
5842                 x_operation_tbl                := l_operation_tbl;
5843                 x_op_resource_tbl              := l_op_resource_tbl;
5844                 x_sub_resource_tbl             := l_sub_resource_tbl;
5845                 x_op_network_tbl               := l_op_network_tbl;
5846                 RETURN;
5847         END IF;
5848 
5849         l_return_status := FND_API.G_RET_STS_SUCCESS;
5850         l_rtg_header_rec.return_status := FND_API.G_RET_STS_SUCCESS;
5851 
5852         --
5853         -- Process Flow Step 3: Check if transaction_type is valid
5854         --
5855 	BOM_Rtg_Globals.Transaction_Type_Validity
5856         (   p_transaction_type  => l_rtg_header_rec.transaction_type
5857         ,   p_entity            => 'Routing_Header'
5858         ,   p_entity_id         => l_rtg_header_rec.assembly_item_name
5859         ,   x_valid             => l_valid
5860         ,   x_Mesg_Token_Tbl    => l_Mesg_Token_Tbl
5861         );
5862 
5863         IF NOT l_valid
5864         THEN
5865                 l_return_status := Error_Handler.G_STATUS_ERROR;
5866                 RAISE EXC_SEV_QUIT_RECORD;
5867         END IF;
5868 
5869         --
5870         -- Process Flow Step 4: Convert User Unique Index to Unique Index
5871         --
5872 
5873         BOM_Rtg_Val_To_Id.Rtg_Header_UUI_To_UI
5874         (  p_rtg_header_rec             => l_rtg_header_rec
5875          , p_rtg_header_unexp_rec       => l_rtg_header_unexp_rec
5876          , x_rtg_header_unexp_rec       => l_rtg_header_unexp_rec
5877          , x_return_status              => l_return_status
5878          , x_mesg_token_tbl             => l_mesg_token_tbl
5879         );
5880 
5881 IF BOM_Rtg_Globals.Get_Debug = 'Y' THEN
5882     Error_Handler.Write_Debug ('Rtg Header: UUI-UI Conversion. Return Status :  '||  l_return_status  );
5883 END IF;
5884 
5885         IF l_return_status = Error_Handler.G_STATUS_ERROR
5886         THEN
5887                 l_other_message := 'BOM_RTG_UUI_SEV_ERROR';
5888                 l_other_token_tbl(1).token_name := 'ASSEMBLY_ITEM_NAME';
5889                 l_other_token_tbl(1).token_value :=
5890                                         l_rtg_header_rec.assembly_item_name;
5891                 RAISE EXC_SEV_QUIT_BRANCH;
5892         ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
5893         THEN
5894                 l_other_message := 'BOM_RTG_UUI_UNEXP_SKIP';
5895                 l_other_token_tbl(1).token_name := 'ASSEMBLY_ITEM_NAME';
5896                 l_other_token_tbl(1).token_value :=
5897                                         l_rtg_header_rec.assembly_item_name;
5898                 RAISE EXC_UNEXP_SKIP_OBJECT;
5899         END IF;
5900 
5901         --
5902         -- Process Flow step 5: Verify Rtg Header's existence
5903         --
5904         Bom_Validate_Rtg_Header.Check_Existence
5905               (   p_rtg_header_rec      => l_rtg_header_rec
5906                 , p_rtg_header_unexp_rec=> l_rtg_header_unexp_rec
5907                 , x_old_rtg_header_rec  => l_old_rtg_header_rec
5908                 , x_old_rtg_header_unexp_rec=> l_old_rtg_header_unexp_rec
5909                 , x_Mesg_Token_Tbl      => l_Mesg_Token_Tbl
5910                 , x_return_status       => l_return_status
5911                 );
5912 
5913 IF BOM_Rtg_Globals.Get_Debug = 'Y' THEN
5914     Error_Handler.Write_Debug ('Rtg Header: Check Existence. Return Status :  '||  l_return_status  );
5915 END IF;
5916 
5917         IF l_return_status = Error_Handler.G_STATUS_ERROR
5918         THEN
5919                 l_other_message := 'BOM_RTG_EXS_SEV_ERROR';
5920                 l_other_token_tbl(1).token_name := 'ASSEMBLY_ITEM_NAME';
5921                 l_other_token_tbl(1).token_value :=
5922                                         l_rtg_header_rec.assembly_item_name;
5923                 RAISE EXC_SEV_QUIT_BRANCH;
5924         ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
5925         THEN
5926                 l_other_message := 'BOM_RTG_EXS_UNEXP_SKIP';
5927                 l_other_token_tbl(1).token_name := 'ASSEMBLY_ITEM_NAME';
5928                 l_other_token_tbl(1).token_value :=
5929                                         l_rtg_header_rec.assembly_item_name;
5930                 RAISE EXC_UNEXP_SKIP_OBJECT;
5931         END IF;
5932 
5933 
5934         --
5935         -- Process Flow Step:6 Check Access to the Bill Item's Rtg Item Type
5936         --
5937         Bom_Validate_Rtg_Header.Check_Access
5938          ( p_assembly_item_name => l_rtg_header_rec.assembly_item_name
5939          , p_assembly_item_id   => l_rtg_header_unexp_rec.assembly_item_id
5940          , p_alternate_rtg_code => l_rtg_header_rec.alternate_routing_code
5941          , p_organization_id    => l_rtg_header_unexp_rec.organization_id
5942          , p_mesg_token_tbl     => l_mesg_token_tbl
5943          , x_mesg_token_tbl     => l_mesg_token_tbl
5944          , x_return_status      => l_return_status
5945          );
5946 
5947 IF BOM_Rtg_Globals.Get_Debug = 'Y' THEN
5948     Error_Handler.Write_Debug ('Rtg Header: Check Access. Return Status :  '||  l_return_status  );
5949 END IF;
5950 
5951         IF l_return_status = Error_Handler.G_STATUS_ERROR
5952         THEN
5953                 l_other_message := 'BOM_RTG_ACC_SEV_ERROR';
5954                 l_other_token_tbl(1).token_name := 'ASSEMBLY_ITEM_NAME';
5955                 l_other_token_tbl(1).token_value :=
5956                                         l_rtg_header_rec.assembly_item_name;
5957                 RAISE EXC_SEV_QUIT_BRANCH;
5958         ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
5959         THEN
5960                 l_other_message := 'BOM_RTG_ACC_UNEXP_SKIP';
5961                 l_other_token_tbl(1).token_name := 'ASSEMBLY_ITEM_NAME';
5962                 l_other_token_tbl(1).token_value :=
5963                                         l_rtg_header_rec.assembly_item_name;
5964                 RAISE EXC_UNEXP_SKIP_OBJECT;
5965         END IF;
5966 
5967         --
5968         -- Process Flow Step: 7 Check Flow Routing's operability for routing.
5969         --
5970         Bom_Validate_Rtg_Header.Check_flow_routing_operability
5971         (  p_assembly_item_name  => l_rtg_header_rec.assembly_item_name
5972          , p_cfm_routing_flag    => l_rtg_header_rec.cfm_routing_flag
5973          , p_organization_code   => l_rtg_header_rec.organization_code
5974          , p_organization_id     => l_rtg_header_Unexp_rec.organization_id
5975          , x_mesg_token_tbl      => l_mesg_token_tbl
5976          , x_return_status       => l_return_status
5977         );
5978 
5979 IF BOM_Rtg_Globals.Get_Debug = 'Y' THEN
5980     Error_Handler.Write_Debug ('Rtg Header:  Check Flow Routing operability. Return Status :  '||  l_return_status  );
5981 END IF;
5982 
5983 
5984         IF l_return_status = Error_Handler.G_STATUS_ERROR
5985         THEN
5986                 l_other_message := 'BOM_RTG_FRACC_ERROR';
5987                 l_other_token_tbl(1).token_name := 'ASSEMBLY_ITEM_NAME';
5988                 l_other_token_tbl(1).token_value :=
5989                                         l_rtg_header_rec.assembly_item_name;
5990                 RAISE EXC_SEV_QUIT_BRANCH;
5991         ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
5992         THEN
5993                 l_other_message := 'BOM_RTG_FRACC_UNEXP_SKIP';
5994                 l_other_token_tbl(1).token_name := 'ASSEMBLY_ITEM_NAME';
5995                 l_other_token_tbl(1).token_value :=
5996                                         l_rtg_header_rec.assembly_item_name;
5997                 RAISE EXC_UNEXP_SKIP_OBJECT;
5998         END IF;
5999 
6000         Bom_Validate_Rtg_Header.Check_lot_controlled_item  -- for bug 3132425
6001                (  p_assembly_item_id  => l_rtg_header_unexp_rec.assembly_item_id
6002                 , p_organization_id   => l_rtg_header_Unexp_rec.organization_id
6003                 , x_mesg_token_tbl    => l_mesg_token_tbl
6004                 , x_return_status     => l_return_status
6005                );
6006 
6007         IF BOM_Rtg_Globals.Get_Debug = 'Y' THEN
6008             Error_Handler.Write_Debug ('Rtg Header:  Check Lot Controlled Item. Return Status :  '||l_return_status);
6009         END IF;
6010 
6011         IF l_return_status = Error_Handler.G_STATUS_ERROR
6012         THEN
6013                 l_other_message := 'BOM_NON_LOT_OSFM';
6014                 l_other_token_tbl(1).token_name := 'ASSEMBLY_ITEM_NAME';
6015                 l_other_token_tbl(1).token_value :=
6016                                         l_rtg_header_rec.assembly_item_name;
6017                 RAISE EXC_SEV_QUIT_BRANCH;
6018        ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
6019        THEN
6020                 RAISE EXC_UNEXP_SKIP_OBJECT;
6021        END IF;
6022 
6023         /* Moved to Entity Defaulting
6024         --
6025         -- Process Flow Step 7.5:  Validation for no_operated columns in
6026         -- flow routing.
6027         --
6028         IF l_rtg_header_rec.cfm_routing_flag = 2
6029         THEN
6030            l_rtg_header_rec.line_code := NULL;
6031            l_rtg_header_rec.mixed_model_map_flag:= NULL;
6032            l_rtg_header_rec.total_product_cycle_time := NULL;
6033         END IF;
6034         */
6035 
6036         --
6037         -- Process Flow Step 8: Value-ID conversion.
6038         --
6039 IF BOM_Rtg_Globals.Get_Debug = 'Y'  THEN
6040     Error_Handler.Write_Debug('Rtg Header: Value-Id Conversion . . .');
6041 END IF;
6042         BOM_Rtg_Val_To_Id.Rtg_Header_VID
6043         (  x_Return_Status         => l_return_status
6044         ,  x_Mesg_Token_Tbl        => l_Mesg_Token_Tbl
6045         ,  p_rtg_header_rec        => l_rtg_header_rec
6046         ,  p_rtg_header_unexp_rec  => l_rtg_header_unexp_rec
6047         ,  x_rtg_header_unexp_rec  => l_rtg_header_unexp_rec
6048         );
6049 
6050 
6051         IF l_return_status = Error_Handler.G_STATUS_ERROR
6052         THEN
6053             IF l_rtg_header_rec.transaction_type = 'CREATE'
6054             THEN
6055                 l_other_message := 'BOM_RTG_VID_CSEV_SKIP';
6056                 l_other_token_tbl(1).token_name := 'ASSEMBLY_ITEM_NAME';
6057                 l_other_token_tbl(1).token_value :=
6058                                         l_rtg_header_rec.assembly_item_name;
6059                 RAISE EXC_SEV_SKIP_BRANCH;
6060             ELSE
6061                 RAISE EXC_SEV_QUIT_RECORD;
6062             END IF;
6063         ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
6064         THEN
6065                 l_other_message := 'BOM_RTG_VID_UNEXP_SKIP';
6066                 l_other_token_tbl(1).token_name := 'ASSEMBLY_ITEM_NAME';
6067                 l_other_token_tbl(1).token_value :=
6068                                         l_rtg_header_rec.assembly_item_name;
6069                 RAISE EXC_UNEXP_SKIP_OBJECT;
6070         ELSIF l_return_status ='S' AND
6071               l_Mesg_Token_Tbl.COUNT <>0
6072         THEN
6073               Bom_Rtg_Error_Handler.Log_Error
6074                 (  p_rtg_header_rec        => l_rtg_header_rec
6075                 ,  p_rtg_revision_tbl      => l_rtg_revision_tbl
6076                 ,  p_operation_tbl         => l_operation_tbl
6077                 ,  p_op_resource_tbl       => l_op_resource_tbl
6078                 ,  p_sub_resource_tbl      => l_sub_resource_tbl
6079                 ,  p_op_network_tbl        => l_op_network_tbl
6080                 ,  p_mesg_token_tbl        => l_mesg_token_tbl
6081                 ,  p_error_status          => 'W'
6082                 ,  p_error_level           => Error_Handler.G_RTG_LEVEL
6083                 ,  p_other_message         => NULL
6084                 ,  p_other_mesg_appid      => 'BOM'
6085                 ,  p_other_status          => NULL
6086                 ,  p_other_token_tbl       => Error_Handler.G_MISS_TOKEN_TBL
6087                 ,  p_error_scope           => NULL
6088                 ,  p_entity_index          => 1
6089                 ,  x_rtg_header_rec        => l_rtg_header_rec
6090                 ,  x_rtg_revision_tbl      => l_rtg_revision_tbl
6091                 ,  x_operation_tbl         => l_operation_tbl
6092                 ,  x_op_resource_tbl       => l_op_resource_tbl
6093                 ,  x_sub_resource_tbl      => l_sub_resource_tbl
6094                 ,  x_op_network_tbl        => l_op_network_tbl
6095                 );
6096         END IF;
6097 
6098         --
6099         -- Process Flow step 10: Attribute Validation for Create and Update
6100         --
6101 
6102         IF l_rtg_header_rec.transaction_type IN
6103                 (BOM_Rtg_Globals.G_OPR_UPDATE, BOM_Rtg_Globals.G_OPR_CREATE)
6104         THEN
6105 
6106            Bom_Validate_Rtg_Header.Check_Attributes
6107                 (   x_return_status            => l_return_status
6108                 ,   x_Mesg_Token_Tbl           => l_Mesg_Token_Tbl
6109                 ,   p_rtg_header_rec           => l_rtg_header_rec
6110                 ,   p_rtg_header_unexp_rec     => l_rtg_header_unexp_rec
6111                 ,   p_old_rtg_header_rec       => l_old_rtg_header_rec
6112                 ,   p_old_rtg_header_unexp_rec => l_old_rtg_header_unexp_rec
6113                 );
6114 
6115 IF BOM_Rtg_Globals.Get_Debug = 'Y' THEN
6116     Error_Handler.Write_Debug ('Rtg Header: Check Attributes. Return Status :  '||  l_return_status  );
6117 END IF ;
6118 
6119 
6120            IF l_return_status = Error_Handler.G_STATUS_ERROR
6121            THEN
6122                IF l_rtg_header_rec.transaction_type = 'CREATE'
6123                THEN
6124                    l_other_message := 'BOM_RTG_ATTVAL_CSEV_SKIP';
6125                    l_other_token_tbl(1).token_name
6126                                                 := 'ASSEMBLY_ITEM_NAME';
6127                    l_other_token_tbl(1).token_value :=
6128                    l_rtg_header_rec.assembly_item_name;
6129                    RAISE EXC_SEV_SKIP_BRANCH;
6130                ELSE
6131                    RAISE EXC_SEV_QUIT_RECORD;
6132                END IF;
6133            ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
6134            THEN
6135                l_other_message := 'BOM_RTG_ATTVAL_UNEXP_SKIP';
6136                l_other_token_tbl(1).token_name
6137                                 := 'ASSEMBLY_ITEM_NAME';
6138                l_other_token_tbl(1).token_value
6139                                 := l_rtg_header_rec.assembly_item_name;
6140 
6141                RAISE EXC_UNEXP_SKIP_OBJECT;
6142            ELSIF l_return_status ='S' AND
6143                         l_Mesg_Token_Tbl.COUNT <>0
6144            THEN
6145 
6146 IF BOM_Rtg_Globals.Get_Debug = 'Y' THEN
6147     Error_Handler.Write_Debug ('Warning :  '||  l_return_status  );
6148 END IF ;
6149                  Bom_Rtg_Error_Handler.Log_Error
6150                 (  p_rtg_header_rec        => l_rtg_header_rec
6151                 ,  p_rtg_revision_tbl      => l_rtg_revision_tbl
6152                 ,  p_operation_tbl         => l_operation_tbl
6153                 ,  p_op_resource_tbl       => l_op_resource_tbl
6154                 ,  p_sub_resource_tbl      => l_sub_resource_tbl
6155                 ,  p_op_network_tbl        => l_op_network_tbl
6156                 ,  p_mesg_token_tbl        => l_mesg_token_tbl
6157                 ,  p_error_status          => 'W'
6158                 ,  p_error_level           => Error_Handler.G_RTG_LEVEL
6159                 ,  p_other_message         => NULL
6160                 ,  p_other_mesg_appid      => 'BOM'
6161                 ,  p_other_status          => NULL
6162                 ,  p_other_token_tbl       => Error_Handler.G_MISS_TOKEN_TBL
6163                 ,  p_error_scope           => NULL
6164                 ,  p_entity_index          => 1
6165                 ,  x_rtg_header_rec        => l_rtg_header_rec
6166                 ,  x_rtg_revision_tbl      => l_rtg_revision_tbl
6167                 ,  x_operation_tbl         => l_operation_tbl
6168                 ,  x_op_resource_tbl       => l_op_resource_tbl
6169                 ,  x_sub_resource_tbl      => l_sub_resource_tbl
6170                 ,  x_op_network_tbl        => l_op_network_tbl
6171                 );
6172            END IF;
6173         END IF;
6174 
6175         --
6176         -- Process Flow Step:12
6177         -- If the Transaction Type is Update/Delete, then Populate_Null_Columns
6178         -- Else Attribute_Defaulting
6179         --
6180         IF l_rtg_header_rec.Transaction_Type IN
6181            (BOM_Rtg_Globals.G_OPR_UPDATE, BOM_Rtg_Globals.G_OPR_DELETE)
6182         THEN
6183 
6184          --
6185          -- Process flow step 12 - Populate NULL columns for Update and
6186          -- Delete.
6187          --
6188                 BOM_Default_Rtg_Header.Populate_NULL_Columns
6189                 (   p_rtg_header_rec            => l_rtg_header_rec
6190                 ,   p_rtg_header_unexp_rec      => l_rtg_header_unexp_rec
6191                 ,   p_Old_rtg_header_rec        => l_old_rtg_header_rec
6192                 ,   p_Old_rtg_header_unexp_rec  => l_old_rtg_header_unexp_rec
6193                 ,   x_rtg_header_rec            => l_rtg_header_rec
6194                 ,   x_rtg_header_unexp_rec      => l_rtg_header_unexp_rec
6195                 );
6196 
6197 IF BOM_Rtg_Globals.Get_Debug = 'Y' THEN
6198     Error_Handler.Write_Debug ('Rtg Header: Populate Null Columns. Return Status :  '||  l_return_status  );
6199 END IF ;
6200 
6201          ELSIF l_rtg_header_rec.Transaction_Type = BOM_Rtg_Globals.G_OPR_CREATE THEN
6202          --
6203          -- Process Flow step 12: Default missing values for Operation CREATE
6204          --
6205                BOM_Default_Rtg_Header.Attribute_Defaulting
6206                 (   p_rtg_header_rec            => l_rtg_header_rec
6207                 ,   p_rtg_header_unexp_rec      => l_rtg_header_unexp_rec
6208                 ,   x_rtg_header_rec            => l_rtg_header_rec
6209                 ,   x_rtg_header_unexp_rec      => l_rtg_header_unexp_rec
6210                 ,   x_Mesg_Token_Tbl            => l_Mesg_Token_Tbl
6211                 ,   x_return_status             => l_return_status
6212                 );
6213 
6214 IF BOM_Rtg_Globals.Get_Debug = 'Y' THEN
6215     Error_Handler.Write_Debug ('Rtg Header: Attribute Defaulting. Return Status :  '||  l_return_status  );
6216 END IF ;
6217 
6218                IF l_return_status = Error_Handler.G_STATUS_ERROR
6219                THEN
6220                    IF l_rtg_header_rec.transaction_type = 'CREATE'
6221                    THEN
6222                        l_other_message := 'BOM_RTG_ATTDEF_CSEV_SKIP';
6223                        l_other_token_tbl(1).token_name := 'ASSEMBLY_ITEM_NAME';
6224                        l_other_token_tbl(1).token_value :=
6225                                         l_rtg_header_rec.assembly_item_name;
6226                        RAISE EXC_SEV_SKIP_BRANCH;
6227                    ELSE
6228                        RAISE EXC_SEV_QUIT_RECORD;
6229                    END IF;
6230                ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
6231                THEN
6232                        l_other_message := 'BOM_RTG_ATTDEF_UNEXP_SKIP';
6233                        l_other_token_tbl(1).token_name := 'ASSEMBLY_ITEM_NAME';
6234                        l_other_token_tbl(1).token_value :=
6235                                         l_rtg_header_rec.assembly_item_name;
6236                        RAISE EXC_UNEXP_SKIP_OBJECT;
6237                ELSIF l_return_status ='S' AND
6238                      l_Mesg_Token_Tbl.COUNT <>0
6239                THEN
6240                        Bom_Rtg_Error_Handler.Log_Error
6241                        (  p_rtg_header_rec        => l_rtg_header_rec
6242                        ,  p_rtg_revision_tbl      => l_rtg_revision_tbl
6243                        ,  p_operation_tbl         => l_operation_tbl
6244                        ,  p_op_resource_tbl       => l_op_resource_tbl
6245                        ,  p_sub_resource_tbl      => l_sub_resource_tbl
6246                        ,  p_op_network_tbl        => l_op_network_tbl
6247                        ,  p_mesg_token_tbl        => l_mesg_token_tbl
6248                        ,  p_error_status          => 'W'
6249                        ,  p_error_level           => Error_Handler.G_RTG_LEVEL
6250                        ,  p_other_message         => NULL
6251                        ,  p_other_mesg_appid      => 'BOM'
6252                        ,  p_other_status          => NULL
6253                        ,  p_other_token_tbl       => Error_Handler.G_MISS_TOKEN_TBL
6254                        ,  p_error_scope           => NULL
6255                        ,  p_entity_index          => 1
6256                        ,  x_rtg_header_rec        => l_rtg_header_rec
6257                        ,  x_rtg_revision_tbl      => l_rtg_revision_tbl
6258                        ,  x_operation_tbl         => l_operation_tbl
6259                        ,  x_op_resource_tbl       => l_op_resource_tbl
6260                        ,  x_sub_resource_tbl      => l_sub_resource_tbl
6261                        ,  x_op_network_tbl        => l_op_network_tbl
6262                        );
6263                END IF;
6264         END IF;
6265 
6266         --
6267         -- Process Flow step 13 - Check Conditionally Required Fields
6268         --
6269         Bom_Validate_Rtg_Header.Check_Required
6270         (   x_return_status             => l_return_status
6271         ,   x_Mesg_Token_Tbl            => l_Mesg_Token_Tbl
6272         ,   p_rtg_header_rec            => l_rtg_header_rec
6273         ,   p_rtg_header_unexp_rec      => l_rtg_header_unexp_rec
6274         );
6275 
6276 IF BOM_Rtg_Globals.Get_Debug = 'Y' THEN
6277     Error_Handler.Write_Debug ('Rtg Header: Check Required. Return Status :  '||  l_return_status  );
6278 END IF ;
6279 
6280        IF l_return_status = Error_Handler.G_STATUS_ERROR
6281        THEN
6282            IF l_rtg_header_rec.transaction_type = BOM_Rtg_Globals.G_OPR_CREATE
6283            THEN
6284                 l_other_message := 'BOM_RTG_CONREQ_CSEV_SKIP';
6285                 l_other_token_tbl(1).token_name := 'ASSEMBLY_ITEM_NAME';
6286                 l_other_token_tbl(1).token_value :=
6287                                         l_rtg_header_rec.assembly_item_name;
6288                 RAISE EXC_SEV_SKIP_BRANCH;
6289            ELSE
6290                 RAISE EXC_SEV_QUIT_RECORD;
6291            END IF;
6292        ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
6293            THEN
6294                 l_other_message := 'BOM_RTG_CONREQ_UNEXP_SKIP';
6295                 l_other_token_tbl(1).token_name := 'ASSEMBLY_ITEM_NAME';
6296                 l_other_token_tbl(1).token_value := l_rtg_header_rec.assembly_item_name;
6297                 RAISE EXC_UNEXP_SKIP_OBJECT;
6298        ELSIF l_return_status ='S' AND
6299                 l_Mesg_Token_Tbl.COUNT <>0
6300        THEN
6301                 Bom_Rtg_Error_Handler.Log_Error
6302                 (  p_rtg_header_rec        => l_rtg_header_rec
6303                 ,  p_rtg_revision_tbl      => l_rtg_revision_tbl
6304                 ,  p_operation_tbl         => l_operation_tbl
6305                 ,  p_op_resource_tbl       => l_op_resource_tbl
6306                 ,  p_sub_resource_tbl      => l_sub_resource_tbl
6307                 ,  p_op_network_tbl        => l_op_network_tbl
6308                 ,  p_mesg_token_tbl        => l_mesg_token_tbl
6309                 ,  p_error_status          => 'W'
6310                 ,  p_error_level           => Error_Handler.G_RTG_LEVEL
6311                 ,  p_other_message         => NULL
6312                 ,  p_other_mesg_appid      => 'BOM'
6313                 ,  p_other_status          => NULL
6314                 ,  p_other_token_tbl       => Error_Handler.G_MISS_TOKEN_TBL
6315                 ,  p_error_scope           => NULL
6316                 ,  p_entity_index          => 1
6317                 ,  x_rtg_header_rec        => l_rtg_header_rec
6318                 ,  x_rtg_revision_tbl      => l_rtg_revision_tbl
6319                 ,  x_operation_tbl         => l_operation_tbl
6320                 ,  x_op_resource_tbl       => l_op_resource_tbl
6321                 ,  x_sub_resource_tbl      => l_sub_resource_tbl
6322                 ,  x_op_network_tbl        => l_op_network_tbl
6323                 );
6324         END IF;
6325 
6326         --
6327         -- Process Flow step 14 - Entity Level Defaulting for Operation CREATE
6328         -- and operation update.
6329 
6330         IF l_rtg_header_rec.Transaction_Type IN (
6331                      BOM_Rtg_Globals.G_OPR_CREATE, BOM_Rtg_Globals.G_OPR_UPDATE)
6332         THEN
6333 
6334            BOM_Default_Rtg_Header.Entity_Attribute_Defaulting
6335                 (   p_rtg_header_rec            => l_rtg_header_rec
6336                 ,   p_rtg_header_unexp_rec      => l_rtg_header_unexp_rec
6337                 ,   x_rtg_header_rec            => l_rtg_header_rec
6338                 ,   x_rtg_header_unexp_rec      => l_rtg_header_unexp_rec
6339                 ,   x_Mesg_Token_Tbl            => l_Mesg_Token_Tbl
6340                 ,   x_return_status             => l_return_status
6341                 );
6342 
6343 IF BOM_Rtg_Globals.Get_Debug = 'Y' THEN
6344     Error_Handler.Write_Debug ('Rtg Header: Entity Level Defaulting. Return Status :  '||  l_return_status  );
6345 END IF ;
6346 
6347            IF l_return_status = Error_Handler.G_STATUS_ERROR
6348            THEN
6349              IF l_rtg_header_rec.transaction_type = 'CREATE'
6350              THEN
6351                 l_other_message := 'BOM_RTG_ENTDEF_CSEV_SKIP';
6352                 l_other_token_tbl(1).token_name := 'ASSEMBLY_ITEM_NAME';
6353                 l_other_token_tbl(1).token_value :=
6354                                         l_rtg_header_rec.assembly_item_name;
6355                 RAISE EXC_SEV_SKIP_BRANCH;
6356              ELSE
6357                 RAISE EXC_SEV_QUIT_RECORD;
6358               END IF;
6359            ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
6360            THEN
6361                 l_other_message := 'BOM_RTG_ENTDEF_UNEXP_SKIP';
6362                 l_other_token_tbl(1).token_name := 'ASSEMBLY_ITEM_NAME';
6363                 l_other_token_tbl(1).token_value :=
6364                                         l_rtg_header_rec.assembly_item_name;
6365                 RAISE EXC_UNEXP_SKIP_OBJECT;
6366            ELSIF l_return_status ='S' AND
6367                 l_Mesg_Token_Tbl.COUNT <>0
6368            THEN
6369            Bom_Rtg_Error_Handler.Log_Error
6370                 (  p_rtg_header_rec        => l_rtg_header_rec
6371                 ,  p_rtg_revision_tbl      => l_rtg_revision_tbl
6372                 ,  p_operation_tbl         => l_operation_tbl
6373                 ,  p_op_resource_tbl       => l_op_resource_tbl
6374                 ,  p_sub_resource_tbl      => l_sub_resource_tbl
6375                 ,  p_op_network_tbl        => l_op_network_tbl
6376                 ,  p_mesg_token_tbl        => l_mesg_token_tbl
6377                 ,  p_error_status          => 'W'
6378                 ,  p_error_level           => Error_Handler.G_RTG_LEVEL
6379                 ,  p_other_message         => NULL
6380                 ,  p_other_mesg_appid      => 'BOM'
6381                 ,  p_other_status          => NULL
6382                 ,  p_other_token_tbl       => Error_Handler.G_MISS_TOKEN_TBL
6383                 ,  p_error_scope           => NULL
6384                 ,  p_entity_index          => 1
6385                 ,  x_rtg_header_rec        => l_rtg_header_rec
6386                 ,  x_rtg_revision_tbl      => l_rtg_revision_tbl
6387                 ,  x_operation_tbl         => l_operation_tbl
6388                 ,  x_op_resource_tbl       => l_op_resource_tbl
6389                 ,  x_sub_resource_tbl      => l_sub_resource_tbl
6390                 ,  x_op_network_tbl        => l_op_network_tbl
6391                 );
6392            END IF;
6393         END IF;
6394 
6395 
6396 
6397         --
6398         -- Process Flow step 15 - Entity Level Validation
6399         --
6400 
6401         --IF l_rtg_header_rec.transaction_type <> G_Globals.G_OPR_DELETE
6402         IF l_rtg_header_rec.transaction_type <> 'DELETE'
6403         THEN
6404 		Bom_Validate_Rtg_Header.Check_Entity
6405                 (  x_return_status        => l_return_status
6406                 ,  x_Mesg_Token_Tbl       => l_Mesg_Token_Tbl
6407                 ,  p_rtg_header_rec       => l_rtg_header_rec
6408                 ,  p_rtg_header_unexp_rec => l_rtg_header_unexp_rec
6409                 ,  p_old_rtg_header_rec   => l_rtg_header_rec
6410                 ,  p_old_rtg_header_unexp_rec => l_old_rtg_header_unexp_rec
6411                 );
6412 
6413 IF BOM_Rtg_Globals.Get_Debug = 'Y' THEN
6414     Error_Handler.Write_Debug ('Rtg Header: Check Entity. Return Status : '||  l_return_status  );
6415 END IF ;
6416 
6417         ELSE
6418                 Bom_Validate_Rtg_Header.Check_Entity_Delete
6419                 ( x_return_status       => l_return_status
6420                 , x_Mesg_Token_Tbl      => l_mesg_token_tbl
6421                 , p_rtg_header_rec      => l_rtg_header_rec
6422                 , p_rtg_header_Unexp_Rec  => l_rtg_header_unexp_rec
6423                 , x_rtg_header_unexp_rec        => l_rtg_header_unexp_rec
6424                 );
6425 
6426 IF BOM_Rtg_Globals.Get_Debug = 'Y' THEN
6427     Error_Handler.Write_Debug ('Rtg Header: Check Entity for Deleting. Return Status : '||  l_return_status  );
6428 END IF ;
6429 
6430         END IF;
6431 
6432         IF l_return_status = Error_Handler.G_STATUS_ERROR
6433         THEN
6434                 IF l_rtg_header_rec.transaction_type = BOM_Rtg_Globals.G_OPR_CREATE
6435                 THEN
6436                 l_other_message := 'BOM_RTG_ENTVAL_CSEV_SKIP';
6437                 l_other_token_tbl(1).token_name := 'ASSEMBLY_ITEM_NAME';
6438                 l_other_token_tbl(1).token_value :=
6439                                         l_rtg_header_rec.assembly_item_name;
6440                         RAISE EXC_SEV_SKIP_BRANCH;
6441                 ELSE
6442                         RAISE EXC_SEV_QUIT_RECORD;
6443                 END IF;
6444         ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
6445         THEN
6446           l_other_message := 'BOM_RTG_ENTVAL_UNEXP_SKIP';
6447           l_other_token_tbl(1).token_name := 'ASSEMBLY_ITEM_NAME';
6448           l_other_token_tbl(1).token_value :=
6449                                   l_rtg_header_rec.assembly_item_name;
6450            RAISE EXC_UNEXP_SKIP_OBJECT;
6451         ELSIF l_return_status ='S' AND
6452            l_Mesg_Token_Tbl.COUNT <>0
6453         THEN
6454                 Bom_Rtg_Error_Handler.Log_Error
6455                 (  p_rtg_header_rec        => l_rtg_header_rec
6456                 ,  p_rtg_revision_tbl      => l_rtg_revision_tbl
6457                 ,  p_operation_tbl         => l_operation_tbl
6458                 ,  p_op_resource_tbl       => l_op_resource_tbl
6459                 ,  p_sub_resource_tbl      => l_sub_resource_tbl
6460                 ,  p_op_network_tbl        => l_op_network_tbl
6461                 ,  p_mesg_token_tbl        => l_mesg_token_tbl
6462                 ,  p_error_status          => 'W'
6463                 ,  p_error_level           => Error_Handler.G_RTG_LEVEL
6464                 ,  p_other_message         => NULL
6465                 ,  p_other_mesg_appid      => 'BOM'
6466                 ,  p_other_status          => NULL
6467                 ,  p_other_token_tbl       => Error_Handler.G_MISS_TOKEN_TBL
6468                 ,  p_error_scope           => NULL
6469                 ,  p_entity_index          => 1
6470                 ,  x_rtg_header_rec        => l_rtg_header_rec
6471                 ,  x_rtg_revision_tbl      => l_rtg_revision_tbl
6472                 ,  x_operation_tbl         => l_operation_tbl
6473                 ,  x_op_resource_tbl       => l_op_resource_tbl
6474                 ,  x_sub_resource_tbl      => l_sub_resource_tbl
6475                 ,  x_op_network_tbl        => l_op_network_tbl
6476                 );
6477         END IF;
6478 
6479         --
6480         -- Process Flow step 16 : Database Writes
6481         --
6482         BOM_Rtg_Header_Util.Perform_Writes
6483         (   p_rtg_header_rec            => l_rtg_header_rec
6484         ,   p_rtg_header_unexp_rec      => l_rtg_header_unexp_rec
6485         ,   x_Mesg_Token_Tbl            => l_Mesg_Token_Tbl
6486         ,   x_return_status             => l_return_status
6487         );
6488 
6489 IF BOM_Rtg_Globals.Get_Debug = 'Y' THEN
6490     Error_Handler.Write_Debug ('Rtg Header: Perform DB Writes. Return Status :  '||  l_return_status  );
6491 END IF ;
6492 
6493         IF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
6494         THEN
6495             l_other_message := 'BOM_RTG_WRITES_UNEXP_SKIP';
6496             l_other_token_tbl(1).token_name := 'ASSEMBLY_ITEM_NAME';
6497             l_other_token_tbl(1).token_value :=
6498                                 l_rtg_header_rec.assembly_item_name;
6499             RAISE EXC_UNEXP_SKIP_OBJECT;
6500         ELSIF l_return_status ='S' AND
6501             l_Mesg_Token_Tbl.COUNT <>0
6502         THEN
6503             Bom_Rtg_Error_Handler.Log_Error
6504             (  p_rtg_header_rec        => l_rtg_header_rec
6505             ,  p_rtg_revision_tbl      => l_rtg_revision_tbl
6506             ,  p_operation_tbl         => l_operation_tbl
6507             ,  p_op_resource_tbl       => l_op_resource_tbl
6508             ,  p_sub_resource_tbl      => l_sub_resource_tbl
6509             ,  p_op_network_tbl        => l_op_network_tbl
6510             ,  p_mesg_token_tbl        => l_mesg_token_tbl
6511             ,  p_error_status          => 'W'
6512             ,  p_error_level           => Error_Handler.G_RTG_LEVEL
6513             ,  p_other_message         => NULL
6514             ,  p_other_mesg_appid      => 'BOM'
6515             ,  p_other_status          => NULL
6516             ,  p_other_token_tbl       => Error_Handler.G_MISS_TOKEN_TBL
6517             ,  p_error_scope           => NULL
6518             ,  p_entity_index          => 1
6519             ,  x_rtg_header_rec        => l_rtg_header_rec
6520             ,  x_rtg_revision_tbl      => l_rtg_revision_tbl
6521             ,  x_operation_tbl         => l_operation_tbl
6522             ,  x_op_resource_tbl       => l_op_resource_tbl
6523             ,  x_sub_resource_tbl      => l_sub_resource_tbl
6524             ,  x_op_network_tbl        => l_op_network_tbl
6525             );
6526 
6527         END IF;
6528      EXCEPTION
6529 
6530      WHEN EXC_SEV_QUIT_RECORD THEN
6531           Bom_Rtg_Error_Handler.Log_Error
6532                 (  p_rtg_header_rec        => l_rtg_header_rec
6533                 ,  p_rtg_revision_tbl      => l_rtg_revision_tbl
6534                 ,  p_operation_tbl         => l_operation_tbl
6535                 ,  p_op_resource_tbl       => l_op_resource_tbl
6536                 ,  p_sub_resource_tbl      => l_sub_resource_tbl
6537                 ,  p_op_network_tbl        => l_op_network_tbl
6538                 ,  p_mesg_token_tbl        => l_mesg_token_tbl
6539                 ,  p_error_status          => Error_Handler.G_STATUS_ERROR
6540                 ,  p_error_scope           => Error_Handler.G_SCOPE_RECORD
6541                 ,  p_error_level           => Error_Handler.G_RTG_LEVEL
6542                 ,  p_other_message         => NULL
6543                 ,  p_other_mesg_appid      => 'BOM'
6544                 ,  p_other_status          => NULL
6545                 ,  p_other_token_tbl       => Error_Handler.G_MISS_TOKEN_TBL
6546                 ,  p_entity_index          => 1
6547                 ,  x_rtg_header_rec        => l_rtg_header_rec
6548                 ,  x_rtg_revision_tbl      => l_rtg_revision_tbl
6549                 ,  x_operation_tbl         => l_operation_tbl
6550                 ,  x_op_resource_tbl       => l_op_resource_tbl
6551                 ,  x_sub_resource_tbl      => l_sub_resource_tbl
6552                 ,  x_op_network_tbl        => l_op_network_tbl
6553                 );
6554 
6555         x_return_status                := l_return_status;
6556         x_Mesg_Token_Tbl               := l_Mesg_Token_Tbl;
6557         x_rtg_header_rec               := l_rtg_header_rec;
6558         x_rtg_revision_tbl             := l_rtg_revision_tbl;
6559         x_operation_tbl                := l_operation_tbl;
6560         x_op_resource_tbl              := l_op_resource_tbl;
6561         x_sub_resource_tbl             := l_sub_resource_tbl;
6562         x_op_network_tbl               := l_op_network_tbl;
6563 
6564        WHEN EXC_SEV_QUIT_BRANCH THEN
6565 
6566                 Bom_Rtg_Error_Handler.Log_Error
6567                 (  p_rtg_header_rec         => l_rtg_header_rec
6568                 ,  p_rtg_revision_tbl       => l_rtg_revision_tbl
6569                 ,  p_operation_tbl          => l_operation_tbl
6570                 ,  p_op_resource_tbl        => l_op_resource_tbl
6571                 ,  p_sub_resource_tbl       => l_sub_resource_tbl
6572                 ,  p_op_network_tbl         => l_op_network_tbl
6573                 ,  p_mesg_token_tbl         => l_mesg_token_tbl
6574                 ,  p_error_status           => Error_Handler.G_STATUS_ERROR
6575                 ,  p_error_scope            => Error_Handler.G_SCOPE_CHILDREN
6576                 ,  p_other_status           => Error_Handler.G_STATUS_ERROR
6577                 ,  p_other_message          => l_other_message
6578                 ,  p_other_token_tbl        => l_other_token_tbl
6579                 ,  p_error_level            => Error_Handler.G_RTG_LEVEL
6580                 ,  p_other_mesg_appid       => 'BOM'
6581                 ,  p_entity_index           => 1
6582                 ,  x_rtg_header_rec         => l_rtg_header_rec
6583                 ,  x_rtg_revision_tbl       => l_rtg_revision_tbl
6584                 ,  x_operation_tbl          => l_operation_tbl
6585                 ,  x_op_resource_tbl        => l_op_resource_tbl
6586                 ,  x_sub_resource_tbl       => l_sub_resource_tbl
6587                 ,  x_op_network_tbl         => l_op_network_tbl
6588                 );
6589 
6590         x_return_status                := l_return_status;
6591         x_Mesg_Token_Tbl               := l_Mesg_Token_Tbl;
6592         x_rtg_header_rec               := l_rtg_header_rec;
6593         x_rtg_revision_tbl             := l_rtg_revision_tbl;
6594         x_operation_tbl                := l_operation_tbl;
6595         x_op_resource_tbl              := l_op_resource_tbl;
6596         x_sub_resource_tbl             := l_sub_resource_tbl;
6597         x_op_network_tbl               := l_op_network_tbl;
6598         RETURN;
6599 
6600     WHEN EXC_SEV_SKIP_BRANCH THEN
6601 
6602              Bom_Rtg_Error_Handler.Log_Error
6603                 (  p_rtg_header_rec        => l_rtg_header_rec
6604                 ,  p_rtg_revision_tbl      => l_rtg_revision_tbl
6605                 ,  p_operation_tbl         => l_operation_tbl
6606                 ,  p_op_resource_tbl       => l_op_resource_tbl
6607                 ,  p_sub_resource_tbl      => l_sub_resource_tbl
6608                 ,  p_op_network_tbl        => l_op_network_tbl
6609                 ,  p_mesg_token_tbl        => l_mesg_token_tbl
6610                 ,  p_error_status          => Error_Handler.G_STATUS_ERROR
6611                 ,  p_error_scope           => Error_Handler.G_SCOPE_RECORD
6612                 ,  p_error_level           => Error_Handler.G_RTG_LEVEL
6613                 ,  p_other_message         => l_other_message
6614                 ,  p_other_token_tbl       => l_other_token_tbl
6615                 ,  p_other_status          => Error_Handler.G_STATUS_NOT_PICKED
6616                 ,  p_other_mesg_appid      => 'BOM'
6617                 ,  p_entity_index          => 1
6618                 ,  x_rtg_header_rec        => l_rtg_header_rec
6619                 ,  x_rtg_revision_tbl      => l_rtg_revision_tbl
6620                 ,  x_operation_tbl         => l_operation_tbl
6621                 ,  x_op_resource_tbl       => l_op_resource_tbl
6622                 ,  x_sub_resource_tbl      => l_sub_resource_tbl
6623                 ,  x_op_network_tbl        => l_op_network_tbl
6624                 );
6625 
6626         x_return_status                := l_return_status;
6627         x_Mesg_Token_Tbl               := l_Mesg_Token_Tbl;
6628         x_rtg_header_rec               := l_rtg_header_rec;
6629         x_rtg_revision_tbl             := l_rtg_revision_tbl;
6630         x_operation_tbl                := l_operation_tbl;
6631         x_op_resource_tbl              := l_op_resource_tbl;
6632         x_sub_resource_tbl             := l_sub_resource_tbl;
6633         x_op_network_tbl               := l_op_network_tbl;
6634         RETURN;
6635 
6636     WHEN EXC_FAT_QUIT_OBJECT THEN
6637 
6638                 Bom_Rtg_Error_Handler.Log_Error
6639                 (  p_rtg_header_rec         => l_rtg_header_rec
6640                 ,  p_rtg_revision_tbl       => l_rtg_revision_tbl
6641                 ,  p_operation_tbl          => l_operation_tbl
6642                 ,  p_op_resource_tbl        => l_op_resource_tbl
6643                 ,  p_sub_resource_tbl       => l_sub_resource_tbl
6644                 ,  p_op_network_tbl         => l_op_network_tbl
6645                 ,  p_mesg_token_tbl         => l_mesg_token_tbl
6646                 ,  p_error_status           => Error_Handler.G_STATUS_FATAL
6647                 ,  p_error_scope            => Error_Handler.G_SCOPE_ALL
6648                 ,  p_other_message          => l_other_message
6649                 ,  p_other_status           => Error_Handler.G_STATUS_FATAL
6650                 ,  p_other_token_tbl        => l_other_token_tbl
6651                 ,  p_error_level            => Error_Handler.G_RTG_LEVEL
6652                 ,  p_other_mesg_appid       => 'BOM'
6653                 ,  p_entity_index           => 1
6654                 ,  x_rtg_header_rec         => l_rtg_header_rec
6655                 ,  x_rtg_revision_tbl       => l_rtg_revision_tbl
6656                 ,  x_operation_tbl          => l_operation_tbl
6657                 ,  x_op_resource_tbl        => l_op_resource_tbl
6658                 ,  x_sub_resource_tbl       => l_sub_resource_tbl
6659                 ,  x_op_network_tbl         => l_op_network_tbl
6660                 );
6661 
6662         x_return_status                := l_return_status;
6663         x_Mesg_Token_Tbl               := l_Mesg_Token_Tbl;
6664         x_rtg_header_rec               := l_rtg_header_rec;
6665         x_rtg_revision_tbl             := l_rtg_revision_tbl;
6666         x_operation_tbl                := l_operation_tbl;
6667         x_op_resource_tbl              := l_op_resource_tbl;
6668         x_sub_resource_tbl             := l_sub_resource_tbl;
6669         x_op_network_tbl               := l_op_network_tbl;
6670         l_return_status := 'Q';
6671 
6672     WHEN EXC_UNEXP_SKIP_OBJECT THEN
6673 
6674                 Bom_Rtg_Error_Handler.Log_Error
6675                 (  p_rtg_header_rec         => l_rtg_header_rec
6676                 ,  p_rtg_revision_tbl       => l_rtg_revision_tbl
6677                 ,  p_operation_tbl          => l_operation_tbl
6678                 ,  p_op_resource_tbl        => l_op_resource_tbl
6679                 ,  p_sub_resource_tbl       => l_sub_resource_tbl
6680                 ,  p_op_network_tbl         => l_op_network_tbl
6681                 ,  p_mesg_token_tbl         => l_mesg_token_tbl
6682                 ,  p_error_status           => Error_Handler.G_STATUS_UNEXPECTED
6683                 ,  p_other_status           => Error_Handler.G_STATUS_NOT_PICKED
6684                 ,  p_other_message          => l_other_message
6685                 ,  p_other_token_tbl        => l_other_token_tbl
6686                 ,  p_error_level            => Error_Handler.G_RTG_LEVEL
6687                 ,  p_other_mesg_appid       => 'BOM'
6688                 ,  p_error_scope            => NULL
6689                 ,  p_entity_index           => 1
6690                 ,  x_rtg_header_rec         => l_rtg_header_rec
6691                 ,  x_rtg_revision_tbl       => l_rtg_revision_tbl
6692                 ,  x_operation_tbl          => l_operation_tbl
6693                 ,  x_op_resource_tbl        => l_op_resource_tbl
6694                 ,  x_sub_resource_tbl       => l_sub_resource_tbl
6695                 ,  x_op_network_tbl         => l_op_network_tbl
6696                 );
6697 
6698         x_return_status                := l_return_status;
6699         x_Mesg_Token_Tbl               := l_Mesg_Token_Tbl;
6700         x_rtg_header_rec               := l_rtg_header_rec;
6701         x_rtg_revision_tbl             := l_rtg_revision_tbl;
6702         x_operation_tbl                := l_operation_tbl;
6703         x_op_resource_tbl              := l_op_resource_tbl;
6704         x_sub_resource_tbl             := l_sub_resource_tbl;
6705         x_op_network_tbl               := l_op_network_tbl;
6706         l_return_status := 'U';
6707 
6708     END; -- END Header processing block
6709 
6710     IF l_return_status in ('Q', 'U')
6711     THEN
6712         x_return_status := l_return_status;
6713         RETURN;
6714     END IF;
6715 
6716     l_bo_return_status := l_return_status;
6717 
6718         --
6719         -- Process Rtg Revisions that are chilren of this header
6720         --
6721 
6722         Rtg_Revisions
6723         (   p_validation_level      => p_validation_level
6724         ,   p_assembly_item_name    => l_rtg_header_rec.assembly_item_name
6725         ,   p_assembly_item_id      => NULL
6726         ,   p_organization_id       => l_rtg_header_unexp_rec.organization_id
6727         ,   p_alternate_rtg_code    => l_rtg_header_rec.alternate_routing_code
6728         ,   p_rtg_revision_tbl      => l_rtg_revision_tbl
6729         ,   p_operation_tbl         => l_operation_tbl
6730         ,   p_op_resource_tbl       => l_op_resource_tbl
6731         ,   p_sub_resource_tbl      => l_sub_resource_tbl
6732         ,   p_op_network_tbl        => l_op_network_tbl
6733         ,   x_rtg_revision_tbl      => l_rtg_revision_tbl
6734         ,   x_operation_tbl         => l_operation_tbl
6735         ,   x_op_resource_tbl       => l_op_resource_tbl
6736         ,   x_sub_resource_tbl      => l_sub_resource_tbl
6737         ,   x_op_network_tbl        => l_op_network_tbl
6738         ,   x_Mesg_Token_Tbl        => l_Mesg_Token_Tbl
6739         ,   x_return_status         => l_return_status
6740         );
6741 
6742     IF l_return_status <> 'S'
6743     THEN
6744         l_bo_return_status := l_return_status;
6745     END IF;
6746 
6747     -- Process operations that are orphans (without immediate revised
6748     -- item parents) but are indirect children of this header
6749 
6750 	 Operation_Sequences
6751          (   p_validation_level    => p_validation_level
6752          ,   p_assembly_item_name  => l_rtg_header_rec.assembly_item_name
6753          ,   p_organization_id     => l_rtg_header_unexp_rec.organization_id
6754          ,   p_alternate_routing_code => l_rtg_header_rec.alternate_routing_code
6755          ,   p_operation_tbl       => l_operation_tbl
6756          ,   p_op_resource_tbl     => l_op_resource_tbl
6757          ,   p_sub_resource_tbl    => l_sub_resource_tbl
6758          ,   p_op_network_tbl      => l_op_network_tbl
6759          ,   x_operation_tbl       => l_operation_tbl
6760          ,   x_op_resource_tbl     => l_op_resource_tbl
6761          ,   x_sub_resource_tbl    => l_sub_resource_tbl
6762          ,   x_op_network_tbl      => l_op_network_tbl
6763          ,   x_Mesg_Token_Tbl      => l_Mesg_Token_Tbl
6764          ,   x_return_status       => l_return_status
6765         );
6766 
6767     IF l_return_status <> 'S'
6768     THEN
6769         l_bo_return_status := l_return_status;
6770     END IF;
6771 
6772     -- Check if the value of SSOS is valid -- Added for SSOS (bug 2689249)
6773 	IF l_rtg_header_rec.ser_start_op_seq IS NOT NULL THEN
6774 
6775 	   BOM_Validate_Rtg_Header.Check_SSOS
6776 	   ( p_rtg_header_rec	=> l_rtg_header_rec
6777            , p_rtg_header_unexp_rec  => l_rtg_header_unexp_rec
6778 	   , x_mesg_token_tbl	=> l_Mesg_Token_Tbl
6779 	   , x_return_status	=> l_return_status
6780 	   );
6781 
6782 	   IF l_return_status <> 'S'
6783 	   THEN
6784 		l_bo_return_status := l_return_status;
6785 		IF l_Mesg_Token_Tbl.COUNT <> 0 THEN
6786                     Bom_Rtg_Error_Handler.Log_Error
6787 		    (  p_rtg_header_rec         => l_rtg_header_rec
6788 		    ,  p_rtg_revision_tbl       => l_rtg_revision_tbl
6789 		    ,  p_operation_tbl          => l_operation_tbl
6790 		    ,  p_op_resource_tbl        => l_op_resource_tbl
6791 		    ,  p_sub_resource_tbl       => l_sub_resource_tbl
6792 		    ,  p_op_network_tbl         => l_op_network_tbl
6793 		    ,  p_mesg_token_tbl         => l_mesg_token_tbl
6794 		    ,  p_error_status           => Error_Handler.G_STATUS_ERROR
6795 		    ,  p_other_status           => NULL
6796 		    ,  p_other_message          => l_other_message
6797 		    ,  p_other_token_tbl        => l_other_token_tbl
6798 		    ,  p_error_level            => Error_Handler.G_RTG_LEVEL
6799 		    ,  p_other_mesg_appid       => 'BOM'
6800 		    ,  p_error_scope            => NULL
6801 		    ,  p_entity_index           => 1
6802 		    ,  x_rtg_header_rec         => l_rtg_header_rec
6803 		    ,  x_rtg_revision_tbl       => l_rtg_revision_tbl
6804 		    ,  x_operation_tbl          => l_operation_tbl
6805 		    ,  x_op_resource_tbl        => l_op_resource_tbl
6806 		    ,  x_sub_resource_tbl       => l_sub_resource_tbl
6807 		    ,  x_op_network_tbl         => l_op_network_tbl
6808 		    );
6809 		END IF;
6810 	   END IF;
6811 	END IF;
6812 
6813     --
6814     -- Process resource that are orphans (without immediate revised
6815     -- item parents) but are indirect children of this header
6816          Operation_Resources
6817          (   p_validation_level    => p_validation_level
6818          ,   p_assembly_item_name  => l_rtg_header_rec.assembly_item_name
6819          ,   p_organization_id     => l_rtg_header_unexp_rec.organization_id
6820          ,   p_effectivity_date  => NULL
6821          ,   p_operation_type    => NULL
6822          ,   p_operation_seq_num => NULL
6823          ,   p_alternate_routing_code   =>
6824                                   l_rtg_header_rec.alternate_routing_code
6825          ,   p_op_resource_tbl     => l_op_resource_tbl
6826          ,   p_sub_resource_tbl    => l_sub_resource_tbl
6827          ,   x_op_resource_tbl     => l_op_resource_tbl
6828          ,   x_sub_resource_tbl    => l_sub_resource_tbl
6829          ,   x_Mesg_Token_Tbl      => l_Mesg_Token_Tbl
6830          ,   x_return_status       => l_return_status
6831     );
6832 
6833     IF l_return_status <> 'S'
6834     THEN
6835         l_bo_return_status := l_return_status;
6836     END IF;
6837 
6838     --
6839     -- Process substitue resource that are orphans (without immediate revised
6840     -- item parents) but are indirect children of this header
6841 
6842         Sub_Operation_Resources
6843         (   p_validation_level     => p_validation_level
6844         ,   p_assembly_item_name   => l_rtg_header_rec.assembly_item_name
6845         ,   p_organization_id      => l_rtg_header_unexp_rec.organization_id
6846         ,   p_alternate_routing_code    =>
6847                                       l_rtg_header_rec.alternate_routing_code
6848         ,   p_sub_resource_tbl     => l_sub_resource_tbl
6849         ,   p_operation_seq_num =>  NULL
6850         ,   p_effectivity_date => NULL
6851         ,   p_operation_type => NULL
6852         ,   x_sub_resource_tbl     => l_sub_resource_tbl
6853         ,   x_Mesg_Token_Tbl       => l_Mesg_Token_Tbl
6854         ,   x_return_status        => l_return_status
6855         );
6856 
6857     IF l_return_status <> 'S'
6858     THEN
6859         l_bo_return_status := l_return_status;
6860     END IF;
6861        Op_networks
6862        (   p_validation_level         => p_validation_level
6863        ,   p_assembly_item_id         => l_rtg_header_unexp_rec.assembly_item_id
6864        ,   p_assembly_item_name       => l_rtg_header_rec.assembly_item_name
6865        ,   p_organization_id          => l_rtg_header_unexp_rec.organization_id
6866        ,   p_alternate_rtg_code       => l_rtg_header_rec.alternate_routing_code
6867        ,   p_op_network_tbl           => l_op_network_tbl
6868        ,   x_op_network_tbl           => l_op_network_tbl
6869        ,   x_Mesg_Token_Tbl           => l_Mesg_Token_Tbl
6870        ,   x_return_status            => l_return_status
6871         );
6872 
6873     -- bug:5235684 SSOS is required for standard/network routing for serial controlled item
6874     -- and it should be present on primary path.
6875     IF ( l_return_status = FND_API.G_RET_STS_SUCCESS )
6876     THEN
6877       Bom_Validate_Rtg_Header.Validate_SSOS
6878           (  p_routing_sequence_id  => l_rtg_header_unexp_rec.routing_sequence_id
6879            , p_ser_start_op_seq     => l_rtg_header_rec.ser_start_op_seq
6880            , p_validate_from_table  => FALSE
6881            , x_mesg_token_tbl       => l_Mesg_Token_Tbl
6882            , x_return_status        => l_return_status );
6883 
6884       IF  ( ( l_return_status <> FND_API.G_RET_STS_SUCCESS ) AND
6885             ( l_Mesg_Token_Tbl.COUNT <> 0 ) )
6886       THEN
6887           Bom_Rtg_Error_Handler.Log_Error
6888             (  p_rtg_header_rec         => l_rtg_header_rec
6889             ,  p_rtg_revision_tbl       => l_rtg_revision_tbl
6890             ,  p_operation_tbl          => l_operation_tbl
6891             ,  p_op_resource_tbl        => l_op_resource_tbl
6892             ,  p_sub_resource_tbl       => l_sub_resource_tbl
6893             ,  p_op_network_tbl         => l_op_network_tbl
6894             ,  p_mesg_token_tbl         => l_mesg_token_tbl
6895             ,  p_error_status           => Error_Handler.G_STATUS_ERROR
6896             ,  p_other_status           => NULL
6897             ,  p_other_message          => l_other_message
6898             ,  p_other_token_tbl        => l_other_token_tbl
6899             ,  p_error_level            => Error_Handler.G_RTG_LEVEL
6900             ,  p_other_mesg_appid       => 'BOM'
6901             ,  p_error_scope            => NULL
6902             ,  p_entity_index           => 1
6903             ,  x_rtg_header_rec         => l_rtg_header_rec
6904             ,  x_rtg_revision_tbl       => l_rtg_revision_tbl
6905             ,  x_operation_tbl          => l_operation_tbl
6906             ,  x_op_resource_tbl        => l_op_resource_tbl
6907             ,  x_sub_resource_tbl       => l_sub_resource_tbl
6908             ,  x_op_network_tbl         => l_op_network_tbl
6909             );
6910       END IF; -- end if l_return_status <> 'S'
6911     END IF; -- end if ( l_return_status = FND_API.G_RET_STS_SUCCESS )
6912 
6913     IF l_return_status <> 'S'
6914     THEN
6915         l_bo_return_status := l_return_status;
6916     END IF;
6917 
6918 
6919      --  Load OUT parameters
6920 
6921      x_return_status                := l_bo_return_status;
6922      x_rtg_header_rec               := l_rtg_header_rec;
6923      x_rtg_revision_tbl             := l_rtg_revision_tbl;
6924      x_operation_tbl                := l_operation_tbl;
6925      x_op_resource_tbl              := l_op_resource_tbl;
6926      x_sub_resource_tbl             := l_sub_resource_tbl;
6927      x_op_network_tbl               := l_op_network_tbl;
6928 
6929 END Rtg_Header;
6930 
6931 
6932 /***************************************************************************
6933 * Procedure     : Process_Rtg
6934 * Parameters IN : RTG Business Object Entities, Record for Header and tables
6935 *                 for the remaining entities
6936 * Parameters OUT: RTG Business Object Entities, Record for Header and tables
6937 *                 for the remaining entities
6938 * Returns       : None
6939 * Purpose       : This is the only exposed procedure in the PVT API.
6940 *                 Process_Rtg will drive the business object processing. It
6941 *                 will take each entity and call individual procedure that will
6942 *                 handle the processing of that entity and its children.
6943 ****************************************************************************/
6944 PROCEDURE Process_Rtg
6945 (   p_api_version_number      IN  NUMBER
6946   , p_validation_level        IN  NUMBER
6947   , x_return_status           IN OUT NOCOPY VARCHAR2
6948   , x_msg_count               IN OUT NOCOPY NUMBER
6949   , p_rtg_header_rec          IN  Bom_Rtg_Pub.Rtg_Header_Rec_Type
6950   , p_rtg_revision_tbl        IN  Bom_Rtg_Pub.Rtg_Revision_Tbl_Type
6951   , p_operation_tbl           IN  Bom_Rtg_Pub.Operation_Tbl_Type
6952   , p_op_resource_tbl         IN  Bom_Rtg_Pub.Op_Resource_Tbl_Type
6953   , p_sub_resource_tbl        IN  Bom_Rtg_Pub.Sub_Resource_Tbl_Type
6954   , p_op_network_tbl          IN  Bom_Rtg_Pub.Op_Network_Tbl_Type
6955   , x_rtg_header_rec          IN OUT NOCOPY Bom_Rtg_Pub.Rtg_Header_Rec_Type
6956   , x_rtg_revision_tbl        IN OUT NOCOPY Bom_Rtg_Pub.Rtg_Revision_Tbl_Type
6957   , x_operation_tbl           IN OUT NOCOPY Bom_Rtg_Pub.Operation_Tbl_Type
6958   , x_op_resource_tbl         IN OUT NOCOPY Bom_Rtg_Pub.Op_Resource_Tbl_Type
6959   , x_sub_resource_tbl        IN OUT NOCOPY Bom_Rtg_Pub.Sub_Resource_Tbl_Type
6960   , x_op_network_tbl          IN OUT NOCOPY Bom_Rtg_Pub.Op_Network_Tbl_Type
6961 )
6962 IS
6963 l_api_version_number          CONSTANT NUMBER := 1.0;
6964 l_api_name                    CONSTANT VARCHAR2(30):= 'Process_Rtg';
6965 l_err_text                    VARCHAR2(240);
6966 l_return_status               VARCHAR2(1);
6967 l_bo_return_status            VARCHAR2(1);
6968 
6969 l_assembly_item_name    VARCHAR2(81);
6970 l_organization_code     VARCHAR2(3);
6971 l_organization_id       NUMBER;
6972 l_rtg_header_rec        Bom_Rtg_Pub.Rtg_Header_Rec_Type;
6973 l_rtg_revision_tbl      Bom_Rtg_Pub.Rtg_Revision_Tbl_Type ;
6974 l_operation_tbl         Bom_Rtg_Pub.Operation_Tbl_Type;
6975 l_op_resource_tbl       Bom_Rtg_Pub.Op_Resource_Tbl_Type ;
6976 l_sub_resource_tbl      Bom_Rtg_Pub.Sub_Resource_Tbl_Type;
6977 l_op_network_tbl        Bom_Rtg_Pub.Op_Network_Tbl_Type;
6978 
6979 
6980 l_mesg_token_tbl              Error_Handler.Mesg_Token_Tbl_Type;
6981 l_other_message               VARCHAR2(2000);
6982 l_other_token_tbl             Error_Handler.Token_Tbl_Type;
6983 
6984 EXC_ERR_PVT_API_MAIN          EXCEPTION;
6985 
6986 BEGIN
6987 IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN
6988     Error_Handler.Write_Debug('Processing Rtg BO Private API . . . ' ) ;
6989 End IF ;
6990 
6991       --  Init local variables.
6992       l_rtg_header_rec    :=  p_rtg_header_rec  ;
6993       l_rtg_revision_tbl  :=  p_rtg_revision_tbl;
6994       l_operation_tbl     :=  p_operation_tbl ;
6995       l_op_resource_tbl   :=  p_op_resource_tbl ;
6996       l_sub_resource_tbl  :=  p_sub_resource_tbl ;
6997       l_op_network_tbl    :=  p_op_network_tbl ;
6998 
6999         -- Business Object starts with a status of Success
7000         l_bo_return_status := 'S';
7001 
7002         --Load environment information into the SYSTEM_INFORMATION record
7003         -- (USER_ID, LOGIN_ID, PROG_APPID, PROG_ID)
7004 
7005         BOM_Rtg_Globals.Init_System_Info_Rec
7006                         (  x_mesg_token_tbl => l_mesg_token_tbl
7007                         ,  x_return_status  => l_return_status
7008                         );
7009 
7010         /* below are changes for OSFM */
7011         BOM_Rtg_Globals.Set_Osfm_NW_Count(0);
7012         BOM_Rtg_Globals.Set_Osfm_NW_Calc_Flag(FALSE);
7013         /* above are changes for OSFM */
7014         /* Initialize System_Information Unit_Effectivity flag
7015 
7016         IF FND_PROFILE.DEFINED('PJM:PJM_UNITEFF_NO_EFFECT') AND
7017                FND_PROFILE.VALUE('PJM:PJM_UNITEFF_NO_EFFECT') = 'Y'
7018         THEN
7019                 BOM_Rtg_Globals.Set_Unit_Effectivity (TRUE);
7020         ELSE
7021                 BOM_Rtg_Globals.Set_Unit_Effectivity (FALSE);
7022         END IF;
7023 
7024        */
7025 
7026         IF l_return_status <> FND_API.G_RET_STS_SUCCESS
7027         THEN
7028                 RAISE EXC_ERR_PVT_API_MAIN;
7029         END IF;
7030 
7031         --
7032         -- Start with processing of the routing header.
7033         --
7034         IF  (l_rtg_header_rec.assembly_item_name <> FND_API.G_MISS_CHAR
7035                 AND l_rtg_header_rec.assembly_item_name IS NOT NULL)
7036         THEN
7037 		Rtg_Header
7038                 (   p_validation_level          => p_validation_level
7039                 ,   p_rtg_header_rec            => l_rtg_header_rec
7040                 ,   p_rtg_revision_tbl          => l_rtg_revision_tbl
7041                 ,   p_operation_tbl             => l_operation_tbl
7042                 ,   p_op_resource_tbl           => l_op_resource_tbl
7043                 ,   p_sub_resource_tbl          => l_sub_resource_tbl
7044                 ,   p_op_network_tbl            => l_op_network_tbl
7045                 ,   x_rtg_header_rec            => l_rtg_header_rec
7046                 ,   x_rtg_revision_tbl          => l_rtg_revision_tbl
7047                 ,   x_operation_tbl             => l_operation_tbl
7048                 ,   x_op_resource_tbl           => l_op_resource_tbl
7049                 ,   x_sub_resource_tbl          => l_sub_resource_tbl
7050                 ,   x_op_network_tbl            => l_op_network_tbl
7051                 ,   x_Mesg_Token_Tbl            => l_Mesg_Token_Tbl
7052                 ,   x_return_status             => l_return_status
7053                 );
7054 
7055                 IF NVL(l_return_status, 'S') = 'Q'
7056                 THEN
7057                         l_return_status := 'F';
7058                         RAISE G_EXC_QUIT_IMPORT;
7059                 ELSIF NVL(l_return_status, 'S') = 'U'
7060                 THEN
7061                         RAISE G_EXC_QUIT_IMPORT;
7062 
7063                 ELSIF NVL(l_return_status, 'S') <> 'S'
7064                 THEN
7065                         l_bo_return_status := l_return_status;
7066                 END IF;
7067 
7068         END IF;  -- Processing Rtg Header Ends
7069 
7070         --
7071         -- Process Rtg Revisions
7072         --
7073         IF l_rtg_revision_tbl.Count <> 0
7074         THEN
7075                 Rtg_Revisions
7076                 (   p_validation_level          => p_validation_level
7077                 ,   p_rtg_revision_tbl          => l_rtg_revision_tbl
7078                 ,   p_operation_tbl             => l_operation_tbl
7079                 ,   p_op_resource_tbl           => l_op_resource_tbl
7080                 ,   p_sub_resource_tbl          => l_sub_resource_tbl
7081                 ,   p_op_network_tbl            => l_op_network_tbl
7082                 ,   p_assembly_item_name => NULL
7083                 ,   p_assembly_item_id=> NULL
7084                 ,   p_organization_id => NULL
7085                 ,   p_alternate_rtg_code => NULL
7086                 ,   x_rtg_revision_tbl          => l_rtg_revision_tbl
7087                 ,   x_operation_tbl             => l_operation_tbl
7088                 ,   x_op_resource_tbl           => l_op_resource_tbl
7089                 ,   x_sub_resource_tbl          => l_sub_resource_tbl
7090                 ,   x_op_network_tbl            => l_op_network_tbl
7091                 ,   x_Mesg_Token_Tbl            => l_Mesg_Token_Tbl
7092                 ,   x_return_status             => l_return_status
7093                 );
7094 
7095                 IF NVL(l_return_status, 'S') = 'Q'
7096                 THEN
7097                         l_return_status := 'F';
7098                         RAISE G_EXC_QUIT_IMPORT;
7099                 ELSIF NVL(l_return_status, 'S') = 'U'
7100                 THEN
7101                         RAISE G_EXC_QUIT_IMPORT;
7102                 ELSIF NVL(l_return_status, 'S') <> 'S'
7103                 THEN
7104                         l_bo_return_status := l_return_status;
7105                 END IF;
7106 
7107         END IF;  -- Processing of Rtg revisions Ends
7108 
7109         --
7110         --  Process operations
7111         --
7112         IF l_operation_tbl.COUNT <> 0
7113         THEN
7114               Operation_Sequences
7115                 (   p_validation_level          => p_validation_level
7116                 ,   p_operation_tbl             => l_operation_tbl
7117                 ,   p_op_resource_tbl           => l_op_resource_tbl
7118                 ,   p_sub_resource_tbl          => l_sub_resource_tbl
7119                 ,   p_op_network_tbl            => l_op_network_tbl
7120                 ,   p_organization_id => NULL
7121                 ,   p_assembly_item_name => NULL
7122                 ,   p_alternate_routing_code => NULL
7123                 ,   x_operation_tbl             => l_operation_tbl
7124                 ,   x_op_resource_tbl           => l_op_resource_tbl
7125                 ,   x_sub_resource_tbl          => l_sub_resource_tbl
7126                 ,   x_op_network_tbl            => l_op_network_tbl
7127                 ,   x_Mesg_Token_Tbl            => l_Mesg_Token_Tbl
7128                 ,   x_return_status             => l_return_status
7129                 );
7130 
7131                 IF NVL(l_return_status, 'S') = 'Q'
7132                 THEN
7133                         l_return_status := 'F';
7134                         RAISE G_EXC_QUIT_IMPORT;
7135                 ELSIF NVL(l_return_status, 'S') = 'U'
7136                 THEN
7137                         RAISE G_EXC_QUIT_IMPORT;
7138                 ELSIF NVL(l_return_status, 'S') <> 'S'
7139                 THEN
7140                         l_bo_return_status := l_return_status;
7141                 END IF;
7142         END IF; -- Processing of operations
7143 /*
7144         -- Not necessary to be called here again
7145 	-- Check if the value of SSOS is valid -- Added for SSOS
7146 	IF l_rtg_header_rec.ser_start_op_seq IS NOT NULL THEN
7147 
7148 	   BOM_Validate_Rtg_Header.Check_SSOS
7149 	   ( p_rtg_header_rec	=> l_rtg_header_rec
7150            , p_rtg_header_unexp_rec  => l_rtg_header_unexp_rec
7151 	   , x_mesg_token_tbl	=> l_Mesg_Token_Tbl
7152 	   , x_return_status	=> l_return_status
7153 	   );
7154 
7155 	   IF l_return_status <> 'S'
7156 	   THEN
7157 		l_bo_return_status := l_return_status;
7158 	   END IF;
7159 	END IF;
7160 */
7161         --
7162         --  Process operation resources
7163         --
7164         IF l_op_resource_tbl.Count <> 0
7165         THEN
7166 	      Operation_Resources
7167                 (   p_validation_level          => p_validation_level
7168                 ,   p_op_resource_tbl           => l_op_resource_tbl
7169                 ,   p_sub_resource_tbl          => l_sub_resource_tbl
7170                 ,   p_organization_id		=> NULL
7171                 ,   p_assembly_item_name	=> NULL
7172                 ,   p_alternate_routing_code	=> NULL
7173                 ,   p_operation_seq_num		=> NULL
7174                 ,   p_effectivity_date		=> NULL
7175                 ,   p_operation_type		=> NULL
7176                 ,   x_op_resource_tbl           => l_op_resource_tbl
7177                 ,   x_sub_resource_tbl          => l_sub_resource_tbl
7178                 ,   x_Mesg_Token_Tbl            => l_Mesg_Token_Tbl
7179                 ,   x_return_status             => l_return_status
7180                 );
7181                 IF NVL(l_return_status, 'S') = 'Q'
7182                 THEN
7183                         l_return_status := 'F';
7184                         RAISE G_EXC_QUIT_IMPORT;
7185                 ELSIF NVL(l_return_status, 'S') = 'U'
7186                 THEN
7187                         RAISE G_EXC_QUIT_IMPORT;
7188                 ELSIF NVL(l_return_status, 'S') <> 'S'
7189                 THEN
7190                         l_bo_return_status := l_return_status;
7191                 END IF;
7192         END IF; -- Processing of operation  resources
7193 
7194         --
7195         --  Process operation substitute resources
7196         --
7197         IF l_sub_resource_tbl.Count <> 0
7198         THEN
7199               Sub_Operation_Resources
7200                 (   p_validation_level          => p_validation_level
7201                 ,   p_sub_resource_tbl          => l_sub_resource_tbl
7202                 ,   p_organization_id		=> NULL
7203                 ,   p_assembly_item_name	=> NULL
7204                 ,   p_alternate_routing_code	=> NULL
7205                 ,   p_operation_seq_num		=>  NULL
7206                 ,   p_effectivity_date		=> NULL
7207                 ,   p_operation_type		=> NULL
7208                 ,   x_sub_resource_tbl          => l_sub_resource_tbl
7209                 ,   x_Mesg_Token_Tbl            => l_Mesg_Token_Tbl
7210                 ,   x_return_status             => l_return_status
7211                 );
7212 
7213                 IF NVL(l_return_status, 'S') = 'Q'
7214                 THEN
7215                         l_return_status := 'F';
7216                         RAISE G_EXC_QUIT_IMPORT;
7217                 ELSIF NVL(l_return_status, 'S') = 'U'
7218                 THEN
7219                         RAISE G_EXC_QUIT_IMPORT;
7220                 ELSIF NVL(l_return_status, 'S') <> 'S'
7221                 THEN
7222                         l_bo_return_status := l_return_status;
7223                 END IF;
7224         END IF; -- Processing of operation sub resources
7225 
7226         --
7227         --  Process operation networks
7228         --
7229         IF l_op_network_tbl.Count <> 0
7230         THEN
7231               Op_Networks
7232                 (
7233                     p_validation_level          => p_validation_level
7234                 ,   p_op_network_tbl            => l_op_network_tbl
7235                 ,   p_assembly_item_name	=> NULL
7236                 ,   p_assembly_item_id		=> NULL
7237                 ,   p_organization_id		=> NULL
7238                 ,   p_alternate_rtg_code	=> NULL
7239                 ,   x_op_network_tbl            => l_op_network_tbl
7240                 ,   x_Mesg_Token_Tbl            => l_Mesg_Token_Tbl
7241                 ,   x_return_status             => l_return_status
7242                 );
7243 
7244                 IF NVL(l_return_status, 'S') = 'Q'
7245                 THEN
7246                         l_return_status := 'F';
7247                         RAISE G_EXC_QUIT_IMPORT;
7248                 ELSIF NVL(l_return_status, 'S') = 'U'
7249                 THEN
7250                         RAISE G_EXC_QUIT_IMPORT;
7251                 ELSIF NVL(l_return_status, 'S') <> 'S'
7252                 THEN
7253                         l_bo_return_status := l_return_status;
7254                 END IF;
7255         END IF; -- Processing of operation network
7256 
7257         x_return_status                := l_bo_return_status;
7258         x_rtg_header_rec               := l_rtg_header_rec;
7259         x_rtg_revision_tbl             := l_rtg_revision_tbl;
7260         x_operation_tbl                := l_operation_tbl;
7261         x_op_resource_tbl              := l_op_resource_tbl;
7262         x_sub_resource_tbl             := l_sub_resource_tbl;
7263         x_op_network_tbl               := l_op_network_tbl;
7264 
7265 
7266     -- Reset system_information business object flags
7267 
7268     BOM_Rtg_Globals.Set_STD_Item_Access( p_std_item_access => NULL);
7269     BOM_Rtg_Globals.Set_MDL_Item_Access( p_mdl_item_access => NULL);
7270     BOM_Rtg_Globals.Set_PLN_Item_Access( p_pln_item_access => NULL);
7271     BOM_Rtg_Globals.Set_OC_Item_Access( p_oc_item_access   => NULL);
7272 
7273 IF BOM_Rtg_Globals.Get_Debug = 'Y' THEN
7274    Error_Handler.Write_Debug
7275    ('-----------------------------------------------------' ) ;
7276    Error_Handler.Write_Debug
7277    ('End of Rtg BO Private API with return_status: ' || x_return_status) ;
7278 END IF;
7279 
7280 -- dbms_output.put_line('after all things with return status = '||x_return_status);
7281 
7282 EXCEPTION
7283 
7284     WHEN EXC_ERR_PVT_API_MAIN THEN
7285     Bom_Rtg_Error_Handler.Log_Error
7286                 (  p_rtg_header_rec        => l_rtg_header_rec
7287                 ,  p_rtg_revision_tbl      => l_rtg_revision_tbl
7288                 ,  p_operation_tbl         => l_operation_tbl
7289                 ,  p_op_resource_tbl       => l_op_resource_tbl
7290                 ,  p_sub_resource_tbl      => l_sub_resource_tbl
7291                 ,  p_op_network_tbl        => l_op_network_tbl
7292                 ,  p_error_status          => FND_API.G_RET_STS_UNEXP_ERROR
7293                 ,  p_other_status          => Error_Handler.G_STATUS_NOT_PICKED
7294                 ,  p_other_message         => l_other_message
7295                 ,  p_other_token_tbl       => l_other_token_tbl
7296                 ,  p_error_level           => 0
7297                 ,  p_Mesg_Token_tbl	       => Error_Handler.G_MISS_MESG_TOKEN_TBL
7298                 ,  p_other_mesg_appid      => 'BOM'
7299                 ,  p_error_scope           => NULL
7300                 ,  p_entity_index          => 1
7301                 ,  x_rtg_header_rec        => l_rtg_header_rec
7302                 ,  x_rtg_revision_tbl      => l_rtg_revision_tbl
7303                 ,  x_operation_tbl         => l_operation_tbl
7304                 ,  x_op_resource_tbl       => l_op_resource_tbl
7305                 ,  x_sub_resource_tbl      => l_sub_resource_tbl
7306                 ,  x_op_network_tbl        => l_op_network_tbl
7307                 );
7308 
7309         x_return_status                := l_return_status;
7310         x_rtg_header_rec               := l_rtg_header_rec;
7311         x_rtg_revision_tbl             := l_rtg_revision_tbl;
7312         x_operation_tbl                := l_operation_tbl;
7313         x_op_resource_tbl              := l_op_resource_tbl;
7314         x_sub_resource_tbl             := l_sub_resource_tbl;
7315         x_op_network_tbl               := l_op_network_tbl;
7316 
7317 -- Reset system_information business object flags
7318 
7319     BOM_Rtg_Globals.Set_STD_Item_Access( p_std_item_access => NULL);
7320     BOM_Rtg_Globals.Set_MDL_Item_Access( p_mdl_item_access => NULL);
7321     BOM_Rtg_Globals.Set_PLN_Item_Access( p_pln_item_access => NULL);
7322     BOM_Rtg_Globals.Set_OC_Item_Access( p_oc_item_access   => NULL);
7323 
7324     WHEN G_EXC_QUIT_IMPORT THEN
7325         x_return_status                := l_return_status;
7326         x_rtg_header_rec               := l_rtg_header_rec;
7327         x_rtg_revision_tbl             := l_rtg_revision_tbl;
7328         x_operation_tbl                := l_operation_tbl;
7329         x_op_resource_tbl              := l_op_resource_tbl;
7330         x_sub_resource_tbl             := l_sub_resource_tbl;
7331         x_op_network_tbl               := l_op_network_tbl;
7332 
7333 IF BOM_Rtg_Globals.Get_Debug = 'Y' THEN
7334    Error_Handler.Write_Debug
7335    ('-----------------------------------------------------' ) ;
7336    Error_Handler.Write_Debug
7337    ('Quit Rtg BO Private API process with return_status: ' || x_return_status) ;
7338 END IF;
7339 
7340 
7341     -- Reset system_information business object flags
7342     BOM_Rtg_Globals.Set_STD_Item_Access( p_std_item_access => NULL);
7343     BOM_Rtg_Globals.Set_MDL_Item_Access( p_mdl_item_access => NULL);
7344     BOM_Rtg_Globals.Set_PLN_Item_Access( p_pln_item_access => NULL);
7345     BOM_Rtg_Globals.Set_OC_Item_Access( p_oc_item_access   => NULL);
7346 
7347     WHEN OTHERS THEN
7348 
7349         l_return_status := Error_Handler.G_STATUS_UNEXPECTED ;
7350         IF FND_MSG_PUB.Check_Msg_Level(FND_MSG_PUB.G_MSG_LVL_UNEXP_ERROR)
7351         THEN
7352                 l_err_text := G_PKG_NAME || ' : Process Rtg '
7353                         || substrb(SQLERRM,1,200);
7354                 Error_Handler.Add_Error_Token
7355                         ( p_Message_Text   => l_err_text
7356                         , p_Mesg_Token_Tbl => l_Mesg_Token_Tbl
7357                         , x_Mesg_Token_Tbl => l_Mesg_Token_Tbl
7358                         );
7359         END IF;
7360 
7361         Bom_Rtg_Error_Handler.Log_Error
7362                 (  p_rtg_header_rec        => l_rtg_header_rec
7363                 ,  p_rtg_revision_tbl      => l_rtg_revision_tbl
7364                 ,  p_operation_tbl         => l_operation_tbl
7365                 ,  p_op_resource_tbl       => l_op_resource_tbl
7366                 ,  p_sub_resource_tbl      => l_sub_resource_tbl
7367                 ,  p_op_network_tbl        => l_op_network_tbl
7368                 ,  p_mesg_token_tbl        => l_mesg_token_tbl
7369                 ,  p_error_status          => Error_Handler.G_STATUS_UNEXPECTED
7370                 ,  p_other_status          => Error_Handler.G_STATUS_NOT_PICKED
7371                 ,  p_other_message         => l_other_message
7372                 ,  p_other_token_tbl       => l_other_token_tbl
7373                 ,  p_error_level           => 0
7374                 ,  p_error_scope           => NULL
7375                 ,  p_other_mesg_appid      => 'BOM'
7376                 ,  p_entity_index          => 1
7377                 ,  x_rtg_header_rec        => l_rtg_header_rec
7378                 ,  x_rtg_revision_tbl      => l_rtg_revision_tbl
7379                 ,  x_operation_tbl         => l_operation_tbl
7380                 ,  x_op_resource_tbl       => l_op_resource_tbl
7381                 ,  x_sub_resource_tbl      => l_sub_resource_tbl
7382                 ,  x_op_network_tbl        => l_op_network_tbl
7383                 );
7384 
7385         x_return_status                := l_return_status;
7386         x_rtg_header_rec               := l_rtg_header_rec;
7387         x_rtg_revision_tbl             := l_rtg_revision_tbl;
7388         x_operation_tbl                := l_operation_tbl;
7389         x_op_resource_tbl              := l_op_resource_tbl;
7390         x_sub_resource_tbl             := l_sub_resource_tbl;
7391         x_op_network_tbl               := l_op_network_tbl;
7392     -- Reset system_information business object flags
7393 
7394     BOM_Rtg_Globals.Set_STD_Item_Access( p_std_item_access => NULL);
7395     BOM_Rtg_Globals.Set_MDL_Item_Access( p_mdl_item_access => NULL);
7396     BOM_Rtg_Globals.Set_PLN_Item_Access( p_pln_item_access => NULL);
7397     BOM_Rtg_Globals.Set_OC_Item_Access( p_oc_item_access   => NULL);
7398 
7399 IF BOM_Rtg_Globals.Get_Debug = 'Y' THEN
7400    Error_Handler.Write_Debug
7401    ('-----------------------------------------------------' ) ;
7402    Error_Handler.Write_Debug
7403    ('Rtg BO Private API process is terminated with unexpected error: ' || x_return_status) ;
7404 END IF;
7405 
7406   END Process_Rtg;
7407 
7408 END Bom_Rtg_Pvt ;