DBA Data[Home] [Help]

PACKAGE BODY: APPS.ENG_ECO_PVT

Source


1 PACKAGE BODY ENG_Eco_PVT AS
2 /* $Header: ENGVECOB.pls 120.18.12020000.6 2013/01/04 08:51:37 jifdeng ship $ */
3 
4 --  Global constant holding the package name
5 
6 G_PKG_NAME              CONSTANT VARCHAR2(30) := 'ENG_Eco_PVT';
7 G_EXC_QUIT_IMPORT       EXCEPTION;
8 
9 G_MISS_ECO_REC          ENG_Eco_PUB.ECO_Rec_Type;
10 G_MISS_ECO_REV_REC      ENG_Eco_PUB.ECO_Revision_Rec_Type;
11 G_MISS_REV_ITEM_REC     ENG_Eco_PUB.Revised_Item_Rec_Type;
12 G_MISS_REV_COMP_REC     BOM_BO_PUB.Rev_Component_Rec_Type;
13 G_MISS_REF_DESG_REC     BOM_BO_PUB.Ref_Designator_Rec_Type;
14 G_MISS_SUB_COMP_REC     BOM_BO_PUB.Sub_Component_Rec_Type;
15 
16 G_MISS_REV_OP_REC       Bom_Rtg_Pub.Rev_Operation_Tbl_Type;   --L1
17 G_MISS_REV_OP_RES_REC   Bom_Rtg_Pub.Rev_Op_Resource_Tbl_Type; --L1
18 G_MISS_REV_SUB_RES_REC  Bom_Rtg_Pub.Rev_Sub_Resource_Tbl_Type;--L1
19 
20     -- Bug 2918350 // kamohan
21     -- Start Changes
22 
23     FUNCTION ret_co_status ( p_change_notice VARCHAR2, p_organization_id NUMBER)
24        RETURN NUMBER
25     IS
26 	CURSOR check_co_sch IS
27 	 SELECT status_type
28 	   FROM eng_engineering_changes
29 	 WHERE change_notice = p_change_notice
30 	      AND organization_id = p_organization_id
31 	      AND nvl(plm_or_erp_change, 'PLM') = 'PLM'; -- Added for bug 3692807
32 
33 	l_chk_co_sch eng_engineering_changes.status_type%TYPE;
34     BEGIN
35 	OPEN check_co_sch;
36 	FETCH check_co_sch INTO l_chk_co_sch;
37 	IF check_co_sch%FOUND THEN
38 		l_chk_co_sch := l_chk_co_sch;
39 	ELSE
40 		l_chk_co_sch := 10000;
41 	END IF;
42 	CLOSE check_co_sch;
43 
44 	RETURN l_chk_co_sch;
45 
46     END ret_co_status;
47 
48     -- End Changes
49 
50 
51 
52 --  L1:  The following part is for ECO enhancement
53 --  Rev_Sub_Operation_Resources
54 
55 PROCEDURE Rev_Sub_Operation_Resources
56 (   p_validation_level        IN  NUMBER
57 ,   p_change_notice           IN  VARCHAR2 := NULL
58 ,   p_organization_id         IN  NUMBER   := NULL
59 ,   p_revised_item_name       IN  VARCHAR2 := NULL
60 ,   p_effectivity_date        IN  DATE     := NULL
61 ,   p_item_revision           IN  VARCHAR2 := NULL
62 ,   p_routing_revision        IN  VARCHAR2 := NULL -- Added by MK on 11/02/00
63 ,   p_from_end_item_number    IN  VARCHAR2 := NULL -- Added by MK on 11/02/00
64 ,   p_operation_seq_num       IN  NUMBER   := NULL
65 ,   p_operation_type          IN  NUMBER   := NULL
66 ,   p_alternate_routing_code  IN  VARCHAR2 := NULL -- Added for bug 13440461
67 ,   p_rev_sub_resource_tbl    IN  Bom_Rtg_Pub.Rev_Sub_Resource_Tbl_Type
68 ,   x_rev_sub_resource_tbl    IN OUT NOCOPY Bom_Rtg_Pub.Rev_Sub_Resource_Tbl_Type
69 ,   x_mesg_token_tbl          OUT NOCOPY Error_Handler.Mesg_Token_Tbl_Type
70 ,   x_return_status           OUT NOCOPY VARCHAR2
71 )
72 
73 IS
74 
75 /* Exposed and Unexposed record */
76 l_eco_rec                ENG_Eco_PUB.Eco_Rec_Type;
77 l_eco_revision_tbl       ENG_Eco_PUB.ECO_Revision_Tbl_Type;
78 l_revised_item_tbl       ENG_Eco_PUB.Revised_Item_Tbl_Type;
79 l_rev_component_rec      BOM_BO_PUB.Rev_Component_Rec_Type;
80 l_rev_component_tbl      BOM_BO_PUB.Rev_Component_Tbl_Type;
81 l_rev_comp_unexp_rec     BOM_BO_PUB.Rev_Comp_Unexposed_Rec_Type;
82 --l_old_rev_component_rec  BOM_BO_PUB.Rev_Component_Rec_Type;
83 --l_old_rev_comp_unexp_rec BOM_BO_PUB.Rev_Comp_Unexposed_Rec_Type;
84 l_ref_designator_tbl     BOM_BO_PUB.Ref_Designator_Tbl_Type;
85 l_sub_component_tbl      BOM_BO_PUB.Sub_Component_Tbl_Type;
86 l_rev_operation_tbl      Bom_Rtg_Pub.Rev_Operation_Tbl_Type;
87 l_rev_op_resource_tbl    Bom_Rtg_Pub.Rev_Op_Resource_Tbl_Type;
88 --l_rev_sub_resource_tbl   Bom_Rtg_Pub.Rev_Sub_Resource_Tbl_Type := p_rev_sub_resource_tbl;
89 l_rev_sub_resource_rec   Bom_Rtg_Pub.Rev_Sub_Resource_rec_Type;
90 l_rev_sub_res_unexp_rec  Bom_Rtg_Pub.Rev_Sub_Res_Unexposed_Rec_Type;
91 l_old_rev_sub_resource_rec   Bom_Rtg_Pub.Rev_Sub_Resource_rec_Type;
92 l_old_rev_sub_res_unexp_rec  Bom_Rtg_Pub.Rev_Sub_Res_Unexposed_Rec_Type;
93 
94 /* Error Handling Variables */
95 l_token_tbl             Error_Handler.Token_Tbl_Type ;
96 l_mesg_token_tbl        Error_Handler.Mesg_Token_Tbl_Type;
97 l_other_token_tbl       Error_Handler.Token_Tbl_Type;
98 l_other_message         VARCHAR2(2000);
99 l_err_text              VARCHAR2(2000);
100 
101 
102 /* Others */
103 l_return_status         VARCHAR2(1);
104 l_bo_return_status      VARCHAR2(1);
105 l_op_parent_exists      BOOLEAN := FALSE;
106 l_rtg_parent_exists     BOOLEAN := FALSE;
107 l_process_children      BOOLEAN := TRUE;
108 l_valid                 BOOLEAN := TRUE;
109 
110 /* Error handler definations */
111 EXC_SEV_QUIT_RECORD     EXCEPTION ;
112 EXC_SEV_QUIT_BRANCH     EXCEPTION ;
113 EXC_UNEXP_SKIP_OBJECT   EXCEPTION ;
114 EXC_SEV_QUIT_SIBLINGS   EXCEPTION ;
115 EXC_SEV_SKIP_BRANCH     EXCEPTION ;
116 EXC_FAT_QUIT_SIBLINGS   EXCEPTION ;
117 EXC_FAT_QUIT_BRANCH     EXCEPTION ;
118 EXC_FAT_QUIT_OBJECT     EXCEPTION ;
119 
120 BEGIN
121 
122    --  Init local table variables.
123    l_return_status    := 'S';
124    l_bo_return_status := 'S';
125    --l_rev_sub_resource_tbl  := p_rev_sub_resource_tbl;
126    x_rev_sub_resource_tbl  := p_rev_sub_resource_tbl;
127    l_rev_sub_res_unexp_rec.organization_id := Eng_Globals.Get_Org_Id;
128 
129    FOR I IN 1..x_rev_sub_resource_tbl.COUNT LOOP
130    -- Processing records for which the return status is null
131    IF (x_rev_sub_resource_tbl(I).return_status IS NULL OR
132         x_rev_sub_resource_tbl(I).return_status  = FND_API.G_MISS_CHAR)
133    THEN
134    BEGIN
135 
136       --  Load local records
137       l_rev_sub_resource_rec := x_rev_sub_resource_tbl(I);
138 
139       l_rev_sub_resource_rec.transaction_type :=
140           UPPER(l_rev_sub_resource_rec.transaction_type);
141 
142 
143 
144       --
145       -- Initialize the Unexposed Record for every iteration of the Loop
146       -- so that sequence numbers get generated for every new row.
147       --
148       l_rev_sub_res_unexp_rec.Revised_Item_Sequence_Id := NULL ;
149       l_rev_sub_res_unexp_rec.Operation_Sequence_Id   := NULL ;
150       l_rev_sub_res_unexp_rec.Substitute_Group_Number := NULL ;
151       l_rev_sub_res_unexp_rec.Resource_Id             := NULL ;
152       l_rev_sub_res_unexp_rec.New_Resource_Id         := NULL ;
153       l_rev_sub_res_unexp_rec.Activity_Id             := NULL ;
154       l_rev_sub_res_unexp_rec.Setup_Id                := NULL ;
155 
156       IF p_operation_seq_num  IS NOT NULL AND
157          p_revised_item_name  IS NOT NULL AND
158          p_effectivity_date   IS NOT NULL AND
159          p_organization_id    IS NOT NULL
160       THEN
161          -- Revised Operation or Operation Sequence parent exists
162          l_op_parent_exists  := TRUE;
163 
164       ELSIF p_revised_item_name IS NOT NULL AND
165             p_organization_id    IS NOT NULL
166       THEN
167          -- Revised Item or Routing parent exists
168          l_rtg_parent_exists := TRUE;
169       END IF ;
170 
171       -- Process Flow Step 2: Check if record has not yet been processed and
172       -- that it is the child of the parent that called this procedure
173       --
174 
175       IF --(l_rev_sub_resource_rec.return_status IS NULL OR
176          -- l_rev_sub_resource_rec.return_status  = FND_API.G_MISS_CHAR)
177          --AND
178          (
179             -- Did Op_Seq call this procedure, that is,
180             -- if revised operation(operation sequence) exists, then is this record a child ?
181             (   l_op_parent_exists AND
182                 l_rev_sub_resource_rec.ECO_name = p_change_notice       AND
183                 l_rev_sub_res_unexp_rec.organization_id
184                                              =   p_organization_id      AND
185                 NVL(l_rev_sub_resource_rec.new_revised_item_revision, FND_API.G_MISS_CHAR )
186                                              =   NVL(p_item_revision, FND_API.G_MISS_CHAR )       AND
187                 l_rev_sub_resource_rec.revised_item_name
188                                              =   p_revised_item_name    AND
189                 NVL(l_rev_sub_resource_rec.alternate_routing_code, FND_API.G_MISS_CHAR )
190                                              =   NVL(p_alternate_routing_code, FND_API.G_MISS_CHAR)    AND   -- Added for bug 13440461
191                 l_rev_sub_resource_rec.operation_sequence_number
192                                              =   p_operation_seq_num    AND
193                 NVL(l_rev_sub_resource_rec.new_routing_revision,FND_API.G_MISS_CHAR )
194                                              =   NVL(p_routing_revision,FND_API.G_MISS_CHAR )     AND -- Added by MK on 11/02/00
195                 NVL(l_rev_sub_resource_rec.from_end_item_unit_number,FND_API.G_MISS_CHAR )
196                                              =   NVL(p_from_end_item_number,FND_API.G_MISS_CHAR ) AND -- Added by MK on 11/02/00
197                 l_rev_sub_resource_rec.op_start_effective_date
198                                              = nvl(ENG_Default_Revised_Item.G_OLD_SCHED_DATE,p_effectivity_date) -- Bug 6657209
199               --  NVL(l_rev_sub_resource_rec.operation_type, 1)
200               --                               = NVL(p_operation_type, 1)
201 
202             )
203             OR
204             -- Did Rtg_Header call this procedure, that is,
205             -- if revised item or routing header exists, then is this record a child ?
206             (  l_rtg_parent_exists AND
207                l_rev_sub_resource_rec.ECO_name = p_change_notice       AND
208                l_rev_sub_res_unexp_rec.organization_id
209                                              =   p_organization_id     AND
210                NVL(l_rev_sub_resource_rec.new_revised_item_revision, FND_API.G_MISS_CHAR )
211                                              =   NVL(p_item_revision, FND_API.G_MISS_CHAR )       AND
212                l_rev_sub_resource_rec.revised_item_name
213                                              = p_revised_item_name     AND
214                NVL(l_rev_sub_resource_rec.alternate_routing_code, FND_API.G_MISS_CHAR )
215                                              =   NVL(p_alternate_routing_code, FND_API.G_MISS_CHAR)    AND   -- Added for bug 13440461
216                NVL(l_rev_sub_resource_rec.new_routing_revision,FND_API.G_MISS_CHAR )
217                                              =   NVL(p_routing_revision,FND_API.G_MISS_CHAR )     AND -- Added by MK on 11/02/00
218                NVL(l_rev_sub_resource_rec.from_end_item_unit_number,FND_API.G_MISS_CHAR )
219                                              =   NVL(p_from_end_item_number,FND_API.G_MISS_CHAR ) AND -- Added by MK on 11/02/00
220                l_rev_sub_resource_rec.op_start_effective_date
221                                              = p_effectivity_date
222              --   NVL(l_rev_sub_resource_rec.alternate_routing_code, 'P')
223              --                      = NVL(p_alternate_routing_code, 'P')
224 
225             )
226            OR
227            (NOT l_rtg_parent_exists AND NOT l_op_parent_exists)
228          )
229       THEN
230          l_return_status := FND_API.G_RET_STS_SUCCESS;
231          l_rev_sub_resource_rec.return_status := FND_API.G_RET_STS_SUCCESS;
232 
233          -- Bug 6657209
234          IF (l_op_parent_exists and ENG_Default_Revised_Item.G_OLD_SCHED_DATE is not null) THEN
235            l_rev_sub_resource_rec.op_start_effective_date := p_effectivity_date;
236          END IF;
237          --
238          -- Process Flow step 3 : Check if transaction_type is valid
239          -- Transaction_Type must be CRATE, UPDATE, DELETE or CANCEL(in only ECO for Rrg)
240          -- Call the Bom_Rtg_Globals.Transaction_Type_Validity
241          --
242          Eng_Globals.Transaction_Type_Validity
243          (   p_transaction_type => l_rev_sub_resource_rec.transaction_type
244          ,   p_entity           => 'Sub_Res'
245          ,   p_entity_id        => l_rev_sub_resource_rec.Sub_Resource_Code
246          ,   x_valid            => l_valid
247          ,   x_mesg_token_tbl   => l_mesg_token_tbl
248          ) ;
249 
250          IF NOT l_valid
251          THEN
252             RAISE EXC_SEV_QUIT_RECORD ;
253          END IF ;
254 
255          --
256          -- Process Flow step 4(a): Convert user unique index to unique
257          -- index I
258          -- Call Rtg_Val_To_Id.Op_Resource_UUI_To_UI Shared Utility Package
259          --
260          BOM_Rtg_Val_To_Id.Rev_Sub_Resource_UUI_To_UI
261          ( p_rev_sub_resource_rec    => l_rev_sub_resource_rec
262          , p_rev_sub_res_unexp_rec   => l_rev_sub_res_unexp_rec
263          , x_rev_sub_res_unexp_rec   => l_rev_sub_res_unexp_rec
264          , x_mesg_token_tbl          => l_mesg_token_tbl
265          , x_return_status           => l_return_status
266          ) ;
267 
268          IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
269          ('Convert to User Unique Index to Index1 completed with return_status: ' || l_return_status) ;
270          END IF;
271 
272          IF l_return_status = Error_Handler.G_STATUS_ERROR
273          THEN
274             l_other_message := 'BOM_SUB_RES_UUI_SEV_ERROR';
275             l_other_token_tbl(1).token_name := 'SUB_RESOURCE_CODE';
276             l_other_token_tbl(1).token_value :=
277                         l_rev_sub_resource_rec.sub_resource_code ;
278             l_other_token_tbl(2).token_name := 'SCHEDULE_SEQ_NUMBER';
279             l_other_token_tbl(2).token_value :=
280                         l_rev_sub_resource_rec.schedule_sequence_number ;
281             RAISE EXC_SEV_QUIT_BRANCH ;
282 
283          ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
284          THEN
285             l_other_message := 'BOM_SUB_RES_UUI_UNEXP_SKIP';
286             l_other_token_tbl(1).token_name := 'SUB_RESOURCE_CODE';
287             l_other_token_tbl(1).token_value :=
288                         l_rev_sub_resource_rec.sub_resource_code ;
289             l_other_token_tbl(2).token_name := 'SCHEDULE_SEQ_NUMBER';
290             l_other_token_tbl(2).token_value :=
291                         l_rev_sub_resource_rec.schedule_sequence_number ;
292             RAISE EXC_UNEXP_SKIP_OBJECT;
293          END IF ;
294 
295          -- Added by MK on 12/03/00 to resolve ECO dependency
296          ENG_Val_To_Id.RtgAndRevitem_UUI_To_UI
297            ( p_revised_item_name        => l_rev_sub_resource_rec.revised_item_name
298            , p_revised_item_id          => l_rev_sub_res_unexp_rec.revised_item_id
299            , p_item_revision            => l_rev_sub_resource_rec.new_revised_item_revision
300            , p_effective_date           => l_rev_sub_resource_rec.op_start_effective_date
301            , p_change_notice            => l_rev_sub_resource_rec.eco_name
302            , p_organization_id          => l_rev_sub_res_unexp_rec.organization_id
303            , p_new_routing_revision     => l_rev_sub_resource_rec.new_routing_revision
304            , p_from_end_item_number     => l_rev_sub_resource_rec.from_end_item_unit_number
305            , p_entity_processed         => 'SR'
306            , p_operation_sequence_number => l_rev_sub_resource_rec.operation_sequence_number
307            , p_sub_resource_code         => l_rev_sub_resource_rec.sub_resource_code
308            , p_schedule_sequence_number  => l_rev_sub_resource_rec.schedule_sequence_number
309            , p_alternate_routing_code    => l_rev_sub_resource_rec.alternate_routing_code    -- Added for bug 13440461
310            , x_revised_item_sequence_id  => l_rev_sub_res_unexp_rec.revised_item_sequence_id
311            , x_routing_sequence_id       => l_rev_sub_res_unexp_rec.routing_sequence_id
312            , x_operation_sequence_id     => l_rev_sub_res_unexp_rec.operation_sequence_id
313            , x_Mesg_Token_Tbl           => l_Mesg_Token_Tbl
314            , x_other_message            => l_other_message
315            , x_other_token_tbl          => l_other_token_tbl
316            , x_Return_Status            => l_return_status
317           ) ;
318 
319          IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
320          ('Convert to User Unique Index to Index1 for Rtg and Rev Item Seq completed with return_status: ' || l_return_status) ;
321          END IF;
322 
323          IF l_return_status = Error_Handler.G_STATUS_ERROR
324          THEN
325             l_other_message := 'BOM_SUB_RES_UUI_SEV_ERROR';
326             l_other_token_tbl(1).token_name := 'SUB_RESOURCE_CODE';
327             l_other_token_tbl(1).token_value :=
328                         l_rev_sub_resource_rec.sub_resource_code ;
329             l_other_token_tbl(2).token_name := 'SCHEDULE_SEQ_NUMBER';
330             l_other_token_tbl(2).token_value :=
331                         l_rev_sub_resource_rec.schedule_sequence_number ;
332             RAISE EXC_SEV_QUIT_BRANCH ;
333 
334          ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
335          THEN
336             l_other_message := 'BOM_SUB_RES_UUI_UNEXP_SKIP';
337             l_other_token_tbl(1).token_name := 'SUB_RESOURCE_CODE';
338             l_other_token_tbl(1).token_value :=
339                         l_rev_sub_resource_rec.sub_resource_code ;
340             l_other_token_tbl(2).token_name := 'SCHEDULE_SEQ_NUMBER';
341             l_other_token_tbl(2).token_value :=
342                         l_rev_sub_resource_rec.schedule_sequence_number ;
343             RAISE EXC_UNEXP_SKIP_OBJECT;
344          END IF ;
345 
346 
347 
348 
349          --
350          -- Process Flow step 4(b): Convert user unique index to unique
351          -- index II
352          -- Call the Rtg_Val_To_Id.Rev_Sub_Resource_UUI_To_UI2
353          --
354         /*
355          Bom_Rtg_Val_To_Id.Rev_Sub_Resource_UUI_To_UI2
356          ( p_rev_sub_resource_rec   => l_rev_sub_resource_rec
357          , p_rev_sub_res_unexp_rec  => l_rev_sub_res_unexp_rec
358          , x_sub_res_unexp_rec      => l_rev_sub_res_unexp_rec
359          , x_mesg_token_tbl         => l_mesg_token_tbl
360          , x_other_message          => l_other_message
361          , x_other_token_tbl        => l_other_token_tbl
362          , x_return_status          => l_return_status
363          ) ;
364 
365          IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
366          ('Convert to User Unique Index to Index2 completed with return_status: ' || l_return_status) ;
367          END IF;
368 
369          IF l_return_status = Error_Handler.G_STATUS_ERROR
370          THEN
371             RAISE EXC_SEV_QUIT_SIBLINGS ;
372          ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
373          THEN
374             l_other_message := 'BOM_SUB_RES_UUI_UNEXP_SKIP';
375             l_other_token_tbl(1).token_name := 'SUB_RESOURCE_CODE';
376             l_other_token_tbl(1).token_value :=
377                         l_rev_sub_resource_rec.sub_resource_code;
378             l_other_token_tbl(2).token_name := 'SCHEDULE_SEQ_NUMBER';
379             l_other_token_tbl(2).token_value :=
380                         l_rev_sub_resource_rec.schedule_sequence_number ;
381             RAISE EXC_UNEXP_SKIP_OBJECT;
382          END IF ;
383 
384         */
385          --
386          -- Process Flow step 5: Verify Substitute Resource's existence
387          -- Call the Bom_Validate_Sub_Op_Res.Check_Existence.
388          --
389          --
390 
391          Bom_Validate_Sub_Op_Res.Check_Existence
392          (  p_rev_sub_resource_rec        => l_rev_sub_resource_rec
393          ,  p_rev_sub_res_unexp_rec       => l_rev_sub_res_unexp_rec
394          ,  x_old_rev_sub_resource_rec    => l_old_rev_sub_resource_rec
395          ,  x_old_rev_sub_res_unexp_rec   => l_old_rev_sub_res_unexp_rec
396          ,  x_mesg_token_tbl              => l_mesg_token_tbl
397          ,  x_return_status               => l_return_status
398          ) ;
399 
400 
401          IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
402          ('Check Existence completed with return_status: ' || l_return_status) ;
403          END IF ;
404 
405          IF l_return_status = Error_Handler.G_STATUS_ERROR
406          THEN
407             l_other_message := 'BOM_SUB_RES_EXS_SEV_SKIP';
408             l_other_token_tbl(1).token_name := 'SUB_RESOURCE_CODE';
409             l_other_token_tbl(1).token_value :=
410                         l_rev_sub_resource_rec.sub_resource_code ;
411             l_other_token_tbl(2).token_name := 'SCHEDULE_SEQ_NUMBER';
412             l_other_token_tbl(2).token_value :=
413                         l_rev_sub_resource_rec.schedule_sequence_number ;
414             -- l_other_token_tbl(3).token_name := 'REVISED_ITEM_NAME';
415             -- l_other_token_tbl(3).token_value :=
416             --            l_rev_sub_resource_rec.revised_item_name ;
417             RAISE EXC_SEV_QUIT_BRANCH;
418          ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
419          THEN
420             l_other_message := 'BOM_SUB_RES_EXS_UNEXP_SKIP';
421             l_other_token_tbl(1).token_name := 'SUB_RESOURCE_CODE';
422             l_other_token_tbl(1).token_value :=
423                         l_rev_sub_resource_rec.sub_resource_code ;
424             l_other_token_tbl(2).token_name := 'SCHEDULE_SEQ_NUMBER';
425             l_other_token_tbl(2).token_value :=
426                         l_rev_sub_resource_rec.schedule_sequence_number ;
427             -- l_other_token_tbl(3).token_name := 'REVISED_ITEM_NAME';
428             -- l_other_token_tbl(3).token_value :=
429             --          l_rev_sub_resource_rec.revised_item_name ;
430             RAISE EXC_UNEXP_SKIP_OBJECT;
431          END IF;
432 
433 
434          --
435          -- Process Flow step 6: Is Substitute Resource record an orphan ?
436          --
437 
438          IF NOT l_op_parent_exists
439          THEN
440 
441             --
442             -- Process Flow step 7: Check lineage
443             --
444             IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Check lineage');     END IF;
445             BOM_Validate_Op_Seq.Check_Lineage
446                 ( p_routing_sequence_id       =>
447                                l_rev_sub_res_unexp_rec.routing_sequence_id
448                 , p_operation_sequence_number =>
449                                l_rev_sub_resource_rec.operation_sequence_number
450                 , p_effectivity_date          =>
451                                l_rev_sub_resource_rec.op_start_effective_date
452                 , p_operation_type            =>
453                                l_rev_sub_resource_rec.operation_type
454                 , p_revised_item_sequence_id  =>
455                                l_rev_sub_res_unexp_rec.revised_item_sequence_id
456                 , x_mesg_token_tbl            => l_mesg_token_tbl
457                 , x_return_status             => l_return_status
458                 ) ;
459 
460             IF l_return_status = Error_Handler.G_STATUS_ERROR
461             THEN
462 
463                 l_Token_Tbl(1).token_name  := 'SUB_RESOURCE_CODE';
464                 l_Token_Tbl(1).token_value := l_rev_sub_resource_rec.sub_resource_code ;
465                 l_Token_Tbl(2).token_name  := 'SCHEDULE_SEQ_NUMBER';
466                 l_Token_Tbl(2).token_value := l_rev_sub_resource_rec.schedule_sequence_number ;
467                 l_Token_Tbl(3).token_name  := 'OP_SEQ_NUMBER' ;
468                 l_Token_Tbl(3).token_value := l_rev_sub_resource_rec.operation_sequence_number ;
469                 l_Token_Tbl(4).token_name  := 'REVISED_ITEM_NAME' ;
470                 l_Token_Tbl(4).token_value := l_rev_sub_resource_rec.revised_item_name;
471 
472                 Error_Handler.Add_Error_Token
473                 (  p_Message_Name  => 'BOM_SUB_RES_REV_ITEM_MISMATCH'
474                 , p_Mesg_Token_Tbl => l_Mesg_Token_Tbl
475                 , x_Mesg_Token_Tbl => l_Mesg_Token_Tbl
476                 , p_Token_Tbl      => l_Token_Tbl
477                 ) ;
478 
479 
480                 l_other_message := 'BOM_SUB_RES_LIN_SEV_SKIP';
481                 l_other_token_tbl(1).token_name := 'SUB_RESOURCE_CODE';
482                 l_other_token_tbl(1).token_value :=
483                             l_rev_sub_resource_rec.sub_resource_code ;
484                 l_other_token_tbl(2).token_name := 'SCHEDULE_SEQ_NUMBER';
485                 l_other_token_tbl(2).token_value :=
486                             l_rev_sub_resource_rec.schedule_sequence_number ;
487 
488                 RAISE EXC_SEV_QUIT_BRANCH;
489 
490             ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
491             THEN
492                 l_other_message := 'BOM_SUB_RES_LIN_UNEXP_SKIP';
493                 l_other_token_tbl(1).token_name := 'SUB_RESOURCE_CODE';
494                 l_other_token_tbl(1).token_value :=
495                             l_rev_sub_resource_rec.sub_resource_code ;
496                 l_other_token_tbl(2).token_name := 'SCHEDULE_SEQ_NUMBER';
497                 l_other_token_tbl(2).token_value :=
498                             l_rev_sub_resource_rec.schedule_sequence_number ;
499                 RAISE EXC_UNEXP_SKIP_OBJECT;
500             END IF;
501 
502             -- Process Flow step 8(a and b): Is ECO impl/cancl, or in wkflw process ?
503             --
504 
505             IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Check ECO access'); END IF;
506 
507             ENG_Validate_ECO.Check_Access
508             ( p_change_notice       => l_rev_sub_resource_rec.ECO_Name
509             , p_organization_id     => l_rev_sub_res_unexp_rec.organization_id
510             , p_Mesg_Token_Tbl      => l_Mesg_Token_Tbl
511             , x_Mesg_Token_Tbl      => l_Mesg_Token_Tbl
512             , x_Return_Status       => l_return_status
513             );
514 
515             IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
516 
517             IF l_return_status = Error_Handler.G_STATUS_ERROR
518             THEN
519                         l_other_message := 'BOM_SUB_RES_ECOACC_FAT_FATAL';
520                         l_other_token_tbl(1).token_name := 'SUB_RESOURCE_CODE';
521                         l_other_token_tbl(1).token_value :=
522                                     l_rev_sub_resource_rec.sub_resource_code ;
523                         l_other_token_tbl(2).token_name := 'SCHEDULE_SEQ_NUMBER';
524                         l_other_token_tbl(2).token_value :=
525                                     l_rev_sub_resource_rec.schedule_sequence_number ;
526                         l_return_status := 'F';
527                         RAISE EXC_FAT_QUIT_OBJECT;
528             ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
529             THEN
530                         l_other_message := 'BOM_SUB_RES_ECOACC_UNEXP_SKIP';
531                         l_other_token_tbl(1).token_name := 'SUB_RESOURCE_CODE';
532                         l_other_token_tbl(1).token_value :=
533                                     l_rev_sub_resource_rec.sub_resource_code ;
534                         l_other_token_tbl(2).token_name := 'SCHEDULE_SEQ_NUMBER';
535                         l_other_token_tbl(2).token_value :=
536                                     l_rev_sub_resource_rec.schedule_sequence_number ;
537                         RAISE EXC_UNEXP_SKIP_OBJECT;
538             END IF;
539 
540             -- Process Flow step 9(a and b): check that user has access to revised item
541             --
542 
543             IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Check Revised item access'); END IF;
544             ENG_Validate_Revised_Item.Check_Access
545             (  p_change_notice   => l_rev_sub_resource_rec.ECO_Name
546             ,  p_organization_id => l_rev_sub_res_unexp_rec.organization_id
547             ,  p_revised_item_id => l_rev_sub_res_unexp_rec.revised_item_id
548             ,  p_new_item_revision  =>
549                                l_rev_sub_resource_rec.new_revised_item_revision
550             ,  p_effectivity_date   =>
551                                l_rev_sub_resource_rec.op_start_effective_date
552             ,  p_new_routing_revsion   => l_rev_sub_resource_rec.new_routing_revision  -- Added by MK on 11/02/00
553             ,  p_from_end_item_number  => l_rev_sub_resource_rec.from_end_item_unit_number -- Added by MK on 11/02/00
554             ,  p_revised_item_name     =>
555                                l_rev_sub_resource_rec.revised_item_name
556             ,  p_entity_processed   => 'SR'                                               -- Added by MK
557             ,  p_operation_seq_num  =>  l_rev_sub_resource_rec.operation_sequence_number  -- Added by MK
558             ,  p_routing_sequence_id => l_rev_sub_res_unexp_rec.routing_sequence_id       -- Added by MK
559             ,  p_Mesg_Token_Tbl     => l_Mesg_Token_Tbl
560             ,  x_Mesg_Token_Tbl     => l_Mesg_Token_Tbl
561             ,  x_return_status      => l_Return_Status
562             );
563 
564             IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
565 
566             IF l_return_status = Error_Handler.G_STATUS_ERROR
567             THEN
568                         l_other_message := 'BOM_SUB_RES_RITACC_FAT_FATAL';
569                         l_other_token_tbl(1).token_name := 'SUB_RESOURCE_CODE';
570                         l_other_token_tbl(1).token_value :=
571                                     l_rev_sub_resource_rec.sub_resource_code ;
572                         l_other_token_tbl(2).token_name := 'SCHEDULE_SEQ_NUMBER';
573                         l_other_token_tbl(2).token_value :=
574                                     l_rev_sub_resource_rec.schedule_sequence_number ;
575                         l_return_status := 'F';
576                         RAISE EXC_FAT_QUIT_SIBLINGS;
577             ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
578             THEN
579                         l_other_message := 'BOM_SUB_RES_RITACC_UNEXP_SKIP';
580                         l_other_token_tbl(1).token_name := 'SUB_RESOURCE_CODE';
581                         l_other_token_tbl(1).token_value :=
582                                     l_rev_sub_resource_rec.sub_resource_code ;
583                         l_other_token_tbl(2).token_name := 'SCHEDULE_SEQ_NUMBER';
584                         l_other_token_tbl(2).token_value :=
585                                     l_rev_sub_resource_rec.schedule_sequence_number ;
586                         RAISE EXC_UNEXP_SKIP_OBJECT;
587             END IF;
588 
589             --
590             -- Process Flow step 10(b) : Check that user has access to revised
591             -- operation
592             -- BOM_Validate_Op_Seq.Check_Access
593 
594             IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Check Operation sequence item access'); END IF;
595             BOM_Validate_Op_Seq.Check_Access
596               (  p_change_notice      => l_rev_sub_resource_rec.ECO_Name
597               ,  p_organization_id    => l_rev_sub_res_unexp_rec.organization_id
598               ,  p_revised_item_id    => l_rev_sub_res_unexp_rec.revised_item_id
599               ,  p_revised_item_name  => l_rev_sub_resource_rec.revised_item_name
600               ,  p_new_item_revision  =>
601                              l_rev_sub_resource_rec.new_revised_item_revision
602               ,  p_effectivity_date   =>
603                              l_rev_sub_resource_rec.op_start_effective_date
604               ,  p_new_routing_revsion   => l_rev_sub_resource_rec.new_routing_revision  -- Added by MK on 11/02/00
605               ,  p_from_end_item_number  => l_rev_sub_resource_rec.from_end_item_unit_number -- Added by MK on 11/02/00
606               ,  p_operation_seq_num  =>
607                              l_rev_sub_resource_rec.operation_sequence_number
608               ,  p_routing_sequence_id=>
609                                    l_rev_sub_res_unexp_rec.routing_sequence_id
610               ,  p_operation_type     => l_rev_sub_resource_rec.operation_type
611               ,  p_entity_processed   => 'SR'
612               ,  p_sub_resource_code  =>
613                             l_rev_sub_resource_rec.sub_resource_code
614               ,  p_sub_group_num      =>
615                             l_rev_sub_resource_rec.schedule_sequence_number
616               ,  p_resource_seq_num   => NULL
617               ,  p_Mesg_Token_Tbl     => l_Mesg_Token_Tbl
618               ,  x_Mesg_Token_Tbl     => l_Mesg_Token_Tbl
619               ,  x_return_status      => l_Return_Status
620              );
621 
622             IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
623 
624             IF l_return_status = Error_Handler.G_STATUS_ERROR
625             THEN
626                         l_other_message := 'BOM_SUB_RES_ACCESS_FAT_FATAL';
627                         l_other_token_tbl(1).token_name := 'SUB_RESOURCE_CODE';
628                         l_other_token_tbl(1).token_value :=
629                                     l_rev_sub_resource_rec.sub_resource_code ;
630                         l_other_token_tbl(2).token_name := 'SCHEDULE_SEQ_NUMBER';
631                         l_other_token_tbl(2).token_value :=
632                                     l_rev_sub_resource_rec.schedule_sequence_number ;
633                         l_return_status := 'F';
634                         RAISE EXC_FAT_QUIT_OBJECT;
635             ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
636             THEN
637                         l_other_message := 'BOM_SUB_RES_ACCESS_UNEXP_SKIP';
638                         l_other_token_tbl(1).token_name := 'SUB_RESOURCE_CODE';
639                         l_other_token_tbl(1).token_value :=
640                                     l_rev_sub_resource_rec.sub_resource_code ;
641                         l_other_token_tbl(2).token_name := 'SCHEDULE_SEQ_NUMBER';
642                         l_other_token_tbl(2).token_value :=
643                                     l_rev_sub_resource_rec.schedule_sequence_number ;
644                         RAISE EXC_UNEXP_SKIP_OBJECT;
645             END IF;
646 
647          END IF; -- parent op does not exist
648 
649          --
650          -- Process Flow step 11 : Check if the parent operation is
651          -- non-referencing operation of type: Event
652          -- Call Bom_Validate_Op_Seq.Check_NonRefEvent
653          --
654          Bom_Validate_Op_Res.Check_NonRefEvent
655          (  p_operation_sequence_id =>
656                                   l_rev_sub_res_unexp_rec.operation_sequence_id
657             ,  p_operation_type       => l_rev_sub_resource_rec.operation_type
658             ,  p_entity_processed     => 'RES'
659             ,  x_mesg_token_tbl       => l_mesg_token_tbl
660             ,  x_return_status        => l_return_status
661          ) ;
662 
663          IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
664             ('Check non-ref operation completed with return_status: '
665                       || l_return_status) ;
666          END IF;
667 
668          IF l_return_status = Error_Handler.G_STATUS_ERROR
669          THEN
670                IF l_rev_sub_resource_rec.operation_type IN (2, 3) -- Process or Line Op
671                THEN
672 
673                   l_token_tbl(1).token_name := 'SUB_RESOURCE_CODE';
674                   l_token_tbl(1).token_value :=
675                           l_rev_sub_resource_rec.sub_resource_code ;
676                   l_token_tbl(2).token_name := 'SCHEDULE_SEQ_NUMBER';
677                   l_token_tbl(2).token_value :=
678                           l_rev_sub_resource_rec.schedule_sequence_number ;
679                   l_token_tbl(3).token_name := 'OP_SEQ_NUMBER';
680                   l_token_tbl(3).token_value :=
681                           l_rev_sub_resource_rec.operation_sequence_number ;
682 
683                   Error_Handler.Add_Error_Token
684                         ( p_Message_Name   => 'BOM_SUB_RES_OPTYPE_NOT_EVENT'
685                         , p_mesg_token_tbl => l_mesg_token_tbl
686                         , x_mesg_token_tbl => l_mesg_token_tbl
687                         , p_Token_Tbl      => l_token_tbl
688                         ) ;
689                ELSE
690 
691                   l_token_tbl(1).token_name := 'SUB_RESOURCE_CODE';
692                   l_token_tbl(1).token_value :=
693                           l_rev_sub_resource_rec.sub_resource_code ;
694                   l_token_tbl(2).token_name := 'SCHEDULE_SEQ_NUMBER';
695                   l_token_tbl(2).token_value :=
696                           l_rev_sub_resource_rec.schedule_sequence_number ;
697                   l_token_tbl(3).token_name := 'OP_SEQ_NUMBER';
698                   l_token_tbl(3).token_value :=
699                           l_rev_sub_resource_rec.operation_sequence_number ;
700 
701                   Error_Handler.Add_Error_Token
702                         ( p_Message_Name   => 'BOM_SUB_RES_MUST_NONREF'
703                         , p_mesg_token_tbl => l_mesg_token_tbl
704                         , x_mesg_token_tbl => l_mesg_token_tbl
705                         , p_Token_Tbl      => l_token_tbl
706                         ) ;
707 
708                END IF ;
709 
710                l_return_status := 'F';
711                l_other_message := 'BOM_SUB_RES_ACCESS_FAT_FATAL';
712                l_other_token_tbl(1).token_name := 'SUB_RESOURCE_CODE';
713                l_other_token_tbl(1).token_value :=
714                                     l_rev_sub_resource_rec.sub_resource_code ;
715                l_other_token_tbl(2).token_name := 'SCHEDULE_SEQ_NUMBER';
716                l_other_token_tbl(2).token_value :=
717                                     l_rev_sub_resource_rec.schedule_sequence_number ;
718 
719                RAISE EXC_FAT_QUIT_SIBLINGS ;
720 
721          ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
722          THEN
723                l_other_message := 'BOM_SUB_RES_ACCESS_UNEXP_SKIP';
724                l_other_token_tbl(1).token_name := 'SUB_RESOURCE_CODE';
725                l_other_token_tbl(1).token_value :=
726                         l_rev_sub_resource_rec.sub_resource_code ;
727                l_other_token_tbl(2).token_name := 'SCHEDULE_SEQ_NUMBER';
728                l_other_token_tbl(2).token_value :=
729                         l_rev_sub_resource_rec.schedule_sequence_number ;
730                RAISE EXC_UNEXP_SKIP_OBJECT;
731          END IF;
732 
733 
734          --
735          -- Process Flow step 12: Value to Id conversions
736          -- Call Rtg_Val_To_Id.Rev_Sub_Resource_VID
737          --
738 
739          Bom_Rtg_Val_To_Id.Rev_Sub_Resource_VID
740          (  p_rev_sub_resource_rec       => l_rev_sub_resource_rec
741          ,  p_rev_sub_res_unexp_rec      => l_rev_sub_res_unexp_rec
742          ,  x_rev_sub_res_unexp_rec      => l_rev_sub_res_unexp_rec
743          ,  x_mesg_token_tbl             => l_mesg_token_tbl
744          ,  x_return_status              => l_return_status
745          );
746 
747          IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
748          ('Value-id conversions completed with return_status: ' || l_return_status) ;
749          END IF ;
750 
751          IF l_return_status = Error_Handler.G_STATUS_ERROR
752          THEN
753             IF l_rev_sub_resource_rec.transaction_type = 'CREATE'
754             THEN
755                l_other_message := 'BOM_SUB_RES_VID_CSEV_SKIP';
756                l_other_token_tbl(1).token_name := 'SUB_RESOURCE_CODE';
757                l_other_token_tbl(1).token_value :=
758                         l_rev_sub_resource_rec.sub_resource_code ;
759                l_other_token_tbl(2).token_name := 'SCHEDULE_SEQ_NUMBER';
760                l_other_token_tbl(2).token_value :=
761                         l_rev_sub_resource_rec.schedule_sequence_number ;
762                RAISE EXC_SEV_SKIP_BRANCH;
763             ELSE
764                RAISE EXC_SEV_QUIT_RECORD ;
765             END IF ;
766 
767          ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
768          THEN
769             l_other_message := 'BOM_SUB_RES_VID_UNEXP_SKIP';
770             l_other_token_tbl(1).token_name := 'SUB_RESOURCE_CODE';
771             l_other_token_tbl(1).token_value :=
772                      l_rev_sub_resource_rec.sub_resource_code ;
773             l_other_token_tbl(2).token_name := 'SCHEDULE_SEQ_NUMBER';
774             l_other_token_tbl(2).token_value :=
775                      l_rev_sub_resource_rec.schedule_sequence_number ;
776             RAISE EXC_UNEXP_SKIP_OBJECT;
777 
778          ELSIF l_return_status ='S' AND l_mesg_token_tbl.COUNT <> 0
779          THEN
780            ECO_Error_Handler.Log_Error
781             (
782                p_rev_sub_resource_tbl=> x_rev_sub_resource_tbl
783             ,  p_mesg_token_tbl      => l_mesg_token_tbl
784             ,  p_error_status        => 'W'
785             ,  p_error_level         => ECO_Error_Handler.G_SR_LEVEL
786             ,  p_entity_index        => I
787             ,  x_eco_rec             => l_ECO_rec
788             ,  x_eco_revision_tbl    => l_eco_revision_tbl
789             ,  x_revised_item_tbl    => l_revised_item_tbl
790             ,  x_rev_component_tbl   => l_rev_component_tbl
791             ,  x_ref_designator_tbl  => l_ref_designator_tbl
792             ,  x_sub_component_tbl   => l_sub_component_tbl
793             ,  x_rev_operation_tbl   => l_rev_operation_tbl
794             ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl
795             ,  x_rev_sub_resource_tbl=> x_rev_sub_resource_tbl
796             ) ;
797 
798 
799          END IF;
800 
801 
802          --
803          -- Process Flow step 13 : Check required fields exist
804          -- (also includes a part of conditionally required fields)
805          --
806          -- No process contents
807 
808          --
809          -- Process Flow step 14 : Attribute Validation for CREATE and UPDATE
810          -- Call Bom_Validate_Op_Res.Check_Attributes
811          --
812 
813          IF l_rev_sub_resource_rec.transaction_type IN
814             (Bom_Rtg_Globals.G_OPR_CREATE, Bom_Rtg_Globals.G_OPR_UPDATE)
815          THEN
816             Bom_Validate_Sub_Op_Res.Check_Attributes
817             ( p_rev_sub_resource_rec   => l_rev_sub_resource_rec
818             , p_rev_sub_res_unexp_rec  => l_rev_sub_res_unexp_rec
819             , x_return_status          => l_return_status
820             , x_mesg_token_tbl         => l_mesg_token_tbl
821             ) ;
822 
823             IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
824             ('Attribute validation completed with return_status: ' ||
825                   l_return_status) ;
826             END IF ;
827 
828             IF l_return_status = Error_Handler.G_STATUS_ERROR
829             THEN
830                IF l_rev_sub_resource_rec.transaction_type = Bom_Rtg_Globals.G_OPR_CREATE
831                THEN
832                   l_other_message := 'BOM_SUB_RES_ATTVAL_CSEV_SKIP';
833                   l_other_token_tbl(1).token_name := 'SUB_RESOURCE_CODE';
834                   l_other_token_tbl(1).token_value :=
835                         l_rev_sub_resource_rec.sub_resource_code ;
836                   l_other_token_tbl(2).token_name := 'SCHEDULE_SEQ_NUMBER';
837                   l_other_token_tbl(2).token_value :=
838                         l_rev_sub_resource_rec.schedule_sequence_number ;
839                   RAISE EXC_SEV_SKIP_BRANCH ;
840                   ELSE
841                      RAISE EXC_SEV_QUIT_RECORD ;
842                END IF;
843             ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
844             THEN
845                l_other_message := 'BOM_SUB_RES_ATTVAL_UNEXP_SKIP';
846                l_other_token_tbl(1).token_name := 'SUB_RESOURCE_CODE';
847                l_other_token_tbl(1).token_value :=
848                         l_rev_sub_resource_rec.sub_resource_code ;
849                l_other_token_tbl(2).token_name := 'SCHEDULE_SEQ_NUMBER';
850                l_other_token_tbl(2).token_value :=
851                         l_rev_sub_resource_rec.schedule_sequence_number ;
852                RAISE EXC_UNEXP_SKIP_OBJECT ;
853             ELSIF l_return_status ='S' AND l_mesg_token_tbl.COUNT <> 0
854             THEN
855                ECO_Error_Handler.Log_Error
856                (
857                   p_rev_sub_resource_tbl=> x_rev_sub_resource_tbl
858                ,  p_mesg_token_tbl      => l_mesg_token_tbl
859                ,  p_error_status        => 'W'
860                ,  p_error_level         => ECO_Error_Handler.G_SR_LEVEL
861                ,  p_entity_index        => I
862                ,  x_eco_rec             => l_ECO_rec
863                ,  x_eco_revision_tbl    => l_eco_revision_tbl
864                ,  x_revised_item_tbl    => l_revised_item_tbl
865                ,  x_rev_component_tbl   => l_rev_component_tbl
866                ,  x_ref_designator_tbl  => l_ref_designator_tbl
867                ,  x_sub_component_tbl   => l_sub_component_tbl
868                ,  x_rev_operation_tbl   => l_rev_operation_tbl
869                ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl
870                ,  x_rev_sub_resource_tbl=> x_rev_sub_resource_tbl
871                ) ;
872            END IF;
873         END IF;
874 
875         IF l_rev_sub_resource_rec.transaction_type IN
876            (Bom_Rtg_Globals.G_OPR_UPDATE, Bom_Rtg_Globals.G_OPR_DELETE)
877         THEN
878 
879         --
880         -- Process flow step 16: Populate NULL columns for Update and Delete
881         -- Call Bom_Default_Op_Res.Populate_Null_Columns
882         --
883 
884            IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Populate NULL columns') ;
885            END IF ;
886 
887            Bom_Default_Sub_Op_Res.Populate_Null_Columns
888            (   p_rev_sub_resource_rec       => l_rev_sub_resource_rec
889            ,   p_old_rev_sub_resource_rec   => l_old_rev_sub_resource_rec
890            ,   p_rev_sub_res_unexp_rec      => l_rev_sub_res_unexp_rec
891            ,   p_old_rev_sub_res_unexp_rec  => l_old_rev_sub_res_unexp_rec
892            ,   x_rev_sub_resource_rec       => l_rev_sub_resource_rec
893            ,   x_rev_sub_res_unexp_rec      => l_rev_sub_res_unexp_rec
894            ) ;
895 
896 
897         ELSIF l_rev_sub_resource_rec.transaction_type = Bom_Rtg_Globals.G_OPR_CREATE
898         THEN
899         --
900         -- Process Flow step 18 : Default missing values for Sub Op Resource (CREATE)
901         -- Call Bom_Default_Op_Res.Attribute_Defaulting
902         --
903 
904            IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Attribute Defaulting') ;
905            END IF ;
906 
907            Bom_Default_Sub_Op_Res.Attribute_Defaulting
908            (   p_rev_sub_resource_rec => l_rev_sub_resource_rec
909            ,   p_rev_sub_res_unexp_rec=> l_rev_sub_res_unexp_rec
910            ,   p_control_rec          => Bom_Rtg_Pub.G_Default_Control_Rec
911            ,   x_rev_sub_resource_rec => l_rev_sub_resource_rec
912            ,   x_rev_sub_res_unexp_rec=> l_rev_sub_res_unexp_rec
913            ,   x_mesg_token_tbl       => l_mesg_token_tbl
914            ,   x_return_status        => l_return_status
915            ) ;
916 
917 
918            IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
919            ('Attribute Defaulting completed with return_status: ' || l_return_status) ;
920            END IF ;
921 
922            IF l_return_status = Error_Handler.G_STATUS_ERROR
923            THEN
924               l_other_message := 'BOM_SUB_RES_ATTDEF_CSEV_SKIP';
925               l_other_token_tbl(1).token_name := 'SUB_RESOURCE_CODE';
926               l_other_token_tbl(1).token_value:=
927                         l_rev_sub_resource_rec.sub_resource_code ;
928               l_other_token_tbl(2).token_name := 'SCHEDULE_SEQ_NUMBER';
929               l_other_token_tbl(2).token_value:=
930                         l_rev_sub_resource_rec.schedule_sequence_number ;
931               RAISE EXC_SEV_SKIP_BRANCH ;
932 
933            ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
934            THEN
935               l_other_message := 'BOM_SUB_RES_ATTDEF_UNEXP_SKIP';
936               l_other_token_tbl(1).token_name := 'SUB_RESOURCE_CODE';
937               l_other_token_tbl(1).token_value:=
938                         l_rev_sub_resource_rec.sub_resource_code ;
939               l_other_token_tbl(2).token_name := 'SCHEDULE_SEQ_NUMBER';
940               l_other_token_tbl(2).token_value:=
941                         l_rev_sub_resource_rec.schedule_sequence_number;
942               RAISE EXC_UNEXP_SKIP_OBJECT ;
943            ELSIF l_return_status ='S' AND l_mesg_token_tbl.COUNT <> 0
944            THEN
945                ECO_Error_Handler.Log_Error
946                (  p_rev_sub_resource_tbl=> x_rev_sub_resource_tbl
947                ,  p_mesg_token_tbl      => l_mesg_token_tbl
948                ,  p_error_status        => 'W'
949                ,  p_error_level         => Error_Handler.G_SR_LEVEL
950                ,  p_entity_index        => I
951                ,  x_ECO_rec             => l_ECO_rec
952                ,  x_eco_revision_tbl    => l_eco_revision_tbl
953                ,  x_revised_item_tbl    => l_revised_item_tbl
954                ,  x_rev_component_tbl   => l_rev_component_tbl
955                ,  x_ref_designator_tbl  => l_ref_designator_tbl
956                ,  x_sub_component_tbl   => l_sub_component_tbl
957                ,  x_rev_operation_tbl   => l_rev_operation_tbl
958                ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl
959                ,  x_rev_sub_resource_tbl=> x_rev_sub_resource_tbl
960                ) ;
961           END IF;
962        END IF;
963 
964        --
965        -- Process Flow step 17: Conditionally Required Attributes
966        -- No process contents
967        --
968 
969        --
970        -- Process Flow step 18: Entity defaulting for CREATE and UPDATE
971        --
972 
973 
974        IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Entity defaulting') ;
975        END IF ;
976        IF l_rev_sub_resource_rec.transaction_type IN ( Bom_Rtg_Globals.G_OPR_CREATE
977                                                  , Bom_Rtg_Globals.G_OPR_UPDATE )
978        THEN
979           Bom_Default_Sub_OP_Res.Entity_Defaulting
980               (   p_rev_sub_resource_rec   => l_rev_sub_resource_rec
981               ,   p_rev_sub_res_unexp_rec  => l_rev_sub_res_unexp_rec
982               ,   p_control_rec            => Bom_Rtg_Pub.G_Default_Control_Rec
983               ,   x_rev_sub_resource_rec   => l_rev_sub_resource_rec
984               ,   x_rev_sub_res_unexp_rec  => l_rev_sub_res_unexp_rec
985               ,   x_mesg_token_tbl         => l_mesg_token_tbl
986               ,   x_return_status          => l_return_status
987               ) ;
988 
989           IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
990           ('Entity defaulting completed with return_status: ' || l_return_status) ;
991           END IF ;
992 
993           IF l_return_status = Error_Handler.G_STATUS_ERROR
994           THEN
995              IF l_rev_sub_resource_rec.transaction_type = Bom_Rtg_Globals.G_OPR_CREATE
996              THEN
997                 l_other_message := 'BOM_SUB_RES_ENTDEF_CSEV_SKIP';
998                 l_other_token_tbl(1).token_name := 'SUB_RESOURCE_CODE';
999                 l_other_token_tbl(1).token_value :=
1000                         l_rev_sub_resource_rec.sub_resource_code ;
1001                 l_other_token_tbl(2).token_name := 'SCHEDULE_SEQ_NUMBER';
1002                 l_other_token_tbl(2).token_value :=
1003                         l_rev_sub_resource_rec.schedule_sequence_number ;
1004                 RAISE EXC_SEV_SKIP_BRANCH ;
1005              ELSE
1006                 RAISE EXC_SEV_QUIT_RECORD ;
1007              END IF;
1008           ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
1009           THEN
1010              l_other_message := 'BOM_SUB_RES_ENTDEF_UNEXP_SKIP';
1011              l_other_token_tbl(1).token_name := 'SUB_RESOURCE_CODE';
1012              l_other_token_tbl(1).token_value :=
1013                         l_rev_sub_resource_rec.sub_resource_code ;
1014              l_other_token_tbl(2).token_name := 'SCHEDULE_SEQ_NUMBER';
1015              l_other_token_tbl(2).token_value :=
1016                         l_rev_sub_resource_rec.schedule_sequence_number ;
1017              RAISE EXC_UNEXP_SKIP_OBJECT ;
1018           ELSIF l_return_status ='S' AND l_mesg_token_tbl.COUNT <> 0
1019           THEN
1020              ECO_Error_Handler.Log_Error
1021              (  p_rev_sub_resource_tbl    => x_rev_sub_resource_tbl
1022              ,  p_mesg_token_tbl      => l_mesg_token_tbl
1023              ,  p_error_status        => 'W'
1024              ,  p_error_level         => ECO_Error_Handler.G_SR_LEVEL
1025              ,  p_entity_index        => I
1026              ,  x_ECO_rec               => l_ECO_rec
1027              ,  x_eco_revision_tbl      => l_eco_revision_tbl
1028              ,  x_revised_item_tbl      => l_revised_item_tbl
1029              ,  x_rev_component_tbl     => l_rev_component_tbl
1030              ,  x_ref_designator_tbl    => l_ref_designator_tbl
1031              ,  x_sub_component_tbl     => l_sub_component_tbl
1032              ,  x_rev_operation_tbl     => l_rev_operation_tbl
1033              ,  x_rev_op_resource_tbl   => l_rev_op_resource_tbl
1034              ,  x_rev_sub_resource_tbl  => x_rev_sub_resource_tbl
1035              ) ;
1036           END IF ;
1037        END IF ;
1038 
1039 
1040        --
1041        -- Process Flow step 19 - Entity Level Validation
1042        -- Call Bom_Validate_Op_Res.Check_Entity
1043        --
1044 
1045 IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN
1046    Error_Handler.Write_Debug('Starting Entity Validation for Sub Op Resources . . . ') ;
1047 END IF ;
1048 
1049           Bom_Validate_Sub_Op_Res.Check_Entity
1050           (  p_rev_sub_resource_rec       => l_rev_sub_resource_rec
1051           ,  p_rev_sub_res_unexp_rec      => l_rev_sub_res_unexp_rec
1052           ,  p_old_rev_sub_resource_rec   => l_old_rev_sub_resource_rec
1053           ,  p_old_rev_sub_res_unexp_rec  => l_old_rev_sub_res_unexp_rec
1054           ,  p_control_rec                => Bom_Rtg_Pub.G_Default_Control_Rec
1055           ,  x_rev_sub_resource_rec       => l_rev_sub_resource_rec
1056           ,  x_rev_sub_res_unexp_rec      => l_rev_sub_res_unexp_rec
1057           ,  x_mesg_token_tbl             => l_mesg_token_tbl
1058           ,  x_return_status              => l_return_status
1059           ) ;
1060 
1061        IF l_return_status = Error_Handler.G_STATUS_ERROR
1062        THEN
1063           IF l_rev_sub_resource_rec.transaction_type = Bom_Rtg_Globals.G_OPR_CREATE
1064           THEN
1065              l_other_message := 'BOM_SUB_RES_ENTVAL_CSEV_SKIP';
1066              l_other_token_tbl(1).token_name := 'SUB_RESOURCE_CODE';
1067              l_other_token_tbl(1).token_value :=
1068                         l_rev_sub_resource_rec.sub_resource_code ;
1069              l_other_token_tbl(2).token_name := 'SCHEDULE_SEQ_NUMBER';
1070              l_other_token_tbl(2).token_value :=
1071                         l_rev_sub_resource_rec.schedule_sequence_number ;
1072              RAISE EXC_SEV_SKIP_BRANCH ;
1073           ELSE
1074              RAISE EXC_SEV_QUIT_RECORD ;
1075           END IF;
1076        ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
1077        THEN
1078           l_other_message := 'BOM_SUB_RES_ENTVAL_UNEXP_SKIP';
1079           l_other_token_tbl(1).token_name := 'SUB_RESOURCE_CODE';
1080           l_other_token_tbl(1).token_value :=
1081                         l_rev_sub_resource_rec.sub_resource_code ;
1082           l_other_token_tbl(2).token_name := 'SCHEDULE_SEQ_NUMBER';
1083           l_other_token_tbl(2).token_value :=
1084                         l_rev_sub_resource_rec.schedule_sequence_number ;
1085           RAISE EXC_UNEXP_SKIP_OBJECT ;
1086        ELSIF l_return_status ='S' AND l_mesg_token_tbl.COUNT <> 0
1087        THEN
1088           ECO_Error_Handler.Log_Error
1089           (  p_rev_sub_resource_tbl=> x_rev_sub_resource_tbl
1090           ,  p_mesg_token_tbl      => l_mesg_token_tbl
1091           ,  p_error_status        => 'W'
1092           ,  p_error_level         => ECO_Error_Handler.G_SR_LEVEL
1093           ,  p_entity_index        => I
1094           ,  x_ECO_rec             => l_ECO_rec
1095           ,  x_eco_revision_tbl    => l_eco_revision_tbl
1096           ,  x_revised_item_tbl    => l_revised_item_tbl
1097           ,  x_rev_component_tbl   => l_rev_component_tbl
1098           ,  x_ref_designator_tbl  => l_ref_designator_tbl
1099           ,  x_sub_component_tbl   => l_sub_component_tbl
1100           ,  x_rev_operation_tbl   => l_rev_operation_tbl
1101           ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl
1102           ,  x_rev_sub_resource_tbl=> x_rev_sub_resource_tbl
1103           ) ;
1104        END IF;
1105 
1106        IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Entity validation completed with '
1107              || l_return_Status || ' proceeding for database writes . . . ') ;
1108        END IF;
1109 
1110        --
1111        -- Process Flow step 20 : Database Writes
1112        --
1113           Bom_Sub_Op_Res_Util.Perform_Writes
1114           (   p_rev_sub_resource_rec => l_rev_sub_resource_rec
1115           ,   p_rev_sub_res_unexp_rec=> l_rev_sub_res_unexp_rec
1116           ,   p_control_rec          => Bom_Rtg_Pub.G_Default_Control_Rec
1117           ,   x_mesg_token_tbl       => l_mesg_token_tbl
1118           ,   x_return_status        => l_return_status
1119           ) ;
1120 
1121        IF l_return_status = ECo_Error_Handler.G_STATUS_UNEXPECTED
1122        THEN
1123           l_other_message := 'BOM_SUB_RES_WRITES_UNEXP_SKIP';
1124           l_other_token_tbl(1).token_name := 'SUB_RESOURCE_CODE';
1125           l_other_token_tbl(1).token_value :=
1126                         l_rev_sub_resource_rec.sub_resource_code ;
1127           l_other_token_tbl(2).token_name := 'SCHEDULE_SEQ_NUMBER';
1128           l_other_token_tbl(2).token_value :=
1129                         l_rev_sub_resource_rec.schedule_sequence_number ;
1130           RAISE EXC_UNEXP_SKIP_OBJECT ;
1131        ELSIF l_return_status ='S' AND
1132           l_mesg_token_tbl.COUNT <>0
1133        THEN
1134           ECO_Error_Handler.Log_Error
1135           (  p_rev_sub_resource_tbl    => x_rev_sub_resource_tbl
1136           ,  p_mesg_token_tbl      => l_mesg_token_tbl
1137           ,  p_error_status        => 'W'
1138           ,  p_error_level         => ECO_Error_Handler.G_SR_LEVEL
1139           ,  p_entity_index        => I
1140           ,  x_ECO_rec             => l_ECO_rec
1141           ,  x_eco_revision_tbl    => l_eco_revision_tbl
1142           ,  x_revised_item_tbl    => l_revised_item_tbl
1143           ,  x_rev_component_tbl   => l_rev_component_tbl
1144           ,  x_ref_designator_tbl  => l_ref_designator_tbl
1145           ,  x_sub_component_tbl   => l_sub_component_tbl
1146           ,  x_rev_operation_tbl   => l_rev_operation_tbl
1147           ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl
1148           ,  x_rev_sub_resource_tbl=> x_rev_sub_resource_tbl
1149           ) ;
1150        END IF;
1151 
1152        IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Database writes completed with status  ' || l_return_status);
1153        END IF;
1154 
1155 
1156     END IF; -- END IF statement that checks RETURN STATUS
1157 
1158     --  Load tables.
1159     x_rev_sub_resource_tbl(I)          := l_rev_sub_resource_rec;
1160 
1161 
1162     --  For loop exception handler.
1163 
1164     EXCEPTION
1165        WHEN EXC_SEV_QUIT_RECORD THEN
1166           ECO_Error_Handler.Log_Error
1167           (  p_rev_sub_resource_tbl    => x_rev_sub_resource_tbl
1168           ,  p_mesg_token_tbl      => l_mesg_token_tbl
1169           ,  p_error_status        => FND_API.G_RET_STS_ERROR
1170           ,  p_error_scope         => Error_Handler.G_SCOPE_RECORD
1171           ,  p_error_level         => ECO_Error_Handler.G_SR_LEVEL
1172           ,  p_entity_index        => I
1173           ,  x_ECO_rec             => l_ECO_rec
1174           ,  x_eco_revision_tbl    => l_eco_revision_tbl
1175           ,  x_revised_item_tbl    => l_revised_item_tbl
1176           ,  x_rev_component_tbl   => l_rev_component_tbl
1177           ,  x_ref_designator_tbl  => l_ref_designator_tbl
1178           ,  x_sub_component_tbl   => l_sub_component_tbl
1179           ,  x_rev_operation_tbl   => l_rev_operation_tbl
1180           ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl
1181           ,  x_rev_sub_resource_tbl=> x_rev_sub_resource_tbl
1182           ) ;
1183 
1184 
1185          IF l_bo_return_status = 'S'
1186          THEN
1187             l_bo_return_status := l_return_status ;
1188          END IF;
1189 
1190          x_return_status       := l_bo_return_status;
1191          x_mesg_token_tbl      := l_mesg_token_tbl ;
1192          --x_rev_sub_resource_tbl    := l_rev_sub_resource_tbl ;
1193 
1194 
1195       WHEN EXC_SEV_QUIT_BRANCH THEN
1196 
1197          ECO_Error_Handler.Log_Error
1198          (  p_rev_sub_resource_tbl=> x_rev_sub_resource_tbl
1199          ,  p_mesg_token_tbl      => l_mesg_token_tbl
1200          ,  p_error_status        => Error_Handler.G_STATUS_ERROR
1201          ,  p_error_scope         => Error_Handler.G_SCOPE_CHILDREN
1202          ,  p_other_status        => ECo_Error_Handler.G_STATUS_ERROR
1203          ,  p_other_message       => l_other_message
1204          ,  p_other_token_tbl     => l_other_token_tbl
1205          ,  p_error_level         => ECO_Error_Handler.G_SR_LEVEL
1206          ,  p_entity_index        => I
1207          ,  x_ECO_rec             => l_ECO_rec
1208          ,  x_eco_revision_tbl    => l_eco_revision_tbl
1209          ,  x_revised_item_tbl    => l_revised_item_tbl
1210          ,  x_rev_component_tbl   => l_rev_component_tbl
1211          ,  x_ref_designator_tbl  => l_ref_designator_tbl
1212          ,  x_sub_component_tbl   => l_sub_component_tbl
1213          ,  x_rev_operation_tbl   => l_rev_operation_tbl
1214          ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl
1215          ,  x_rev_sub_resource_tbl=> x_rev_sub_resource_tbl
1216          ) ;
1217 
1218 
1219          IF l_bo_return_status = 'S'
1220          THEN
1221             l_bo_return_status := l_return_status;
1222          END IF;
1223 
1224          x_return_status       := l_bo_return_status;
1225          x_mesg_token_tbl      := l_mesg_token_tbl ;
1226          --x_rev_sub_resource_tbl    := l_rev_sub_resource_tbl ;
1227 
1228       WHEN EXC_SEV_SKIP_BRANCH THEN
1229          ECO_Error_Handler.Log_Error
1230          (  p_rev_sub_resource_tbl=> x_rev_sub_resource_tbl
1231          ,  p_mesg_token_tbl      => l_mesg_token_tbl
1232          ,  p_error_status        => Error_Handler.G_STATUS_ERROR
1233          ,  p_error_scope         => Error_Handler.G_SCOPE_CHILDREN
1234          ,  p_other_status        => Error_Handler.G_STATUS_NOT_PICKED
1235          ,  p_other_message       => l_other_message
1236          ,  p_other_token_tbl     => l_other_token_tbl
1237          ,  p_error_level         => ECO_Error_Handler.G_SR_LEVEL
1238          ,  p_entity_index        => I
1239          ,  x_ECO_rec             => l_ECO_rec
1240          ,  x_eco_revision_tbl    => l_eco_revision_tbl
1241          ,  x_revised_item_tbl    => l_revised_item_tbl
1242          ,  x_rev_component_tbl   => l_rev_component_tbl
1243          ,  x_ref_designator_tbl  => l_ref_designator_tbl
1244          ,  x_sub_component_tbl   => l_sub_component_tbl
1245          ,  x_rev_operation_tbl   => l_rev_operation_tbl
1246          ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl
1247          ,  x_rev_sub_resource_tbl=> x_rev_sub_resource_tbl
1248          ) ;
1249 
1250         IF l_bo_return_status = 'S'
1251         THEN
1252            l_bo_return_status  := l_return_status ;
1253         END IF;
1254         x_return_status        := l_bo_return_status;
1255         x_mesg_token_tbl       := l_mesg_token_tbl ;
1256         --x_rev_sub_resource_tbl := l_rev_sub_resource_tbl ;
1257 
1258       WHEN EXC_SEV_QUIT_SIBLINGS THEN
1259          ECO_Error_Handler.Log_Error
1260          (  p_rev_sub_resource_tbl=> x_rev_sub_resource_tbl
1261          ,  p_mesg_token_tbl      => l_mesg_token_tbl
1262          ,  p_error_status        => Error_Handler.G_STATUS_ERROR
1263          ,  p_error_scope         => Error_Handler.G_SCOPE_SIBLINGS
1264          ,  p_other_status        => Error_Handler.G_STATUS_ERROR
1265          ,  p_other_message       => l_other_message
1266          ,  p_other_token_tbl     => l_other_token_tbl
1267          ,  p_error_level         => ECO_Error_Handler.G_SR_LEVEL
1268          ,  p_entity_index        => I
1269          ,  x_ECO_rec             => l_ECO_rec
1270          ,  x_eco_revision_tbl    => l_eco_revision_tbl
1271          ,  x_revised_item_tbl    => l_revised_item_tbl
1272          ,  x_rev_component_tbl   => l_rev_component_tbl
1273          ,  x_ref_designator_tbl  => l_ref_designator_tbl
1274          ,  x_sub_component_tbl   => l_sub_component_tbl
1275          ,  x_rev_operation_tbl   => l_rev_operation_tbl
1276          ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl
1277          ,  x_rev_sub_resource_tbl=> x_rev_sub_resource_tbl
1278          ) ;
1279 
1280          IF l_bo_return_status = 'S'
1281          THEN
1282            l_bo_return_status  := l_return_status ;
1283          END IF;
1284          x_return_status       := l_bo_return_status;
1285          x_mesg_token_tbl      := l_mesg_token_tbl ;
1286          --x_rev_sub_resource_tbl    := l_rev_sub_resource_tbl ;
1287 
1288 
1289       WHEN EXC_FAT_QUIT_BRANCH THEN
1290          ECO_Error_Handler.Log_Error
1291          (  p_rev_sub_resource_tbl=> x_rev_sub_resource_tbl
1292          ,  p_mesg_token_tbl      => l_mesg_token_tbl
1293          ,  p_error_status        => Error_Handler.G_STATUS_FATAL
1294          ,  p_error_scope         => Error_Handler.G_SCOPE_CHILDREN
1295          ,  p_other_status        => Error_Handler.G_STATUS_FATAL
1296          ,  p_other_message       => l_other_message
1297          ,  p_other_token_tbl     => l_other_token_tbl
1298          ,  p_error_level         => ECO_Error_Handler.G_SR_LEVEL
1299          ,  p_entity_index        => I
1300          ,  x_ECO_rec             => l_ECO_rec
1301          ,  x_eco_revision_tbl    => l_eco_revision_tbl
1302          ,  x_revised_item_tbl    => l_revised_item_tbl
1303          ,  x_rev_component_tbl   => l_rev_component_tbl
1304          ,  x_ref_designator_tbl  => l_ref_designator_tbl
1305          ,  x_sub_component_tbl   => l_sub_component_tbl
1306          ,  x_rev_operation_tbl   => l_rev_operation_tbl
1307          ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl
1308          ,  x_rev_sub_resource_tbl=> x_rev_sub_resource_tbl
1309          ) ;
1310 
1311          x_return_status         := Error_Handler.G_STATUS_FATAL;
1312          x_mesg_token_tbl        := l_mesg_token_tbl ;
1313          --x_rev_sub_resource_tbl  := l_rev_sub_resource_tbl ;
1314 
1315 
1316       WHEN EXC_FAT_QUIT_SIBLINGS THEN
1317          ECO_Error_Handler.Log_Error
1318          (  p_rev_sub_resource_tbl=> x_rev_sub_resource_tbl
1319          ,  p_mesg_token_tbl      => l_mesg_token_tbl
1320          ,  p_error_status        => Error_Handler.G_STATUS_FATAL
1321          ,  p_error_scope         => Error_Handler.G_SCOPE_SIBLINGS
1322          ,  p_other_status        => Error_Handler.G_STATUS_FATAL
1323          ,  p_other_message       => l_other_message
1324          ,  p_other_token_tbl     => l_other_token_tbl
1325          ,  p_error_level         => ECO_Error_Handler.G_SR_LEVEL
1326          ,  p_entity_index        => I
1327          ,  x_ECO_rec             => l_ECO_rec
1328          ,  x_eco_revision_tbl    => l_eco_revision_tbl
1329          ,  x_revised_item_tbl    => l_revised_item_tbl
1330          ,  x_rev_component_tbl   => l_rev_component_tbl
1331          ,  x_ref_designator_tbl  => l_ref_designator_tbl
1332          ,  x_sub_component_tbl   => l_sub_component_tbl
1333          ,  x_rev_operation_tbl   => l_rev_operation_tbl
1334          ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl
1335          ,  x_rev_sub_resource_tbl=> x_rev_sub_resource_tbl
1336          ) ;
1337 
1338         x_return_status       := Error_Handler.G_STATUS_FATAL;
1339         x_mesg_token_tbl      := l_mesg_token_tbl ;
1340         --x_rev_sub_resource_tbl    := l_rev_sub_resource_tbl ;
1341 
1342     WHEN EXC_FAT_QUIT_OBJECT THEN
1343          ECO_Error_Handler.Log_Error
1344          (  p_rev_sub_resource_tbl=> x_rev_sub_resource_tbl
1345          ,  p_mesg_token_tbl      => l_mesg_token_tbl
1346          ,  p_error_status        => Error_Handler.G_STATUS_FATAL
1347          ,  p_error_scope         => Error_Handler.G_SCOPE_ALL
1348          ,  p_other_status        => Error_Handler.G_STATUS_FATAL
1349          ,  p_other_message       => l_other_message
1350          ,  p_other_token_tbl     => l_other_token_tbl
1351          ,  p_error_level         => ECO_Error_Handler.G_SR_LEVEL
1352          ,  p_entity_index        => I
1353          ,  x_ECO_rec             => l_ECO_rec
1354          ,  x_eco_revision_tbl    => l_eco_revision_tbl
1355          ,  x_revised_item_tbl    => l_revised_item_tbl
1356          ,  x_rev_component_tbl   => l_rev_component_tbl
1357          ,  x_ref_designator_tbl  => l_ref_designator_tbl
1358          ,  x_sub_component_tbl   => l_sub_component_tbl
1359          ,  x_rev_operation_tbl   => l_rev_operation_tbl
1360          ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl
1361          ,  x_rev_sub_resource_tbl=> x_rev_sub_resource_tbl
1362          ) ;
1363 
1364          l_return_status       := 'Q';
1365          x_mesg_token_tbl      := l_mesg_token_tbl ;
1366          --x_rev_sub_resource_tbl    := l_rev_sub_resource_tbl ;
1367 
1368       WHEN EXC_UNEXP_SKIP_OBJECT THEN
1369          ECO_Error_Handler.Log_Error
1370          (  p_rev_sub_resource_tbl=> x_rev_sub_resource_tbl
1371          ,  p_mesg_token_tbl      => l_mesg_token_tbl
1372          ,  p_error_status        => Error_Handler.G_STATUS_UNEXPECTED
1373          ,  p_other_status        => Error_Handler.G_STATUS_NOT_PICKED
1374          ,  p_other_message       => l_other_message
1375          ,  p_other_token_tbl     => l_other_token_tbl
1376          ,  p_error_level         => ECO_Error_Handler.G_SR_LEVEL
1377          ,  x_ECO_rec             => l_ECO_rec
1378          ,  x_eco_revision_tbl    => l_eco_revision_tbl
1379          ,  x_revised_item_tbl    => l_revised_item_tbl
1380          ,  x_rev_component_tbl   => l_rev_component_tbl
1381          ,  x_ref_designator_tbl  => l_ref_designator_tbl
1382          ,  x_sub_component_tbl   => l_sub_component_tbl
1383          ,  x_rev_operation_tbl   => l_rev_operation_tbl
1384          ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl
1385          ,  x_rev_sub_resource_tbl=> x_rev_sub_resource_tbl
1386          ) ;
1387 
1388          l_return_status       := 'U';
1389          x_mesg_token_tbl      := l_mesg_token_tbl ;
1390          --x_rev_sub_resource_tbl    := l_rev_sub_resource_tbl ;
1391 
1392    END ; -- END block
1393 
1394 
1395    IF l_return_status in ('Q', 'U')
1396    THEN
1397       x_return_status := l_return_status;
1398       RETURN ;
1399    END IF;
1400 
1401    END IF; -- End of processing records for which the return status is null
1402    END LOOP; -- END Substitute Operation Resources processing loop
1403 
1404    --  Load OUT parameters
1405    IF NVL(l_return_status, 'S') <> 'S'
1406    THEN
1407       x_return_status     := l_return_status;
1408    END IF;
1409 
1410    x_mesg_token_tbl      := l_mesg_token_tbl ;
1411    --x_rev_sub_resource_tbl    := l_rev_sub_resource_tbl ;
1412    x_mesg_token_tbl      := l_mesg_token_tbl ;
1413 
1414 END Rev_Sub_Operation_Resources ;
1415 
1416 --  Rev_Operation_Resources
1417 
1418 /****************************************************************************
1419 * Procedure : Rev_Operation_Resources
1420 * Parameters IN   : Revised Operation Resources Table and all the other sibiling entities
1421 * Parameters OUT  : Revised Operatin Resources and all the other sibiling entities
1422 * Purpose   : This procedure will process all the Revised Operation Resources records.
1423 *
1424 *****************************************************************************/
1425 
1426 PROCEDURE Rev_Operation_Resources
1427 (   p_validation_level              IN  NUMBER
1428 ,   p_change_notice                 IN  VARCHAR2 := NULL
1429 ,   p_organization_id               IN  NUMBER   := NULL
1430 ,   p_revised_item_name             IN  VARCHAR2 := NULL
1431 ,   p_effectivity_date              IN  DATE     := NULL
1432 ,   p_item_revision                 IN  VARCHAR2 := NULL
1433 ,   p_routing_revision              IN  VARCHAR2 := NULL -- Added by MK on 11/02/00
1434 ,   p_from_end_item_number          IN  VARCHAR2 := NULL -- Added by MK on 11/02/00
1435 ,   p_operation_seq_num             IN  NUMBER   := NULL
1436 ,   p_operation_type                IN  NUMBER   := NULL
1437 ,   p_alternate_routing_code        IN  VARCHAR2 := NULL -- Added for bug 13440461
1438 ,   p_rev_op_resource_tbl           IN  Bom_Rtg_Pub.Rev_Op_Resource_Tbl_Type
1439 ,   p_rev_sub_resource_tbl          IN  Bom_Rtg_Pub.Rev_Sub_Resource_Tbl_Type
1440 ,   x_rev_op_resource_tbl           IN OUT NOCOPY Bom_Rtg_Pub.Rev_Op_Resource_Tbl_Type
1441 ,   x_rev_sub_resource_tbl          IN OUT NOCOPY Bom_Rtg_Pub.Rev_Sub_Resource_Tbl_Type
1442 ,   x_mesg_token_tbl                OUT NOCOPY Error_Handler.Mesg_Token_Tbl_Type
1443 ,   x_return_status                 OUT NOCOPY VARCHAR2
1444 )
1445 IS
1446 
1447 /* Exposed and Unexposed record */
1448 l_rev_op_resource_rec         Bom_Rtg_Pub.Rev_Op_Resource_Rec_Type ;
1449 l_rev_op_res_unexp_rec        Bom_Rtg_Pub.Rev_Op_Res_Unexposed_Rec_Type ;
1450 --l_rev_op_resource_tbl         Bom_Rtg_Pub.Rev_Op_Resource_Tbl_Type ;
1451 l_old_rev_op_resource_rec     Bom_Rtg_Pub.Rev_Op_Resource_Rec_Type ;
1452 l_old_rev_op_res_unexp_rec    Bom_Rtg_Pub.Rev_Op_Res_Unexposed_Rec_Type ;
1453 
1454 
1455 
1456 /* Other Entities */
1457 l_eco_rec                ENG_Eco_PUB.Eco_Rec_Type;
1458 l_eco_revision_tbl       ENG_Eco_PUB.ECO_Revision_Tbl_Type;
1459 l_revised_item_tbl       ENG_Eco_PUB.Revised_Item_Tbl_Type;
1460 l_rev_component_rec      BOM_BO_PUB.Rev_Component_Rec_Type;
1461 l_rev_component_tbl      BOM_BO_PUB.Rev_Component_Tbl_Type;
1462 l_rev_comp_unexp_rec     BOM_BO_PUB.Rev_Comp_Unexposed_Rec_Type;
1463 l_old_rev_component_rec  BOM_BO_PUB.Rev_Component_Rec_Type;
1464 l_old_rev_comp_unexp_rec BOM_BO_PUB.Rev_Comp_Unexposed_Rec_Type;
1465 l_ref_designator_tbl     BOM_BO_PUB.Ref_Designator_Tbl_Type;
1466 l_sub_component_tbl      BOM_BO_PUB.Sub_Component_Tbl_Type;
1467 l_rev_operation_tbl      Bom_Rtg_Pub.Rev_Operation_Tbl_Type ;
1468 --l_rev_sub_resource_tbl   Bom_Rtg_Pub.Rev_Sub_Resource_Tbl_Type ;
1469 --                                   := p_rev_sub_resource_tbl ;
1470 
1471 
1472 /* Error Handling Variables */
1473 l_token_tbl             Error_Handler.Token_Tbl_Type ;
1474 l_mesg_token_tbl        Error_Handler.Mesg_Token_Tbl_Type ;
1475 l_other_token_tbl       Error_Handler.Token_Tbl_Type;
1476 l_other_message         VARCHAR2(2000);
1477 l_err_text              VARCHAR2(2000);
1478 
1479 
1480 /* Others */
1481 l_return_status         VARCHAR2(1);
1482 l_bo_return_status      VARCHAR2(1);
1483 l_op_parent_exists      BOOLEAN := FALSE;
1484 l_item_parent_exists    BOOLEAN := FALSE;
1485 l_process_children      BOOLEAN := TRUE;
1486 l_valid                 BOOLEAN := TRUE;
1487 
1488 /* Error handler definations */
1489 EXC_SEV_QUIT_RECORD     EXCEPTION ;
1490 EXC_SEV_QUIT_BRANCH     EXCEPTION ;
1491 EXC_UNEXP_SKIP_OBJECT   EXCEPTION ;
1492 EXC_SEV_QUIT_SIBLINGS   EXCEPTION ;
1493 EXC_SEV_SKIP_BRANCH     EXCEPTION ;
1494 EXC_FAT_QUIT_SIBLINGS   EXCEPTION ;
1495 EXC_FAT_QUIT_BRANCH     EXCEPTION ;
1496 EXC_FAT_QUIT_OBJECT     EXCEPTION ;
1497 
1498 BEGIN
1499 
1500    --  Init local table variables.
1501    l_return_status    := 'S';
1502    l_bo_return_status := 'S';
1503    --l_rev_op_resource_tbl  := p_rev_op_resource_tbl;
1504    x_rev_op_resource_tbl  := p_rev_op_resource_tbl;
1505    x_rev_sub_resource_tbl  := p_rev_sub_resource_tbl;
1506 
1507    l_rev_op_res_unexp_rec.organization_id := Eng_Globals.Get_Org_Id;
1508 
1509    FOR I IN 1..x_rev_op_resource_tbl.COUNT LOOP
1510    -- Processing records for which the return status is null
1511    IF (x_rev_op_resource_tbl(I).return_status IS NULL OR
1512         x_rev_op_resource_tbl(I).return_status  = FND_API.G_MISS_CHAR) THEN
1513    BEGIN
1514 
1515       --  Load local records
1516       l_rev_op_resource_rec := x_rev_op_resource_tbl(I) ;
1517 
1518       l_rev_op_resource_rec.transaction_type :=
1519          UPPER(l_rev_op_resource_rec.transaction_type) ;
1520 
1521       --
1522       -- Initialize the Unexposed Record for every iteration of the Loop
1523       -- so that sequence numbers get generated for every new row.
1524       --
1525       l_rev_op_res_unexp_rec.Revised_Item_Sequence_Id:= NULL ;
1526       l_rev_op_res_unexp_rec.Operation_Sequence_Id   := NULL ;
1527       l_rev_op_res_unexp_rec.Substitute_Group_Number := NULL ;
1528       l_rev_op_res_unexp_rec.Resource_Id             := NULL ;
1529       l_rev_op_res_unexp_rec.Activity_Id             := NULL ;
1530       l_rev_op_res_unexp_rec.Setup_Id                := NULL ;
1531 
1532 
1533       IF p_operation_seq_num  IS NOT NULL AND
1534          p_revised_item_name  IS NOT NULL AND
1535          p_effectivity_date   IS NOT NULL AND
1536          p_organization_id    IS NOT NULL AND
1537          p_change_notice IS NOT NULL
1538       THEN
1539          -- Revised Operation parent exists
1540          l_op_parent_exists  := TRUE ;
1541 
1542       ELSIF p_revised_item_name IS NOT NULL AND
1543             p_effectivity_date IS NOT NULL  AND
1544             /* p_item_revision IS NOT NULL     AND Commented for Bug 6485168 */
1545             p_change_notice IS NOT NULL     AND
1546             p_organization_id IS NOT NULL
1547       THEN
1548 
1549          -- Revised Item parent exists
1550          l_item_parent_exists := TRUE ;
1551       END IF ;
1552 
1553       -- Process Flow Step 2: Check if record has not yet been processed and
1554       -- that it is the child of the parent that called this procedure
1555       --
1556 
1557       IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
1558                         ('ECO Name: ' || p_change_notice ||
1559                          ' Org: ' || p_organization_id ||
1560                          ' Eff. Dt: ' || to_char(p_effectivity_date) ||
1561                          ' Revision: ' || p_item_revision ||
1562                          ' Rev Item: ' || p_revised_item_name ||
1563                          ' Op. Seq: ' || p_operation_seq_num); END IF;
1564 
1565 
1566       IF --(l_rev_op_resource_rec.return_status IS NULL OR
1567          --l_rev_op_resource_rec.return_status  = FND_API.G_MISS_CHAR)
1568          --AND
1569          (
1570             -- Did Op_Seq call this procedure, that is,
1571             -- if revised operation(operation sequence) exists, then is this record a child ?
1572             (l_op_parent_exists AND
1573                (l_rev_op_resource_rec.ECO_Name
1574                                              = p_change_notice    AND
1575                 l_rev_op_res_unexp_rec.organization_id
1576                                              = p_organization_id  AND
1577                 l_rev_op_resource_rec.op_start_effective_date
1578                                              = nvl(ENG_Default_Revised_Item.G_OLD_SCHED_DATE,p_effectivity_date) AND -- Bug 6657209
1579                 NVL(l_rev_op_resource_rec.new_revised_item_revision, FND_API.G_MISS_CHAR )
1580                                              = NVL(p_item_revision, FND_API.G_MISS_CHAR )   AND
1581                 l_rev_op_resource_rec.revised_item_name
1582                                             = p_revised_item_name AND
1583                 NVL(l_rev_op_resource_rec.alternate_routing_code, FND_API.G_MISS_CHAR )
1584                                             = NVL(p_alternate_routing_code, FND_API.G_MISS_CHAR) AND --Added for bug 13440461
1585                 NVL(l_rev_op_resource_rec.new_routing_revision, FND_API.G_MISS_CHAR )
1586                                              = NVL(p_routing_revision, FND_API.G_MISS_CHAR ) AND -- Added by MK on 11/02/00
1587                 NVL(l_rev_op_resource_rec.from_end_item_unit_number, FND_API.G_MISS_CHAR )
1588                                              = NVL(p_from_end_item_number, FND_API.G_MISS_CHAR ) AND -- Added by MK on 11/02/00
1589                 l_rev_op_resource_rec.operation_sequence_number
1590                                             = p_operation_seq_num AND
1591                 NVL(l_rev_op_resource_rec.operation_type, 1)
1592                                            = NVL(p_operation_type, 1)
1593                 )
1594              )
1595              OR
1596              -- Did Rev_Items call this procedure, that is,
1597              -- if revised item exists, then is this record a child ?
1598 
1599              (l_item_parent_exists AND
1600                (l_rev_op_resource_rec.ECO_Name
1601                                                 = p_change_notice AND
1602                 l_rev_op_res_unexp_rec.organization_id
1603                                               = p_organization_id AND
1604                 l_rev_op_resource_rec.revised_item_name
1605                                             = p_revised_item_name AND
1606                 NVL(l_rev_op_resource_rec.alternate_routing_code, FND_API.G_MISS_CHAR )
1607                                             = NVL(p_alternate_routing_code, FND_API.G_MISS_CHAR) AND --Added for bug 13440461
1608                 l_rev_op_resource_rec.op_start_effective_date
1609                                              = p_effectivity_date AND
1610                 NVL(l_rev_op_resource_rec.new_routing_revision, FND_API.G_MISS_CHAR )
1611                                              = NVL(p_routing_revision, FND_API.G_MISS_CHAR ) AND -- Added by MK on 11/02/00
1612                 NVL(l_rev_op_resource_rec.from_end_item_unit_number, FND_API.G_MISS_CHAR )
1613                                              = NVL(p_from_end_item_number, FND_API.G_MISS_CHAR ) AND -- Added by MK on 11/02/00
1614                 NVL(l_rev_op_resource_rec.new_revised_item_revision, FND_API.G_MISS_CHAR )
1615                                                   = NVL(p_item_revision, FND_API.G_MISS_CHAR ) )
1616              )
1617 
1618              OR
1619 
1620              (NOT l_item_parent_exists AND
1621               NOT l_op_parent_exists)
1622          )
1623 
1624       THEN
1625          l_return_status := FND_API.G_RET_STS_SUCCESS;
1626          l_rev_op_resource_rec.return_status := FND_API.G_RET_STS_SUCCESS;
1627 
1628          -- Bug 6657209
1629            IF (l_op_parent_exists and ENG_Default_Revised_Item.G_OLD_SCHED_DATE is not null) THEN
1630               l_rev_op_resource_rec.op_start_effective_date := p_effectivity_date;
1631            END IF;
1632 
1633          --
1634          -- Process Flow step 3 :Check if transaction_type is valid
1635          -- Transaction_Type must be CRATE, UPDATE, DELETE or CANCEL(in only ECO for Rrg)
1636          -- Call the Bom_Rtg_Globals.Transaction_Type_Validity
1637          --
1638 
1639          Eng_Globals.Transaction_Type_Validity
1640          (   p_transaction_type => l_rev_op_resource_rec.transaction_type
1641          ,   p_entity           => 'Op_Res'
1642          ,   p_entity_id        => l_rev_op_resource_rec.resource_sequence_number
1643          ,   x_valid            => l_valid
1644          ,   x_mesg_token_tbl   => l_mesg_token_tbl
1645          ) ;
1646 
1647          IF NOT l_valid
1648          THEN
1649             RAISE EXC_SEV_QUIT_RECORD ;
1650          END IF ;
1651 
1652          --
1653          -- Process Flow step 4(a): Convert user unique index to unique
1654          -- index I
1655          -- Call Rtg_Val_To_Id.Op_Resource_UUI_To_UI Shared Utility Package
1656          --
1657 
1658          Bom_Rtg_Val_To_Id.Rev_Op_Resource_UUI_To_UI
1659          ( p_rev_op_resource_rec    => l_rev_op_resource_rec
1660          , p_rev_op_res_unexp_rec   => l_rev_op_res_unexp_rec
1661          , x_rev_op_res_unexp_rec   => l_rev_op_res_unexp_rec
1662          , x_mesg_token_tbl         => l_mesg_token_tbl
1663          , x_return_status          => l_return_status
1664          ) ;
1665 
1666          IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
1667          ('Convert to User Unique Index to Index1 completed with return_status: ' || l_return_status) ;
1668          END IF;
1669 
1670          IF l_return_status = Error_Handler.G_STATUS_ERROR
1671          THEN
1672             l_other_message := 'BOM_RES_UUI_SEV_ERROR';
1673             l_other_token_tbl(1).token_name := 'RES_SEQ_NUMBER';
1674             l_other_token_tbl(1).token_value :=
1675                         l_rev_op_resource_rec.resource_sequence_number ;
1676             RAISE EXC_SEV_QUIT_BRANCH ;
1677 
1678          ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
1679          THEN
1680             l_other_message := 'BOM_RES_UUI_UNEXP_SKIP';
1681             l_other_token_tbl(1).token_name := 'RES_SEQ_NUMBER';
1682             l_other_token_tbl(1).token_value :=
1683                         l_rev_op_resource_rec.resource_sequence_number ;
1684             RAISE EXC_UNEXP_SKIP_OBJECT;
1685          END IF ;
1686 
1687 
1688          -- Added by MK on 12/03/00 to resolve ECO dependency
1689          ENG_Val_To_Id.RtgAndRevitem_UUI_To_UI
1690            ( p_revised_item_name        => l_rev_op_resource_rec.revised_item_name
1691            , p_revised_item_id          => l_rev_op_res_unexp_rec.revised_item_id
1692            , p_item_revision            => l_rev_op_resource_rec.new_revised_item_revision
1693            , p_effective_date           => l_rev_op_resource_rec.op_start_effective_date
1694            , p_change_notice            => l_rev_op_resource_rec.eco_name
1695            , p_organization_id          => l_rev_op_res_unexp_rec.organization_id
1696            , p_new_routing_revision     => l_rev_op_resource_rec.new_routing_revision
1697            , p_from_end_item_number     => l_rev_op_resource_rec.from_end_item_unit_number
1698            , p_entity_processed         => 'RES'
1699            , p_operation_sequence_number => l_rev_op_resource_rec.operation_sequence_number
1700            , p_resource_sequence_number  => l_rev_op_resource_rec.resource_sequence_number
1701            , p_alternate_routing_code    => l_rev_op_resource_rec.alternate_routing_code    -- Added for bug 13440461
1702            , x_revised_item_sequence_id  => l_rev_op_res_unexp_rec.revised_item_sequence_id
1703            , x_routing_sequence_id       => l_rev_op_res_unexp_rec.routing_sequence_id
1704            , x_operation_sequence_id     => l_rev_op_res_unexp_rec.operation_sequence_id
1705            , x_Mesg_Token_Tbl           => l_Mesg_Token_Tbl
1706            , x_other_message            => l_other_message
1707            , x_other_token_tbl          => l_other_token_tbl
1708            , x_Return_Status            => l_return_status
1709           ) ;
1710 
1711          IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
1712          ('Convert to User Unique Index to Index1 for Rtg and Rev Item Seq completed with return_status: ' || l_return_status) ;
1713          END IF;
1714 
1715          IF l_return_status = Error_Handler.G_STATUS_ERROR
1716          THEN
1717             l_other_message := 'BOM_RES_UUI_SEV_ERROR';
1718             l_other_token_tbl(1).token_name := 'RES_SEQ_NUMBER';
1719             l_other_token_tbl(1).token_value :=
1720                         l_rev_op_resource_rec.resource_sequence_number ;
1721             RAISE EXC_SEV_QUIT_BRANCH ;
1722 
1723          ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
1724          THEN
1725             l_other_message := 'BOM_RES_UUI_UNEXP_SKIP';
1726             l_other_token_tbl(1).token_name := 'RES_SEQ_NUMBER';
1727             l_other_token_tbl(1).token_value :=
1728                         l_rev_op_resource_rec.resource_sequence_number ;
1729             RAISE EXC_UNEXP_SKIP_OBJECT;
1730          END IF ;
1731 
1732 
1733          --
1734          -- Process Flow step 4(b): Convert user unique index to unique
1735          -- index II
1736          -- Call the Rtg_Val_To_Id.Operation_UUI_To_UI2
1737          --
1738          /*
1739          Bom_Rtg_Val_To_Id.Rev_Op_Resource_UUI_To_UI2
1740          ( p_rev_op_resource_rec    => l_rev_op_resource_rec
1741          , p_rev_op_res_unexp_rec   => l_rev_op_res_unexp_rec
1742          , x_rev_op_res_unexp_rec   => l_rev_op_res_unexp_rec
1743          , x_mesg_token_tbl         => l_mesg_token_tbl
1744          , x_other_message          => l_other_message
1745          , x_other_token_tbl        => l_other_token_tbl
1746          , x_return_status          => l_return_status
1747          ) ;
1748 
1749          IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
1750          ('Convert to User Unique Index to Index2 completed with return_status: ' || l_return_status) ;
1751          END IF;
1752 
1753          IF l_return_status = Error_Handler.G_STATUS_ERROR
1754          THEN
1755             RAISE EXC_SEV_QUIT_SIBLINGS ;
1756          ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
1757          THEN
1758             l_other_message := 'BOM_RES_UUI_UNEXP_SKIP';
1759             l_other_token_tbl(1).token_name := 'RES_SEQ_NUMBER';
1760             l_other_token_tbl(1).token_value :=
1761                    l_rev_op_resource_rec.resource_sequence_number ;
1762             RAISE EXC_UNEXP_SKIP_OBJECT;
1763          END IF ;
1764          */
1765          --
1766          -- Process Flow step 5: Verify Operation Resource's existence
1767          -- Call the Bom_Validate_Op_Seq.Check_Existence
1768          --
1769          --
1770 
1771          Bom_Validate_Op_Res.Check_Existence
1772          (  p_rev_op_resource_rec        => l_rev_op_resource_rec
1773          ,  p_rev_op_res_unexp_rec       => l_rev_op_res_unexp_rec
1774          ,  x_old_rev_op_resource_rec    => l_old_rev_op_resource_rec
1775          ,  x_old_rev_op_res_unexp_rec   => l_old_rev_op_res_unexp_rec
1776          ,  x_mesg_token_tbl             => l_mesg_token_tbl
1777          ,  x_return_status              => l_return_status
1778          ) ;
1779 
1780          IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
1781          ('Check Existence completed with return_status: ' || l_return_status) ;
1782          END IF ;
1783 
1784          IF l_return_status = Error_Handler.G_STATUS_ERROR
1785          THEN
1786             l_other_message := 'BOM_RES_EXS_SEV_SKIP';
1787             l_other_token_tbl(1).token_name := 'RES_SEQ_NUMBER';
1788             l_other_token_tbl(1).token_value :=
1789                           l_rev_op_resource_rec.resource_sequence_number ;
1790             l_other_token_tbl(2).token_name := 'REVISED_ITEM_NAME';
1791             l_other_token_tbl(2).token_value :=
1792                           l_rev_op_resource_rec.revised_item_name ;
1793             RAISE EXC_SEV_QUIT_BRANCH;
1794          ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
1795          THEN
1796             l_other_message := 'BOM_RES_EXS_UNEXP_SKIP';
1797             l_other_token_tbl(1).token_name := 'RES_SEQ_NUMBER';
1798             l_other_token_tbl(1).token_value :=
1799                           l_rev_op_resource_rec.resource_sequence_number ;
1800             l_other_token_tbl(2).token_name := 'REVISED_ITEM_NAME';
1801             l_other_token_tbl(2).token_value :=
1802                           l_rev_op_resource_rec.revised_item_name ;
1803             RAISE EXC_UNEXP_SKIP_OBJECT;
1804          END IF;
1805 
1806          --
1807          -- Process Flow step 6: Is Operation Resource record an orphan ?
1808          --
1809 
1810          IF NOT l_op_parent_exists
1811          THEN
1812 
1813             --
1814             -- Process Flow step 7: Check lineage
1815             --
1816             IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Check lineage');     END IF;
1817 
1818             BOM_Validate_Op_Seq.Check_Lineage
1819             ( p_routing_sequence_id       =>
1820                              l_rev_op_res_unexp_rec.routing_sequence_id
1821             , p_operation_sequence_number =>
1822                              l_rev_op_resource_rec.operation_sequence_number
1823             , p_effectivity_date          =>
1824                              l_rev_op_resource_rec.op_start_effective_date
1825             , p_operation_type            =>
1826                              l_rev_op_resource_rec.operation_type
1827             , p_revised_item_sequence_id  =>
1828                              l_rev_op_res_unexp_rec.revised_item_sequence_id
1829             , x_mesg_token_tbl            => l_mesg_token_tbl
1830             , x_return_status             => l_return_status
1831             ) ;
1832 
1833             IF l_return_status = Error_Handler.G_STATUS_ERROR
1834             THEN
1835                 l_Token_Tbl(1).token_name  := 'RES_SEQ_NUMBER' ;
1836                 l_Token_Tbl(1).token_value := l_rev_op_resource_rec.resource_sequence_number ;
1837                 l_Token_Tbl(2).token_name  := 'OP_SEQ_NUMBER' ;
1838                 l_Token_Tbl(2).token_value := l_rev_op_resource_rec.operation_sequence_number ;
1839                 l_Token_Tbl(3).token_name  := 'REVISED_ITEM_NAME' ;
1840                 l_Token_Tbl(3).token_value := l_rev_op_resource_rec.revised_item_name;
1841 
1842                 Error_Handler.Add_Error_Token
1843                 ( p_Message_Name  => 'BOM_RES_REV_ITEM_MISMATCH'
1844                 , p_Mesg_Token_Tbl => l_Mesg_Token_Tbl
1845                 , x_Mesg_Token_Tbl => l_Mesg_Token_Tbl
1846                 , p_Token_Tbl      => l_Token_Tbl
1847                 ) ;
1848 
1849 
1850                 l_other_message := 'BOM_RES_LIN_SEV_SKIP';
1851                 l_other_token_tbl(1).token_name := 'RES_SEQ_NUMBER';
1852                 l_other_token_tbl(1).token_value :=
1853                                l_rev_op_resource_rec.resource_sequence_number ;
1854                 RAISE EXC_SEV_QUIT_BRANCH;
1855 
1856             ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
1857             THEN
1858                 l_other_message := 'BOM_RES_LIN_UNEXP_SKIP';
1859                 l_other_token_tbl(1).token_name := 'RES_SEQ_NUMBER';
1860                 l_other_token_tbl(1).token_value :=
1861                            l_rev_op_resource_rec.resource_sequence_number ;
1862                 RAISE EXC_UNEXP_SKIP_OBJECT;
1863             END IF;
1864 
1865             IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
1866 
1867 
1868                 -- Process Flow step 8(a and b): Is ECO impl/cancl, or in wkflw process ?
1869                 --
1870 
1871                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Check ECO access'); END IF;
1872 
1873                 ENG_Validate_ECO.Check_Access
1874                 ( p_change_notice       => l_rev_op_resource_rec.ECO_Name
1875                 , p_organization_id     =>
1876                                         l_rev_op_res_unexp_rec.organization_id
1877                 , p_Mesg_Token_Tbl      => l_Mesg_Token_Tbl
1878                 , x_Mesg_Token_Tbl      => l_Mesg_Token_Tbl
1879                 , x_Return_Status       => l_return_status
1880                 );
1881 
1882                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
1883 
1884                 IF l_return_status = Error_Handler.G_STATUS_ERROR
1885                 THEN
1886                         l_other_message := 'BOM_RES_ECOACC_FAT_FATAL' ;
1887                         l_other_token_tbl(1).token_name := 'RES_SEQ_NUMBER';
1888                         l_other_token_tbl(1).token_value :=
1889                                l_rev_op_resource_rec.operation_sequence_number;
1890                         l_return_status := 'F';
1891                         RAISE EXC_FAT_QUIT_OBJECT;
1892                 ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
1893                 THEN
1894                         l_other_message := 'BOM_RES_ECOACC_UNEXP_SKIP' ;
1895                         l_other_token_tbl(1).token_name := 'RES_SEQ_NUMBER';
1896                         l_other_token_tbl(1).token_value :=
1897                                l_rev_op_resource_rec.resource_sequence_number;
1898                         RAISE EXC_UNEXP_SKIP_OBJECT;
1899                 END IF;
1900 
1901                 --
1902                 -- Process Flow step 9(a and b): check that user has access to revised item
1903                 --
1904 
1905                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Check Revised item access'); END IF;
1906                 ENG_Validate_Revised_Item.Check_Access
1907                 (  p_change_notice   => l_rev_op_resource_rec.ECO_Name
1908                 ,  p_organization_id => l_rev_op_res_unexp_rec.organization_id
1909                 ,  p_revised_item_id => l_rev_op_res_unexp_rec.revised_item_id
1910                 ,  p_new_item_revision  =>
1911                                l_rev_op_resource_rec.new_revised_item_revision
1912                 ,  p_effectivity_date   =>
1913                                l_rev_op_resource_rec.op_start_effective_date
1914                 ,  p_new_routing_revsion   => l_rev_op_resource_rec.new_routing_revision  -- Added by MK on 11/02/00
1915                 ,  p_from_end_item_number  => l_rev_op_resource_rec.from_end_item_unit_number -- Added by MK on 11/02/00
1916                 ,  p_revised_item_name  =>
1917                                l_rev_op_resource_rec.revised_item_name
1918                 ,  p_entity_processed   => 'RES'                                             -- Added by MK
1919                 ,  p_operation_seq_num  =>  l_rev_op_resource_rec.operation_sequence_number  -- Added by MK
1920                 ,  p_routing_sequence_id => l_rev_op_res_unexp_rec.routing_sequence_id       -- Added by MK
1921 
1922                 ,  p_Mesg_Token_Tbl     => l_Mesg_Token_Tbl
1923                 ,  x_Mesg_Token_Tbl     => l_Mesg_Token_Tbl
1924                 ,  x_return_status      => l_Return_Status
1925                 );
1926 
1927                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
1928 
1929                 IF l_return_status = Error_Handler.G_STATUS_ERROR
1930                 THEN
1931                         l_other_message := 'BOM_RES_RITACC_FAT_FATAL';
1932                         l_other_token_tbl(1).token_name := 'RES_SEQ_NUMBER';
1933                         l_other_token_tbl(1).token_value :=
1934                                l_rev_op_resource_rec.resource_sequence_number;
1935                         l_return_status := 'F';
1936                         RAISE EXC_FAT_QUIT_SIBLINGS;
1937                 ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
1938                 THEN
1939                         l_other_message := 'BOM_RES_RITACC_UNEXP_SKIP';
1940                         l_other_token_tbl(1).token_name := 'RES_SEQ_NUMBER';
1941                         l_other_token_tbl(1).token_value :=
1942                                l_rev_op_resource_rec.resource_sequence_number;
1943                         RAISE EXC_UNEXP_SKIP_OBJECT;
1944                 END IF;
1945 
1946 
1947             --
1948             -- Process Flow step 10(b) : Check that user has access to revised
1949             -- operation
1950             -- BOM_Validate_Op_Seq.Check_Access
1951 
1952             IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Check Operation sequence item access'); END IF;
1953                 BOM_Validate_Op_Seq.Check_Access
1954                 (  p_change_notice     => l_rev_op_resource_rec.ECO_Name
1955                 ,  p_organization_id   => l_rev_op_res_unexp_rec.organization_id
1956                 ,  p_revised_item_id   => l_rev_op_res_unexp_rec.revised_item_id
1957                 ,  p_revised_item_name => l_rev_op_resource_rec.revised_item_name
1958                 ,  p_new_item_revision =>
1959                                 l_rev_op_resource_rec.new_revised_item_revision
1960                 ,  p_effectivity_date  =>
1961                                 l_rev_op_resource_rec.op_start_effective_date
1962                 ,  p_new_routing_revsion   => l_rev_op_resource_rec.new_routing_revision  -- Added by MK on 11/02/00
1963                 ,  p_from_end_item_number  => l_rev_op_resource_rec.from_end_item_unit_number -- Added by MK on 11/02/00
1964                 ,  p_operation_seq_num =>
1965                                 l_rev_op_resource_rec.operation_sequence_number
1966                 ,  p_routing_sequence_id=>
1967                                 l_rev_op_res_unexp_rec.routing_sequence_id
1968                 ,  p_operation_type    =>
1969                                 l_rev_op_resource_rec.operation_type
1970                 ,  p_entity_processed  => 'RES'
1971                 ,  p_resource_seq_num  =>
1972                                 l_rev_op_resource_rec.resource_sequence_number
1973                 ,  p_sub_resource_code => NULL
1974                 ,  p_sub_group_num     => NULL
1975                 ,  p_Mesg_Token_Tbl    => l_Mesg_Token_Tbl
1976                 ,  x_Mesg_Token_Tbl    => l_Mesg_Token_Tbl
1977                 ,  x_return_status     => l_Return_Status
1978                 );
1979 
1980                IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
1981 
1982                 IF l_return_status = Error_Handler.G_STATUS_ERROR
1983                 THEN
1984                         l_other_message := 'BOM_RES_ACCESS_FAT_FATAL';
1985                         l_other_token_tbl(1).token_name := 'RES_SEQ_NUMBER';
1986                         l_other_token_tbl(1).token_value :=
1987                                 l_rev_op_resource_rec.resource_sequence_number;
1988                         l_return_status := 'F';
1989                         RAISE EXC_FAT_QUIT_OBJECT;
1990                 ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
1991                 THEN
1992                         l_other_message := 'BOM_RES_ACCESS_UNEXP_SKIP';
1993                         l_other_token_tbl(1).token_name := 'RES_SEQ_NUMBER';
1994                         l_other_token_tbl(1).token_value :=
1995                                l_rev_op_resource_rec.resource_sequence_number;
1996                         RAISE EXC_UNEXP_SKIP_OBJECT;
1997                 END IF;
1998 
1999          END IF; -- parent op does not exist
2000 
2001          --
2002          -- Process Flow step 11 : Check if the parent operation is
2003          -- non-referencing operation of type: Event
2004          --
2005          Bom_Validate_Op_Res.Check_NonRefEvent
2006             (  p_operation_sequence_id     => l_rev_op_res_unexp_rec.operation_sequence_id
2007             ,  p_operation_type            => l_rev_op_resource_rec.operation_type
2008             ,  p_entity_processed          => 'RES'
2009             ,  x_mesg_token_tbl            => l_mesg_token_tbl
2010             ,  x_return_status             => l_return_status
2011             ) ;
2012 
2013          IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
2014             ('Check non-ref operation completed with return_status: ' || l_return_status) ;
2015          END IF ;
2016 
2017          IF l_return_status = Error_Handler.G_STATUS_ERROR
2018          THEN
2019                IF  l_rev_op_resource_rec.operation_type IN (2,3) -- Process or Line Op
2020                THEN
2021 
2022                   l_token_tbl(1).token_name := 'RES_SEQ_NUMBER';
2023                   l_token_tbl(1).token_value :=
2024                           l_rev_op_resource_rec.resource_sequence_number ;
2025                   l_token_tbl(2).token_name := 'OP_SEQ_NUMBER';
2026                   l_token_tbl(2).token_value :=
2027                           l_rev_op_resource_rec.operation_sequence_number ;
2028 
2029                   Error_Handler.Add_Error_Token
2030                         ( p_Message_Name   => 'BOM_RES_OPTYPE_NOT_EVENT'
2031                         , p_mesg_token_tbl => l_mesg_token_tbl
2032                         , x_mesg_token_tbl => l_mesg_token_tbl
2033                         , p_Token_Tbl      => l_token_tbl
2034                         ) ;
2035 
2036                ELSE
2037                   l_token_tbl(1).token_name := 'RES_SEQ_NUMBER';
2038                   l_token_tbl(1).token_value :=
2039                           l_rev_op_resource_rec.resource_sequence_number ;
2040                   l_token_tbl(2).token_name := 'OP_SEQ_NUMBER';
2041                   l_token_tbl(2).token_value :=
2042                           l_rev_op_resource_rec.operation_sequence_number ;
2043 
2044                   Error_Handler.Add_Error_Token
2045                         ( p_Message_Name   => 'BOM_RES_MUST_NONREF'
2046                         , p_mesg_token_tbl => l_mesg_token_tbl
2047                         , x_mesg_token_tbl => l_mesg_token_tbl
2048                         , p_Token_Tbl      => l_token_tbl
2049                         ) ;
2050 
2051 
2052                END IF ;
2053 
2054                l_return_status := 'F';
2055                l_other_message := 'BOM_RES_ACCESS_FAT_FATAL';
2056                l_other_token_tbl(1).token_name := 'RES_SEQ_NUMBER';
2057                l_other_token_tbl(1).token_value :=
2058                                 l_rev_op_resource_rec.resource_sequence_number;
2059                RAISE EXC_FAT_QUIT_SIBLINGS ;
2060 
2061          ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
2062          THEN
2063                l_other_message := 'BOM_RES_ACCESS_UNEXP_SKIP';
2064                l_other_token_tbl(1).token_name := 'RES_SEQ_NUMBER';
2065                l_other_token_tbl(1).token_value :=
2066                           l_rev_op_resource_rec.resource_sequence_number ;
2067                RAISE EXC_UNEXP_SKIP_OBJECT;
2068          END IF;
2069 
2070 
2071          --
2072          -- Process Flow step 11: Value to Id conversions
2073          -- Call Rtg_Val_To_Id.Rev_Op_Resource_VID
2074          --
2075          Bom_Rtg_Val_To_Id.Rev_Op_Resource_VID
2076          (  p_rev_op_resource_rec        => l_rev_op_resource_rec
2077          ,  p_rev_op_res_unexp_rec       => l_rev_op_res_unexp_rec
2078          ,  x_rev_op_res_unexp_rec       => l_rev_op_res_unexp_rec
2079          ,  x_mesg_token_tbl             => l_mesg_token_tbl
2080          ,  x_return_status              => l_return_status
2081          );
2082 
2083          IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
2084          ('Value-id conversions completed with return_status: ' || l_return_status) ;
2085          END IF ;
2086 
2087          IF l_return_status = Error_Handler.G_STATUS_ERROR
2088          THEN
2089             IF l_rev_op_resource_rec.transaction_type = 'CREATE'
2090             THEN
2091                l_other_message := 'BOM_RES_VID_CSEV_SKIP';
2092                l_other_token_tbl(1).token_name := 'RES_SEQ_NUMBER';
2093                l_other_token_tbl(1).token_value :=
2094                           l_rev_op_resource_rec.resource_sequence_number ;
2095                RAISE EXC_SEV_SKIP_BRANCH;
2096             ELSE
2097                RAISE EXC_SEV_QUIT_RECORD ;
2098             END IF ;
2099 
2100          ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
2101          THEN
2102             l_other_message := 'BOM_RES_VID_UNEXP_SKIP';
2103             l_other_token_tbl(1).token_name := 'RES_SEQ_NUMBER';
2104             l_other_token_tbl(1).token_value :=
2105                           l_rev_op_resource_rec.resource_sequence_number ;
2106             RAISE EXC_UNEXP_SKIP_OBJECT;
2107 
2108          ELSIF l_return_status ='S' AND l_mesg_token_tbl .COUNT <>0
2109          THEN
2110             ECO_Error_Handler.Log_Error
2111             (  p_rev_op_resource_tbl     => x_rev_op_resource_tbl
2112             ,  p_rev_sub_resource_tbl    => x_rev_sub_resource_tbl
2113             ,  p_mesg_token_tbl      => l_mesg_token_tbl
2114             ,  p_error_status        => 'W'
2115             ,  p_error_level         => Error_Handler.G_RES_LEVEL
2116             ,  p_entity_index        => I
2117             ,  x_ECO_rec             => l_ECO_rec
2118             ,  x_eco_revision_tbl    => l_eco_revision_tbl
2119             ,  x_revised_item_tbl    => l_revised_item_tbl
2120             ,  x_rev_component_tbl   => l_rev_component_tbl
2121             ,  x_ref_designator_tbl  => l_ref_designator_tbl
2122             ,  x_sub_component_tbl   => l_sub_component_tbl
2123             ,  x_rev_operation_tbl   => l_rev_operation_tbl
2124             ,  x_rev_op_resource_tbl => x_rev_op_resource_tbl
2125             ,  x_rev_sub_resource_tbl=> x_rev_sub_resource_tbl
2126             ) ;
2127          END IF;
2128 
2129 
2130          --
2131          -- Process Flow step 13 : Check required fields exist
2132          -- (also includes a part of conditionally required fields)
2133          --
2134 
2135          -- No required fields checking
2136 
2137 
2138          --
2139          -- Process Flow step 14 : Attribute Validation for CREATE and UPDATE
2140          -- Call Bom_Validate_Op_Res.Check_Attributes
2141          --
2142          IF l_rev_op_resource_rec.transaction_type IN
2143             (Bom_Rtg_Globals.G_OPR_CREATE, Bom_Rtg_Globals.G_OPR_UPDATE)
2144          THEN
2145             Bom_Validate_Op_Res.Check_Attributes
2146             ( p_rev_op_resource_rec   => l_rev_op_resource_rec
2147             , p_rev_op_res_unexp_rec  => l_rev_op_res_unexp_rec
2148             , x_return_status     => l_return_status
2149             , x_mesg_token_tbl    => l_mesg_token_tbl
2150             ) ;
2151 
2152             IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
2153             ('Attribute validation completed with return_status: ' || l_return_status) ;
2154             END IF ;
2155 
2156 
2157             IF l_return_status = Error_Handler.G_STATUS_ERROR
2158             THEN
2159                IF l_rev_op_resource_rec.transaction_type = Bom_Rtg_Globals.G_OPR_CREATE
2160                THEN
2161                   l_other_message := 'BOM_RES_ATTVAL_CSEV_SKIP';
2162                   l_other_token_tbl(1).token_name := 'RES_SEQ_NUMBER';
2163                   l_other_token_tbl(1).token_value :=
2164                            l_rev_op_resource_rec.resource_sequence_number ;
2165                   RAISE EXC_SEV_SKIP_BRANCH ;
2166                   ELSE
2167                      RAISE EXC_SEV_QUIT_RECORD ;
2168                END IF;
2169             ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
2170             THEN
2171                l_other_message := 'BOM_RES_ATTVAL_UNEXP_SKIP';
2172                l_other_token_tbl(1).token_name := 'RES_SEQ_NUMBER';
2173                l_other_token_tbl(1).token_value :=
2174                            l_rev_op_resource_rec.resource_sequence_number ;
2175                RAISE EXC_UNEXP_SKIP_OBJECT ;
2176             ELSIF l_return_status ='S' AND l_mesg_token_tbl.COUNT <> 0
2177             THEN
2178                ECO_Error_Handler.Log_Error
2179                (  p_rev_op_resource_tbl     => x_rev_op_resource_tbl
2180                ,  p_rev_sub_resource_tbl    => x_rev_sub_resource_tbl
2181                ,  p_mesg_token_tbl      => l_mesg_token_tbl
2182                ,  p_error_status        => 'W'
2183                ,  p_error_level         => Error_Handler.G_RES_LEVEL
2184                ,  p_entity_index        => I
2185                ,  x_ECO_rec             => l_ECO_rec
2186                ,  x_eco_revision_tbl    => l_eco_revision_tbl
2187                ,  x_revised_item_tbl    => l_revised_item_tbl
2188                ,  x_rev_component_tbl   => l_rev_component_tbl
2189                ,  x_ref_designator_tbl  => l_ref_designator_tbl
2190                ,  x_sub_component_tbl   => l_sub_component_tbl
2191                ,  x_rev_operation_tbl   => l_rev_operation_tbl
2192                ,  x_rev_op_resource_tbl => x_rev_op_resource_tbl
2193                ,  x_rev_sub_resource_tbl=> x_rev_sub_resource_tbl
2194                ) ;
2195            END IF;
2196         END IF;
2197 
2198         --
2199         -- Process flow step: Query the operation resource  record using by Res Seq Num
2200         -- Call Bom_Res_Seq_Util.Query_Row
2201         --
2202 
2203         IF (l_rev_op_resource_rec.transaction_type = ENG_GLOBALS.G_OPR_CREATE
2204             AND l_rev_op_resource_rec.acd_type IN ( 2, 3 )) -- ACD Type: Change or Disable
2205         THEN
2206 
2207             Bom_Op_Res_Util.Query_Row
2208             ( p_resource_sequence_number  =>  l_rev_op_resource_rec.resource_sequence_number
2209             , p_operation_sequence_id     =>  l_rev_op_res_unexp_rec.operation_sequence_id
2210             , p_acd_type                  =>  FND_API.G_MISS_NUM
2211             , p_mesg_token_tbl            =>  l_mesg_token_tbl
2212             , x_rev_op_resource_rec       =>  l_old_rev_op_resource_rec
2213             , x_rev_op_res_unexp_rec      =>  l_old_rev_op_res_unexp_rec
2214             , x_mesg_token_tbl            =>  l_mesg_token_tbl
2215             , x_return_status             =>  l_return_status
2216             ) ;
2217 
2218             IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
2219             ('Query the original op res for rev op res with acd type : change or delete completed with return_status: ' || l_return_status) ;
2220             END IF ;
2221 
2222             IF l_return_status <> Eng_Globals.G_RECORD_FOUND
2223             THEN
2224                   l_return_status := Error_Handler.G_STATUS_ERROR ;
2225                   l_token_tbl(1).token_name := 'RES_SEQ_NUMBER';
2226                   l_token_tbl(1).token_value :=
2227                            l_rev_op_resource_rec.resource_sequence_number ;
2228                   l_token_tbl(2).token_name  := 'OP_SEQ_NUMBER';
2229                   l_token_tbl(2).token_value :=
2230                            l_rev_op_resource_rec.operation_sequence_number ;
2231 
2232                   Error_Handler.Add_Error_Token
2233                   ( p_message_name       => 'BOM_RES_CREATE_REC_NOT_FOUND'
2234                   , p_mesg_token_tbl     => l_Mesg_Token_Tbl
2235                   , p_token_tbl          => l_Token_Tbl
2236                   , x_Mesg_Token_Tbl     => l_Mesg_Token_Tbl
2237                   );
2238 
2239                   l_other_message := 'BOM_RES_QRY_CSEV_SKIP';
2240                   l_other_token_tbl(1).token_name := 'RES_SEQ_NUMBER';
2241                   l_other_token_tbl(1).token_value :=
2242                            l_rev_op_resource_rec.resource_sequence_number ;
2243                   RAISE EXC_SEV_SKIP_BRANCH;
2244            ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
2245            THEN
2246                   l_other_message := 'BOM_RES_QRY_UNEXP_SKIP';
2247                   l_other_token_tbl(1).token_name := 'RES_SEQ_NUMBER';
2248                   l_other_token_tbl(1).token_value :=
2249                            l_rev_op_resource_rec.resource_sequence_number ;
2250                   RAISE EXC_UNEXP_SKIP_OBJECT;
2251           END IF;
2252 
2253         END IF;
2254 
2255 
2256         IF (l_rev_op_resource_rec.transaction_type = ENG_GLOBALS.G_OPR_CREATE
2257            AND l_rev_op_resource_rec.acd_type IN ( 2, 3 ) ) -- ACD Type : Change or Disable
2258         OR
2259            l_rev_op_resource_rec.transaction_type IN (ENG_GLOBALS.G_OPR_UPDATE ,
2260                                                       ENG_GLOBALS.G_OPR_DELETE)
2261         THEN
2262 
2263         --
2264         -- Process flow step 12: Populate NULL columns for Update and Delete
2265         -- Call Bom_Default_Op_Res.Populate_Null_Columns
2266         --
2267 
2268            IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Populate NULL columns') ;
2269            END IF ;
2270 
2271            Bom_Default_Op_Res.Populate_Null_Columns
2272            (   p_rev_op_resource_rec     => l_rev_op_resource_rec
2273            ,   p_old_rev_op_resource_rec => l_old_rev_op_resource_rec
2274            ,   p_rev_op_res_unexp_rec    => l_rev_op_res_unexp_rec
2275            ,   p_old_rev_op_res_unexp_rec=> l_old_rev_op_res_unexp_rec
2276            ,   x_rev_op_resource_rec     => l_rev_op_resource_rec
2277            ,   x_rev_op_res_unexp_rec    => l_rev_op_res_unexp_rec
2278            ) ;
2279 
2280 
2281         ELSIF l_rev_op_resource_rec.transaction_type = Bom_Rtg_Globals.G_OPR_CREATE
2282         THEN
2283         --
2284         -- Process Flow step 13 : Default missing values for Op Resource (CREATE)
2285         -- Call Bom_Default_Op_Res.Attribute_Defaulting
2286         --
2287 
2288            IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Attribute Defaulting') ;
2289            END IF ;
2290 
2291            Bom_Default_Op_res.Attribute_Defaulting
2292            (   p_rev_op_resource_rec     => l_rev_op_resource_rec
2293            ,   p_rev_op_res_unexp_rec    => l_rev_op_res_unexp_rec
2294            ,   p_control_rec             => Bom_Rtg_Pub.G_Default_Control_Rec
2295            ,   x_rev_op_resource_rec     => l_rev_op_resource_rec
2296            ,   x_rev_op_res_unexp_rec    => l_rev_op_res_unexp_rec
2297            ,   x_mesg_token_tbl          => l_mesg_token_tbl
2298            ,   x_return_status           => l_return_status
2299            ) ;
2300 
2301 
2302            IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
2303            ('Attribute Defaulting completed with return_status: ' || l_return_status) ;
2304            END IF ;
2305 
2306            IF l_return_status = Error_Handler.G_STATUS_ERROR
2307            THEN
2308               l_other_message := 'BOM_RES_ATTDEF_CSEV_SKIP';
2309               l_other_token_tbl(1).token_name := 'RES_SEQ_NUMBER';
2310               l_other_token_tbl(1).token_value :=
2311                           l_rev_op_resource_rec.resource_sequence_number ;
2312               RAISE EXC_SEV_SKIP_BRANCH ;
2313 
2314            ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
2315            THEN
2316               l_other_message := 'BOM_RES_ATTDEF_UNEXP_SKIP';
2317               l_other_token_tbl(1).token_name := 'RES_SEQ_NUMBER';
2318               l_other_token_tbl(1).token_value :=
2319                            l_rev_op_resource_rec.resource_sequence_number ;
2320               RAISE EXC_UNEXP_SKIP_OBJECT ;
2321            ELSIF l_return_status ='S' AND l_mesg_token_tbl .COUNT <> 0
2322            THEN
2323                ECO_Error_Handler.Log_Error
2324                (  p_rev_op_resource_tbl     => x_rev_op_resource_tbl
2325                ,  p_rev_sub_resource_tbl    => x_rev_sub_resource_tbl
2326                ,  p_mesg_token_tbl      => l_mesg_token_tbl
2327                ,  p_error_status        => 'W'
2328                ,  p_error_level         => Error_Handler.G_RES_LEVEL
2329                ,  p_entity_index        => I
2330                ,  x_ECO_rec             => l_ECO_rec
2331                ,  x_eco_revision_tbl    => l_eco_revision_tbl
2332                ,  x_revised_item_tbl    => l_revised_item_tbl
2333                ,  x_rev_component_tbl   => l_rev_component_tbl
2334                ,  x_ref_designator_tbl  => l_ref_designator_tbl
2335                ,  x_sub_component_tbl   => l_sub_component_tbl
2336                ,  x_rev_operation_tbl   => l_rev_operation_tbl
2337                ,  x_rev_op_resource_tbl => x_rev_op_resource_tbl
2338                ,  x_rev_sub_resource_tbl=> x_rev_sub_resource_tbl
2339                ) ;
2340           END IF;
2341        END IF;
2342 
2343        --
2344        -- Process Flow step 17: Conditionally Required Attributes
2345        --
2346        --
2347        -- No Conditionally Required Attributes
2348 
2349 
2350        --
2351        -- Process Flow step 18: Entity defaulting for CREATE and UPDATE
2352        --
2353        IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Entity defaulting') ;
2354        END IF ;
2355        IF l_rev_op_resource_rec.transaction_type IN ( Bom_Rtg_Globals.G_OPR_CREATE
2356                                                 , Bom_Rtg_Globals.G_OPR_UPDATE )
2357        THEN
2358           Bom_Default_Op_res.Entity_Defaulting
2359               (   p_rev_op_resource_rec   => l_rev_op_resource_rec
2360               ,   p_rev_op_res_unexp_rec  => l_rev_op_res_unexp_rec
2361               ,   p_control_rec           => Bom_Rtg_Pub.G_Default_Control_Rec
2362               ,   x_rev_op_resource_rec   => l_rev_op_resource_rec
2363               ,   x_rev_op_res_unexp_rec  => l_rev_op_res_unexp_rec
2364               ,   x_mesg_token_tbl        => l_mesg_token_tbl
2365               ,   x_return_status         => l_return_status
2366               ) ;
2367 
2368           IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
2369           ('Entity defaulting completed with return_status: ' || l_return_status) ;
2370           END IF ;
2371 
2372           IF l_return_status = Error_Handler.G_STATUS_ERROR
2373           THEN
2374              IF l_rev_op_resource_rec.transaction_type = Bom_Rtg_Globals.G_OPR_CREATE
2375              THEN
2376                 l_other_message := 'BOM_RES_ENTDEF_CSEV_SKIP';
2377                 l_other_token_tbl(1).token_name  := 'RES_SEQ_NUMBER';
2378                 l_other_token_tbl(1).token_value :=
2379                           l_rev_op_resource_rec.operation_sequence_number ;
2380                 RAISE EXC_SEV_SKIP_BRANCH ;
2381              ELSE
2382                 RAISE EXC_SEV_QUIT_RECORD ;
2383              END IF;
2384           ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
2385           THEN
2386              l_other_message := 'BOM_RES_ENTDEF_UNEXP_SKIP';
2387              l_other_token_tbl(1).token_name  := 'RES_SEQ_NUMBER';
2388              l_other_token_tbl(1).token_value :=
2389                           l_rev_op_resource_rec.resource_sequence_number ;
2390              RAISE EXC_UNEXP_SKIP_OBJECT ;
2391           ELSIF l_return_status ='S' AND l_mesg_token_tbl .COUNT <> 0
2392           THEN
2393              ECO_Error_Handler.Log_Error
2394              (  p_rev_op_resource_tbl         => x_rev_op_resource_tbl
2395              ,  p_rev_sub_resource_tbl        => x_rev_sub_resource_tbl
2396              ,  p_mesg_token_tbl          => l_mesg_token_tbl
2397              ,  p_error_status            => 'W'
2398              ,  p_error_level             => Error_Handler.G_RES_LEVEL
2399              ,  p_entity_index            => I
2400              ,  x_ECO_rec                 => l_ECO_rec
2401              ,  x_eco_revision_tbl        => l_eco_revision_tbl
2402              ,  x_revised_item_tbl        => l_revised_item_tbl
2403              ,  x_rev_component_tbl       => l_rev_component_tbl
2404              ,  x_ref_designator_tbl      => l_ref_designator_tbl
2405              ,  x_sub_component_tbl       => l_sub_component_tbl
2406              ,  x_rev_operation_tbl       => l_rev_operation_tbl
2407              ,  x_rev_op_resource_tbl     => x_rev_op_resource_tbl
2408              ,  x_rev_sub_resource_tbl    => x_rev_sub_resource_tbl
2409              ) ;
2410           END IF ;
2411        END IF ;
2412 
2413        --
2414        -- Process Flow step 16 - Entity Level Validation
2415        -- Call Bom_Validate_Op_Res.Check_Entity
2416        --
2417        IF Bom_Rtg_Globals.Get_Debug = 'Y'
2418        THEN Error_Handler.Write_Debug('Starting with Op Resources entity validation . . . ') ;
2419        END IF ;
2420 
2421           Bom_Validate_Op_Res.Check_Entity
2422           (  p_rev_op_resource_rec       => l_rev_op_resource_rec
2423           ,  p_rev_op_res_unexp_rec      => l_rev_op_res_unexp_rec
2424           ,  p_old_rev_op_resource_rec   => l_old_rev_op_resource_rec
2425           ,  p_old_rev_op_res_unexp_rec  => l_old_rev_op_res_unexp_rec
2426           ,  p_control_rec               => Bom_Rtg_Pub.G_Default_Control_Rec
2427           ,  x_rev_op_resource_rec       => l_rev_op_resource_rec
2428           ,  x_rev_op_res_unexp_rec      => l_rev_op_res_unexp_rec
2429           ,  x_mesg_token_tbl            => l_mesg_token_tbl
2430           ,  x_return_status             => l_return_status
2431           ) ;
2432 
2433 
2434        IF l_return_status = Error_Handler.G_STATUS_ERROR
2435        THEN
2436           IF l_rev_op_resource_rec.transaction_type = Bom_Rtg_Globals.G_OPR_CREATE
2437           THEN
2438              l_other_message := 'BOM_RES_ENTVAL_CSEV_SKIP';
2439              l_other_token_tbl(1).token_name  := 'RES_SEQ_NUMBER';
2440              l_other_token_tbl(1).token_value :=
2441                            l_rev_op_resource_rec.resource_sequence_number ;
2442              RAISE EXC_SEV_SKIP_BRANCH ;
2443           ELSE
2444              RAISE EXC_SEV_QUIT_RECORD ;
2445           END IF;
2446        ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
2447        THEN
2448           l_other_message := 'BOM_RES_ENTVAL_UNEXP_SKIP';
2449           l_other_token_tbl(1).token_name := 'RES_SEQ_NUMBER';
2450           l_other_token_tbl(1).token_value :=
2451                         l_rev_op_resource_rec.resource_sequence_number ;
2452           RAISE EXC_UNEXP_SKIP_OBJECT ;
2453        ELSIF l_return_status ='S' AND l_mesg_token_tbl .COUNT <> 0
2454        THEN
2455           ECO_Error_Handler.Log_Error
2456           (  p_rev_op_resource_tbl  => x_rev_op_resource_tbl
2457           ,  p_rev_sub_resource_tbl => x_rev_sub_resource_tbl
2458           ,  p_mesg_token_tbl       => l_mesg_token_tbl
2459           ,  p_error_status         => 'W'
2460           ,  p_error_level          => Error_Handler.G_RES_LEVEL
2461           ,  p_entity_index         => I
2462           ,  x_ECO_rec              => l_ECO_rec
2463           ,  x_eco_revision_tbl     => l_eco_revision_tbl
2464           ,  x_revised_item_tbl     => l_revised_item_tbl
2465           ,  x_rev_component_tbl    => l_rev_component_tbl
2466           ,  x_ref_designator_tbl   => l_ref_designator_tbl
2467           ,  x_sub_component_tbl    => l_sub_component_tbl
2468           ,  x_rev_operation_tbl    => l_rev_operation_tbl
2469           ,  x_rev_op_resource_tbl  => x_rev_op_resource_tbl
2470           ,  x_rev_sub_resource_tbl => x_rev_sub_resource_tbl
2471           ) ;
2472        END IF;
2473 
2474        IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Entity validation completed with '
2475              || l_return_Status || ' proceeding for database writes . . . ') ;
2476        END IF;
2477 
2478        --
2479        -- Process Flow step 16 : Database Writes
2480        --
2481        Bom_Op_Res_Util.Perform_Writes
2482           (   p_rev_op_resource_rec     => l_rev_op_resource_rec
2483           ,   p_rev_op_res_unexp_rec    => l_rev_op_res_unexp_rec
2484           ,   p_control_rec             => Bom_Rtg_Pub.G_Default_Control_Rec
2485           ,   x_mesg_token_tbl          => l_mesg_token_tbl
2486           ,   x_return_status           => l_return_status
2487           ) ;
2488 
2489        IF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
2490        THEN
2491           l_other_message := 'BOM_RES_WRITES_UNEXP_SKIP';
2492           l_other_token_tbl(1).token_name := 'RES_SEQ_NUMBER';
2493           l_other_token_tbl(1).token_value :=
2494                           l_rev_op_resource_rec.resource_sequence_number ;
2495           RAISE EXC_UNEXP_SKIP_OBJECT ;
2496        ELSIF l_return_status ='S' AND
2497           l_mesg_token_tbl .COUNT <>0
2498        THEN
2499           ECO_Error_Handler.Log_Error
2500           (  p_rev_op_resource_tbl => x_rev_op_resource_tbl
2501           ,  p_mesg_token_tbl      => l_mesg_token_tbl
2502           ,  p_error_status        => 'W'
2503           ,  p_error_level         => Error_Handler.G_RES_LEVEL
2504           ,  p_entity_index        => I
2505           ,  x_ECO_rec             => l_ECO_rec
2506           ,  x_eco_revision_tbl    => l_eco_revision_tbl
2507           ,  x_revised_item_tbl    => l_revised_item_tbl
2508           ,  x_rev_component_tbl   => l_rev_component_tbl
2509           ,  x_ref_designator_tbl  => l_ref_designator_tbl
2510           ,  x_sub_component_tbl   => l_sub_component_tbl
2511           ,  x_rev_operation_tbl   => l_rev_operation_tbl
2512           ,  x_rev_op_resource_tbl => x_rev_op_resource_tbl
2513           ,  x_rev_sub_resource_tbl=> x_rev_sub_resource_tbl
2514           ) ;
2515        END IF;
2516 
2517        IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Database writes completed with status:  ' || l_return_status);
2518        END IF;
2519 
2520     END IF; -- END IF statement that checks RETURN STATUS
2521 
2522     --  Load tables.
2523     x_rev_op_resource_tbl(I)  := l_rev_op_resource_rec;
2524 
2525 
2526     --  For loop exception handler.
2527 
2528     EXCEPTION
2529        WHEN EXC_SEV_QUIT_RECORD THEN
2530           ECO_Error_Handler.Log_Error
2531           (  p_rev_op_resource_tbl => x_rev_op_resource_tbl
2532           ,  p_mesg_token_tbl      => l_mesg_token_tbl
2533           ,  p_error_status        => FND_API.G_RET_STS_ERROR
2534           ,  p_error_scope         => Error_Handler.G_SCOPE_RECORD
2535           ,  p_error_level         => Error_Handler.G_RES_LEVEL
2536           ,  p_entity_index        => I
2537           ,  x_ECO_rec             => l_ECO_rec
2538           ,  x_eco_revision_tbl    => l_eco_revision_tbl
2539           ,  x_revised_item_tbl    => l_revised_item_tbl
2540           ,  x_rev_component_tbl   => l_rev_component_tbl
2541           ,  x_ref_designator_tbl  => l_ref_designator_tbl
2542           ,  x_sub_component_tbl   => l_sub_component_tbl
2543           ,  x_rev_operation_tbl   => l_rev_operation_tbl
2544           ,  x_rev_op_resource_tbl => x_rev_op_resource_tbl
2545           ,  x_rev_sub_resource_tbl=> x_rev_sub_resource_tbl
2546           ) ;
2547 
2548 
2549          IF l_bo_return_status = 'S'
2550          THEN
2551             l_bo_return_status := l_return_status ;
2552          END IF;
2553 
2554          x_return_status           := l_bo_return_status;
2555          x_mesg_token_tbl          := l_mesg_token_tbl ;
2556          --x_rev_op_resource_tbl     := l_rev_op_resource_tbl ;
2557       --   x_rev_sub_resource_tbl    := l_rev_sub_resource_tbl ;
2558 
2559 
2560       WHEN EXC_SEV_QUIT_BRANCH THEN
2561 
2562          ECO_Error_Handler.Log_Error
2563          (  p_rev_op_resource_tbl => x_rev_op_resource_tbl
2564          ,  p_mesg_token_tbl      => l_mesg_token_tbl
2565          ,  p_error_status        => Error_Handler.G_STATUS_ERROR
2566          ,  p_error_scope         => Error_Handler.G_SCOPE_CHILDREN
2567          ,  p_other_status        => Error_Handler.G_STATUS_ERROR
2568          ,  p_other_message       => l_other_message
2569          ,  p_other_token_tbl     => l_other_token_tbl
2570          ,  p_error_level         => Error_Handler.G_RES_LEVEL
2571          ,  p_entity_index        => I
2572          ,  x_ECO_rec             => l_ECO_rec
2573          ,  x_eco_revision_tbl    => l_eco_revision_tbl
2574          ,  x_revised_item_tbl    => l_revised_item_tbl
2575          ,  x_rev_component_tbl   => l_rev_component_tbl
2576          ,  x_ref_designator_tbl  => l_ref_designator_tbl
2577          ,  x_sub_component_tbl   => l_sub_component_tbl
2578          ,  x_rev_operation_tbl   => l_rev_operation_tbl
2579          ,  x_rev_op_resource_tbl => x_rev_op_resource_tbl
2580          ,  x_rev_sub_resource_tbl=> x_rev_sub_resource_tbl
2581          ) ;
2582 
2583 
2584          IF l_bo_return_status = 'S'
2585          THEN
2586             l_bo_return_status  := l_return_status;
2587          END IF;
2588 
2589          x_return_status        := l_bo_return_status;
2590          x_mesg_token_tbl       := l_mesg_token_tbl ;
2591          --x_rev_op_resource_tbl     := l_rev_op_resource_tbl ;
2592          --x_rev_sub_resource_tbl := l_rev_sub_resource_tbl ;
2593 
2594       WHEN EXC_SEV_SKIP_BRANCH THEN
2595          ECO_Error_Handler.Log_Error
2596          (  p_rev_op_resource_tbl => x_rev_op_resource_tbl
2597          ,  p_mesg_token_tbl      => l_mesg_token_tbl
2598          ,  p_error_status        => Error_Handler.G_STATUS_ERROR
2599          ,  p_error_scope         => Error_Handler.G_SCOPE_CHILDREN
2600          ,  p_other_status        => Error_Handler.G_STATUS_NOT_PICKED
2601          ,  p_other_message       => l_other_message
2602          ,  p_other_token_tbl     => l_other_token_tbl
2603          ,  p_error_level         => Error_Handler.G_RES_LEVEL
2604          ,  p_entity_index        => I
2605          ,  x_ECO_rec             => l_ECO_rec
2606          ,  x_eco_revision_tbl    => l_eco_revision_tbl
2607          ,  x_revised_item_tbl    => l_revised_item_tbl
2608          ,  x_rev_component_tbl   => l_rev_component_tbl
2609          ,  x_ref_designator_tbl  => l_ref_designator_tbl
2610          ,  x_sub_component_tbl   => l_sub_component_tbl
2611          ,  x_rev_operation_tbl   => l_rev_operation_tbl
2612          ,  x_rev_op_resource_tbl => x_rev_op_resource_tbl
2613          ,  x_rev_sub_resource_tbl=> x_rev_sub_resource_tbl
2614          ) ;
2615 
2616         IF l_bo_return_status = 'S'
2617         THEN
2618            l_bo_return_status     := l_return_status ;
2619         END IF;
2620         x_return_status           := l_bo_return_status;
2621         x_mesg_token_tbl          := l_mesg_token_tbl ;
2622         --x_rev_op_resource_tbl     := l_rev_op_resource_tbl ;
2623         --x_rev_sub_resource_tbl    := l_rev_sub_resource_tbl ;
2624 
2625      WHEN EXC_SEV_QUIT_SIBLINGS THEN
2626          ECO_Error_Handler.Log_Error
2627          (  p_rev_op_resource_tbl => x_rev_op_resource_tbl
2628          ,  p_mesg_token_tbl      => l_mesg_token_tbl
2629          ,  p_error_status        => Error_Handler.G_STATUS_ERROR
2630          ,  p_error_scope         => Error_Handler.G_SCOPE_SIBLINGS
2631          ,  p_other_status        => Error_Handler.G_STATUS_ERROR
2632          ,  p_other_message       => l_other_message
2633          ,  p_other_token_tbl     => l_other_token_tbl
2634          ,  p_error_level         => Error_Handler.G_RES_LEVEL
2635          ,  p_entity_index        => I
2636          ,  x_ECO_rec             => l_ECO_rec
2637          ,  x_eco_revision_tbl    => l_eco_revision_tbl
2638          ,  x_revised_item_tbl    => l_revised_item_tbl
2639          ,  x_rev_component_tbl   => l_rev_component_tbl
2640          ,  x_ref_designator_tbl  => l_ref_designator_tbl
2641          ,  x_sub_component_tbl   => l_sub_component_tbl
2642          ,  x_rev_operation_tbl   => l_rev_operation_tbl
2643          ,  x_rev_op_resource_tbl => x_rev_op_resource_tbl
2644          ,  x_rev_sub_resource_tbl=> x_rev_sub_resource_tbl
2645          ) ;
2646 
2647          IF l_bo_return_status = 'S'
2648          THEN
2649            l_bo_return_status  := l_return_status ;
2650          END IF;
2651          x_return_status       := l_bo_return_status;
2652          x_mesg_token_tbl      := l_mesg_token_tbl ;
2653          --x_rev_op_resource_tbl     := l_rev_op_resource_tbl ;
2654          --x_rev_sub_resource_tbl := l_rev_sub_resource_tbl ;
2655 
2656 
2657       WHEN EXC_FAT_QUIT_BRANCH THEN
2658          ECO_Error_Handler.Log_Error
2659          (  p_rev_op_resource_tbl => x_rev_op_resource_tbl
2660          ,  p_mesg_token_tbl      => l_mesg_token_tbl
2661          ,  p_error_status        => Error_Handler.G_STATUS_FATAL
2662          ,  p_error_scope         => Error_Handler.G_SCOPE_CHILDREN
2663          ,  p_other_status        => Error_Handler.G_STATUS_FATAL
2664          ,  p_other_message       => l_other_message
2665          ,  p_other_token_tbl     => l_other_token_tbl
2666          ,  p_error_level         => Error_Handler.G_RES_LEVEL
2667          ,  p_entity_index        => I
2668          ,  x_ECO_rec             => l_ECO_rec
2669          ,  x_eco_revision_tbl    => l_eco_revision_tbl
2670          ,  x_revised_item_tbl    => l_revised_item_tbl
2671          ,  x_rev_component_tbl   => l_rev_component_tbl
2672          ,  x_ref_designator_tbl  => l_ref_designator_tbl
2673          ,  x_sub_component_tbl   => l_sub_component_tbl
2674          ,  x_rev_operation_tbl   => l_rev_operation_tbl
2675          ,  x_rev_op_resource_tbl => x_rev_op_resource_tbl
2676          ,  x_rev_sub_resource_tbl=> x_rev_sub_resource_tbl
2677          ) ;
2678 
2679          x_return_status       := Error_Handler.G_STATUS_FATAL;
2680          x_mesg_token_tbl      := l_mesg_token_tbl ;
2681          --x_rev_op_resource_tbl     := l_rev_op_resource_tbl ;
2682          --x_rev_sub_resource_tbl    := l_rev_sub_resource_tbl ;
2683 
2684 
2685       WHEN EXC_FAT_QUIT_SIBLINGS THEN
2686          ECO_Error_Handler.Log_Error
2687          (  p_rev_op_resource_tbl => x_rev_op_resource_tbl
2688          ,  p_mesg_token_tbl      => l_mesg_token_tbl
2689          ,  p_error_status        => Error_Handler.G_STATUS_FATAL
2690          ,  p_error_scope         => Error_Handler.G_SCOPE_SIBLINGS
2691          ,  p_other_status        => Error_Handler.G_STATUS_FATAL
2692          ,  p_other_message       => l_other_message
2693          ,  p_other_token_tbl     => l_other_token_tbl
2694          ,  p_error_level         => Error_Handler.G_RES_LEVEL
2695          ,  p_entity_index        => I
2696          ,  x_ECO_rec             => l_ECO_rec
2697          ,  x_eco_revision_tbl    => l_eco_revision_tbl
2698          ,  x_revised_item_tbl    => l_revised_item_tbl
2699          ,  x_rev_component_tbl   => l_rev_component_tbl
2700          ,  x_ref_designator_tbl  => l_ref_designator_tbl
2701          ,  x_sub_component_tbl   => l_sub_component_tbl
2702          ,  x_rev_operation_tbl   => l_rev_operation_tbl
2703          ,  x_rev_op_resource_tbl => x_rev_op_resource_tbl
2704          ,  x_rev_sub_resource_tbl=> x_rev_sub_resource_tbl
2705          ) ;
2706 
2707         x_return_status       := Error_Handler.G_STATUS_FATAL;
2708         x_mesg_token_tbl      := l_mesg_token_tbl ;
2709         --x_rev_op_resource_tbl     := l_rev_op_resource_tbl ;
2710         --x_rev_sub_resource_tbl    := l_rev_sub_resource_tbl ;
2711 
2712     WHEN EXC_FAT_QUIT_OBJECT THEN
2713          ECO_Error_Handler.Log_Error
2714          (  p_rev_op_resource_tbl => x_rev_op_resource_tbl
2715          ,  p_rev_sub_resource_tbl => x_rev_sub_resource_tbl
2716          ,  p_mesg_token_tbl      => l_mesg_token_tbl
2717          ,  p_error_status        => Error_Handler.G_STATUS_FATAL
2718          ,  p_error_scope         => Error_Handler.G_SCOPE_ALL
2719          ,  p_other_status        => Error_Handler.G_STATUS_FATAL
2720          ,  p_other_message       => l_other_message
2721          ,  p_other_token_tbl     => l_other_token_tbl
2722          ,  p_error_level         => Error_Handler.G_RES_LEVEL
2723          ,  p_entity_index        => I
2724          ,  x_ECO_rec             => l_ECO_rec
2725          ,  x_eco_revision_tbl    => l_eco_revision_tbl
2726          ,  x_revised_item_tbl    => l_revised_item_tbl
2727          ,  x_rev_component_tbl   => l_rev_component_tbl
2728          ,  x_ref_designator_tbl  => l_ref_designator_tbl
2729          ,  x_sub_component_tbl   => l_sub_component_tbl
2730          ,  x_rev_operation_tbl   => l_rev_operation_tbl
2731          ,  x_rev_op_resource_tbl => x_rev_op_resource_tbl
2732          ,  x_rev_sub_resource_tbl=> x_rev_sub_resource_tbl
2733          ) ;
2734 
2735          l_return_status       := 'Q';
2736          x_mesg_token_tbl      := l_mesg_token_tbl ;
2737          --x_rev_op_resource_tbl     := l_rev_op_resource_tbl ;
2738          --x_rev_sub_resource_tbl    := l_rev_sub_resource_tbl ;
2739 
2740       WHEN EXC_UNEXP_SKIP_OBJECT THEN
2741          ECO_Error_Handler.Log_Error
2742          (  p_rev_op_resource_tbl => x_rev_op_resource_tbl
2743          ,  p_mesg_token_tbl      => l_mesg_token_tbl
2744          ,  p_error_status        => Error_Handler.G_STATUS_UNEXPECTED
2745          ,  p_other_status        => Error_Handler.G_STATUS_NOT_PICKED
2746          ,  p_other_message       => l_other_message
2747          ,  p_other_token_tbl     => l_other_token_tbl
2748          ,  p_error_level         => Error_Handler.G_RES_LEVEL
2749          ,  x_ECO_rec             => l_ECO_rec
2750          ,  x_eco_revision_tbl    => l_eco_revision_tbl
2751          ,  x_revised_item_tbl    => l_revised_item_tbl
2752          ,  x_rev_component_tbl   => l_rev_component_tbl
2753          ,  x_ref_designator_tbl  => l_ref_designator_tbl
2754          ,  x_sub_component_tbl   => l_sub_component_tbl
2755          ,  x_rev_operation_tbl   => l_rev_operation_tbl
2756          ,  x_rev_op_resource_tbl => x_rev_op_resource_tbl
2757          ,  x_rev_sub_resource_tbl=> x_rev_sub_resource_tbl
2758          ) ;
2759 
2760          l_return_status       := 'U';
2761          x_mesg_token_tbl      := l_mesg_token_tbl ;
2762          --x_rev_op_resource_tbl     := l_rev_op_resource_tbl ;
2763          --x_rev_sub_resource_tbl    := l_rev_sub_resource_tbl ;
2764 
2765    END ; -- END block
2766 
2767    IF l_return_status in ('Q', 'U')
2768    THEN
2769       x_return_status := l_return_status;
2770       RETURN ;
2771    END IF;
2772 
2773    END IF; -- End of processing records for which the return status is null
2774    END LOOP; -- END Operation Resources processing loop
2775 
2776    --  Load OUT parameters
2777    IF NVL(l_return_status, 'S') <> 'S'
2778    THEN
2779       x_return_status    := l_return_status;
2780    END IF;
2781 
2782    x_mesg_token_tbl          := l_mesg_token_tbl ;
2783    --x_rev_op_resource_tbl     := l_rev_op_resource_tbl ;
2784    --x_rev_sub_resource_tbl    := l_rev_sub_resource_tbl ;
2785    x_mesg_token_tbl          := l_mesg_token_tbl ;
2786 
2787 END Rev_Operation_Resources ;
2788 
2789 
2790 PROCEDURE Rev_Operation_Sequences
2791 (   p_validation_level              IN  NUMBER
2792 ,   p_change_notice                 IN  VARCHAR2 := NULL
2793 ,   p_organization_id               IN  NUMBER   := NULL
2794 ,   p_revised_item_name             IN  VARCHAR2 := NULL
2795 ,   p_effectivity_date              IN  DATE     := NULL
2796 ,   p_item_revision                 IN  VARCHAR2 := NULL
2797 ,   p_routing_revision              IN  VARCHAR2 := NULL -- Added by MK on 11/02/00
2798 ,   p_from_end_item_number          IN  VARCHAR2 := NULL -- Added by MK on 11/02/00
2799 ,   p_alternate_routing_code        IN  VARCHAR2 := NULL -- Added for bug 13440461
2800 ,   p_rev_operation_tbl             IN  Bom_Rtg_Pub.Rev_Operation_Tbl_Type
2801 ,   p_rev_op_resource_tbl           IN  Bom_Rtg_Pub.Rev_Op_Resource_Tbl_Type
2802 ,   p_rev_sub_resource_tbl          IN  Bom_Rtg_Pub.Rev_Sub_Resource_Tbl_Type
2803 ,   x_rev_operation_tbl             IN OUT NOCOPY Bom_Rtg_Pub.Rev_Operation_Tbl_Type
2804 ,   x_rev_op_resource_tbl           IN OUT NOCOPY Bom_Rtg_Pub.Rev_Op_Resource_Tbl_Type
2805 ,   x_rev_sub_resource_tbl          IN OUT NOCOPY Bom_Rtg_Pub.Rev_Sub_Resource_Tbl_Type
2806 ,   x_mesg_token_tbl                OUT NOCOPY Error_Handler.Mesg_Token_Tbl_Type
2807 ,   x_return_status                 OUT NOCOPY VARCHAR2
2808 )
2809 
2810 IS
2811 
2812 /* Exposed and Unexposed record */
2813 l_rev_operation_rec         Bom_Rtg_Pub.Rev_Operation_Rec_Type ;
2814 --l_rev_operation_tbl         Bom_Rtg_Pub.Rev_Operation_Tbl_Type ;
2815 l_rev_op_unexp_rec          Bom_Rtg_Pub.Rev_Op_Unexposed_Rec_Type ;
2816 l_old_rev_operation_rec     Bom_Rtg_Pub.Rev_Operation_Rec_Type ;
2817 l_old_rev_op_unexp_rec      Bom_Rtg_Pub.Rev_Op_Unexposed_Rec_Type ;
2818 
2819 /* Other Entities */
2820 l_eco_rec                ENG_Eco_PUB.Eco_Rec_Type;
2821 l_eco_revision_tbl       ENG_Eco_PUB.ECO_Revision_Tbl_Type;
2822 l_revised_item_tbl       ENG_Eco_PUB.Revised_Item_Tbl_Type;
2823 l_rev_component_rec      BOM_BO_PUB.Rev_Component_Rec_Type;
2824 l_rev_component_tbl      BOM_BO_PUB.Rev_Component_Tbl_Type;
2825 l_rev_comp_unexp_rec     BOM_BO_PUB.Rev_Comp_Unexposed_Rec_Type;
2826 l_old_rev_component_rec  BOM_BO_PUB.Rev_Component_Rec_Type;
2827 l_old_rev_comp_unexp_rec BOM_BO_PUB.Rev_Comp_Unexposed_Rec_Type;
2828 l_ref_designator_tbl     BOM_BO_PUB.Ref_Designator_Tbl_Type;
2829 l_sub_component_tbl      BOM_BO_PUB.Sub_Component_Tbl_Type;
2830 --l_rev_op_resource_tbl    Bom_Rtg_Pub.Rev_Op_Resource_Tbl_Type   := p_rev_op_resource_tbl ;
2831 --l_rev_sub_resource_tbl   Bom_Rtg_Pub.Rev_Sub_Resource_Tbl_Type  := p_rev_sub_resource_tbl ;
2832 
2833 /* Others */
2834 l_return_status         VARCHAR2(1) ;
2835 l_bo_return_status      VARCHAR2(1) ;
2836 l_process_children      BOOLEAN := TRUE ;
2837 l_item_parent_exists    BOOLEAN := FALSE ;
2838 l_valid                 BOOLEAN := TRUE ;
2839 l_dummy                 NUMBER ;
2840 
2841 /* Error Handling Variables */
2842 l_token_tbl             Error_Handler.Token_Tbl_Type ;
2843 l_mesg_token_tbl        Error_Handler.Mesg_Token_Tbl_Type;
2844 l_other_token_tbl       Error_Handler.Token_Tbl_Type ;
2845 l_other_message         VARCHAR2(2000);
2846 l_err_text              VARCHAR2(2000);
2847 
2848 EXC_SEV_QUIT_RECORD     EXCEPTION ;
2849 EXC_SEV_QUIT_BRANCH     EXCEPTION ;
2850 EXC_UNEXP_SKIP_OBJECT   EXCEPTION ;
2851 EXC_SEV_QUIT_SIBLINGS   EXCEPTION ;
2852 EXC_SEV_SKIP_BRANCH     EXCEPTION ;
2853 EXC_FAT_QUIT_SIBLINGS   EXCEPTION ;
2854 EXC_FAT_QUIT_BRANCH     EXCEPTION ;
2855 EXC_FAT_QUIT_OBJECT     EXCEPTION ;
2856 
2857 BEGIN
2858 
2859    --  Init local table variables.
2860    l_return_status        := FND_API.G_RET_STS_SUCCESS ;
2861    l_bo_return_status     := FND_API.G_RET_STS_SUCCESS ;
2862    x_return_status        := FND_API.G_RET_STS_SUCCESS;  -- Bug 7606951
2863    x_rev_operation_tbl    := p_rev_operation_tbl ;
2864    x_rev_op_resource_tbl  := p_rev_op_resource_tbl ;
2865    x_rev_sub_resource_tbl := p_rev_sub_resource_tbl ;
2866 
2867    l_rev_op_unexp_rec.organization_id := Eng_Globals.Get_Org_Id;
2868 
2869 
2870    FOR I IN 1..x_rev_operation_tbl.COUNT LOOP
2871 
2872    IF (x_rev_operation_tbl(I).return_status IS NULL OR
2873         x_rev_operation_tbl(I).return_status = FND_API.G_MISS_CHAR) THEN
2874 
2875    BEGIN
2876 
2877        --  Load local records.
2878        l_rev_operation_rec := x_rev_operation_tbl(I);
2879 
2880        l_rev_operation_rec.transaction_type :=
2881        UPPER(l_rev_operation_rec.transaction_type);
2882 
2883        /* make sure to set process_children to false at the start of
2884           every iteration */
2885 
2886        l_process_children := FALSE;    /* Bug 6485168 */
2887 
2888         --
2889         -- Initialize the Unexposed Record for every iteration of the Loop
2890         -- so that sequence numbers get generated for every new row.
2891         --
2892         l_rev_op_unexp_rec.Revised_Item_Sequence_Id    := NULL ;
2893         l_rev_op_unexp_rec.Operation_Sequence_Id       := NULL ;
2894         l_rev_op_unexp_rec.Old_Operation_Sequence_Id   := NULL ;
2895         l_rev_op_unexp_rec.Routing_Sequence_Id         := NULL ;
2896         l_rev_op_unexp_rec.Revised_Item_Id             := NULL ;
2897         l_rev_op_unexp_rec.Department_Id               := NULL ;
2898         l_rev_op_unexp_rec.Standard_Operation_Id       := NULL ;
2899 
2900         IF p_revised_item_name IS NOT NULL AND
2901            p_effectivity_date  IS NOT NULL AND
2902            p_change_notice     IS NOT NULL AND
2903            p_organization_id   IS NOT NULL
2904         THEN
2905                 -- revised item parent exists
2906                 l_item_parent_exists := TRUE;
2907         END IF;
2908 
2909 
2910         -- Process Flow Step 2: Check if record has not yet been processed and
2911         -- that it is the child of the parent that called this procedure
2912         --
2913 
2914           IF --(l_rev_operation_rec.return_status IS NULL OR
2915             --l_rev_operation_rec.return_status = FND_API.G_MISS_CHAR)
2916            --AND
2917 
2918             -- Did Rev_Items call this procedure, that is,
2919             -- if revised item exists, then is this record a child ?
2920 
2921             (NOT l_item_parent_exists
2922              OR
2923              (l_item_parent_exists AND
2924               (l_rev_operation_rec.ECO_Name = p_change_notice AND
2925                l_rev_op_unexp_rec.organization_id = p_organization_id AND
2926                l_rev_operation_rec.revised_item_name = p_revised_item_name AND
2927                NVL(l_rev_operation_rec.alternate_routing_code, FND_API.G_MISS_CHAR )
2928                                              = NVL(p_alternate_routing_code, FND_API.G_MISS_CHAR ) AND    -- Added for bug 13440461
2929                l_rev_operation_rec.start_effective_date = nvl(ENG_Default_Revised_Item.G_OLD_SCHED_DATE,p_effectivity_date) AND -- Bug 6657209
2930                NVL(l_rev_operation_rec.new_routing_revision, FND_API.G_MISS_CHAR )
2931                                              =   NVL(p_routing_revision, FND_API.G_MISS_CHAR )     AND -- Added by MK on 11/02/00
2932                NVL(l_rev_operation_rec.from_end_item_unit_number, FND_API.G_MISS_CHAR )
2933                                              =   NVL(p_from_end_item_number, FND_API.G_MISS_CHAR ) AND -- Added by MK on 11/02/00
2934                NVL(l_rev_operation_rec.new_revised_item_revision, FND_API.G_MISS_CHAR )
2935                                              = NVL(p_item_revision, FND_API.G_MISS_CHAR) ))
2936             )
2937         THEN
2938 
2939          l_return_status := FND_API.G_RET_STS_SUCCESS;
2940          l_rev_operation_rec.return_status := FND_API.G_RET_STS_SUCCESS;
2941 
2942          -- Bug 6657209
2943            IF (l_item_parent_exists and ENG_Default_Revised_Item.G_OLD_SCHED_DATE is not null) THEN
2944               l_rev_operation_rec.start_effective_date := p_effectivity_date;
2945            END IF;
2946 
2947          --
2948          -- Process Flow step 3 :Check if transaction_type is valid
2949          -- Transaction_Type must be CRATE, UPDATE, DELETE or CANCEL
2950          -- Call the Bom_Rtg_Globals.Transaction_Type_Validity
2951          --
2952 
2953          ENG_GLOBALS.Transaction_Type_Validity
2954          (   p_transaction_type => l_rev_operation_rec.transaction_type
2955          ,   p_entity           => 'Op_Seq'
2956          ,   p_entity_id        => l_rev_operation_rec.operation_sequence_number
2957          ,   x_valid            => l_valid
2958          ,   x_mesg_token_tbl   => l_mesg_token_tbl
2959          ) ;
2960 
2961          IF NOT l_valid
2962          THEN
2963             RAISE EXC_SEV_QUIT_RECORD ;
2964          END IF ;
2965 
2966          --
2967          -- Process Flow step 4(a): Convert user unique index to unique
2968          -- index I
2969          -- Call Rtg_Val_To_Id.Operation_UUI_To_UI Shared Utility Package
2970          --
2971          Bom_Rtg_Val_To_Id.Rev_Operation_UUI_To_UI
2972          ( p_rev_operation_rec  => l_rev_operation_rec
2973          , p_rev_op_unexp_rec   => l_rev_op_unexp_rec
2974          , x_rev_op_unexp_rec   => l_rev_op_unexp_rec
2975          , x_mesg_token_tbl     => l_mesg_token_tbl
2976          , x_return_status      => l_return_status
2977          ) ;
2978 
2979          IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
2980          ('Convert to User Unique Index to Index1 completed with return_status: ' || l_return_status) ;
2981          END IF;
2982 
2983          IF l_return_status = Error_Handler.G_STATUS_ERROR
2984          THEN
2985             l_other_message := 'BOM_OP_UUI_SEV_ERROR';
2986             l_other_token_tbl(1).token_name := 'OP_SEQ_NUMBER';
2987             l_other_token_tbl(1).token_value :=
2988                         l_rev_operation_rec.operation_sequence_number ;
2989             RAISE EXC_SEV_QUIT_BRANCH ;
2990 
2991          ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
2992          THEN
2993             l_other_message := 'BOM_OP_UUI_UNEXP_SKIP';
2994             l_other_token_tbl(1).token_name := 'OP_SEQ_NUMBER';
2995             l_other_token_tbl(1).token_value :=
2996                         l_rev_operation_rec.operation_sequence_number ;
2997             RAISE EXC_UNEXP_SKIP_OBJECT;
2998          END IF ;
2999 
3000 
3001          -- Added by MK on 12/03/00 to resolve ECO dependency
3002          ENG_Val_To_Id.RtgAndRevitem_UUI_To_UI
3003            ( p_revised_item_name        => l_rev_operation_rec.revised_item_name
3004            , p_revised_item_id          => l_rev_op_unexp_rec.revised_item_id
3005            , p_item_revision            => l_rev_operation_rec.new_revised_item_revision
3006            , p_effective_date           => l_rev_operation_rec.start_effective_date
3007            , p_change_notice            => l_rev_operation_rec.eco_name
3008            , p_organization_id          => l_rev_op_unexp_rec.organization_id
3009            , p_new_routing_revision     => l_rev_operation_rec.new_routing_revision
3010            , p_from_end_item_number     => l_rev_operation_rec.from_end_item_unit_number
3011            , p_entity_processed         => 'ROP'
3012            , p_operation_sequence_number => l_rev_operation_rec.operation_sequence_number
3013            , p_alternate_routing_code    => l_rev_operation_rec.alternate_routing_code    -- Added for bug 13440461
3014            , x_revised_item_sequence_id  => l_rev_op_unexp_rec.revised_item_sequence_id
3015            , x_routing_sequence_id       => l_rev_op_unexp_rec.routing_sequence_id
3016            , x_operation_sequence_id    => l_dummy
3017            , x_Mesg_Token_Tbl           => l_Mesg_Token_Tbl
3018            , x_other_message            => l_other_message
3019            , x_other_token_tbl          => l_other_token_tbl
3020            , x_Return_Status            => l_return_status
3021           ) ;
3022 
3023          IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
3024          ('Convert to User Unique Index to Index1 for Rtg and Rev Item Seq completed with return_status: ' || l_return_status) ;
3025          END IF;
3026 
3027          IF l_return_status = Error_Handler.G_STATUS_ERROR
3028          THEN
3029             l_other_message := 'BOM_OP_UUI_SEV_ERROR';
3030             l_other_token_tbl(1).token_name := 'OP_SEQ_NUMBER';
3031             l_other_token_tbl(1).token_value :=
3032                         l_rev_operation_rec.operation_sequence_number ;
3033             RAISE EXC_SEV_QUIT_BRANCH ;
3034 
3035          ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
3036          THEN
3037             l_other_message := 'BOM_OP_UUI_UNEXP_SKIP';
3038             l_other_token_tbl(1).token_name := 'OP_SEQ_NUMBER';
3039             l_other_token_tbl(1).token_value :=
3040                         l_rev_operation_rec.operation_sequence_number ;
3041             RAISE EXC_UNEXP_SKIP_OBJECT;
3042          END IF ;
3043 
3044 
3045          --
3046          -- Process Flow step 4(b): Convert user unique index to unique
3047          -- index II
3048          -- Call the Rtg_Val_To_Id.Operation_UUI_To_UI2
3049          --
3050          /*
3051          Bom_Rtg_Val_To_Id.Rev_Operation_UUI_To_UI2
3052          ( p_rev_operation_rec  => l_rev_operation_rec
3053          , p_rev_op_unexp_rec   => l_rev_op_unexp_rec
3054          , x_rev_op_unexp_rec   => l_rev_op_unexp_rec
3055          , x_mesg_token_tbl     => l_mesg_token_tbl
3056          , x_other_message      => l_other_message
3057          , x_other_token_tbl    => l_other_token_tbl
3058          , x_return_status      => l_return_status
3059          ) ;
3060 
3061          IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
3062          ('Convert to User Unique Index to Index2 completed with return_status: ' || l_return_status) ;
3063          END IF;
3064 
3065          IF l_return_status = Error_Handler.G_STATUS_ERROR
3066          THEN
3067             RAISE EXC_SEV_QUIT_SIBLINGS ;
3068          ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
3069          THEN
3070             l_other_message := 'BOM_OP_UUI_UNEXP_SKIP';
3071             l_other_token_tbl(1).token_name := 'OP_SEQ_NUMBER';
3072             l_other_token_tbl(1).token_value :=
3073                    l_rev_operation_rec.operation_sequence_number ;
3074             RAISE EXC_UNEXP_SKIP_OBJECT;
3075          END IF ;
3076          */
3077 
3078          -- Set Unit Controlled Item
3079          Bom_Rtg_Globals.Set_Unit_Controlled_Item
3080            ( p_inventory_item_id => l_rev_comp_unexp_rec.revised_item_id
3081            , p_organization_id   => l_rev_comp_unexp_rec.organization_id
3082            );
3083 
3084          IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
3085          ('Set unit controlled item flag . . .' ) ;
3086          END IF ;
3087 
3088          --
3089          -- Process Flow step 5 : Check the parent revised item is controlled
3090          -- by model unit effectivity
3091          --
3092          --
3093          IF Bom_Rtg_Globals.Get_Unit_Controlled_Item THEN
3094              l_return_status := FND_API.G_RET_STS_ERROR;
3095              l_token_tbl(1).token_name  := 'OP_SEQ_NUMBER';
3096              l_token_tbl(1).token_value := l_rev_operation_rec.operation_sequence_number ;
3097              l_token_tbl(2).token_name  := 'REVISED_ITEM_NAME';
3098              l_token_tbl(2).token_value := l_rev_operation_rec.revised_item_name ;
3099 
3100              Error_Handler.Add_Error_Token
3101              ( p_Message_Name   => 'BOM_OP_ECO_MDLUNITEFFECT'
3102              , p_mesg_token_tbl => l_mesg_token_tbl
3103              , x_mesg_token_tbl => l_mesg_token_tbl
3104              , p_Token_Tbl      => l_token_tbl
3105              ) ;
3106 
3107              l_return_status := 'F';
3108              RAISE EXC_FAT_QUIT_SIBLINGS ; -- RAISE EXC_FAT_QUIT_BRANCH
3109          END IF;
3110 
3111          IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
3112          ('Check if the parent item is unit controlled item with return_status: ' || l_return_status) ;
3113          END IF ;
3114 
3115          --
3116          -- Process Flow step 6: Verify Operation Sequence's existence
3117          -- Call the Bom_Validate_Op_Seq.Check_Existence
3118          --
3119          --
3120          Bom_Validate_Op_Seq.Check_Existence
3121          (  p_rev_operation_rec          => l_rev_operation_rec
3122          ,  p_rev_op_unexp_rec           => l_rev_op_unexp_rec
3123          ,  x_old_rev_operation_rec      => l_old_rev_operation_rec
3124          ,  x_old_rev_op_unexp_rec       => l_old_rev_op_unexp_rec
3125          ,  x_mesg_token_tbl             => l_mesg_token_tbl
3126          ,  x_return_status              => l_return_status
3127          ) ;
3128 
3129 
3130          IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
3131          ('Check Existence completed with return_status: ' || l_return_status) ;
3132          END IF ;
3133 
3134          IF l_return_status = Error_Handler.G_STATUS_ERROR
3135          THEN
3136             l_other_message := 'BOM_OP_EXS_SEV_SKIP';
3137             l_other_token_tbl(1).token_name  := 'OP_SEQ_NUMBER';
3138             l_other_token_tbl(1).token_value :=
3139                           l_rev_operation_rec.operation_sequence_number ;
3140             l_other_token_tbl(2).token_name  := 'REVISED_ITEM_NAME';
3141             l_other_token_tbl(2).token_value :=
3142                           l_rev_operation_rec.revised_item_name ;
3143             RAISE EXC_SEV_QUIT_BRANCH;
3144          ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
3145          THEN
3146             l_other_message := 'BOM_OP_EXS_UNEXP_SKIP';
3147             l_other_token_tbl(1).token_name  := 'OP_SEQ_NUMBER';
3148             l_other_token_tbl(1).token_value :=
3149                           l_rev_operation_rec.operation_sequence_number ;
3150             l_other_token_tbl(2).token_name  := 'REVISED_ITEM_NAME';
3151             l_other_token_tbl(2).token_value :=
3152                           l_rev_operation_rec.revised_item_name ;
3153             RAISE EXC_UNEXP_SKIP_OBJECT;
3154          END IF;
3155 
3156          --
3157          -- Process Flow step 7: Check lineage
3158          --
3159          IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Check lineage'); END IF;
3160          IF l_rev_operation_rec.transaction_type IN
3161             (Bom_Rtg_Globals.G_OPR_UPDATE, Bom_Rtg_Globals.G_OPR_DELETE,
3162             Bom_Rtg_Globals.G_OPR_CANCEL)
3163          THEN
3164 
3165              BOM_Validate_Op_Seq.Check_Lineage
3166              ( p_routing_sequence_id       =>
3167                                    l_rev_op_unexp_rec.routing_sequence_id
3168              , p_operation_sequence_number =>
3169                                    l_rev_operation_rec.operation_sequence_number
3170              , p_effectivity_date          =>
3171                                    l_rev_operation_rec.start_effective_date
3172              , p_operation_type            =>
3173                                    l_rev_operation_rec.operation_type
3174              , p_revised_item_sequence_id  =>
3175                                    l_rev_op_unexp_rec.revised_item_sequence_id
3176              , x_mesg_token_tbl            => l_mesg_token_tbl
3177              , x_return_status             => l_return_status
3178              ) ;
3179 
3180              IF l_return_status = Error_Handler.G_STATUS_ERROR
3181              THEN
3182 
3183                   l_Token_Tbl(1).token_name  := 'OP_SEQ_NUMBER';
3184                   l_Token_Tbl(1).token_value :=
3185                                l_rev_operation_rec.operation_sequence_number ;
3186                   l_Token_Tbl(2).token_name  := 'REVISED_ITEM_NAME';
3187                   l_Token_Tbl(2).token_value :=
3188                                l_rev_operation_rec.revised_item_name ;
3189                   l_token_tbl(3).token_name  := 'ECO_NAME' ;
3190                   l_token_tbl(3).token_value := l_rev_operation_rec.eco_name ;
3191 
3192                   Error_Handler.Add_Error_Token
3193                   ( p_Message_Name   => 'BOM_OP_REV_ITEM_MISMATCH'
3194                   , p_Mesg_Token_Tbl => l_Mesg_Token_Tbl
3195                   , x_mesg_token_tbl => l_Mesg_Token_Tbl
3196                   , p_Token_Tbl      => l_Token_Tbl
3197                   ) ;
3198 
3199                   l_other_message := 'BOM_OP_LIN_SEV_SKIP';
3200                   l_other_token_tbl(1).token_name  := 'OP_SEQ_NUMBER';
3201                   l_other_token_tbl(1).token_value :=
3202                               l_rev_operation_rec.operation_sequence_number ;
3203                   RAISE EXC_SEV_QUIT_BRANCH;
3204 
3205              ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
3206              THEN
3207                   l_other_message := 'BOM_OP_LIN_UNEXP_SKIP';
3208                   l_other_token_tbl(1).token_name  := 'OP_SEQ_NUMBER';
3209                   l_other_token_tbl(1).token_value :=
3210                               l_rev_operation_rec.operation_sequence_number ;
3211                   RAISE EXC_UNEXP_SKIP_OBJECT;
3212              END IF;
3213          END IF ;
3214 
3215          --
3216          -- Process Flow step 8: Is Operation Sequence record an orphan ?
3217          --
3218 
3219          IF NOT l_item_parent_exists
3220          THEN
3221 
3222 
3223                 --
3224                 -- Process Flow step 9(a and b): Is ECO impl/cancl, or in wkflw process ?
3225                 --
3226               IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('ECO Check access'); END IF;
3227                 ENG_Validate_ECO.Check_Access
3228                 ( p_change_notice       => l_rev_operation_rec.ECO_Name
3229                 , p_organization_id     => l_rev_op_unexp_rec.organization_id
3230                 , p_Mesg_Token_Tbl      => l_Mesg_Token_Tbl
3231                 , x_Mesg_Token_Tbl      => l_Mesg_Token_Tbl
3232                 , x_Return_Status       => l_return_status
3233                 );
3234 
3235                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
3236 
3237                 IF l_return_status = Error_Handler.G_STATUS_ERROR
3238                 THEN
3239                         l_other_message := 'BOM_OP_ECOACC_FAT_FATAL';
3240                         l_other_token_tbl(1).token_name  := 'OP_SEQ_NUMBER';
3241                         l_other_token_tbl(1).token_value :=
3242                                         l_rev_operation_rec.operation_sequence_number ;
3243                         l_return_status := 'F';
3244                         RAISE EXC_FAT_QUIT_OBJECT;
3245                 ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
3246                 THEN
3247                         l_other_message := 'BOM_OP_ECOACC_UNEXP_SKIP';
3248                         l_other_token_tbl(1).token_name  := 'OP_SEQ_NUMBER';
3249                         l_other_token_tbl(1).token_value :=
3250                                         l_rev_operation_rec.operation_sequence_number ;
3251                         RAISE EXC_UNEXP_SKIP_OBJECT;
3252                 END IF;
3253 
3254 
3255                 -- Process Flow step 10(a and b): check that user has access to revised item
3256                 --
3257 
3258                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Revised Item Check access'); END IF;
3259                 ENG_Validate_Revised_Item.Check_Access
3260                 (  p_change_notice      => l_rev_operation_rec.ECO_Name
3261                 ,  p_organization_id    => l_rev_op_unexp_rec.organization_id
3262                 ,  p_revised_item_id    => l_rev_op_unexp_rec.revised_item_id
3263                 ,  p_new_item_revision  => l_rev_operation_rec.new_revised_item_revision
3264                 ,  p_effectivity_date   => l_rev_operation_rec.start_effective_date
3265                 ,  p_new_routing_revsion   => l_rev_operation_rec.new_routing_revision  -- Added by MK on 11/02/00
3266                 ,  p_from_end_item_number  => l_rev_operation_rec.from_end_item_unit_number -- Added by MK on 11/02/00
3267                 ,  p_revised_item_name  => l_rev_operation_rec.revised_item_name
3268                 ,  p_entity_processed   => 'ROP'  -- Added by MK on 12/03 to resolve Eco dependency
3269                 ,  p_Mesg_Token_Tbl     => l_Mesg_Token_Tbl
3270                 ,  x_Mesg_Token_Tbl     => l_Mesg_Token_Tbl
3271                 ,  x_return_status      => l_Return_Status
3272                 );
3273 
3274                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
3275 
3276                 IF l_return_status = Error_Handler.G_STATUS_ERROR
3277                 THEN
3278                         l_other_message := 'BOM_OP_RITACC_FAT_FATAL';
3279                         l_other_token_tbl(1).token_name  := 'OP_SEQ_NUMBER';
3280                         l_other_token_tbl(1).token_value :=
3281                                         l_rev_operation_rec.operation_sequence_number;
3282                         l_return_status := 'F';
3283                         RAISE EXC_FAT_QUIT_SIBLINGS;
3284                 ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
3285                 THEN
3286                         l_other_message := 'BOM_OP_RITACC_UNEXP_SKIP';
3287                         l_other_token_tbl(1).token_name  := 'OP_SEQ_NUMBER';
3288                         l_other_token_tbl(1).token_value :=
3289                                         l_rev_operation_rec.operation_sequence_number ;
3290                         RAISE EXC_UNEXP_SKIP_OBJECT;
3291                 END IF;
3292 
3293                 --
3294                 -- Process Flow step  : Check Assembly Item Operability for Operation
3295                 -- BOM_Validate_Op_Seq.Check_Access
3296                 --
3297                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Operation Check access'); END IF;
3298                 BOM_Validate_Op_Seq.Check_Access
3299                 (  p_change_notice     => l_rev_operation_rec.ECO_Name
3300                 ,  p_organization_id   => l_rev_op_unexp_rec.organization_id
3301                 ,  p_revised_item_id   => l_rev_op_unexp_rec.revised_item_id
3302                 ,  p_revised_item_name => l_rev_operation_rec.revised_item_name
3303                 ,  p_new_item_revision =>
3304                                   l_rev_operation_rec.new_revised_item_revision
3305                 ,  p_effectivity_date  =>
3306                                   l_rev_operation_rec.start_effective_date
3307                 ,  p_new_routing_revsion   => l_rev_operation_rec.new_routing_revision  -- Added by MK on 11/02/00
3308                 ,  p_from_end_item_number  => l_rev_operation_rec.from_end_item_unit_number -- Added by MK on 11/02/00
3309 
3310                 ,  p_operation_seq_num  =>
3311                                   l_rev_operation_rec.operation_sequence_number
3312                 ,  p_routing_sequence_id =>
3313                                   l_rev_op_unexp_rec.routing_sequence_id
3314                 ,  p_operation_type   =>
3315                                   l_rev_operation_rec.operation_type
3316                 ,  p_entity_processed => 'OP'
3317                 ,  p_resource_seq_num  => NULL
3318                 ,  p_sub_resource_code => NULL
3319                 ,  p_sub_group_num     => NULL
3320                 ,  p_Mesg_Token_Tbl    => l_Mesg_Token_Tbl
3321                 ,  x_Mesg_Token_Tbl    => l_Mesg_Token_Tbl
3322                 ,  x_return_status     => l_Return_Status
3323                 );
3324 
3325                IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('In check access of operations, return_status: ' || l_return_status); END IF;
3326 
3327                 IF l_return_status = Error_Handler.G_STATUS_ERROR
3328                 THEN
3329                    l_other_message := 'BOM_OP_ACCESS_FAT_FATAL';
3330                    l_other_token_tbl(1).token_name := 'OP_SEQ_NUMBER';
3331                    l_other_token_tbl(1).token_value :=
3332                          l_rev_operation_rec.operation_sequence_number ;
3333                    l_return_status := 'F' ;
3334                    RAISE EXC_FAT_QUIT_SIBLINGS ; -- Check EXC_FAT_QUIT_OBJECT
3335                 ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
3336                         THEN
3337                         l_other_message := 'BOM_OP_ACCESS_UNEXP_SKIP';
3338                         l_other_token_tbl(1).token_name := 'OP_SEQ_NUMBER';
3339                         l_other_token_tbl(1).token_value :=
3340                               l_rev_operation_rec.operation_sequence_number ;
3341                         RAISE EXC_UNEXP_SKIP_OBJECT;
3342                 END IF;
3343 
3344 
3345                 --
3346                 -- Process Flow step 11 : Check the routing does not have a common
3347                 --
3348 
3349                 Bom_Validate_Op_Seq.Check_CommonRtg
3350                 (  p_routing_sequence_id  =>
3351                                         l_rev_op_unexp_rec.routing_sequence_id
3352                 ,  x_mesg_token_tbl       => l_mesg_token_tbl
3353                 ,  x_return_status        => l_return_status
3354                 ) ;
3355 
3356                 IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
3357                 ('Check the routing non-referenced common completed with return_status: ' || l_return_status) ;
3358                 END IF ;
3359 
3360                 IF l_return_status = Error_Handler.G_STATUS_ERROR
3361                 THEN
3362                         l_token_tbl(1).token_name  := 'OP_SEQ_NUMBER';
3363                         l_token_tbl(1).token_value :=
3364                                 l_rev_operation_rec.operation_sequence_number ;
3365                         l_token_tbl(2).token_name  := 'REVISED_ITEM_NAME';
3366                         l_token_tbl(2).token_value :=
3367                                 l_rev_operation_rec.revised_item_name ;
3368                         Error_Handler.Add_Error_Token
3369                         ( p_Message_Name   => 'BOM_OP_RTG_HAVECOMMON'
3370                         , p_mesg_token_tbl => l_mesg_token_tbl
3371                         , x_mesg_token_tbl => l_mesg_token_tbl
3372                         , p_Token_Tbl      => l_token_tbl
3373                         ) ;
3374 
3375                         l_return_status := 'F';
3376                         RAISE EXC_FAT_QUIT_SIBLINGS ; -- RAISE EXC_FAT_QUIT_BRANCH ;
3377 
3378                 ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
3379                 THEN
3380                         l_other_message := 'BOM_OP_ACCESS_UNEXP_SKIP';
3381                         l_other_token_tbl(1).token_name := 'OP_SEQ_NUMBER';
3382                         l_other_token_tbl(1).token_value :=
3383                            l_rev_operation_rec.operation_sequence_number ;
3384                         RAISE EXC_UNEXP_SKIP_OBJECT;
3385                 END IF;
3386 
3387          END IF ;  -- End of process for an orphan
3388 
3389 
3390          /* In future release If ECO for Flow Routing is supported,
3391             this step should be implemented.
3392 
3393          -- Process Flow Step  : Check parent CFM Routing Flag
3394          -- Validate Non-Operated Columns using CFM Routing Flag
3395          -- Standard Routing, Flow Routing, Lot Based Routing.
3396          -- If a non-operated column is not null, the procedure set it to null
3397          -- and occur Warning.
3398          --
3399          BOM_Validate_Op_Seq.Check_NonOperated_Attribute
3400          ( p_rev_operation_rec    => l_rev_operation_rec
3401          , p_rev_op_unexp_rec     => l_rev_op_unexp_rec
3402          , x_rev_operation_rec    => l_rev_operation_rec
3403          , x_rev_op_unexp_rec     => l_rev_op_unexp_rec
3404          , x_mesg_token_tbl       => l_mesg_token_tbl
3405          , x_return_status        => l_return_status
3406          ) ;
3407 
3408          IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
3409          ('Check non-operating columns completed with return_status: ' || l_return_status) ;
3410          END IF ;
3411 
3412          IF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
3413          THEN
3414             l_other_message := 'BOM_OP_NOPATTR_UNEXP_SKIP';
3415             l_other_token_tbl(1).token_name := 'OP_SEQ_NUMBER';
3416             l_other_token_tbl(1).token_value :=
3417                           l_rev_operation_rec.operation_sequence_number ;
3418             RAISE EXC_UNEXP_SKIP_OBJECT;
3419 
3420          ELSIF l_return_status ='S' AND l_mesg_token_tbl .COUNT <>0
3421          THEN
3422             ECO_Error_Handler.Log_Error
3423             (  p_rev_operation_tbl   => l_rev_operation_tbl
3424             ,  p_rev_op_resource_tbl => l_rev_op_resource_tbl
3425             ,  p_rev_sub_resource_tbl=> l_rev_sub_resource_tbl
3426             ,  p_mesg_token_tbl      => l_mesg_token_tbl
3427             ,  p_error_status        => 'W'
3428             ,  p_error_level         => Error_Handler.G_OP_LEVEL
3429             ,  p_entity_index        => I
3430             ,  x_ECO_rec             => l_ECO_rec
3431             ,  x_eco_revision_tbl    => l_eco_revision_tbl
3432             ,  x_revised_item_tbl    => l_revised_item_tbl
3433             ,  x_rev_component_tbl   => l_rev_component_tbl
3434             ,  x_ref_designator_tbl  => l_ref_designator_tbl
3435             ,  x_sub_component_tbl   => l_sub_component_tbl
3436             ,  x_rev_operation_tbl   => l_rev_operation_tbl
3437             ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl
3438             ,  x_rev_sub_resource_tbl=> l_rev_sub_resource_tbl
3439             ) ;
3440          END IF;
3441          */
3442 
3443 
3444          --
3445          -- Process Flow step 12: Value to Id conversions
3446          -- Call Rtg_Val_To_Id.Operation_VID
3447          --
3448          Bom_Rtg_Val_To_Id.Rev_Operation_VID
3449          (  p_rev_operation_rec          => l_rev_operation_rec
3450          ,  p_rev_op_unexp_rec           => l_rev_op_unexp_rec
3451          ,  x_rev_op_unexp_rec           => l_rev_op_unexp_rec
3452          ,  x_mesg_token_tbl             => l_mesg_token_tbl
3453          ,  x_return_status              => l_return_status
3454          );
3455 
3456          IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
3457          ('Value-id conversions completed with return_status: ' ||
3458                                                l_return_status) ;
3459          END IF ;
3460 
3461          IF l_return_status = Error_Handler.G_STATUS_ERROR
3462          THEN
3463             IF l_rev_operation_rec.transaction_type = 'CREATE'
3464             THEN
3465                l_other_message := 'BOM_OP_VID_CSEV_SKIP';
3466                l_other_token_tbl(1).token_name := 'OP_SEQ_NUMBER';
3467                l_other_token_tbl(1).token_value :=
3468                           l_rev_operation_rec.operation_sequence_number ;
3469                RAISE EXC_SEV_SKIP_BRANCH;
3470             ELSE
3471                RAISE EXC_SEV_QUIT_RECORD ;
3472             END IF ;
3473 
3474          ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
3475          THEN
3476             l_other_message := 'BOM_OP_VID_UNEXP_SKIP';
3477             l_other_token_tbl(1).token_name := 'OP_SEQ_NUMBER';
3478             l_other_token_tbl(1).token_value :=
3479                           l_rev_operation_rec.operation_sequence_number ;
3480             RAISE EXC_UNEXP_SKIP_OBJECT;
3481 
3482          ELSIF l_return_status ='S' AND l_mesg_token_tbl .COUNT <>0
3483          THEN
3484             ECO_Error_Handler.Log_Error
3485             (  p_rev_operation_tbl       => x_rev_operation_tbl
3486             ,  p_rev_op_resource_tbl     => x_rev_op_resource_tbl
3487             ,  p_rev_sub_resource_tbl    => x_rev_sub_resource_tbl
3488             ,  p_mesg_token_tbl      => l_mesg_token_tbl
3489             ,  p_error_status        => 'W'
3490             ,  p_error_level         => Error_Handler.G_OP_LEVEL
3491             ,  p_entity_index        => I
3492             ,  x_ECO_rec             => l_ECO_rec
3493             ,  x_eco_revision_tbl    => l_eco_revision_tbl
3494             ,  x_revised_item_tbl    => l_revised_item_tbl
3495             ,  x_rev_component_tbl   => l_rev_component_tbl
3496             ,  x_ref_designator_tbl  => l_ref_designator_tbl
3497             ,  x_sub_component_tbl   => l_sub_component_tbl
3498             ,  x_rev_operation_tbl   => x_rev_operation_tbl
3499             ,  x_rev_op_resource_tbl => x_rev_op_resource_tbl
3500             ,  x_rev_sub_resource_tbl=> x_rev_sub_resource_tbl
3501             ) ;
3502          END IF;
3503 
3504          --
3505          -- Process Flow step 13 : Check required fields exist
3506          -- (also includes a part of conditionally required fields)
3507          --
3508 
3509          Bom_Validate_Op_Seq.Check_Required
3510          ( p_rev_operation_rec          => l_rev_operation_rec
3511          , x_return_status              => l_return_status
3512          , x_mesg_token_tbl             => l_mesg_token_tbl
3513          ) ;
3514 
3515 
3516          IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
3517          ('Check required completed with return_status: ' || l_return_status) ;
3518          END IF ;
3519 
3520 
3521          IF l_return_status = Error_Handler.G_STATUS_ERROR
3522          THEN
3523             IF l_rev_operation_rec.transaction_type = Bom_Rtg_Globals.G_OPR_CREATE
3524             THEN
3525                l_other_message := 'BOM_OP_REQ_CSEV_SKIP';
3526                l_other_token_tbl(1).token_name := 'OP_SEQ_NUMBER';
3527                l_other_token_tbl(1).token_value :=
3528                           l_rev_operation_rec.operation_sequence_number ;
3529                RAISE EXC_SEV_SKIP_BRANCH ;
3530             ELSE
3531                RAISE EXC_SEV_QUIT_RECORD ;
3532             END IF;
3533          ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
3534          THEN
3535             l_other_message := 'BOM_OP_REQ_UNEXP_SKIP';
3536             l_other_token_tbl(1).token_name := 'OP_SEQ_NUMBER';
3537             l_other_token_tbl(1).token_value :=
3538                           l_rev_operation_rec.operation_sequence_number ;
3539             RAISE EXC_UNEXP_SKIP_OBJECT ;
3540          END IF;
3541 
3542 
3543          --
3544          -- Process Flow step 14 : Attribute Validation for CREATE and UPDATE
3545          --
3546          --
3547          IF l_rev_operation_rec.transaction_type IN
3548             (Bom_Rtg_Globals.G_OPR_CREATE, Bom_Rtg_Globals.G_OPR_UPDATE)
3549          THEN
3550             Bom_Validate_Op_Seq.Check_Attributes
3551             ( p_rev_operation_rec => l_rev_operation_rec
3552             , p_rev_op_unexp_rec  => l_rev_op_unexp_rec
3553             , x_return_status     => l_return_status
3554             , x_mesg_token_tbl    => l_mesg_token_tbl
3555             ) ;
3556 
3557             IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
3558             ('Attribute validation completed with return_status: ' || l_return_status) ;
3559             END IF ;
3560 
3561             IF l_return_status = Error_Handler.G_STATUS_ERROR
3562             THEN
3563                IF l_rev_operation_rec.transaction_type = Bom_Rtg_Globals.G_OPR_CREATE
3564                THEN
3565                   l_other_message := 'BOM_OP_ATTVAL_CSEV_SKIP';
3566                   l_other_token_tbl(1).token_name := 'OP_SEQ_NUMBER';
3567                   l_other_token_tbl(1).token_value :=
3568                            l_rev_operation_rec.operation_sequence_number ;
3569                   RAISE EXC_SEV_SKIP_BRANCH ;
3570                   ELSE
3571                      RAISE EXC_SEV_QUIT_RECORD ;
3572                END IF;
3573             ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
3574             THEN
3575                l_other_message := 'BOM_OP_ATTVAL_UNEXP_SKIP';
3576                l_other_token_tbl(1).token_name := 'OP_SEQ_NUMBER';
3577                l_other_token_tbl(1).token_value :=
3578                            l_rev_operation_rec.operation_sequence_number ;
3579                RAISE EXC_UNEXP_SKIP_OBJECT ;
3580             ELSIF l_return_status ='S' AND l_mesg_token_tbl .COUNT <> 0
3581             THEN
3582                ECO_Error_Handler.Log_Error
3583                (  p_rev_operation_tbl   => x_rev_operation_tbl
3584                ,  p_rev_op_resource_tbl => x_rev_op_resource_tbl
3585                ,  p_rev_sub_resource_tbl=> x_rev_sub_resource_tbl
3586                ,  p_mesg_token_tbl      => l_mesg_token_tbl
3587                ,  p_error_status        => 'W'
3588                ,  p_error_level         => Error_Handler.G_OP_LEVEL
3589                ,  p_entity_index        => I
3590                ,  x_ECO_rec             => l_ECO_rec
3591                ,  x_eco_revision_tbl    => l_eco_revision_tbl
3592                ,  x_revised_item_tbl    => l_revised_item_tbl
3593                ,  x_rev_component_tbl   => l_rev_component_tbl
3594                ,  x_ref_designator_tbl  => l_ref_designator_tbl
3595                ,  x_sub_component_tbl   => l_sub_component_tbl
3596                ,  x_rev_operation_tbl   => x_rev_operation_tbl
3597                ,  x_rev_op_resource_tbl => x_rev_op_resource_tbl
3598                ,  x_rev_sub_resource_tbl=> x_rev_sub_resource_tbl
3599                ) ;
3600            END IF;
3601         END IF;
3602 
3603         --
3604         -- Process flow step: Query the operation record using by Old Op Seq Num
3605         -- and Old Effectivity Date Call Bom_Op_Seq_Util.Query_Row
3606         --
3607 
3608         IF (l_rev_operation_rec.transaction_type = ENG_GLOBALS.G_OPR_CREATE
3609             AND l_rev_operation_rec.acd_type IN (2 ,3)    ) -- ACD Type: Change or Disable
3610         THEN
3611 
3612             IF l_rev_operation_rec.old_operation_sequence_number IS NULL OR
3613                l_rev_operation_rec.old_operation_sequence_number = FND_API.G_MISS_NUM
3614             THEN
3615                l_rev_operation_rec.old_operation_sequence_number
3616                    := l_rev_operation_rec.operation_sequence_number ;
3617             END IF ;
3618 
3619             Bom_Op_Seq_Util.Query_Row
3620             ( p_operation_sequence_number =>
3621                               l_rev_operation_rec.old_operation_sequence_number
3622             , p_effectivity_date          =>
3623                               l_rev_operation_rec.old_start_effective_date
3624             , p_routing_sequence_id       =>
3625                               l_rev_op_unexp_rec.routing_sequence_id
3626             , p_operation_type            => l_rev_operation_rec.operation_type
3627             , p_mesg_token_tbl            => l_mesg_token_tbl
3628             , x_rev_operation_rec         => l_old_rev_operation_rec
3629             , x_rev_op_unexp_rec          => l_old_rev_op_unexp_rec
3630             , x_mesg_token_tbl            => l_mesg_token_tbl
3631             , x_return_status             => l_return_status
3632             ) ;
3633 
3634             IF l_return_status <> Eng_Globals.G_RECORD_FOUND
3635             THEN
3636                   l_return_status := Error_Handler.G_STATUS_ERROR ;
3637                   l_Token_Tbl(1).token_name := 'OP_SEQ_NUMBER';
3638                   l_Token_Tbl(1).token_value :=
3639                            l_rev_operation_rec.operation_sequence_number ;
3640 
3641                   Error_Handler.Add_Error_Token
3642                   ( p_message_name       => 'BOM_OP_CREATE_REC_NOT_FOUND'
3643                   , p_mesg_token_tbl     => l_Mesg_Token_Tbl
3644                   , p_token_tbl          => l_Token_Tbl
3645                   , x_Mesg_Token_Tbl     => l_Mesg_Token_Tbl
3646                   );
3647 
3648                   l_other_message := 'BOM_OP_QRY_CSEV_SKIP';
3649                   l_other_token_tbl(1).token_name := 'OP_SEQ_NUMBER';
3650                   l_other_token_tbl(1).token_value :=
3651                            l_rev_operation_rec.operation_sequence_number ;
3652                   RAISE EXC_SEV_SKIP_BRANCH;
3653            ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
3654            THEN
3655                     l_other_message := 'BOM_OP_QRY_UNEXP_SKIP';
3656                     l_other_token_tbl(1).token_name := 'OP_SEQ_NUMBER';
3657                     l_other_token_tbl(1).token_value :=
3658                            l_rev_operation_rec.operation_sequence_number ;
3659                    RAISE EXC_UNEXP_SKIP_OBJECT;
3660           END IF;
3661         END IF;
3662 
3663 
3664         IF (l_rev_operation_rec.transaction_type = ENG_GLOBALS.G_OPR_CREATE
3665            AND l_rev_operation_rec.acd_type IN ( 2,3 ) ) -- ACD Type : Change or Disable
3666         OR
3667            l_rev_operation_rec.transaction_type IN (ENG_GLOBALS.G_OPR_UPDATE ,
3668                                                     ENG_GLOBALS.G_OPR_DELETE ,
3669                                                     ENG_GLOBALS.G_OPR_CANCEL)
3670         THEN
3671 
3672         --
3673         -- Process flow step 15: Populate NULL columns for Update and Delete
3674         -- and Creates with ACD_Type 'Add'.
3675         -- Call Bom_Default_Op_Seq.Populate_Null_Columns
3676         --
3677 
3678            IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Populate NULL columns') ;
3679            END IF ;
3680 
3681 
3682            Bom_Default_Op_Seq.Populate_Null_Columns
3683            (   p_rev_operation_rec     => l_rev_operation_rec
3684            ,   p_old_rev_operation_Rec => l_old_rev_operation_rec
3685            ,   p_rev_op_unexp_rec      => l_rev_op_unexp_rec
3686            ,   p_old_rev_op_unexp_rec  => l_old_rev_op_unexp_rec
3687            ,   x_rev_operation_rec     => l_rev_operation_rec
3688            ,   x_rev_op_unexp_rec      => l_rev_op_unexp_rec
3689            ) ;
3690 
3691 
3692         ELSIF l_rev_operation_rec.transaction_type = Bom_Rtg_Globals.G_OPR_CREATE
3693               AND l_rev_operation_rec.acd_type <> 2  -- ACD Type : Not Change
3694         THEN
3695         --
3696         -- Process Flow step 16 : Default missing values for Operation (CREATE)
3697         -- (also includes Entity Defaulting)
3698         -- Call Bom_Default_Op_Seq.Attribute_Defaulting
3699         --
3700 
3701            Bom_Default_Op_Seq.Attribute_Defaulting
3702            (   p_rev_operation_rec   => l_rev_operation_rec
3703            ,   p_rev_op_unexp_rec    => l_rev_op_unexp_rec
3704            ,   p_control_rec         => Bom_Rtg_Pub.G_Default_Control_Rec
3705            ,   x_rev_operation_rec   => l_rev_operation_rec
3706            ,   x_rev_op_unexp_rec    => l_rev_op_unexp_rec
3707            ,   x_mesg_token_tbl      => l_mesg_token_tbl
3708            ,   x_return_status       => l_return_status
3709            ) ;
3710 
3711            IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
3712            ('Attribute Defaulting completed with return_status: ' || l_return_status) ;
3713            END IF ;
3714 
3715 
3716            IF l_return_status = Error_Handler.G_STATUS_ERROR
3717            THEN
3718               l_other_message := 'BOM_OP_ATTDEF_CSEV_SKIP';
3719               l_other_token_tbl(1).token_name := 'OP_SEQ_NUMBER';
3720               l_other_token_tbl(1).token_value :=
3721                           l_rev_operation_rec.operation_sequence_number ;
3722               RAISE EXC_SEV_SKIP_BRANCH ;
3723 
3724            ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
3725            THEN
3726               l_other_message := 'BOM_OP_ATTDEF_UNEXP_SKIP';
3727               l_other_token_tbl(1).token_name := 'OP_SEQ_NUMBER';
3728               l_other_token_tbl(1).token_value :=
3729                            l_rev_operation_rec.operation_sequence_number ;
3730               RAISE EXC_UNEXP_SKIP_OBJECT ;
3731            ELSIF l_return_status ='S' AND l_mesg_token_tbl .COUNT <> 0
3732            THEN
3733                ECO_Error_Handler.Log_Error
3734                (  p_rev_operation_tbl   => x_rev_operation_tbl
3735                ,  p_rev_op_resource_tbl => x_rev_op_resource_tbl
3736                ,  p_rev_sub_resource_tbl=> x_rev_sub_resource_tbl
3737                ,  p_mesg_token_tbl      => l_mesg_token_tbl
3738                ,  p_error_status        => 'W'
3739                ,  p_error_level         => Error_Handler.G_OP_LEVEL
3740                ,  p_entity_index        => I
3741                ,  x_ECO_rec             => l_ECO_rec
3742                ,  x_eco_revision_tbl    => l_eco_revision_tbl
3743                ,  x_revised_item_tbl    => l_revised_item_tbl
3744                ,  x_rev_component_tbl   => l_rev_component_tbl
3745                ,  x_ref_designator_tbl  => l_ref_designator_tbl
3746                ,  x_sub_component_tbl   => l_sub_component_tbl
3747                ,  x_rev_operation_tbl   => x_rev_operation_tbl
3748                ,  x_rev_op_resource_tbl => x_rev_op_resource_tbl
3749                ,  x_rev_sub_resource_tbl=> x_rev_sub_resource_tbl
3750               ) ;
3751           END IF;
3752        END IF;
3753 
3754 
3755        --
3756        -- Process Flow step 17: Conditionally Required Attributes
3757        --
3758        --
3759        IF l_rev_operation_rec.transaction_type IN ( Bom_Rtg_Globals.G_OPR_CREATE
3760                                                   , Bom_Rtg_Globals.G_OPR_UPDATE )
3761        THEN
3762           Bom_Validate_Op_Seq.Check_Conditionally_Required
3763           ( p_rev_operation_rec          => l_rev_operation_rec
3764           , p_rev_op_unexp_rec           => l_rev_op_unexp_rec
3765           , x_return_status              => l_return_status
3766           , x_mesg_token_tbl             => l_mesg_token_tbl
3767           ) ;
3768 
3769           IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
3770           ('Check Conditionally Required Attr. completed with return_status: ' || l_return_status) ;
3771           END IF ;
3772 
3773           IF l_return_status = Error_Handler.G_STATUS_ERROR
3774           THEN
3775              IF l_rev_operation_rec.transaction_type = Bom_Rtg_Globals.G_OPR_CREATE
3776              THEN
3777                 l_other_message := 'BOM_OP_CONREQ_CSEV_SKIP';
3778                 l_other_token_tbl(1).token_name := 'OP_SEQ_NUMBER';
3779                 l_other_token_tbl(1).token_value :=
3780                           l_rev_operation_rec.operation_sequence_number ;
3781                 RAISE EXC_SEV_SKIP_BRANCH ;
3782              ELSE
3783                 RAISE EXC_SEV_QUIT_RECORD ;
3784              END IF;
3785           ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
3786           THEN
3787              l_other_message := 'BOM_OP_CONREQ_UNEXP_SKIP';
3788              l_other_token_tbl(1).token_name := 'OP_SEQ_NUMBER';
3789              l_other_token_tbl(1).token_value :=
3790                           l_rev_operation_rec.operation_sequence_number ;
3791              RAISE EXC_UNEXP_SKIP_OBJECT ;
3792           ELSIF l_return_status ='S' AND l_mesg_token_tbl .COUNT <> 0
3793           THEN
3794              ECO_Error_Handler.Log_Error
3795              (  p_rev_operation_tbl   => x_rev_operation_tbl
3796              ,  p_rev_op_resource_tbl => x_rev_op_resource_tbl
3797              ,  p_rev_sub_resource_tbl=> x_rev_sub_resource_tbl
3798              ,  p_mesg_token_tbl      => l_mesg_token_tbl
3799              ,  p_error_status        => 'W'
3800              ,  p_error_level         => Error_Handler.G_OP_LEVEL
3801              ,  p_entity_index        => I
3802              ,  x_ECO_rec             => l_ECO_rec
3803              ,  x_eco_revision_tbl    => l_eco_revision_tbl
3804              ,  x_revised_item_tbl    => l_revised_item_tbl
3805              ,  x_rev_component_tbl   => l_rev_component_tbl
3806              ,  x_ref_designator_tbl  => l_ref_designator_tbl
3807              ,  x_sub_component_tbl   => l_sub_component_tbl
3808              ,  x_rev_operation_tbl   => x_rev_operation_tbl
3809              ,  x_rev_op_resource_tbl => x_rev_op_resource_tbl
3810              ,  x_rev_sub_resource_tbl=> x_rev_sub_resource_tbl
3811              ) ;
3812           END IF;
3813        END IF;
3814 
3815 
3816        --
3817        -- Process Flow step 18: Entity defaulting for CREATE and UPDATE
3818        -- Merged into Process Flow step 13 : Default missing values
3819        --
3820 
3821        IF l_rev_operation_rec.transaction_type IN ( Bom_Rtg_Globals.G_OPR_CREATE
3822                                                   , Bom_Rtg_Globals.G_OPR_UPDATE )
3823        THEN
3824           Bom_Default_Op_Seq.Entity_Defaulting
3825               (   p_rev_operation_rec   => l_rev_operation_rec
3826               ,   p_rev_op_unexp_rec    => l_rev_op_unexp_rec
3827               ,   p_control_rec         => Bom_Rtg_Pub.G_Default_Control_Rec
3828               ,   x_rev_operation_rec   => l_rev_operation_rec
3829               ,   x_rev_op_unexp_rec    => l_rev_op_unexp_rec
3830               ,   x_mesg_token_tbl  => l_mesg_token_tbl
3831               ,   x_return_status   => l_return_status
3832               ) ;
3833 
3834           IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
3835           ('Entity defaulting completed with return_status: ' || l_return_status) ;
3836           END IF ;
3837 
3838           IF l_return_status = Error_Handler.G_STATUS_ERROR
3839           THEN
3840              IF l_rev_operation_rec.transaction_type = Bom_Rtg_Globals.G_OPR_CREATE
3841              THEN
3842                 l_other_message := 'BOM_OP_ENTDEF_CSEV_SKIP';
3843                 l_other_token_tbl(1).token_name := 'OP_SEQ_NUMBER';
3844                 l_other_token_tbl(1).token_value :=
3845                           l_rev_operation_rec.operation_sequence_number ;
3846                 RAISE EXC_SEV_SKIP_BRANCH ;
3847              ELSE
3848                 RAISE EXC_SEV_QUIT_RECORD ;
3849              END IF;
3850           ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
3851           THEN
3852              l_other_message := 'BOM_OP_ENTDEF_UNEXP_SKIP';
3853              l_other_token_tbl(1).token_name := 'OP_SEQ_NUMBER';
3854              l_other_token_tbl(1).token_value :=
3855                           l_rev_operation_rec.operation_sequence_number ;
3856              RAISE EXC_UNEXP_SKIP_OBJECT ;
3857           ELSIF l_return_status ='S' AND l_mesg_token_tbl .COUNT <> 0
3858           THEN
3859              ECO_Error_Handler.Log_Error
3860              (  p_rev_operation_tbl   => x_rev_operation_tbl
3861              ,  p_rev_op_resource_tbl => x_rev_op_resource_tbl
3862              ,  p_rev_sub_resource_tbl=> x_rev_sub_resource_tbl
3863              ,  p_mesg_token_tbl      => l_mesg_token_tbl
3864              ,  p_error_status        => 'W'
3865              ,  p_error_level         => Error_Handler.G_OP_LEVEL
3866              ,  p_entity_index        => I
3867              ,  x_ECO_rec             => l_ECO_rec
3868              ,  x_eco_revision_tbl    => l_eco_revision_tbl
3869              ,  x_revised_item_tbl    => l_revised_item_tbl
3870              ,  x_rev_component_tbl   => l_rev_component_tbl
3871              ,  x_ref_designator_tbl  => l_ref_designator_tbl
3872              ,  x_sub_component_tbl   => l_sub_component_tbl
3873              ,  x_rev_operation_tbl   => x_rev_operation_tbl
3874              ,  x_rev_op_resource_tbl => x_rev_op_resource_tbl
3875              ,  x_rev_sub_resource_tbl=> x_rev_sub_resource_tbl
3876              ) ;
3877           END IF ;
3878        END IF ;
3879 
3880 
3881        --
3882        -- Process Flow step 19 - Entity Level Validation
3883        -- Call Bom_Validate_Op_Seq.Check_Entity
3884        --
3885 
3886        IF Bom_Rtg_Globals.Get_Debug = 'Y'
3887        THEN Error_Handler.Write_Debug('Starting with Revised Operatin Entity Validation . . . ') ;
3888        END IF ;
3889 
3890           Bom_Validate_Op_Seq.Check_Entity
3891           (  p_rev_operation_rec     => l_rev_operation_rec
3892           ,  p_rev_op_unexp_rec      => l_rev_op_unexp_rec
3893           ,  p_old_rev_operation_rec => l_old_rev_operation_rec
3894           ,  p_old_rev_op_unexp_rec  => l_old_rev_op_unexp_rec
3895           ,  p_control_rec           => Bom_Rtg_Pub.G_Default_Control_Rec
3896           ,  x_rev_operation_rec     => l_rev_operation_rec
3897           ,  x_rev_op_unexp_rec      => l_rev_op_unexp_rec
3898           ,  x_mesg_token_tbl        => l_mesg_token_tbl
3899           ,  x_return_status         => l_return_status
3900           ) ;
3901 
3902 
3903        IF l_return_status = Error_Handler.G_STATUS_ERROR
3904        THEN
3905           IF l_rev_operation_rec.transaction_type = Bom_Rtg_Globals.G_OPR_CREATE
3906           THEN
3907              l_other_message := 'BOM_OP_ENTVAL_CSEV_SKIP';
3908              l_other_token_tbl(1).token_name := 'OP_SEQ_NUMBER';
3909              l_other_token_tbl(1).token_value :=
3910                            l_rev_operation_rec.operation_sequence_number ;
3911              RAISE EXC_SEV_SKIP_BRANCH ;
3912           ELSE
3913              RAISE EXC_SEV_QUIT_RECORD ;
3914           END IF;
3915        ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
3916        THEN
3917           l_other_message := 'BOM_OP_ENTVAL_UNEXP_SKIP';
3918           l_other_token_tbl(1).token_name := 'OP_SEQ_NUMBER';
3919           l_other_token_tbl(1).token_value :=
3920                         l_rev_operation_rec.operation_sequence_number ;
3921           RAISE EXC_UNEXP_SKIP_OBJECT ;
3922        ELSIF l_return_status ='S' AND l_mesg_token_tbl .COUNT <> 0
3923        THEN
3924           ECO_Error_Handler.Log_Error
3925           (  p_rev_operation_tbl   => x_rev_operation_tbl
3926           ,  p_rev_op_resource_tbl => x_rev_op_resource_tbl
3927           ,  p_rev_sub_resource_tbl=> x_rev_sub_resource_tbl
3928           ,  p_mesg_token_tbl      => l_mesg_token_tbl
3929           ,  p_error_status        => 'W'
3930           ,  p_error_level         => Error_Handler.G_OP_LEVEL
3931           ,  p_entity_index        => I
3932           ,  x_ECO_rec             => l_ECO_rec
3933           ,  x_eco_revision_tbl    => l_eco_revision_tbl
3934           ,  x_revised_item_tbl    => l_revised_item_tbl
3935           ,  x_rev_component_tbl   => l_rev_component_tbl
3936           ,  x_ref_designator_tbl  => l_ref_designator_tbl
3937           ,  x_sub_component_tbl   => l_sub_component_tbl
3938           ,  x_rev_operation_tbl   => x_rev_operation_tbl
3939           ,  x_rev_op_resource_tbl => x_rev_op_resource_tbl
3940           ,  x_rev_sub_resource_tbl=> x_rev_sub_resource_tbl
3941           ) ;
3942        END IF;
3943 
3944        IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Entity validation completed with '
3945              || l_return_Status || ' proceeding for database writes . . . ') ;
3946        END IF;
3947 
3948        --
3949        -- Process Flow step 20 : Database Writes
3950        --
3951        IF l_rev_operation_rec.transaction_type = BOM_Rtg_Globals.G_OPR_CANCEL
3952        THEN
3953 
3954 IF BOM_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
3955 ('Operatin Sequence: Perform Cancel Operation . . .') ;
3956 END IF ;
3957 
3958            ENG_Globals.Cancel_Operation
3959            ( p_operation_sequence_id  => l_rev_op_unexp_rec.operation_sequence_id
3960            , p_cancel_comments        => l_rev_operation_rec.cancel_comments
3961            , p_op_seq_num             => l_rev_operation_rec.operation_sequence_number
3962            , p_user_id                => BOM_Rtg_Globals.Get_User_Id
3963            , p_login_id               => BOM_Rtg_Globals.Get_Login_Id
3964            , p_prog_id                => BOM_Rtg_Globals.Get_Prog_Id
3965            , p_prog_appid             => BOM_Rtg_Globals.Get_Prog_AppId
3966            , x_return_status          => l_return_status
3967            , x_mesg_token_tbl         => l_mesg_token_tbl
3968            ) ;
3969 
3970 IF BOM_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
3971 ('Cancel Operation is completed with return status ' || l_return_status ) ;
3972 END IF ;
3973 
3974        ELSE
3975            /*
3976            Added If condition for bug#13655045, If alternate_routing_code is not NULL
3977            then calling  ENG_Globals.Perform_Writes_For_Alt_Rtg.
3978            */
3979            IF(l_rev_operation_rec.alternate_routing_code is NULL)
3980            THEN
3981              ENG_Globals.Perform_Writes_For_Primary_Rtg
3982              (   p_rev_operation_rec       => l_rev_operation_rec
3983              ,   p_rev_op_unexp_rec        => l_rev_op_unexp_rec
3984              ,   x_mesg_token_tbl          => l_mesg_token_tbl
3985              ,   x_return_status           => l_return_status
3986              ) ;
3987            ELSE
3988              ENG_Globals.Perform_Writes_For_Alt_Rtg
3989              (   p_rev_operation_rec       => l_rev_operation_rec
3990              ,   p_rev_op_unexp_rec        => l_rev_op_unexp_rec
3991              ,   x_mesg_token_tbl          => l_mesg_token_tbl
3992              ,   x_return_status           => l_return_status
3993              ) ;
3994            END IF;
3995 
3996            IF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
3997            THEN
3998                l_other_message := 'BOM_OP_WRITES_UNEXP_SKIP';
3999                l_other_token_tbl(1).token_name := 'OP_SEQ_NUMBER';
4000                l_other_token_tbl(1).token_value :=
4001                           l_rev_operation_rec.operation_sequence_number ;
4002                RAISE EXC_UNEXP_SKIP_OBJECT ;
4003            ELSIF l_return_status ='S' AND
4004                l_mesg_token_tbl .COUNT <>0
4005            THEN
4006                ECO_Error_Handler.Log_Error
4007                (  p_rev_operation_tbl   => x_rev_operation_tbl
4008                ,  p_rev_op_resource_tbl => x_rev_op_resource_tbl
4009                ,  p_rev_sub_resource_tbl=> x_rev_sub_resource_tbl
4010                ,  p_mesg_token_tbl      => l_mesg_token_tbl
4011                ,  p_error_status        => 'W'
4012                ,  p_error_level         => Error_Handler.G_OP_LEVEL
4013                ,  p_entity_index        => I
4014                ,  x_ECO_rec             => l_ECO_rec
4015                ,  x_eco_revision_tbl    => l_eco_revision_tbl
4016                ,  x_revised_item_tbl    => l_revised_item_tbl
4017                ,  x_rev_component_tbl   => l_rev_component_tbl
4018                ,  x_ref_designator_tbl  => l_ref_designator_tbl
4019                ,  x_sub_component_tbl   => l_sub_component_tbl
4020                ,  x_rev_operation_tbl   => x_rev_operation_tbl
4021                ,  x_rev_op_resource_tbl => x_rev_op_resource_tbl
4022                ,  x_rev_sub_resource_tbl=> x_rev_sub_resource_tbl
4023                ) ;
4024            END IF;
4025 
4026            Bom_Op_Seq_Util.Perform_Writes
4027               (   p_rev_operation_rec       => l_rev_operation_rec
4028               ,   p_rev_op_unexp_rec        => l_rev_op_unexp_rec
4029               ,   p_control_rec             => Bom_Rtg_Pub.G_Default_Control_Rec
4030               ,   x_mesg_token_tbl          => l_mesg_token_tbl
4031               ,   x_return_status           => l_return_status
4032               ) ;
4033 
4034            IF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
4035            THEN
4036                l_other_message := 'BOM_OP_WRITES_UNEXP_SKIP';
4037                l_other_token_tbl(1).token_name := 'OP_SEQ_NUMBER';
4038                l_other_token_tbl(1).token_value :=
4039                           l_rev_operation_rec.operation_sequence_number ;
4040                RAISE EXC_UNEXP_SKIP_OBJECT ;
4041            ELSIF l_return_status ='S' AND
4042                l_mesg_token_tbl .COUNT <>0
4043            THEN
4044                ECO_Error_Handler.Log_Error
4045                (  p_rev_operation_tbl   => x_rev_operation_tbl
4046                ,  p_rev_op_resource_tbl => x_rev_op_resource_tbl
4047                ,  p_rev_sub_resource_tbl=> x_rev_sub_resource_tbl
4048                ,  p_mesg_token_tbl      => l_mesg_token_tbl
4049                ,  p_error_status        => 'W'
4050                ,  p_error_level         => Error_Handler.G_OP_LEVEL
4051                ,  p_entity_index        => I
4052                ,  x_ECO_rec             => l_ECO_rec
4053                ,  x_eco_revision_tbl    => l_eco_revision_tbl
4054                ,  x_revised_item_tbl    => l_revised_item_tbl
4055                ,  x_rev_component_tbl   => l_rev_component_tbl
4056                ,  x_ref_designator_tbl  => l_ref_designator_tbl
4057                ,  x_sub_component_tbl   => l_sub_component_tbl
4058                ,  x_rev_operation_tbl   => x_rev_operation_tbl
4059                ,  x_rev_op_resource_tbl => x_rev_op_resource_tbl
4060                ,  x_rev_sub_resource_tbl=> x_rev_sub_resource_tbl
4061                ) ;
4062            END IF;
4063 
4064        END IF ;
4065 
4066 
4067        IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Database writes completed with status  ' || l_return_status);
4068        END IF;
4069 
4070      /*Bug 6485168. l_process_children should be set inside the if clause. In the else set it to false
4071      END IF; -- END IF statement that checks RETURN STATUS
4072      */
4073     --  Load tables.
4074     x_rev_operation_tbl(I)          := l_rev_operation_rec;
4075 
4076     -- Indicate that children need to be processed
4077     l_process_children := TRUE;
4078 
4079      ELSE
4080 
4081      l_process_children := FALSE;
4082 
4083     END IF; -- END IF statement that checks RETURN STATUS
4084 
4085     --  For loop exception handler.
4086 
4087     EXCEPTION
4088        WHEN EXC_SEV_QUIT_RECORD THEN
4089           ECO_Error_Handler.Log_Error
4090           (  p_rev_operation_tbl       => x_rev_operation_tbl
4091           ,  p_rev_op_resource_tbl     => x_rev_op_resource_tbl
4092           ,  p_rev_sub_resource_tbl    => x_rev_sub_resource_tbl
4093           ,  p_mesg_token_tbl          => l_mesg_token_tbl
4094           ,  p_error_status            => FND_API.G_RET_STS_ERROR
4095           ,  p_error_scope             => Error_Handler.G_SCOPE_RECORD
4096           ,  p_error_level             => Error_Handler.G_OP_LEVEL
4097           ,  p_entity_index            => I
4098           ,  x_eco_rec                 => l_eco_rec
4099           ,  x_eco_revision_tbl        => l_eco_revision_tbl
4100           ,  x_revised_item_tbl        => l_revised_item_tbl
4101           ,  x_rev_component_tbl       => l_rev_component_tbl
4102           ,  x_ref_designator_tbl      => l_ref_designator_tbl
4103           ,  x_sub_component_tbl       => l_sub_component_tbl
4104           ,  x_rev_operation_tbl       => x_rev_operation_tbl
4105           ,  x_rev_op_resource_tbl     => x_rev_op_resource_tbl
4106           ,  x_rev_sub_resource_tbl    => x_rev_sub_resource_tbl
4107           ) ;
4108 
4109          l_process_children := TRUE;
4110 
4111          IF l_bo_return_status = 'S'
4112          THEN
4113             l_bo_return_status := l_return_status;
4114          END IF;
4115 
4116          x_return_status           := l_bo_return_status;
4117          x_mesg_token_tbl          := l_mesg_token_tbl ;
4118 
4119          --x_rev_operation_tbl       := l_rev_operation_tbl ;
4120          --x_rev_op_resource_tbl     := l_rev_op_resource_tbl ;
4121          --x_rev_sub_resource_tbl    := l_rev_sub_resource_tbl ;
4122 
4123 
4124       WHEN EXC_SEV_QUIT_BRANCH THEN
4125 
4126           ECO_Error_Handler.Log_Error
4127           (  p_rev_operation_tbl       => x_rev_operation_tbl
4128           ,  p_rev_op_resource_tbl     => x_rev_op_resource_tbl
4129           ,  p_rev_sub_resource_tbl    => x_rev_sub_resource_tbl
4130           ,  p_mesg_token_tbl          => l_mesg_token_tbl
4131           ,  p_error_status            => FND_API.G_RET_STS_ERROR
4132           ,  p_error_scope             => Error_Handler.G_SCOPE_RECORD
4133           ,  p_error_level             => Error_Handler.G_OP_LEVEL
4134           ,  p_entity_index            => I
4135           ,  x_eco_rec                 => l_eco_rec
4136           ,  x_eco_revision_tbl        => l_eco_revision_tbl
4137           ,  x_revised_item_tbl        => l_revised_item_tbl
4138           ,  x_rev_component_tbl       => l_rev_component_tbl
4139           ,  x_ref_designator_tbl      => l_ref_designator_tbl
4140           ,  x_sub_component_tbl       => l_sub_component_tbl
4141           ,  x_rev_operation_tbl       => x_rev_operation_tbl
4142           ,  x_rev_op_resource_tbl     => x_rev_op_resource_tbl
4143           ,  x_rev_sub_resource_tbl    => x_rev_sub_resource_tbl
4144           );
4145 
4146          l_process_children := FALSE;
4147 
4148          IF l_bo_return_status = 'S'
4149          THEN
4150             l_bo_return_status  := l_return_status;
4151          END IF;
4152 
4153          x_return_status           := l_bo_return_status;
4154          x_mesg_token_tbl          := l_mesg_token_tbl ;
4155 
4156          --x_rev_operation_tbl       := l_rev_operation_tbl ;
4157          --x_rev_op_resource_tbl     := l_rev_op_resource_tbl ;
4158          --x_rev_sub_resource_tbl    := l_rev_sub_resource_tbl ;
4159 
4160 
4161       WHEN EXC_SEV_SKIP_BRANCH THEN
4162           ECO_Error_Handler.Log_Error
4163           (  p_rev_operation_tbl       => x_rev_operation_tbl
4164           ,  p_rev_op_resource_tbl     => x_rev_op_resource_tbl
4165           ,  p_rev_sub_resource_tbl    => x_rev_sub_resource_tbl
4166           ,  p_mesg_token_tbl          => l_mesg_token_tbl
4167           ,  p_error_status            => FND_API.G_RET_STS_ERROR
4168           ,  p_error_scope             => Error_Handler.G_SCOPE_RECORD
4169           ,  p_error_level             => Error_Handler.G_OP_LEVEL
4170           ,  p_entity_index            => I
4171           ,  x_eco_rec                 => l_eco_rec
4172           ,  x_eco_revision_tbl        => l_eco_revision_tbl
4173           ,  x_revised_item_tbl        => l_revised_item_tbl
4174           ,  x_rev_component_tbl       => l_rev_component_tbl
4175           ,  x_ref_designator_tbl      => l_ref_designator_tbl
4176           ,  x_sub_component_tbl       => l_sub_component_tbl
4177           ,  x_rev_operation_tbl       => x_rev_operation_tbl
4178           ,  x_rev_op_resource_tbl     => x_rev_op_resource_tbl
4179           ,  x_rev_sub_resource_tbl    => x_rev_sub_resource_tbl
4180           ) ;
4181 
4182         l_process_children    := FALSE ;
4183         IF l_bo_return_status = 'S'
4184         THEN
4185            l_bo_return_status := l_return_status ;
4186         END IF;
4187 
4188          x_return_status           := l_bo_return_status;
4189          x_mesg_token_tbl          := l_mesg_token_tbl ;
4190 
4191          --x_rev_operation_tbl       := l_rev_operation_tbl ;
4192          --x_rev_op_resource_tbl     := l_rev_op_resource_tbl ;
4193          --x_rev_sub_resource_tbl    := l_rev_sub_resource_tbl ;
4194 
4195 
4196       WHEN EXC_SEV_QUIT_SIBLINGS THEN
4197           ECO_Error_Handler.Log_Error
4198           (  p_rev_operation_tbl       => x_rev_operation_tbl
4199           ,  p_rev_op_resource_tbl     => x_rev_op_resource_tbl
4200           ,  p_rev_sub_resource_tbl    => x_rev_sub_resource_tbl
4201           ,  p_mesg_token_tbl          => l_mesg_token_tbl
4202           ,  p_error_status            => FND_API.G_RET_STS_ERROR
4203           ,  p_error_scope             => Error_Handler.G_SCOPE_RECORD
4204           ,  p_error_level             => Error_Handler.G_OP_LEVEL
4205           ,  p_entity_index            => I
4206           ,  x_eco_rec                 => l_eco_rec
4207           ,  x_eco_revision_tbl        => l_eco_revision_tbl
4208           ,  x_revised_item_tbl        => l_revised_item_tbl
4209           ,  x_rev_component_tbl       => l_rev_component_tbl
4210           ,  x_ref_designator_tbl      => l_ref_designator_tbl
4211           ,  x_sub_component_tbl       => l_sub_component_tbl
4212           ,  x_rev_operation_tbl       => x_rev_operation_tbl
4213           ,  x_rev_op_resource_tbl     => x_rev_op_resource_tbl
4214           ,  x_rev_sub_resource_tbl    => x_rev_sub_resource_tbl
4215           ) ;
4216 
4217 
4218          l_process_children    := FALSE ;
4219          IF l_bo_return_status = 'S'
4220          THEN
4221            l_bo_return_status  := l_return_status ;
4222          END IF;
4223 
4224          x_return_status           := l_bo_return_status;
4225          x_mesg_token_tbl          := l_mesg_token_tbl ;
4226 
4227          --x_rev_operation_tbl       := l_rev_operation_tbl ;
4228          --x_rev_op_resource_tbl     := l_rev_op_resource_tbl ;
4229          --x_rev_sub_resource_tbl    := l_rev_sub_resource_tbl ;
4230 
4231 
4232 
4233       WHEN EXC_FAT_QUIT_BRANCH THEN
4234           ECO_Error_Handler.Log_Error
4235           (  p_rev_operation_tbl       => x_rev_operation_tbl
4236           ,  p_rev_op_resource_tbl     => x_rev_op_resource_tbl
4237           ,  p_rev_sub_resource_tbl    => x_rev_sub_resource_tbl
4238           ,  p_mesg_token_tbl          => l_mesg_token_tbl
4239           ,  p_error_status            => FND_API.G_RET_STS_ERROR
4240           ,  p_error_scope             => Error_Handler.G_SCOPE_RECORD
4241           ,  p_error_level             => Error_Handler.G_OP_LEVEL
4242           ,  p_entity_index            => I
4243           ,  x_eco_rec                 => l_eco_rec
4244           ,  x_eco_revision_tbl        => l_eco_revision_tbl
4245           ,  x_revised_item_tbl        => l_revised_item_tbl
4246           ,  x_rev_component_tbl       => l_rev_component_tbl
4247           ,  x_ref_designator_tbl      => l_ref_designator_tbl
4248           ,  x_sub_component_tbl       => l_sub_component_tbl
4249           ,  x_rev_operation_tbl       => x_rev_operation_tbl
4250           ,  x_rev_op_resource_tbl     => x_rev_op_resource_tbl
4251           ,  x_rev_sub_resource_tbl    => x_rev_sub_resource_tbl
4252           ) ;
4253 
4254          l_process_children    := FALSE ;
4255          x_return_status       := Error_Handler.G_STATUS_FATAL;
4256          x_mesg_token_tbl      := l_mesg_token_tbl ;
4257 
4258          --x_rev_operation_tbl       := l_rev_operation_tbl ;
4259          --x_rev_op_resource_tbl     := l_rev_op_resource_tbl ;
4260          --x_rev_sub_resource_tbl    := l_rev_sub_resource_tbl ;
4261 
4262 
4263 
4264       WHEN EXC_FAT_QUIT_SIBLINGS THEN
4265           ECO_Error_Handler.Log_Error
4266           (  p_rev_operation_tbl       => x_rev_operation_tbl
4267           ,  p_rev_op_resource_tbl     => x_rev_op_resource_tbl
4268           ,  p_rev_sub_resource_tbl    => x_rev_sub_resource_tbl
4269           ,  p_mesg_token_tbl          => l_mesg_token_tbl
4270           ,  p_error_status            => FND_API.G_RET_STS_ERROR
4271           ,  p_error_scope             => Error_Handler.G_SCOPE_RECORD
4272           ,  p_error_level             => Error_Handler.G_OP_LEVEL
4273           ,  p_entity_index            => I
4274           ,  x_eco_rec                 => l_eco_rec
4275           ,  x_eco_revision_tbl        => l_eco_revision_tbl
4276           ,  x_revised_item_tbl        => l_revised_item_tbl
4277           ,  x_rev_component_tbl       => l_rev_component_tbl
4278           ,  x_ref_designator_tbl      => l_ref_designator_tbl
4279           ,  x_sub_component_tbl       => l_sub_component_tbl
4280           ,  x_rev_operation_tbl       => x_rev_operation_tbl
4281           ,  x_rev_op_resource_tbl     => x_rev_op_resource_tbl
4282           ,  x_rev_sub_resource_tbl    => x_rev_sub_resource_tbl
4283           ) ;
4284 
4285 
4286         l_process_children    := FALSE ;
4287         x_return_status       := Error_Handler.G_STATUS_FATAL;
4288         x_mesg_token_tbl      := l_mesg_token_tbl ;
4289 
4290         --x_rev_operation_tbl       := l_rev_operation_tbl ;
4291         --x_rev_op_resource_tbl     := l_rev_op_resource_tbl ;
4292         --x_rev_sub_resource_tbl    := l_rev_sub_resource_tbl ;
4293 
4294 
4295     WHEN EXC_FAT_QUIT_OBJECT THEN
4296           ECO_Error_Handler.Log_Error
4297           (  p_rev_operation_tbl       => x_rev_operation_tbl
4298           ,  p_rev_op_resource_tbl     => x_rev_op_resource_tbl
4299           ,  p_rev_sub_resource_tbl    => x_rev_sub_resource_tbl
4300           ,  p_mesg_token_tbl          => l_mesg_token_tbl
4301           ,  p_error_status            => FND_API.G_RET_STS_ERROR
4302           ,  p_error_scope             => Error_Handler.G_SCOPE_RECORD
4303           ,  p_error_level             => Error_Handler.G_OP_LEVEL
4304           ,  p_entity_index            => I
4305           ,  x_eco_rec                 => l_eco_rec
4306           ,  x_eco_revision_tbl        => l_eco_revision_tbl
4307           ,  x_revised_item_tbl        => l_revised_item_tbl
4308           ,  x_rev_component_tbl       => l_rev_component_tbl
4309           ,  x_ref_designator_tbl      => l_ref_designator_tbl
4310           ,  x_sub_component_tbl       => l_sub_component_tbl
4311           ,  x_rev_operation_tbl       => x_rev_operation_tbl
4312           ,  x_rev_op_resource_tbl     => x_rev_op_resource_tbl
4313           ,  x_rev_sub_resource_tbl    => x_rev_sub_resource_tbl
4314           ) ;
4315 
4316          l_return_status       := 'Q';
4317          x_mesg_token_tbl      := l_mesg_token_tbl ;
4318 
4319          --x_rev_operation_tbl       := l_rev_operation_tbl ;
4320          --x_rev_op_resource_tbl     := l_rev_op_resource_tbl ;
4321          --x_rev_sub_resource_tbl    := l_rev_sub_resource_tbl ;
4322 
4323 
4324       WHEN EXC_UNEXP_SKIP_OBJECT THEN
4325           ECO_Error_Handler.Log_Error
4326           (  p_rev_operation_tbl       => x_rev_operation_tbl
4327           ,  p_rev_op_resource_tbl     => x_rev_op_resource_tbl
4328           ,  p_rev_sub_resource_tbl    => x_rev_sub_resource_tbl
4329           ,  p_mesg_token_tbl          => l_mesg_token_tbl
4330           ,  p_error_status            => Error_Handler.G_STATUS_UNEXPECTED
4331           ,  p_error_level             => Error_Handler.G_OP_LEVEL
4332           ,  p_entity_index            => I
4333           ,  p_other_status            => Error_Handler.G_STATUS_NOT_PICKED
4334           ,  p_other_message           => l_other_message
4335           ,  p_other_token_tbl         => l_other_token_tbl
4336           ,  x_eco_rec                 => l_eco_rec
4337           ,  x_eco_revision_tbl        => l_eco_revision_tbl
4338           ,  x_revised_item_tbl        => l_revised_item_tbl
4339           ,  x_rev_component_tbl       => l_rev_component_tbl
4340           ,  x_ref_designator_tbl      => l_ref_designator_tbl
4341           ,  x_sub_component_tbl       => l_sub_component_tbl
4342           ,  x_rev_operation_tbl       => x_rev_operation_tbl
4343           ,  x_rev_op_resource_tbl     => x_rev_op_resource_tbl
4344           ,  x_rev_sub_resource_tbl    => x_rev_sub_resource_tbl
4345           ) ;
4346          l_return_status       := 'U';
4347          x_mesg_token_tbl      := l_mesg_token_tbl ;
4348 
4349          --x_rev_operation_tbl       := l_rev_operation_tbl ;
4350          --x_rev_op_resource_tbl     := l_rev_op_resource_tbl ;
4351          --x_rev_sub_resource_tbl    := l_rev_sub_resource_tbl ;
4352 
4353    END ; -- END block
4354 
4355 
4356    IF l_return_status in ('Q', 'U')
4357    THEN
4358       x_return_status := l_return_status;
4359       RETURN ;
4360    END IF;
4361 
4362    IF l_process_children
4363    THEN
4364       -- Process Operation Resources that are direct children of this
4365       -- Operation
4366       Rev_Operation_Resources
4367       (   p_validation_level         => p_validation_level
4368       ,   p_change_notice            => l_rev_operation_rec.eco_name
4369       ,   p_organization_id          =>
4370                        l_rev_op_unexp_rec.organization_id
4371       ,   p_revised_item_name        =>
4372                        l_rev_operation_rec.revised_item_name
4373       ,   p_alternate_routing_code   =>
4374                        l_rev_operation_rec.alternate_routing_code    -- Uncommented for bug 13440461
4375       ,   p_operation_seq_num        =>
4376                        l_rev_operation_rec.operation_sequence_number
4377       ,   p_item_revision            =>
4378                        l_rev_operation_rec.new_revised_item_revision
4379       ,   p_effectivity_date         =>
4380                        l_rev_operation_rec.start_effective_date
4381       ,   p_routing_revision         =>
4382                        l_rev_operation_rec.new_routing_revision   -- Added by MK on 11/02/00
4383       ,   p_from_end_item_number     =>
4384                        l_rev_operation_rec.from_end_item_unit_number -- Added by MK on 11/02/0
4385       ,   p_operation_type           =>
4386                        l_rev_operation_rec.operation_type
4387       ,   p_rev_op_resource_tbl      => x_rev_op_resource_tbl
4388       ,   p_rev_sub_resource_tbl     => x_rev_sub_resource_tbl
4389       ,   x_rev_op_resource_tbl      => x_rev_op_resource_tbl
4390       ,   x_rev_sub_resource_tbl     => x_rev_sub_resource_tbl
4391       ,   x_mesg_token_tbl           => l_mesg_token_tbl
4392       ,   x_return_status            => l_return_status
4393       ) ;
4394 
4395        -- Bug 7606951. Populate l_bo_return_status if l_return_status is not S
4396        IF l_return_status <> FND_API.G_RET_STS_SUCCESS
4397        THEN
4398           l_bo_return_status := l_return_status;
4399        END IF;
4400       -- Process Substitute Operation Resources that are direct children of this
4401       -- operation
4402 
4403      Rev_Sub_Operation_Resources
4404       (   p_validation_level         => p_validation_level
4405       ,   p_change_notice            => l_rev_operation_rec.eco_name
4406       ,   p_organization_id          =>
4407                        l_rev_op_unexp_rec.organization_id
4408       ,   p_revised_item_name        =>
4409                        l_rev_operation_rec.revised_item_name
4410       ,   p_alternate_routing_code   =>
4411                        l_rev_operation_rec.alternate_routing_code    -- Uncommented for bug 13440461
4412       ,   p_operation_seq_num        =>
4413                        l_rev_operation_rec.operation_sequence_number
4414       ,   p_item_revision            =>
4415                        l_rev_operation_rec.new_revised_item_revision
4416       ,   p_effectivity_date         =>
4417                        l_rev_operation_rec.start_effective_date
4418       ,   p_routing_revision         =>
4419                        l_rev_operation_rec.new_routing_revision   -- Added by MK on 11/02/00
4420       ,   p_from_end_item_number     =>
4421                        l_rev_operation_rec.from_end_item_unit_number -- Added by MK on 11/02/00
4422       ,   p_operation_type           => l_rev_operation_rec.operation_type
4423       ,   p_rev_sub_resource_tbl         => x_rev_sub_resource_tbl
4424       ,   x_rev_sub_resource_tbl         => x_rev_sub_resource_tbl
4425       ,   x_mesg_token_tbl           => l_mesg_token_tbl
4426       ,   x_return_status            => l_return_status
4427       ) ;
4428 
4429      -- Bug 7606951. Populate l_bo_return_status if l_return_status is not S
4430      IF l_return_status <> FND_API.G_RET_STS_SUCCESS
4431      THEN
4432         l_bo_return_status := l_return_status;
4433      END IF;
4434 
4435     END IF;   -- Process children
4436    END IF;
4437    END LOOP; -- END Operation Sequences processing loop
4438 
4439    --  Load OUT parameters
4440    /*  Bug 7606951. Changed l_return_status to l_bo_return_status
4441    IF NVL(l_return_status, 'S') <> 'S' */
4442    IF NVL(l_bo_return_status, 'S') <> 'S'
4443    THEN
4444       x_return_status     := l_bo_return_status;
4445    END IF;
4446 
4447    x_mesg_token_tbl          := l_mesg_token_tbl ;
4448    --x_rev_operation_tbl       := l_rev_operation_tbl ;
4449    --x_rev_op_resource_tbl     := l_rev_op_resource_tbl ;
4450    --x_rev_sub_resource_tbl    := l_rev_sub_resource_tbl ;
4451 
4452 END Rev_Operation_Sequences ;
4453 
4454 
4455 --  L1:  The above part is for ECO enhancement
4456 
4457 
4458 --  Sub_Comps
4459 
4460 PROCEDURE Sub_Comps
4461 (   p_validation_level              IN  NUMBER
4462 ,   p_change_notice                 IN  VARCHAR2 := NULL
4463 ,   p_organization_id               IN  NUMBER := NULL
4464 ,   p_revised_item_name             IN  VARCHAR2 := NULL
4465 ,   p_alternate_bom_code            IN  VARCHAR2 := NULL  -- Bug 3991176
4466 ,   p_effectivity_date              IN  DATE := NULL
4467 ,   p_item_revision                 IN  VARCHAR2 := NULL
4468 ,   p_routing_revision              IN  VARCHAR2 := NULL -- Added by MK on 11/02/00
4469 ,   p_from_end_item_number          IN  VARCHAR2 := NULL -- Added by MK on 11/02/00
4470 ,   p_component_item_name           IN  VARCHAR2 := NULL
4471 ,   p_operation_seq_num             IN  NUMBER := NULL
4472 ,   p_sub_component_tbl             IN  BOM_BO_PUB.Sub_Component_Tbl_Type
4473 ,   x_sub_component_tbl             IN OUT NOCOPY BOM_BO_PUB.Sub_Component_Tbl_Type
4474 ,   x_Mesg_Token_Tbl                OUT NOCOPY Error_Handler.Mesg_Token_Tbl_Type
4475 ,   x_return_status                 OUT NOCOPY VARCHAR2
4476 )
4477 IS
4478 l_Mesg_Token_Tbl        Error_Handler.Mesg_Token_Tbl_Type;
4479 l_other_token_tbl       Error_Handler.Token_Tbl_Type;
4480 l_other_message         VARCHAR2(2000);
4481 l_err_text              VARCHAR2(2000);
4482 l_valid                 BOOLEAN := TRUE;
4483 l_item_parent_exists    BOOLEAN := FALSE;
4484 l_comp_parent_exists    BOOLEAN := FALSE;
4485 l_Return_Status         VARCHAR2(1);
4486 l_bo_return_status      VARCHAR2(1);
4487 l_eco_rec               ENG_Eco_PUB.Eco_Rec_Type;
4488 l_eco_revision_tbl      ENG_Eco_PUB.ECO_Revision_Tbl_Type;
4489 l_revised_item_tbl      ENG_Eco_PUB.Revised_Item_Tbl_Type;
4490 l_rev_component_tbl     BOM_BO_PUB.Rev_Component_Tbl_Type;
4491 l_ref_designator_tbl    BOM_BO_PUB.Ref_Designator_Tbl_Type;
4492 l_sub_component_rec     BOM_BO_PUB.Sub_Component_Rec_Type;
4493 --l_sub_component_tbl     BOM_BO_PUB.Sub_Component_Tbl_Type := p_sub_component_tbl;
4494 l_old_sub_component_rec BOM_BO_PUB.Sub_Component_Rec_Type;
4495 l_sub_comp_unexp_rec    BOM_BO_PUB.Sub_Comp_Unexposed_Rec_Type;
4496 l_old_sub_comp_unexp_rec BOM_BO_PUB.Sub_Comp_Unexposed_Rec_Type;
4497 l_return_value          NUMBER;
4498 l_Token_Tbl             Error_Handler.Token_Tbl_Type;
4499 
4500 l_rev_operation_tbl      Bom_Rtg_Pub.Rev_Operation_Tbl_Type;
4501 l_rev_op_resource_tbl    Bom_Rtg_Pub.Rev_Op_Resource_Tbl_Type;
4502 l_rev_sub_resource_tbl   Bom_Rtg_Pub.Rev_Sub_Resource_Tbl_Type;
4503 
4504 
4505 EXC_SEV_QUIT_RECORD     EXCEPTION;
4506 EXC_SEV_QUIT_BRANCH     EXCEPTION;
4507 EXC_SEV_QUIT_SIBLINGS   EXCEPTION;
4508 EXC_FAT_QUIT_OBJECT     EXCEPTION;
4509 EXC_FAT_QUIT_SIBLINGS   EXCEPTION;
4510 EXC_FAT_QUIT_BRANCH     EXCEPTION;
4511 EXC_UNEXP_SKIP_OBJECT   EXCEPTION;
4512 
4513 BEGIN
4514 
4515     l_return_status := 'S';
4516     l_bo_return_status := 'S';
4517 
4518     l_comp_parent_exists := FALSE;
4519     l_item_parent_exists := FALSE;
4520 
4521     --  Init local table variables.
4522 
4523     x_sub_component_tbl            := p_sub_component_tbl;
4524 
4525     l_sub_comp_unexp_rec.organization_id := ENG_GLOBALS.Get_org_id;
4526 
4527     FOR I IN 1..x_sub_component_tbl.COUNT LOOP
4528 
4529     IF (x_sub_component_tbl(I).return_status IS NULL OR
4530             x_sub_component_tbl(I).return_status = FND_API.G_MISS_CHAR) THEN
4531 
4532     BEGIN
4533 
4534         --  Load local records.
4535 
4536         l_sub_component_rec := x_sub_component_tbl(I);
4537 
4538         l_sub_component_rec.transaction_type :=
4539                 UPPER(l_sub_component_rec.transaction_type);
4540 
4541         IF p_component_item_name IS NOT NULL AND
4542            p_operation_seq_num IS NOT NULL AND
4543            p_revised_item_name IS NOT NULL AND
4544            p_effectivity_date IS NOT NULL AND
4545            p_change_notice IS NOT NULL AND
4546            p_organization_id IS NOT NULL
4547         THEN
4548                 -- revised comp parent exists
4549 
4550                 l_comp_parent_exists := TRUE;
4551         ELSIF p_revised_item_name IS NOT NULL AND
4552            p_effectivity_date IS NOT NULL AND
4553            --p_item_revision IS NOT NULL    AND   (Commented for bug 3766816 - Forward porting for bug 3747487)
4554            p_change_notice IS NOT NULL AND
4555            p_organization_id IS NOT NULL
4556         THEN
4557                 -- revised item parent exists
4558 
4559                 l_item_parent_exists := TRUE;
4560         END IF;
4561 
4562         -- Process Flow Step 2: Check if record has not yet been processed and
4563         -- that it is the child of the parent that called this procedure
4564         --
4565 
4566         IF --(l_sub_component_rec.return_status IS NULL OR
4567             --l_sub_component_rec.return_status = FND_API.G_MISS_CHAR)
4568            --AND
4569 
4570            -- Did Rev_Comps call this procedure, that is,
4571            -- if revised comp exists, then is this record a child ?
4572 
4573            ((l_comp_parent_exists AND
4574                (l_sub_component_rec.ECO_Name = p_change_notice AND
4575                 l_sub_comp_unexp_rec.organization_id = p_organization_id AND
4576                 l_sub_component_rec.start_effective_date = nvl(ENG_Default_Revised_Item.G_OLD_SCHED_DATE,p_effectivity_date) AND  -- Bug 6657209
4577                 NVL(l_sub_component_rec.new_revised_item_revision, FND_API.G_MISS_CHAR )
4578                                              =   NVL(p_item_revision, FND_API.G_MISS_CHAR ) AND
4579                 l_sub_component_rec.revised_item_name = p_revised_item_name AND
4580                 NVL(l_sub_component_rec.alternate_bom_code,'NULL') = NVL(p_alternate_bom_code,'NULL') AND -- Bug 3991176
4581                 NVL(l_sub_component_rec.new_routing_revision, FND_API.G_MISS_CHAR )
4582                                              =   NVL(p_routing_revision, FND_API.G_MISS_CHAR )     AND -- Added by MK on 11/02/00
4583                 NVL(l_sub_component_rec.from_end_item_unit_number, FND_API.G_MISS_CHAR )
4584                                              =   NVL(p_from_end_item_number, FND_API.G_MISS_CHAR ) AND -- Added by MK on 11/02/00
4585                 l_sub_component_rec.component_item_name = p_component_item_name AND
4586                 l_sub_component_rec.operation_sequence_number = p_operation_seq_num))
4587 
4588             OR
4589 
4590             -- Did Rev_Items call this procedure, that is,
4591             -- if revised item exists, then is this record a child ?
4592 
4593             (l_item_parent_exists AND
4594                (l_sub_component_rec.ECO_Name = p_change_notice AND
4595                 l_sub_comp_unexp_rec.organization_id = p_organization_id AND
4596                 l_sub_component_rec.revised_item_name = p_revised_item_name AND
4597                 NVL(l_sub_component_rec.alternate_bom_code,'NULL') = NVL(p_alternate_bom_code,'NULL') AND -- Bug 3991176
4598                 l_sub_component_rec.start_effective_date = p_effectivity_date AND
4599                 NVL(l_sub_component_rec.new_routing_revision, FND_API.G_MISS_CHAR )
4600                                              =   NVL(p_routing_revision, FND_API.G_MISS_CHAR )     AND -- Added by MK on 11/02/00
4601                 NVL(l_sub_component_rec.from_end_item_unit_number, FND_API.G_MISS_CHAR )
4602                                              =   NVL(p_from_end_item_number, FND_API.G_MISS_CHAR ) AND -- Added by MK on 11/02/0
4603                 NVL(l_sub_component_rec.new_revised_item_revision, FND_API.G_MISS_CHAR )
4604                                              =   NVL(p_item_revision, FND_API.G_MISS_CHAR ) ))
4605 
4606              OR
4607 
4608              (NOT l_comp_parent_exists AND
4609               NOT l_item_parent_exists))
4610         THEN
4611 
4612            l_return_status := FND_API.G_RET_STS_SUCCESS;
4613 
4614            l_sub_component_rec.return_status := FND_API.G_RET_STS_SUCCESS;
4615 
4616            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Processing substitite component: ' || l_sub_component_rec.substitute_component_name); END IF;
4617 
4618            -- Bug 6657209
4619            IF (l_comp_parent_exists and ENG_Default_Revised_Item.G_OLD_SCHED_DATE is not null) THEN
4620               l_sub_component_rec.start_effective_date := p_effectivity_date;
4621            END IF;
4622 
4623            -- Check if transaction_type is valid
4624            --
4625 
4626            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Check transaction_type validity'); END IF;
4627            ENG_GLOBALS.Transaction_Type_Validity
4628            (   p_transaction_type       => l_sub_component_rec.transaction_type
4629            ,   p_entity                 => 'Sub_Comps'
4630            ,   p_entity_id              => l_sub_component_rec.revised_item_name
4631            ,   x_valid                  => l_valid
4632            ,   x_Mesg_Token_Tbl         => l_Mesg_Token_Tbl
4633            );
4634 
4635            IF NOT l_valid
4636            THEN
4637                 l_return_status := Error_Handler.G_STATUS_ERROR;
4638                 RAISE EXC_SEV_QUIT_RECORD;
4639            END IF;
4640 
4641            -- Process Flow step 4(a): Convert user unique index to unique index I
4642            --
4643 
4644            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Converting user unique index to unique index I'); END IF;
4645            Bom_Val_To_Id.Sub_Component_UUI_To_UI
4646                 ( p_sub_component_rec  => l_sub_component_rec
4647                 , p_sub_comp_unexp_rec => l_sub_comp_unexp_rec
4648                 , x_sub_comp_unexp_rec => l_sub_comp_unexp_rec
4649                 , x_Mesg_Token_Tbl     => l_Mesg_Token_Tbl
4650                 , x_Return_Status      => l_return_status
4651                 );
4652 
4653            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
4654 
4655            IF l_return_status = Error_Handler.G_STATUS_ERROR
4656            THEN
4657                 RAISE EXC_SEV_QUIT_RECORD;
4658            ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
4659            THEN
4660                 l_other_message := 'BOM_SBC_UUI_UNEXP_SKIP';
4661                 l_other_token_tbl(1).token_name := 'SUBSTITUTE_ITEM_NAME';
4662                 l_other_token_tbl(1).token_value := l_sub_component_rec.substitute_component_name;
4663                 RAISE EXC_UNEXP_SKIP_OBJECT;
4664            END IF;
4665 
4666            -- Process Flow step 4(b): Convert user unique index to unique index II
4667            --
4668 
4669 
4670            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Converting user unique index to unique index II'); END IF;
4671            Bom_Val_To_Id.Sub_Component_UUI_To_UI2
4672                 ( p_sub_component_rec  => l_sub_component_rec
4673                 , p_sub_comp_unexp_rec => l_sub_comp_unexp_rec
4674                 , x_sub_comp_unexp_rec => l_sub_comp_unexp_rec
4675                 , x_Mesg_Token_Tbl     => l_Mesg_Token_Tbl
4676                 , x_other_message      => l_other_message
4677                 , x_other_token_tbl    => l_other_token_tbl
4678                 , x_Return_Status      => l_return_status
4679                 );
4680 
4681            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
4682 
4683            IF l_return_status = Error_Handler.G_STATUS_ERROR
4684            THEN
4685                 RAISE EXC_SEV_QUIT_SIBLINGS;
4686            ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
4687            THEN
4688                 l_other_message := 'BOM_SBC_UUI_UNEXP_SKIP';
4689                 l_other_token_tbl(1).token_name := 'SUBSTITUTE_ITEM_NAME';
4690                 l_other_token_tbl(1).token_value := l_sub_component_rec.substitute_component_name;
4691                 RAISE EXC_UNEXP_SKIP_OBJECT;
4692            END IF;
4693 
4694            IF Bom_Globals.Get_Debug = 'Y' THEN
4695                Error_Handler.Write_Debug('Converting user unique index to unique index II for Bill and Rev Item Seq Id');
4696            END IF;
4697            -- Added by MK on 12/03/00 to resolve ECO dependency
4698            ENG_Val_To_Id.BillAndRevitem_UUI_To_UI
4699            ( p_revised_item_name        => l_sub_component_rec.revised_item_name
4700            , p_alternate_bom_code       => l_sub_component_rec.alternate_bom_code -- Bug 3991176
4701            , p_revised_item_id          => l_sub_comp_unexp_rec.revised_item_id
4702            , p_item_revision            => l_sub_component_rec.new_revised_item_revision
4703            , p_effective_date           => l_sub_component_rec.start_effective_date
4704            , p_change_notice            => l_sub_component_rec.eco_name
4705            , p_organization_id          => l_sub_comp_unexp_rec.organization_id
4706            , p_new_routing_revision     => l_sub_component_rec.new_routing_revision
4707            , p_from_end_item_number     => l_sub_component_rec.from_end_item_unit_number
4708            , p_entity_processed         => 'SBC'
4709            , p_component_item_name      => l_sub_component_rec.component_item_name
4710            , p_component_item_id        => l_sub_comp_unexp_rec.component_item_id
4711            , p_operation_sequence_number => l_sub_component_rec.operation_sequence_number
4712            , p_rfd_sbc_name             => l_sub_component_rec.substitute_component_name
4713            , p_transaction_type         => l_sub_component_rec.transaction_type
4714            , x_revised_item_sequence_id => l_sub_comp_unexp_rec.revised_item_sequence_id
4715            , x_bill_sequence_id         => l_sub_comp_unexp_rec.bill_sequence_id
4716            , x_component_sequence_id    => l_sub_comp_unexp_rec.component_sequence_id
4717            , x_Mesg_Token_Tbl           => l_Mesg_Token_Tbl
4718            , x_other_message            => l_other_message
4719            , x_other_token_tbl          => l_other_token_tbl
4720            , x_Return_Status            => l_return_status
4721           ) ;
4722 
4723            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
4724 
4725            IF l_return_status = Error_Handler.G_STATUS_ERROR
4726            THEN
4727                 RAISE EXC_SEV_QUIT_SIBLINGS;
4728            ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
4729            THEN
4730                 l_other_message := 'BOM_SBC_UUI_UNEXP_SKIP';
4731                 l_other_token_tbl(1).token_name := 'SUBSTITUTE_ITEM_NAME';
4732                 l_other_token_tbl(1).token_value := l_sub_component_rec.substitute_component_name;
4733                 RAISE EXC_UNEXP_SKIP_OBJECT;
4734            END IF;
4735 
4736 
4737 
4738 
4739            -- Process Flow step 5: Verify Substitute Component's existence
4740            --
4741 
4742            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Check existence'); END IF;
4743            Bom_Validate_Sub_Component.Check_Existence
4744                 (  p_sub_component_rec          => l_sub_component_rec
4745                 ,  p_sub_comp_unexp_rec         => l_sub_comp_unexp_rec
4746                 ,  x_old_sub_component_rec      => l_old_sub_component_rec
4747                 ,  x_old_sub_comp_unexp_rec     => l_old_sub_comp_unexp_rec
4748                 ,  x_Mesg_Token_Tbl             => l_Mesg_Token_Tbl
4749                 ,  x_return_status              => l_Return_Status
4750                 );
4751 
4752            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
4753 
4754            IF l_return_status = Error_Handler.G_STATUS_ERROR
4755            THEN
4756                 RAISE EXC_SEV_QUIT_RECORD;
4757            ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
4758            THEN
4759                 l_other_message := 'BOM_SBC_EXS_UNEXP_SKIP';
4760                 l_other_token_tbl(1).token_name := 'SUBSTITUTE_ITEM_NAME';
4761                 l_other_token_tbl(1).token_value := l_sub_component_rec.substitute_component_name;
4762                 l_other_token_tbl(2).token_name := 'REVISED_COMPONENT_NAME';
4763                 l_other_token_tbl(2).token_value := l_sub_component_rec.component_item_name;
4764                 RAISE EXC_UNEXP_SKIP_OBJECT;
4765            END IF;
4766 
4767            -- Process Flow step 7: Is Subsitute Component record an orphan ?
4768 
4769            IF NOT l_comp_parent_exists
4770            THEN
4771 
4772                 -- Process Flow step 6: Check lineage
4773                 --
4774 
4775                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Check lineage');     END IF;
4776                 Bom_Validate_Sub_Component.Check_Lineage
4777                 (  p_sub_component_rec          => l_sub_component_rec
4778                 ,  p_sub_comp_unexp_rec         => l_sub_comp_unexp_rec
4779                 ,  x_Mesg_Token_Tbl             => l_Mesg_Token_Tbl
4780                 ,  x_return_status              => l_Return_Status
4781                 );
4782 
4783                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
4784 
4785                 IF l_return_status = Error_Handler.G_STATUS_ERROR
4786                 THEN
4787                         RAISE EXC_SEV_QUIT_BRANCH;
4788                 ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
4789                 THEN
4790                         l_other_message := 'BOM_SBC_LIN_UNEXP_SKIP';
4791                         l_other_token_tbl(1).token_name := 'SUBSTITUTE_ITEM_NAME';
4792                         l_other_token_tbl(1).token_value := l_sub_component_rec.substitute_component_name;
4793                         RAISE EXC_UNEXP_SKIP_OBJECT;
4794                 END IF;
4795 
4796                 -- Process Flow step 8(a and b): Is ECO impl/cancl, or in wkflw process ?
4797                 --
4798 
4799                 ENG_Validate_ECO.Check_Access
4800                 (  p_change_notice      => l_sub_component_rec.ECO_Name
4801                 ,  p_organization_id    => l_sub_comp_unexp_rec.organization_id
4802                 , p_Mesg_Token_Tbl      => l_Mesg_Token_Tbl
4803                 , x_Mesg_Token_Tbl      => l_Mesg_Token_Tbl
4804                 , x_Return_Status       => l_return_status
4805                 );
4806 
4807                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
4808 
4809                 IF l_return_status = Error_Handler.G_STATUS_ERROR
4810                 THEN
4811                         l_other_message := 'BOM_SBC_ECOACC_FAT_FATAL';
4812                         l_other_token_tbl(1).token_name := 'SUBSTITUTE_ITEM_NAME';
4813                         l_other_token_tbl(1).token_value := l_sub_component_rec.substitute_component_name;
4814                         l_return_status := 'F';
4815                         RAISE EXC_FAT_QUIT_OBJECT;
4816                 ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
4817                 THEN
4818                         l_other_message := 'BOM_SBC_ECOACC_UNEXP_SKIP';
4819                         l_other_token_tbl(1).token_name := 'SUBSTITUTE_ITEM_NAME';
4820                         l_other_token_tbl(1).token_value := l_sub_component_rec.substitute_component_name;
4821                         RAISE EXC_UNEXP_SKIP_OBJECT;
4822                 END IF;
4823 
4824                 -- Process Flow step 9(a and b): check that user has access to revised item
4825                 --
4826 
4827                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Check access'); END IF;
4828                 ENG_Validate_Revised_Item.Check_Access
4829                 (  p_change_notice      => l_sub_component_rec.ECO_Name
4830                 ,  p_organization_id    => l_sub_comp_unexp_rec.organization_id
4831                 ,  p_revised_item_id    => l_sub_comp_unexp_rec.revised_item_id
4832                 ,  p_new_item_revision  => l_sub_component_rec.new_revised_item_revision
4833                 ,  p_effectivity_date   => l_sub_component_rec.start_effective_date
4834                 ,  p_new_routing_revsion   => l_sub_component_rec.new_routing_revision  -- Added by MK on 11/02/00
4835                 ,  p_from_end_item_number  => l_sub_component_rec.from_end_item_unit_number -- Added by MK on 11/02/00
4836                 ,  p_revised_item_name  => l_sub_component_rec.revised_item_name
4837                 ,  p_entity_processed   => 'SBC' -- Bug 4210718
4838                 ,  p_alternate_bom_code => l_sub_component_rec.alternate_bom_code -- Bug 4210718
4839                 ,  p_Mesg_Token_Tbl     => l_Mesg_Token_Tbl
4840                 ,  x_Mesg_Token_Tbl     => l_Mesg_Token_Tbl
4841                 ,  x_return_status      => l_Return_Status
4842                 );
4843 
4844                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
4845 
4846                 IF l_return_status = Error_Handler.G_STATUS_ERROR
4847                 THEN
4848                         l_other_message := 'BOM_SBC_RITACC_FAT_FATAL';
4849                         l_other_token_tbl(1).token_name := 'SUBSTITUTE_ITEM_NAME';
4850                         l_other_token_tbl(1).token_value := l_sub_component_rec.substitute_component_name;
4851                         l_return_status := 'F';
4852                         RAISE EXC_FAT_QUIT_SIBLINGS;
4853                 ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
4854                 THEN
4855                         l_other_message := 'BOM_SBC_RITACC_UNEXP_SKIP';
4856                         l_other_token_tbl(1).token_name := 'SUBSTITUTE_ITEM_NAME';
4857                         l_other_token_tbl(1).token_value := l_sub_component_rec.substitute_component_name;
4858                         RAISE EXC_UNEXP_SKIP_OBJECT;
4859                 END IF;
4860 
4861                 -- Process Flow step 10: check that user has access to revised component
4862                 --
4863 
4864                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Check access'); END IF;
4865                 Bom_Validate_Bom_Component.Check_Access
4866                 (  p_change_notice      => l_sub_component_rec.ECO_Name
4867                 ,  p_organization_id    => l_sub_comp_unexp_rec.organization_id
4868                 ,  p_revised_item_id    => l_sub_comp_unexp_rec.revised_item_id
4869                 ,  p_new_item_revision  => l_sub_component_rec.new_revised_item_revision
4870                 ,  p_effectivity_date   => l_sub_component_rec.start_effective_date
4871                 ,  p_new_routing_revsion  => l_sub_component_rec.new_routing_revision -- Added by MK on 11/02/00
4872                 ,  p_from_end_item_number => l_sub_component_rec.from_end_item_unit_number -- Added by MK on 11/02/00
4873                 ,  p_revised_item_name  => l_sub_component_rec.revised_item_name
4874                 ,  p_component_item_id  => l_sub_comp_unexp_rec.component_item_id
4875                 ,  p_operation_seq_num  => l_sub_component_rec.operation_sequence_number
4876                 ,  p_bill_sequence_id   => l_sub_comp_unexp_rec.bill_sequence_id
4877                 ,  p_component_name     => l_sub_component_rec.component_item_name
4878                 ,  p_entity_processed   => 'SBC'
4879                 ,  p_rfd_sbc_name       => l_sub_component_rec.substitute_component_name
4880                 ,  p_Mesg_Token_Tbl     => l_Mesg_Token_Tbl
4881                 ,  x_Mesg_Token_Tbl     => l_Mesg_Token_Tbl
4882                 ,  x_return_status      => l_Return_Status
4883                 );
4884 
4885                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
4886 
4887                 IF l_return_status = Error_Handler.G_STATUS_ERROR
4888                 THEN
4889                         l_other_message := 'BOM_SBC_CMPACC_FAT_FATAL';
4890                         l_other_token_tbl(1).token_name := 'SUBSTITUTE_ITEM_NAME';
4891                         l_other_token_tbl(1).token_value := l_sub_component_rec.substitute_component_name;
4892                         l_other_token_tbl(2).token_name := 'REVISED_COMPONENT_NAME';
4893                         l_other_token_tbl(2).token_value := l_sub_component_rec.component_item_name;
4894                         l_return_status := 'F';
4895                         RAISE EXC_FAT_QUIT_SIBLINGS;
4896                 ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
4897                 THEN
4898                         l_other_message := 'BOM_SBC_CMPACC_UNEXP_SKIP';
4899                         l_other_token_tbl(1).token_name := 'SUBSTITUTE_ITEM_NAME';
4900                         l_other_token_tbl(1).token_value := l_sub_component_rec.substitute_component_name;
4901                         l_other_token_tbl(2).token_name := 'REVISED_COMPONENT_NAME';
4902                         l_other_token_tbl(2).token_value := l_sub_component_rec.component_item_name;
4903                         RAISE EXC_UNEXP_SKIP_OBJECT;
4904                 END IF;
4905 
4906                 -- Process Flow step 11: does user have access to substitute component ?
4907                 --
4908 
4909                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Check access'); END IF;
4910                 Bom_Validate_Sub_Component.Check_Access
4911                 (  p_sub_component_rec => l_sub_component_rec
4912                 ,  p_sub_comp_unexp_rec => l_sub_comp_unexp_rec
4913                 ,  x_Mesg_Token_Tbl     => l_Mesg_Token_Tbl
4914                 ,  x_return_status      => l_Return_Status
4915                 );
4916 
4917                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
4918 
4919                 IF l_return_status = Error_Handler.G_STATUS_ERROR
4920                 THEN
4921                         l_other_message := 'BOM_SBC_ACCESS_FAT_FATAL';
4922                         l_other_token_tbl(1).token_name := 'SUBSTITUTE_ITEM_NAME';
4923                         l_other_token_tbl(1).token_value := l_sub_component_rec.substitute_component_name;
4924                         l_return_status := 'F';
4925                         RAISE EXC_FAT_QUIT_BRANCH;
4926                 ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
4927                 THEN
4928                         l_other_message := 'BOM_SBC_ACCESS_UNEXP_SKIP';
4929                         l_other_token_tbl(1).token_name := 'SUBSTITUTE_ITEM_NAME';
4930                         l_other_token_tbl(1).token_value := l_sub_component_rec.substitute_component_name;
4931                         RAISE EXC_UNEXP_SKIP_OBJECT;
4932                 END IF;
4933 
4934            END IF;
4935 
4936            -- Process Flow step 12: Attribute Validation for CREATE and UPDATE
4937            --
4938 
4939            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Attribute Validation'); END IF;
4940            IF l_sub_component_rec.Transaction_Type IN
4941                 (ENG_GLOBALS.G_OPR_CREATE, ENG_GLOBALS.G_OPR_UPDATE)
4942            THEN
4943                 Bom_Validate_Sub_Component.Check_Attributes
4944                 ( x_return_status              => l_return_status
4945                 , x_Mesg_Token_Tbl             => l_Mesg_Token_Tbl
4946                 , p_sub_component_rec          => l_sub_component_rec
4947                 , p_sub_comp_unexp_rec         => l_sub_comp_unexp_rec
4948                 );
4949 
4950                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
4951 
4952                 IF l_return_status = Error_Handler.G_STATUS_ERROR
4953                 THEN
4954                    RAISE EXC_SEV_QUIT_RECORD;
4955                 ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
4956                 THEN
4957                    l_other_message := 'BOM_SBC_ATTVAL_UNEXP_SKIP';
4958                    l_other_token_tbl(1).token_name := 'SUBSTITUTE_ITEM_NAME';
4959                    l_other_token_tbl(1).token_value := l_sub_component_rec.substitute_component_name;
4960                    RAISE EXC_UNEXP_SKIP_OBJECT;
4961                 ELSIF l_return_status = 'S' AND
4962                       x_Mesg_Token_Tbl.COUNT <>0
4963                 THEN
4964                    Eco_Error_Handler.Log_Error
4965                         (  p_sub_component_tbl  => x_sub_component_tbl
4966                         ,  p_mesg_token_tbl     => l_mesg_token_tbl
4967                         ,  p_error_status       => 'W'
4968                         ,  p_error_level        => 6
4969                         ,  p_entity_index       => I
4970                         ,  x_eco_rec            => l_eco_rec
4971                         ,  x_eco_revision_tbl   => l_eco_revision_tbl
4972                         ,  x_revised_item_tbl   => l_revised_item_tbl
4973                         ,  x_rev_component_tbl  => l_rev_component_tbl
4974                         ,  x_ref_designator_tbl => l_ref_designator_tbl
4975                         ,  x_sub_component_tbl  => x_sub_component_tbl
4976                         ,  x_rev_operation_tbl   => l_rev_operation_tbl   --L1
4977                         ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl --L1
4978                         ,  x_rev_sub_resource_tbl=> l_rev_sub_resource_tbl--L1
4979                         );
4980                 END IF;
4981            END IF;
4982 
4983            IF l_sub_component_rec.Transaction_Type IN
4984                 (ENG_GLOBALS.G_OPR_UPDATE, ENG_GLOBALS.G_OPR_DELETE)
4985            THEN
4986 
4987                 -- Process flow step 13 - Populate NULL columns for Update and
4988                 -- Delete.
4989 
4990                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Populating NULL Columns'); END IF;
4991                 Bom_Default_Sub_Component.Populate_NULL_Columns
4992                 (   p_sub_component_rec         => l_sub_component_rec
4993                 ,   p_old_sub_component_rec     => l_old_sub_component_rec
4994                 ,   p_sub_comp_unexp_rec        => l_sub_comp_unexp_rec
4995                 ,   p_old_sub_comp_unexp_rec    => l_old_sub_comp_unexp_rec
4996                 ,   x_sub_component_rec         => l_sub_component_rec
4997                 ,   x_sub_comp_unexp_rec        => l_sub_comp_unexp_rec
4998                 );
4999 
5000            ELSIF l_sub_component_rec.Transaction_Type = ENG_GLOBALS.G_OPR_CREATE THEN
5001 
5002                 -- Process Flow step 14: Default missing values for Operation CREATE
5003                 --
5004 
5005                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Attribute Defaulting'); END IF;
5006                 Bom_Default_Sub_Component.Attribute_Defaulting
5007                 (   p_sub_component_rec         => l_sub_component_rec
5008                 ,   p_sub_comp_unexp_rec        => l_sub_comp_unexp_rec
5009                 ,   x_sub_component_rec         => l_sub_component_rec
5010                 ,   x_sub_comp_unexp_rec        => l_sub_comp_unexp_rec
5011                 ,   x_Mesg_Token_Tbl            => l_Mesg_Token_Tbl
5012                 ,   x_return_status             => l_return_status
5013                 );
5014 
5015                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
5016 
5017                 IF l_return_status = Error_Handler.G_STATUS_ERROR
5018                 THEN
5019                         RAISE EXC_SEV_QUIT_RECORD;
5020                 ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
5021                 THEN
5022                         l_other_message := 'BOM_SBC_ATTDEF_UNEXP_SKIP';
5023                         l_other_token_tbl(1).token_name := 'SUBSTITUTE_ITEM_NAME';
5024                         l_other_token_tbl(1).token_value := l_sub_component_rec.substitute_component_name;
5025                         RAISE EXC_UNEXP_SKIP_OBJECT;
5026                 ELSIF l_return_status ='S' AND
5027                         l_Mesg_Token_Tbl.COUNT <>0
5028                 THEN
5029                         Eco_Error_Handler.Log_Error
5030                         (  p_sub_component_tbl   => x_sub_component_tbl
5031                         ,  p_mesg_token_tbl      => l_mesg_token_tbl
5032                         ,  p_error_status        => 'W'
5033                         ,  p_error_level         => 6
5034                         ,  p_entity_index        => I
5035                         ,  x_eco_rec             => l_eco_rec
5036                         ,  x_eco_revision_tbl    => l_eco_revision_tbl
5037                         ,  x_revised_item_tbl    => l_revised_item_tbl
5038                         ,  x_rev_component_tbl   => l_rev_component_tbl
5039                         ,  x_ref_designator_tbl  => l_ref_designator_tbl
5040                         ,  x_sub_component_tbl   => x_sub_component_tbl
5041                         ,  x_rev_operation_tbl   => l_rev_operation_tbl   --L1
5042                         ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl --L1
5043                         ,  x_rev_sub_resource_tbl=> l_rev_sub_resource_tbl--L1
5044                         );
5045                 END IF;
5046            END IF;
5047 
5048            -- Process Flow step 15 - Entity Level Validation
5049            --
5050 
5051            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Entity validation'); END IF;
5052            Bom_Validate_Sub_Component.Check_Entity
5053                 (  p_sub_component_rec          => l_sub_component_rec
5054                 ,  p_sub_comp_unexp_rec         => l_sub_comp_unexp_rec
5055                 ,  x_Mesg_Token_Tbl             => l_Mesg_Token_Tbl
5056                 ,  x_return_status              => l_Return_Status
5057                 );
5058 
5059            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
5060 
5061            IF l_return_status = Error_Handler.G_STATUS_ERROR
5062            THEN
5063                 RAISE EXC_SEV_QUIT_RECORD;
5064            ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
5065            THEN
5066                 l_other_message := 'BOM_SBC_ENTVAL_UNEXP_SKIP';
5067                 l_other_token_tbl(1).token_name := 'SUBSTITUTE_ITEM_NAME';
5068                 l_other_token_tbl(1).token_value := l_sub_component_rec.substitute_component_name;
5069                 RAISE EXC_UNEXP_SKIP_OBJECT;
5070            ELSIF l_return_status ='S' AND
5071                 l_Mesg_Token_Tbl.COUNT <>0
5072            THEN
5073                 Eco_Error_Handler.Log_Error
5074                 (  p_sub_component_tbl   => x_sub_component_tbl
5075                 ,  p_mesg_token_tbl      => l_mesg_token_tbl
5076                 ,  p_error_status        => 'W'
5077                 ,  p_error_level         => 6
5078                 ,  p_entity_index        => I
5079                 ,  x_eco_rec             => l_eco_rec
5080                 ,  x_eco_revision_tbl    => l_eco_revision_tbl
5081                 ,  x_revised_item_tbl    => l_revised_item_tbl
5082                 ,  x_rev_component_tbl   => l_rev_component_tbl
5083                 ,  x_ref_designator_tbl  => l_ref_designator_tbl
5084                 ,  x_sub_component_tbl   => x_sub_component_tbl
5085                 ,  x_rev_operation_tbl   => l_rev_operation_tbl   --L1
5086                 ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl --L1
5087                 ,  x_rev_sub_resource_tbl=> l_rev_sub_resource_tbl--L1
5088                 );
5089            END IF;
5090 
5091            -- Process Flow step 16 : Database Writes
5092            --
5093 
5094            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Writing to the database'); END IF;
5095            Bom_Sub_Component_Util.Perform_Writes
5096                 (   p_sub_component_rec         => l_sub_component_rec
5097                 ,   p_sub_comp_unexp_rec        => l_sub_comp_unexp_rec
5098                 ,   x_Mesg_Token_Tbl            => l_Mesg_Token_Tbl
5099                 ,   x_return_status             => l_return_status
5100                 );
5101 
5102            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
5103 
5104            IF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
5105            THEN
5106                 l_other_message := 'BOM_SBC_WRITES_UNEXP_SKIP';
5107                 l_other_token_tbl(1).token_name := 'SUBSTITUTE_ITEM_NAME';
5108                 l_other_token_tbl(1).token_value := l_sub_component_rec.substitute_component_name;
5109                 RAISE EXC_UNEXP_SKIP_OBJECT;
5110            ELSIF l_return_status ='S' AND
5111               l_Mesg_Token_Tbl.COUNT <>0
5112            THEN
5113                 Eco_Error_Handler.Log_Error
5114                 (  p_sub_component_tbl   => x_sub_component_tbl
5115                 ,  p_mesg_token_tbl      => l_mesg_token_tbl
5116                 ,  p_error_status        => 'W'
5117                 ,  p_error_level         => 6
5118                 ,  p_entity_index        => I
5119                 ,  x_eco_rec             => l_eco_rec
5120                 ,  x_eco_revision_tbl    => l_eco_revision_tbl
5121                 ,  x_revised_item_tbl    => l_revised_item_tbl
5122                 ,  x_rev_component_tbl   => l_rev_component_tbl
5123                 ,  x_ref_designator_tbl  => l_ref_designator_tbl
5124                 ,  x_sub_component_tbl   => x_sub_component_tbl
5125                 ,  x_rev_operation_tbl   => l_rev_operation_tbl   --L1
5126                 ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl --L1
5127                 ,  x_rev_sub_resource_tbl=> l_rev_sub_resource_tbl--L1
5128                 );
5129            END IF;
5130 
5131         END IF; -- END IF statement that checks RETURN STATUS
5132 
5133         --  Load tables.
5134 
5135         x_sub_component_tbl(I)          := l_sub_component_rec;
5136 
5137     --  For loop exception handler.
5138 
5139 
5140     EXCEPTION
5141 
5142        WHEN EXC_SEV_QUIT_RECORD THEN
5143 
5144         Eco_Error_Handler.Log_Error
5145                 (  p_sub_component_tbl   => x_sub_component_tbl
5146                 ,  p_mesg_token_tbl      => l_mesg_token_tbl
5147                 ,  p_error_status        => Error_Handler.G_STATUS_ERROR
5148                 ,  p_error_scope         => Error_Handler.G_SCOPE_RECORD
5149                 ,  p_error_level         => 6
5150                 ,  p_entity_index        => I
5151                 ,  x_eco_rec             => l_eco_rec
5152                 ,  x_eco_revision_tbl    => l_eco_revision_tbl
5153                 ,  x_revised_item_tbl    => l_revised_item_tbl
5154                 ,  x_rev_component_tbl   => l_rev_component_tbl
5155                 ,  x_ref_designator_tbl  => l_ref_designator_tbl
5156                 ,  x_sub_component_tbl   => x_sub_component_tbl
5157                 ,  x_rev_operation_tbl   => l_rev_operation_tbl    --L1
5158                 ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl  --L1
5159                 ,  x_rev_sub_resource_tbl=> l_rev_sub_resource_tbl --L1
5160                 );
5161 
5162         IF l_bo_return_status = 'S'
5163         THEN
5164                 l_bo_return_status     := l_return_status;
5165         END IF;
5166         x_return_status                := l_bo_return_status;
5167         x_Mesg_Token_Tbl               := l_Mesg_Token_Tbl;
5168         --x_sub_component_tbl            := l_sub_component_tbl;
5169 
5170        WHEN EXC_SEV_QUIT_BRANCH THEN
5171 
5172         Eco_Error_Handler.Log_Error
5173                 (  p_sub_component_tbl  => x_sub_component_tbl
5174                 ,  p_mesg_token_tbl     => l_mesg_token_tbl
5175                 ,  p_error_status       => Error_Handler.G_STATUS_ERROR
5176                 ,  p_error_scope        => Error_Handler.G_SCOPE_CHILDREN
5177                 ,  p_other_status       => Error_Handler.G_STATUS_ERROR
5178                 ,  p_other_message      => l_other_message
5179                 ,  p_other_token_tbl    => l_other_token_tbl
5180                 ,  p_error_level        => 6
5181                 ,  p_entity_index       => I
5182                 ,  x_eco_rec            => l_eco_rec
5183                 ,  x_eco_revision_tbl   => l_eco_revision_tbl
5184                 ,  x_revised_item_tbl   => l_revised_item_tbl
5185                 ,  x_rev_component_tbl  => l_rev_component_tbl
5186                 ,  x_ref_designator_tbl => l_ref_designator_tbl
5187                 ,  x_sub_component_tbl  => x_sub_component_tbl
5188                 ,  x_rev_operation_tbl   => l_rev_operation_tbl   --L1
5189                 ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl --L1
5190                 ,  x_rev_sub_resource_tbl=> l_rev_sub_resource_tbl--L1
5191                 );
5192 
5193         IF l_bo_return_status = 'S'
5194         THEN
5195                 l_bo_return_status     := l_return_status;
5196         END IF;
5197         x_return_status                := l_bo_return_status;
5198         x_Mesg_Token_Tbl               := l_Mesg_Token_Tbl;
5199         --x_sub_component_tbl            := l_sub_component_tbl;
5200 
5201        WHEN EXC_SEV_QUIT_SIBLINGS THEN
5202 
5203         Eco_Error_Handler.Log_Error
5204                 (  p_sub_component_tbl  => x_sub_component_tbl
5205                 ,  p_mesg_token_tbl     => l_mesg_token_tbl
5206                 ,  p_error_status       => Error_Handler.G_STATUS_ERROR
5207                 ,  p_error_scope        => Error_Handler.G_SCOPE_SIBLINGS
5208                 ,  p_other_status       => Error_Handler.G_STATUS_ERROR
5209                 ,  p_other_message      => l_other_message
5210                 ,  p_other_token_tbl    => l_other_token_tbl
5211                 ,  p_error_level        => 6
5212                 ,  p_entity_index       => I
5213                 ,  x_eco_rec            => l_eco_rec
5214                 ,  x_eco_revision_tbl   => l_eco_revision_tbl
5215                 ,  x_revised_item_tbl   => l_revised_item_tbl
5216                 ,  x_rev_component_tbl  => l_rev_component_tbl
5217                 ,  x_ref_designator_tbl => l_ref_designator_tbl
5218                 ,  x_sub_component_tbl  => x_sub_component_tbl
5219                 ,  x_rev_operation_tbl   => l_rev_operation_tbl   --L1
5220                 ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl --L1
5221                 ,  x_rev_sub_resource_tbl=> l_rev_sub_resource_tbl--L1
5222                 );
5223 
5224         IF l_bo_return_status = 'S'
5225         THEN
5226                 l_bo_return_status     := l_return_status;
5227         END IF;
5228         x_return_status                := l_bo_return_status;
5229         x_Mesg_Token_Tbl               := l_Mesg_Token_Tbl;
5230         --x_sub_component_tbl            := l_sub_component_tbl;
5231 
5232         RETURN;
5233 
5234        WHEN EXC_FAT_QUIT_SIBLINGS THEN
5235 
5236         Eco_Error_Handler.Log_Error
5237                 (  p_sub_component_tbl  => x_sub_component_tbl
5238                 ,  p_mesg_token_tbl     => l_mesg_token_tbl
5239                 ,  p_error_status       => Error_Handler.G_STATUS_FATAL
5240                 ,  p_error_scope        => Error_Handler.G_SCOPE_SIBLINGS
5241                 ,  p_other_status       => Error_Handler.G_STATUS_FATAL
5242                 ,  p_other_message      => l_other_message
5243                 ,  p_other_token_tbl    => l_other_token_tbl
5244                 ,  p_error_level        => 6
5245                 ,  p_entity_index       => I
5246                 ,  x_eco_rec            => l_eco_rec
5247                 ,  x_eco_revision_tbl   => l_eco_revision_tbl
5248                 ,  x_revised_item_tbl   => l_revised_item_tbl
5249                 ,  x_rev_component_tbl  => l_rev_component_tbl
5250                 ,  x_ref_designator_tbl => l_ref_designator_tbl
5251                 ,  x_sub_component_tbl  => x_sub_component_tbl
5252                 ,  x_rev_operation_tbl   => l_rev_operation_tbl   --L1
5253                 ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl --L1
5254                 ,  x_rev_sub_resource_tbl=> l_rev_sub_resource_tbl--L1
5255                 );
5256 
5257         x_return_status                := Error_Handler.G_STATUS_FATAL;
5258         x_Mesg_Token_Tbl               := l_Mesg_Token_Tbl;
5259         --x_sub_component_tbl            := l_sub_component_tbl;
5260 
5261         RETURN;
5262 
5263        WHEN EXC_FAT_QUIT_BRANCH THEN
5264 
5265         Eco_Error_Handler.Log_Error
5266                 (  p_sub_component_tbl  => x_sub_component_tbl
5267                 ,  p_mesg_token_tbl     => l_mesg_token_tbl
5268                 ,  p_error_status       => Error_Handler.G_STATUS_FATAL
5269                 ,  p_error_scope        => Error_Handler.G_SCOPE_CHILDREN
5270                 ,  p_other_status       => Error_Handler.G_STATUS_FATAL
5271                 ,  p_other_message      => l_other_message
5272                 ,  p_other_token_tbl    => l_other_token_tbl
5273                 ,  p_error_level        => 6
5274                 ,  p_entity_index       => I
5275                 ,  x_eco_rec            => l_eco_rec
5276                 ,  x_eco_revision_tbl   => l_eco_revision_tbl
5277                 ,  x_revised_item_tbl   => l_revised_item_tbl
5278                 ,  x_rev_component_tbl  => l_rev_component_tbl
5279                 ,  x_ref_designator_tbl => l_ref_designator_tbl
5280                 ,  x_sub_component_tbl  => x_sub_component_tbl
5281                 ,  x_rev_operation_tbl   => l_rev_operation_tbl   --L1
5282                 ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl --L1
5283                 ,  x_rev_sub_resource_tbl=> l_rev_sub_resource_tbl--L1
5284                 );
5285 
5286         x_return_status                := Error_Handler.G_STATUS_FATAL;
5287         x_Mesg_Token_Tbl               := l_Mesg_Token_Tbl;
5288         --x_sub_component_tbl            := l_sub_component_tbl;
5289 
5290        WHEN EXC_FAT_QUIT_OBJECT THEN
5291 
5292         Eco_Error_Handler.Log_Error
5293                 (  p_sub_component_tbl  => x_sub_component_tbl
5294                 ,  p_mesg_token_tbl     => l_mesg_token_tbl
5295                 ,  p_error_status       => Error_Handler.G_STATUS_FATAL
5296                 ,  p_error_scope        => Error_Handler.G_SCOPE_ALL
5297                 ,  p_other_status       => Error_Handler.G_STATUS_FATAL
5298                 ,  p_other_message      => l_other_message
5299                 ,  p_other_token_tbl    => l_other_token_tbl
5300                 ,  p_error_level        => 6
5301                 ,  p_entity_index       => I
5302                 ,  x_eco_rec            => l_eco_rec
5303                 ,  x_eco_revision_tbl   => l_eco_revision_tbl
5304                 ,  x_revised_item_tbl   => l_revised_item_tbl
5305                 ,  x_rev_component_tbl  => l_rev_component_tbl
5306                 ,  x_ref_designator_tbl => l_ref_designator_tbl
5307                 ,  x_sub_component_tbl  => x_sub_component_tbl
5308                 ,  x_rev_operation_tbl   => l_rev_operation_tbl   --L1
5309                 ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl --L1
5310                 ,  x_rev_sub_resource_tbl=> l_rev_sub_resource_tbl--L1
5311                 );
5312 
5313         x_return_status                := Error_Handler.G_STATUS_FATAL;
5314         x_Mesg_Token_Tbl               := l_Mesg_Token_Tbl;
5315         --x_sub_component_tbl            := l_sub_component_tbl;
5316 
5317         l_return_status := 'Q';
5318 
5319        WHEN EXC_UNEXP_SKIP_OBJECT THEN
5320 
5321         Eco_Error_Handler.Log_Error
5322                 (  p_sub_component_tbl  => x_sub_component_tbl
5323                 ,  p_mesg_token_tbl     => l_mesg_token_tbl
5324                 ,  p_error_status       => Error_Handler.G_STATUS_UNEXPECTED
5325                 ,  p_other_status       => Error_Handler.G_STATUS_NOT_PICKED
5326                 ,  p_other_message      => l_other_message
5327                 ,  p_other_token_tbl    => l_other_token_tbl
5328                 ,  p_error_level        => 6
5329                 ,  x_ECO_rec            => l_ECO_rec
5330                 ,  x_eco_revision_tbl   => l_eco_revision_tbl
5331                 ,  x_revised_item_tbl   => l_revised_item_tbl
5332                 ,  x_rev_component_tbl  => l_rev_component_tbl
5333                 ,  x_ref_designator_tbl => l_ref_designator_tbl
5334                 ,  x_sub_component_tbl  => x_sub_component_tbl
5335                 ,  x_rev_operation_tbl   => l_rev_operation_tbl   --L1
5336                 ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl --L1
5337                 ,  x_rev_sub_resource_tbl=> l_rev_sub_resource_tbl--L1
5338                 );
5339 
5340         x_return_status                := l_bo_return_status;
5341         --x_sub_component_tbl            := l_sub_component_tbl;
5342         x_Mesg_Token_Tbl               := l_Mesg_Token_Tbl;
5343 
5344         l_return_status := 'U';
5345 
5346         END; -- END block
5347      END IF;
5348      END LOOP; -- END Substitute Components processing loop
5349 
5350     IF l_return_status in ('Q', 'U')
5351     THEN
5352         x_return_status := l_return_status;
5353         RETURN;
5354     END IF;
5355 
5356     --  Load OUT parameters
5357 
5358      x_return_status            := l_bo_return_status;
5359      --x_sub_component_tbl        := l_sub_component_tbl;
5360      x_Mesg_Token_Tbl           := l_Mesg_Token_Tbl;
5361 
5362 END Sub_Comps;
5363 
5364 
5365 --  Ref_Desgs
5366 
5367 PROCEDURE Ref_Desgs
5368 (   p_validation_level              IN  NUMBER
5369 ,   p_change_notice                 IN  VARCHAR2 := NULL
5370 ,   p_organization_id               IN  NUMBER := NULL
5371 ,   p_revised_item_name             IN  VARCHAR2 := NULL
5372 ,   p_alternate_bom_code            IN  VARCHAR2 := NULL  -- Bug 3991176
5373 ,   p_effectivity_date              IN  DATE := NULL
5374 ,   p_item_revision                 IN  VARCHAR2 := NULL
5375 ,   p_routing_revision              IN  VARCHAR2 := NULL -- Added by MK on 11/02/00
5376 ,   p_from_end_item_number          IN  VARCHAR2 := NULL -- Added by MK on 11/02/00
5377 ,   p_component_item_name           IN  VARCHAR2 := NULL
5378 ,   p_operation_seq_num             IN  NUMBER := NULL
5379 ,   p_ref_designator_tbl            IN  BOM_BO_PUB.Ref_Designator_Tbl_Type
5380 ,   p_sub_component_tbl             IN  BOM_BO_PUB.Sub_Component_Tbl_Type
5381 ,   x_ref_designator_tbl            IN OUT NOCOPY BOM_BO_PUB.Ref_Designator_Tbl_Type
5382 ,   x_sub_component_tbl             IN OUT NOCOPY BOM_BO_PUB.Sub_Component_Tbl_Type
5383 ,   x_Mesg_Token_Tbl                OUT NOCOPY Error_Handler.Mesg_Token_Tbl_Type
5384 ,   x_return_status                 OUT NOCOPY VARCHAR2
5385 )
5386 IS
5387 l_Mesg_Token_Tbl        Error_Handler.Mesg_Token_Tbl_Type;
5388 l_other_token_tbl       Error_Handler.Token_Tbl_Type;
5389 l_other_message         VARCHAR2(2000);
5390 l_err_text              VARCHAR2(2000);
5391 l_valid                 BOOLEAN := TRUE;
5392 l_item_parent_exists    BOOLEAN := FALSE;
5393 l_comp_parent_exists    BOOLEAN := FALSE;
5394 l_Return_Status         VARCHAR2(1);
5395 l_bo_return_status      VARCHAR2(1);
5396 l_eco_rec               ENG_Eco_PUB.Eco_Rec_Type;
5397 l_eco_revision_tbl      ENG_Eco_PUB.ECO_Revision_Tbl_Type;
5398 l_revised_item_tbl      ENG_Eco_PUB.Revised_Item_Tbl_Type;
5399 l_rev_component_tbl     BOM_BO_PUB.Rev_Component_Tbl_Type;
5400 l_ref_designator_rec    BOM_BO_PUB.Ref_Designator_Rec_Type;
5401 --l_ref_designator_tbl    BOM_BO_PUB.Ref_Designator_Tbl_Type := p_ref_designator_tbl;
5402 l_old_ref_designator_rec BOM_BO_PUB.Ref_Designator_Rec_Type;
5403 l_ref_desg_unexp_rec    BOM_BO_PUB.Ref_Desg_Unexposed_Rec_Type;
5404 l_old_ref_desg_unexp_rec BOM_BO_PUB.Ref_Desg_Unexposed_Rec_Type;
5405 --l_sub_component_tbl     BOM_BO_PUB.Sub_Component_Tbl_Type := p_sub_component_tbl;
5406 l_return_value          NUMBER;
5407 l_Token_Tbl             Error_Handler.Token_Tbl_Type;
5408 
5409 l_rev_operation_tbl      Bom_Rtg_Pub.Rev_Operation_Tbl_Type;
5410 l_rev_op_resource_tbl    Bom_Rtg_Pub.Rev_Op_Resource_Tbl_Type;
5411 l_rev_sub_resource_tbl   Bom_Rtg_Pub.Rev_Sub_Resource_Tbl_Type;
5412 
5413 EXC_SEV_QUIT_RECORD     EXCEPTION;
5414 EXC_SEV_QUIT_BRANCH     EXCEPTION;
5415 EXC_SEV_QUIT_SIBLINGS   EXCEPTION;
5416 EXC_FAT_QUIT_OBJECT     EXCEPTION;
5417 EXC_FAT_QUIT_SIBLINGS   EXCEPTION;
5418 EXC_UNEXP_SKIP_OBJECT   EXCEPTION;
5419 
5420 BEGIN
5421 
5422     --  Init local table variables.
5423 
5424     l_return_status := 'S';
5425     l_bo_return_status := 'S';
5426 
5427     x_ref_designator_tbl           := p_ref_designator_tbl;
5428     x_sub_component_tbl            := p_sub_component_tbl;
5429 
5430     l_ref_desg_unexp_rec.organization_id := ENG_GLOBALS.Get_org_id;
5431 
5432 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Within processing Ref Designators . . . '); END IF;
5433 
5434 
5435     FOR I IN 1..x_ref_designator_tbl.COUNT LOOP
5436     IF (x_ref_designator_tbl(I).return_status IS NULL OR
5437          x_ref_designator_tbl(I).return_status = FND_API.G_MISS_CHAR) THEN
5438 
5439     BEGIN
5440 
5441         --  Load local records.
5442 
5443         l_ref_designator_rec := x_ref_designator_tbl(I);
5444 
5445         l_ref_designator_rec.transaction_type :=
5446                 UPPER(l_ref_designator_rec.transaction_type);
5447 
5448 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Processing Ref Designator . . . ' || l_ref_designator_rec.reference_designator_name || 'at count ' || to_char(i)); END IF;
5449 
5450         IF p_component_item_name IS NOT NULL AND
5451            p_operation_seq_num IS NOT NULL AND
5452            p_revised_item_name IS NOT NULL AND
5453            p_effectivity_date IS NOT NULL AND
5454            p_change_notice IS NOT NULL AND
5455            p_organization_id IS NOT NULL
5456         THEN
5457                 -- revised comp parent exists
5458 
5459                 l_comp_parent_exists := TRUE;
5460 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Called by Rev_Comps . . .'); END IF;
5461 
5462         ELSIF p_revised_item_name IS NOT NULL AND
5463            p_effectivity_date IS NOT NULL AND
5464            --p_item_revision IS NOT NULL AND	(Commented for bug 3766816 - Forward porting for bug 3747487)
5465            p_change_notice IS NOT NULL AND
5466            p_organization_id IS NOT NULL
5467         THEN
5468                 -- revised item parent exists
5469 
5470                 l_item_parent_exists := TRUE;
5471 
5472 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Called by Rev_Items . . .'); END IF;
5473 
5474         END IF;
5475 
5476         -- Process Flow Step 2: Check if record has not yet been processed and
5477         -- that it is the child of the parent that called this procedure
5478         --
5479 
5480 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
5481                         ('ECO Name: ' || p_change_notice ||
5482                          ' Org     : ' || p_organization_id ||
5483                          ' Eff. Dt : ' || to_char(p_effectivity_date) ||
5484                          ' Revision: ' || p_item_revision ||
5485                          ' Rev Item: ' || p_revised_item_name ||
5486                          ' Rev Comp: ' || p_component_item_name ||
5487                          ' Op. Seq : ' || p_operation_seq_num); END IF;
5488 
5489         IF --(l_ref_designator_rec.return_status IS NULL OR
5490             --l_ref_designator_rec.return_status = FND_API.G_MISS_CHAR)
5491            --AND
5492 
5493            -- Did Rev_Comps call this procedure, that is,
5494            -- if revised comp exists, then is this record a child ?
5495 
5496            ((l_comp_parent_exists AND
5497                (l_ref_designator_rec.ECO_Name = p_change_notice AND
5498                 l_ref_desg_unexp_rec.organization_id = p_organization_id AND
5499                 l_ref_designator_rec.start_effective_date = nvl(ENG_Default_Revised_Item.G_OLD_SCHED_DATE,p_effectivity_date) AND -- bug 6657209
5500                 NVL(l_ref_designator_rec.new_revised_item_revision, FND_API.G_MISS_CHAR )
5501                                              =   NVL(p_item_revision, FND_API.G_MISS_CHAR )     AND
5502                 NVL(l_ref_designator_rec.new_routing_revision, FND_API.G_MISS_CHAR )
5503                                              =   NVL(p_routing_revision, FND_API.G_MISS_CHAR )  AND -- Added by MK on 11/02/00
5504                 NVL(l_ref_designator_rec.from_end_item_unit_number, FND_API.G_MISS_CHAR )
5505                                              =   NVL(p_from_end_item_number, FND_API.G_MISS_CHAR )  AND -- Added by MK on 11/02/00
5506                 l_ref_designator_rec.revised_item_name = p_revised_item_name AND
5507                 NVL(l_ref_designator_rec.alternate_bom_code,'NULL') = NVL(p_alternate_bom_code,'NULL') AND -- Bug 3991176
5508                 l_ref_designator_rec.component_item_name = p_component_item_name AND
5509                 l_ref_designator_rec.operation_sequence_number = p_operation_seq_num))
5510 
5511              OR
5512 
5513              -- Did Rev_Items call this procedure, that is,
5514              -- if revised item exists, then is this record a child ?
5515 
5516              (l_item_parent_exists AND
5517                (l_ref_designator_rec.ECO_Name = p_change_notice AND
5518                 l_ref_desg_unexp_rec.organization_id = p_organization_id AND
5519                 l_ref_designator_rec.revised_item_name = p_revised_item_name AND
5520                 NVL(l_ref_designator_rec.alternate_bom_code,'NULL') = NVL(p_alternate_bom_code,'NULL') AND -- Bug 3991176
5521                 l_ref_designator_rec.start_effective_date = p_effectivity_date AND
5522                 NVL(l_ref_designator_rec.new_routing_revision, FND_API.G_MISS_CHAR )
5523                                              =   NVL(p_routing_revision, FND_API.G_MISS_CHAR )  AND -- Added by MK on 11/02/00
5524                 NVL(l_ref_designator_rec.from_end_item_unit_number, FND_API.G_MISS_CHAR )
5525                                              =   NVL(p_from_end_item_number, FND_API.G_MISS_CHAR )  AND -- Added by MK on 11/02/00
5526                 NVL(l_ref_designator_rec.new_revised_item_revision, FND_API.G_MISS_CHAR )
5527                                              =   NVL(p_item_revision, FND_API.G_MISS_CHAR ) ))
5528 
5529              OR
5530 
5531              (NOT l_item_parent_exists AND
5532               NOT l_comp_parent_exists))
5533         THEN
5534 
5535            l_return_status := FND_API.G_RET_STS_SUCCESS;
5536 
5537            l_ref_designator_rec.return_status := FND_API.G_RET_STS_SUCCESS;
5538 
5539            -- Bug 6657209
5540            IF (l_comp_parent_exists and ENG_Default_Revised_Item.G_OLD_SCHED_DATE is not null) THEN
5541               l_ref_designator_rec.start_effective_date := p_effectivity_date;
5542            END IF;
5543 
5544            -- Check if transaction_type is valid
5545            --
5546 
5547           IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Check transaction_type validity'); END IF;
5548 
5549 
5550 	   ENG_GLOBALS.Transaction_Type_Validity
5551            (   p_transaction_type       => l_ref_designator_rec.transaction_type
5552            ,   p_entity                 => 'Ref_Desgs'
5553            ,   p_entity_id              => l_ref_designator_rec.revised_item_name
5554            ,   x_valid                  => l_valid
5555            ,   x_Mesg_Token_Tbl         => l_Mesg_Token_Tbl
5556            );
5557 
5558            IF NOT l_valid
5559            THEN
5560                 l_return_status := Error_Handler.G_STATUS_ERROR;
5561                 RAISE EXC_SEV_QUIT_RECORD;
5562            END IF;
5563 
5564            -- Process Flow step 4(a): Convert user unique index to unique index I
5565            --
5566 
5567            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Converting user unique index to unique index I'); END IF;
5568            Bom_Val_To_Id.Ref_Designator_UUI_To_UI
5569                 ( p_ref_designator_rec => l_ref_designator_rec
5570                 , p_ref_desg_unexp_rec => l_ref_desg_unexp_rec
5571                 , x_ref_desg_unexp_rec => l_ref_desg_unexp_rec
5572                 , x_Mesg_Token_Tbl     => l_Mesg_Token_Tbl
5573                 , x_Return_Status      => l_return_status
5574                 );
5575 
5576            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
5577 
5578            IF l_return_status = Error_Handler.G_STATUS_ERROR
5579            THEN
5580                 RAISE EXC_SEV_QUIT_RECORD;
5581            ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
5582            THEN
5583                 l_other_message := 'BOM_RFD_UUI_UNEXP_SKIP';
5584                 l_other_token_tbl(1).token_name := 'REFERENCE_DESIGNATOR_NAME';
5585                 l_other_token_tbl(1).token_value := l_ref_designator_rec.reference_designator_name;
5586                 RAISE EXC_UNEXP_SKIP_OBJECT;
5587            END IF;
5588 
5589            -- Process Flow step 4(b): Convert user unique index to unique index II
5590            --
5591 
5592            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Converting user unique index to unique index II'); END IF;
5593            Bom_Val_To_Id.Ref_Designator_UUI_To_UI2
5594                 ( p_ref_designator_rec => l_ref_designator_rec
5595                 , p_ref_desg_unexp_rec => l_ref_desg_unexp_rec
5596                 , x_ref_desg_unexp_rec => l_ref_desg_unexp_rec
5597                 , x_Mesg_Token_Tbl     => l_Mesg_Token_Tbl
5598                 , x_other_message      => l_other_message
5599                 , x_other_token_tbl    => l_other_token_tbl
5600                 , x_Return_Status      => l_return_status
5601                 );
5602 
5603            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
5604 
5605            IF l_return_status = Error_Handler.G_STATUS_ERROR
5606            THEN
5607                 RAISE EXC_SEV_QUIT_SIBLINGS;
5608            ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
5609            THEN
5610                 l_other_message := 'BOM_RFD_UUI_UNEXP_SKIP';
5611                 l_other_token_tbl(1).token_name := 'REFERENCE_DESIGNATOR_NAME';
5612                 l_other_token_tbl(1).token_value := l_ref_designator_rec.reference_designator_name;
5613                 RAISE EXC_UNEXP_SKIP_OBJECT;
5614            END IF;
5615 
5616 
5617            IF Bom_Globals.Get_Debug = 'Y' THEN
5618            Error_Handler.Write_Debug('Converting user unique index to unique index II for Bill and Rev Item Seq Id');
5619            END IF;
5620 
5621            -- Added by MK on 12/03/00 to resolve ECO dependency
5622            ENG_Val_To_Id.BillAndRevitem_UUI_To_UI
5623            ( p_revised_item_name        => l_ref_designator_rec.revised_item_name
5624            , p_alternate_bom_code       => l_ref_designator_rec.alternate_bom_code -- Bug 3991176
5625            , p_revised_item_id          => l_ref_desg_unexp_rec.revised_item_id
5626            , p_item_revision            => l_ref_designator_rec.new_revised_item_revision
5627            , p_effective_date           => l_ref_designator_rec.start_effective_date
5628            , p_change_notice            => l_ref_designator_rec.eco_name
5629            , p_organization_id          => l_ref_desg_unexp_rec.organization_id
5630            , p_new_routing_revision     => l_ref_designator_rec.new_routing_revision
5631            , p_from_end_item_number     => l_ref_designator_rec.from_end_item_unit_number
5632            , p_entity_processed         => 'RFD'
5633            , p_component_item_name      => l_ref_designator_rec.component_item_name
5634            , p_component_item_id        => l_ref_desg_unexp_rec.component_item_id
5635            , p_operation_sequence_number => l_ref_designator_rec.operation_sequence_number
5636            , p_rfd_sbc_name             => l_ref_designator_rec.reference_designator_name
5637            , p_transaction_type         => l_ref_designator_rec.transaction_type
5638            , x_revised_item_sequence_id => l_ref_desg_unexp_rec.revised_item_sequence_id
5639            , x_bill_sequence_id         => l_ref_desg_unexp_rec.bill_sequence_id
5640            , x_component_sequence_id    => l_ref_desg_unexp_rec.component_sequence_id
5641            , x_Mesg_Token_Tbl           => l_Mesg_Token_Tbl
5642            , x_other_message            => l_other_message
5643            , x_other_token_tbl          => l_other_token_tbl
5644            , x_Return_Status            => l_return_status
5645           ) ;
5646 
5647 
5648            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
5649 
5650            IF l_return_status = Error_Handler.G_STATUS_ERROR
5651            THEN
5652                 RAISE EXC_SEV_QUIT_SIBLINGS;
5653            ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
5654            THEN
5655                 l_other_message := 'BOM_RFD_UUI_UNEXP_SKIP';
5656                 l_other_token_tbl(1).token_name := 'REFERENCE_DESIGNATOR_NAME';
5657                 l_other_token_tbl(1).token_value := l_ref_designator_rec.reference_designator_name;
5658                 RAISE EXC_UNEXP_SKIP_OBJECT;
5659            END IF;
5660 
5661 
5662            -- Process Flow step 5: Verify Reference Designator's existence
5663            --
5664 
5665            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Check existence'); END IF;
5666            Bom_Validate_Ref_Designator.Check_Existence
5667                 (  p_ref_designator_rec         => l_ref_designator_rec
5668                 ,  p_ref_desg_unexp_rec         => l_ref_desg_unexp_rec
5669                 ,  x_old_ref_designator_rec     => l_old_ref_designator_rec
5670                 ,  x_old_ref_desg_unexp_rec     => l_old_ref_desg_unexp_rec
5671                 ,  x_Mesg_Token_Tbl             => l_Mesg_Token_Tbl
5672                 ,  x_return_status              => l_Return_Status
5673                 );
5674 
5675            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
5676 
5677            IF l_return_status = Error_Handler.G_STATUS_ERROR
5678            THEN
5679                 RAISE EXC_SEV_QUIT_RECORD;
5680            ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
5681            THEN
5682                 l_other_message := 'BOM_RFD_EXS_UNEXP_SKIP';
5683                 l_other_token_tbl(1).token_name := 'REFERENCE_DESIGNATOR_NAME';
5684                 l_other_token_tbl(1).token_value := l_ref_designator_rec.reference_designator_name;
5685                 l_other_token_tbl(2).token_name := 'REVISED_COMPONENT_NAME';
5686                 l_other_token_tbl(2).token_value := l_ref_designator_rec.component_item_name;
5687                 RAISE EXC_UNEXP_SKIP_OBJECT;
5688            END IF;
5689 
5690            -- Process Flow step 6: Is Revised Component record an orphan ?
5691 
5692            IF NOT l_comp_parent_exists
5693            THEN
5694 
5695                 -- Process Flow step 7: Check lineage
5696                 --
5697 
5698                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Check lineage');     END IF;
5699                 Bom_Validate_Ref_Designator.Check_Lineage
5700                 (  p_ref_designator_rec         => l_ref_designator_rec
5701                 ,  p_ref_desg_unexp_rec         => l_ref_desg_unexp_rec
5702                 ,  x_Mesg_Token_Tbl             => l_Mesg_Token_Tbl
5703                 ,  x_return_status              => l_Return_Status
5704                 );
5705 
5706                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
5707 
5708                 IF l_return_status = Error_Handler.G_STATUS_ERROR
5709                 THEN
5710                         RAISE EXC_SEV_QUIT_BRANCH;
5711                 ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
5712                 THEN
5713                         l_other_message := 'BOM_RFD_LIN_UNEXP_SKIP';
5714                         l_other_token_tbl(1).token_name := 'REFERENCE_DESIGNATOR_NAME';
5715                         l_other_token_tbl(1).token_value := l_ref_designator_rec.reference_designator_name;
5716                         RAISE EXC_UNEXP_SKIP_OBJECT;
5717                 END IF;
5718 
5719                 -- Process Flow step 8(a and b): Is ECO impl/cancl, or in wkflw process ?
5720                 --
5721 
5722                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug(' Check ECO access'); END IF;
5723 
5724                 ENG_Validate_ECO.Check_Access
5725                 ( p_change_notice       => l_ref_designator_rec.ECO_Name
5726                 , p_organization_id     => l_ref_desg_unexp_rec.organization_id
5727                 , p_Mesg_Token_Tbl      => l_Mesg_Token_Tbl
5728                 , x_Mesg_Token_Tbl      => l_Mesg_Token_Tbl
5729                 , x_Return_Status       => l_return_status
5730                 );
5731 
5732                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
5733 
5734                 IF l_return_status = Error_Handler.G_STATUS_ERROR
5735                 THEN
5736                         l_other_message := 'BOM_RFD_ECOACC_FAT_FATAL';
5737                         l_other_token_tbl(1).token_name := 'REFERENCE_DESIGNATOR_NAME';
5738                         l_other_token_tbl(1).token_value := l_ref_designator_rec.reference_designator_name;
5739                         l_return_status := 'F';
5740                         RAISE EXC_FAT_QUIT_OBJECT;
5741                 ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
5742                 THEN
5743                         l_other_message := 'BOM_RFD_ECOACC_UNEXP_SKIP';
5744                         l_other_token_tbl(1).token_name := 'REFERENCE_DESIGNATOR_NAME';
5745                         l_other_token_tbl(1).token_value := l_ref_designator_rec.reference_designator_name;
5746                         RAISE EXC_UNEXP_SKIP_OBJECT;
5747                 END IF;
5748 
5749                 -- Process Flow step 9(a and b): check that user has access to revised item
5750                 --
5751 
5752                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Check access'); END IF;
5753                 ENG_Validate_Revised_Item.Check_Access
5754                 (  p_change_notice      => l_ref_designator_rec.ECO_Name
5755                 ,  p_organization_id    => l_ref_desg_unexp_rec.organization_id
5756                 ,  p_revised_item_id    => l_ref_desg_unexp_rec.revised_item_id
5757                 ,  p_new_item_revision  => l_ref_designator_rec.new_revised_item_revision
5758                 ,  p_effectivity_date   => l_ref_designator_rec.start_effective_date
5759                 ,  p_new_routing_revsion  => l_ref_designator_rec.new_routing_revision -- Added by MK on 11/02/00
5760                 ,  p_from_end_item_number => l_ref_designator_rec.from_end_item_unit_number -- Added by MK on 11/02/00
5761                 ,  p_revised_item_name  => l_ref_designator_rec.revised_item_name
5762                 ,  p_entity_processed   => 'RFD' -- Bug 4210718
5763                 ,  p_alternate_bom_code => l_ref_designator_rec.alternate_bom_code -- Bug 4210718
5764                 ,  p_Mesg_Token_Tbl     => l_Mesg_Token_Tbl
5765                 ,  x_Mesg_Token_Tbl     => l_Mesg_Token_Tbl
5766                 ,  x_return_status      => l_Return_Status
5767                 );
5768 
5769                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
5770 
5771                 IF l_return_status = Error_Handler.G_STATUS_ERROR
5772                 THEN
5773                         l_other_message := 'BOM_RFD_RITACC_FAT_FATAL';
5774                         l_other_token_tbl(1).token_name := 'REFERENCE_DESIGNATOR_NAME';
5775                         l_other_token_tbl(1).token_value := l_ref_designator_rec.reference_designator_name;
5776                         l_return_status := 'F';
5777                         RAISE EXC_FAT_QUIT_SIBLINGS;
5778                 ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
5779                 THEN
5780                         l_other_message := 'BOM_RFD_RITACC_UNEXP_SKIP';
5781                         l_other_token_tbl(1).token_name := 'REFERENCE_DESIGNATOR_NAME';
5782                         l_other_token_tbl(1).token_value := l_ref_designator_rec.reference_designator_name;
5783                         RAISE EXC_UNEXP_SKIP_OBJECT;
5784                 END IF;
5785 
5786                 -- Process Flow step 10: check that user has access to revised component
5787                 --
5788 
5789                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Check access'); END IF;
5790                 Bom_Validate_Bom_Component.Check_Access
5791                 (  p_change_notice      => l_ref_designator_rec.ECO_Name
5792                 ,  p_organization_id    => l_ref_desg_unexp_rec.organization_id
5793                 ,  p_revised_item_id    => l_ref_desg_unexp_rec.revised_item_id
5794                 ,  p_new_item_revision  => l_ref_designator_rec.new_revised_item_revision
5795                 ,  p_effectivity_date   => l_ref_designator_rec.start_effective_date
5796                 ,  p_new_routing_revsion  => l_ref_designator_rec.new_routing_revision -- Added by MK on 11/02/00
5797                 ,  p_from_end_item_number => l_ref_designator_rec.from_end_item_unit_number -- Added by MK on 11/02/00
5798                 ,  p_revised_item_name  => l_ref_designator_rec.revised_item_name
5799                 ,  p_component_item_id  => l_ref_desg_unexp_rec.component_item_id
5800                 ,  p_operation_seq_num  => l_ref_designator_rec.operation_sequence_number
5801                 ,  p_bill_sequence_id   => l_ref_desg_unexp_rec.bill_sequence_id
5802                 ,  p_component_name     => l_ref_designator_rec.component_item_name
5803                 ,  p_entity_processed   => 'RFD'
5804                 ,  p_rfd_sbc_name       => l_ref_designator_rec.reference_designator_name
5805                 ,  p_Mesg_Token_Tbl     => l_Mesg_Token_Tbl
5806                 ,  x_Mesg_Token_Tbl     => l_Mesg_Token_Tbl
5807                 ,  x_return_status      => l_Return_Status
5808                 );
5809 
5810                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
5811 
5812                 IF l_return_status = Error_Handler.G_STATUS_ERROR
5813                 THEN
5814                         l_other_message := 'BOM_RFD_CMPACC_FAT_FATAL';
5815                         l_other_token_tbl(1).token_name := 'REFERENCE_DESIGNATOR_NAME';
5816                         l_other_token_tbl(1).token_value := l_ref_designator_rec.reference_designator_name;
5817                         l_return_status := 'F';
5818                         RAISE EXC_FAT_QUIT_SIBLINGS;
5819                 ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
5820                 THEN
5821                         l_other_message := 'BOM_RFD_CMPACC_UNEXP_SKIP';
5822                         l_other_token_tbl(1).token_name := 'REFERENCE_DESIGNATOR_NAME';
5823                         l_other_token_tbl(1).token_value := l_ref_designator_rec.reference_designator_name;
5824                         RAISE EXC_UNEXP_SKIP_OBJECT;
5825                 END IF;
5826 
5827                 -- Process Flow step 8(b): check that user has access to ECO
5828                 --
5829 
5830                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Check access'); END IF;
5831                 Bom_Validate_Ref_Designator.Check_Access
5832                 (  p_ref_designator_rec => l_ref_designator_rec
5833                 ,  p_ref_desg_unexp_rec => l_ref_desg_unexp_rec
5834                 ,  x_Mesg_Token_Tbl     => l_Mesg_Token_Tbl
5835                 ,  x_return_status      => l_Return_Status
5836                 );
5837 
5838                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
5839 
5840                 IF l_return_status = Error_Handler.G_STATUS_ERROR
5841                 THEN
5842                         l_return_status := 'F';
5843                         RAISE EXC_FAT_QUIT_SIBLINGS;
5844                 ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
5845                 THEN
5846                         RAISE EXC_UNEXP_SKIP_OBJECT;
5847                 END IF;
5848 
5849            END IF;
5850 
5851            IF l_ref_designator_rec.transaction_type IN
5852                 (ENG_GLOBALS.G_OPR_UPDATE, ENG_GLOBALS.G_OPR_DELETE)
5853            THEN
5854 
5855                 -- Process flow step 11 - Populate NULL columns for Update and
5856                 -- Delete.
5857 
5858                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Populating NULL Columns'); END IF;
5859                 Bom_Default_Ref_Designator.Populate_NULL_Columns
5860                 (   p_ref_designator_rec        => l_ref_designator_rec
5861                 ,   p_old_ref_designator_rec    => l_old_ref_designator_rec
5862                 ,   p_ref_desg_unexp_rec        => l_ref_desg_unexp_rec
5863                 ,   p_old_ref_desg_unexp_rec    => l_old_ref_desg_unexp_rec
5864                 ,   x_ref_designator_rec        => l_ref_designator_rec
5865                 ,   x_ref_desg_unexp_rec        => l_ref_desg_unexp_rec
5866                 );
5867 
5868            END IF;
5869 
5870            -- Process Flow step 12 - Entity Level Validation
5871            -- Added Check_Entity_Delete by MK on 11/14/00
5872            --
5873            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Entity validation'); END IF;
5874 
5875            IF l_ref_designator_rec.transaction_type = 'DELETE'
5876            THEN
5877 
5878            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Calling Entity Delete validation'); END IF;
5879 
5880                 Bom_Validate_Ref_Designator.Check_Entity_Delete
5881                 (  p_ref_designator_rec         => l_ref_designator_rec
5882                 ,  p_ref_desg_unexp_rec         => l_ref_desg_unexp_rec
5883                 ,  x_Mesg_Token_Tbl             => l_Mesg_Token_Tbl
5884                 ,  x_return_status              => l_Return_Status
5885                 );
5886            ELSE
5887                 Bom_Validate_Ref_Designator.Check_Entity
5888                 (  p_ref_designator_rec         => l_ref_designator_rec
5889                 ,  p_ref_desg_unexp_rec         => l_ref_desg_unexp_rec
5890                 ,  x_Mesg_Token_Tbl             => l_Mesg_Token_Tbl
5891                 ,  x_return_status              => l_Return_Status
5892                 );
5893            END IF ;
5894 
5895            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
5896 
5897            IF l_return_status = Error_Handler.G_STATUS_ERROR
5898            THEN
5899                 RAISE EXC_SEV_QUIT_RECORD;
5900            ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
5901            THEN
5902                 l_other_message := 'BOM_RFD_ENTVAL_UNEXP_SKIP';
5903                 l_other_token_tbl(1).token_name := 'REFERENCE_DESIGNATOR_NAME';
5904                 l_other_token_tbl(1).token_value := l_ref_designator_rec.reference_designator_name;
5905                 RAISE EXC_UNEXP_SKIP_OBJECT;
5906            ELSIF l_return_status ='S' AND
5907                 l_Mesg_Token_Tbl.COUNT <>0
5908            THEN
5909                 Eco_Error_Handler.Log_Error
5910                 (  p_ref_designator_tbl => x_ref_designator_tbl
5911                 ,  p_sub_component_tbl  => x_sub_component_tbl
5912                 ,  p_mesg_token_tbl     => l_mesg_token_tbl
5913                 ,  p_error_status       => 'W'
5914                 ,  p_error_level        => 5
5915                 ,  p_entity_index       => I
5916                 ,  x_eco_rec            => l_eco_rec
5917                 ,  x_eco_revision_tbl   => l_eco_revision_tbl
5918                 ,  x_revised_item_tbl   => l_revised_item_tbl
5919                 ,  x_rev_component_tbl  => l_rev_component_tbl
5920                 ,  x_ref_designator_tbl => x_ref_designator_tbl
5921                 ,  x_sub_component_tbl  => x_sub_component_tbl
5922                 ,  x_rev_operation_tbl   => l_rev_operation_tbl   --L1
5923                 ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl --L1
5924                 ,  x_rev_sub_resource_tbl=> l_rev_sub_resource_tbl--L1
5925                 );
5926            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Log Error For Warning '); END IF;
5927            END IF;
5928 
5929            -- Process Flow step 14 : Database Writes
5930            --
5931 
5932            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Writing to the database'); END IF;
5933            Bom_Ref_Designator_Util.Perform_Writes
5934                 (   p_ref_designator_rec        => l_ref_designator_rec
5935                 ,   p_ref_desg_unexp_rec        => l_ref_desg_unexp_rec
5936                 ,   x_Mesg_Token_Tbl            => l_Mesg_Token_Tbl
5937                 ,   x_return_status             => l_return_status
5938                 );
5939 
5940            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
5941 
5942            IF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
5943            THEN
5944                 l_other_message := 'BOM_RFD_WRITES_UNEXP_SKIP';
5945                 l_other_token_tbl(1).token_name := 'REFERENCE_DESIGNATOR_NAME';
5946                 l_other_token_tbl(1).token_value := l_ref_designator_rec.reference_designator_name;
5947                 RAISE EXC_UNEXP_SKIP_OBJECT;
5948            ELSIF l_return_status ='S' AND
5949               l_Mesg_Token_Tbl.COUNT <>0
5950            THEN
5951                 Eco_Error_Handler.Log_Error
5952                 (  p_ref_designator_tbl => x_ref_designator_tbl
5953                 ,  p_sub_component_tbl  => x_sub_component_tbl
5954                 ,  p_mesg_token_tbl     => l_mesg_token_tbl
5955                 ,  p_error_status       => 'W'
5956                 ,  p_error_level        => 5
5957                 ,  p_entity_index       => I
5958                 ,  x_eco_rec            => l_eco_rec
5959                 ,  x_eco_revision_tbl   => l_eco_revision_tbl
5960                 ,  x_revised_item_tbl   => l_revised_item_tbl
5961                 ,  x_rev_component_tbl  => l_rev_component_tbl
5962                 ,  x_ref_designator_tbl => x_ref_designator_tbl
5963                 ,  x_sub_component_tbl  => x_sub_component_tbl
5964                 ,  x_rev_operation_tbl   => l_rev_operation_tbl   --L1
5965                 ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl --L1
5966                 ,  x_rev_sub_resource_tbl=> l_rev_sub_resource_tbl--L1
5967                 );
5968            END IF;
5969 
5970         END IF; -- END IF statement that checks RETURN STATUS
5971 
5972         --  Load tables.
5973 
5974         x_ref_designator_tbl(I)          := l_ref_designator_rec;
5975 
5976     --  For loop exception handler.
5977 
5978 
5979     EXCEPTION
5980 
5981        WHEN EXC_SEV_QUIT_RECORD THEN
5982 
5983         Eco_Error_Handler.Log_Error
5984                 (  p_ref_designator_tbl => x_ref_designator_tbl
5985                 ,  p_sub_component_tbl  => x_sub_component_tbl
5986                 ,  p_mesg_token_tbl     => l_mesg_token_tbl
5987                 ,  p_error_status       => Error_Handler.G_STATUS_ERROR
5988                 ,  p_error_scope        => Error_Handler.G_SCOPE_RECORD
5989                 ,  p_error_level        => 5
5990                 ,  p_entity_index       => I
5991                 ,  x_eco_rec            => l_eco_rec
5992                 ,  x_eco_revision_tbl   => l_eco_revision_tbl
5993                 ,  x_revised_item_tbl   => l_revised_item_tbl
5994                 ,  x_rev_component_tbl  => l_rev_component_tbl
5995                 ,  x_ref_designator_tbl => x_ref_designator_tbl
5996                 ,  x_sub_component_tbl  => x_sub_component_tbl
5997                 ,  x_rev_operation_tbl   => l_rev_operation_tbl   --L1
5998                 ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl --L1
5999                 ,  x_rev_sub_resource_tbl=> l_rev_sub_resource_tbl--L1
6000                 );
6001 
6002         IF l_bo_return_status = 'S'
6003         THEN
6004                 l_bo_return_status     := l_return_status;
6005         END IF;
6006         x_return_status                := l_bo_return_status;
6007         x_Mesg_Token_Tbl               := l_Mesg_Token_Tbl;
6008         --x_ref_designator_tbl           := l_ref_designator_tbl;
6009         --x_sub_component_tbl            := l_sub_component_tbl;
6010 
6011        WHEN EXC_SEV_QUIT_BRANCH THEN
6012 
6013         Eco_Error_Handler.Log_Error
6014                 (  p_ref_designator_tbl => x_ref_designator_tbl
6015                 ,  p_sub_component_tbl  => x_sub_component_tbl
6016                 ,  p_mesg_token_tbl     => l_mesg_token_tbl
6017                 ,  p_error_status       => Error_Handler.G_STATUS_ERROR
6018                 ,  p_error_scope        => Error_Handler.G_SCOPE_CHILDREN
6019                 ,  p_other_status       => Error_Handler.G_STATUS_ERROR
6020                 ,  p_other_message      => l_other_message
6021                 ,  p_other_token_tbl    => l_other_token_tbl
6022                 ,  p_error_level        => 5
6023                 ,  p_entity_index       => I
6024                 ,  x_eco_rec            => l_eco_rec
6025                 ,  x_eco_revision_tbl   => l_eco_revision_tbl
6026                 ,  x_revised_item_tbl   => l_revised_item_tbl
6027                 ,  x_rev_component_tbl  => l_rev_component_tbl
6028                 ,  x_ref_designator_tbl => x_ref_designator_tbl
6029                 ,  x_sub_component_tbl  => x_sub_component_tbl
6030                 ,  x_rev_operation_tbl   => l_rev_operation_tbl   --L1
6031                 ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl --L1
6032                 ,  x_rev_sub_resource_tbl=> l_rev_sub_resource_tbl--L1
6033                 );
6034 
6035         IF l_bo_return_status = 'S'
6036         THEN
6037                 l_bo_return_status     := l_return_status;
6038         END IF;
6039         x_return_status                := l_bo_return_status;
6040         x_Mesg_Token_Tbl               := l_Mesg_Token_Tbl;
6041         --x_ref_designator_tbl           := l_ref_designator_tbl;
6042         --x_sub_component_tbl            := l_sub_component_tbl;
6043 
6044        WHEN EXC_SEV_QUIT_SIBLINGS THEN
6045 
6046         Eco_Error_Handler.Log_Error
6047                 (  p_ref_designator_tbl => x_ref_designator_tbl
6048                 ,  p_sub_component_tbl  => x_sub_component_tbl
6049                 ,  p_mesg_token_tbl     => l_mesg_token_tbl
6050                 ,  p_error_status       => Error_Handler.G_STATUS_ERROR
6051                 ,  p_error_scope        => Error_Handler.G_SCOPE_SIBLINGS
6052                 ,  p_other_status       => Error_Handler.G_STATUS_ERROR
6053                 ,  p_other_message      => l_other_message
6054                 ,  p_other_token_tbl    => l_other_token_tbl
6055                 ,  p_error_level        => 5
6056                 ,  p_entity_index       => I
6057                 ,  x_eco_rec            => l_eco_rec
6058                 ,  x_eco_revision_tbl   => l_eco_revision_tbl
6059                 ,  x_revised_item_tbl   => l_revised_item_tbl
6060                 ,  x_rev_component_tbl  => l_rev_component_tbl
6061                 ,  x_ref_designator_tbl => x_ref_designator_tbl
6062                 ,  x_sub_component_tbl  => x_sub_component_tbl
6063                 ,  x_rev_operation_tbl   => l_rev_operation_tbl   --L1
6064                 ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl --L1
6065                 ,  x_rev_sub_resource_tbl=> l_rev_sub_resource_tbl--L1
6066                 );
6067 
6068         IF l_bo_return_status = 'S'
6069         THEN
6070                 l_bo_return_status     := l_return_status;
6071         END IF;
6072         x_return_status                := l_bo_return_status;
6073         x_Mesg_Token_Tbl               := l_Mesg_Token_Tbl;
6074         --x_ref_designator_tbl           := l_ref_designator_tbl;
6075         --x_sub_component_tbl            := l_sub_component_tbl;
6076 
6077         RETURN;
6078 
6079        WHEN EXC_FAT_QUIT_SIBLINGS THEN
6080 
6081         Eco_Error_Handler.Log_Error
6082                 (  p_ref_designator_tbl => x_ref_designator_tbl
6083                 ,  p_sub_component_tbl  => x_sub_component_tbl
6084                 ,  p_mesg_token_tbl     => l_mesg_token_tbl
6085                 ,  p_error_status       => Error_Handler.G_STATUS_FATAL
6086                 ,  p_error_scope        => Error_Handler.G_SCOPE_SIBLINGS
6087                 ,  p_other_status       => Error_Handler.G_STATUS_FATAL
6088                 ,  p_other_message      => l_other_message
6089                 ,  p_other_token_tbl    => l_other_token_tbl
6090                 ,  p_error_level        => 5
6091                 ,  p_entity_index       => I
6092                 ,  x_eco_rec            => l_eco_rec
6093                 ,  x_eco_revision_tbl   => l_eco_revision_tbl
6094                 ,  x_revised_item_tbl   => l_revised_item_tbl
6095                 ,  x_rev_component_tbl  => l_rev_component_tbl
6096                 ,  x_ref_designator_tbl => x_ref_designator_tbl
6097                 ,  x_sub_component_tbl  => x_sub_component_tbl
6098                 ,  x_rev_operation_tbl   => l_rev_operation_tbl   --L1
6099                 ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl --L1
6100                 ,  x_rev_sub_resource_tbl=> l_rev_sub_resource_tbl--L1
6101                 );
6102 
6103         x_return_status                := Error_Handler.G_STATUS_FATAL;
6104         x_Mesg_Token_Tbl               := l_Mesg_Token_Tbl;
6105         --x_ref_designator_tbl           := l_ref_designator_tbl;
6106         --x_sub_component_tbl            := l_sub_component_tbl;
6107 
6108         RETURN;
6109 
6110        WHEN EXC_FAT_QUIT_OBJECT THEN
6111 
6112         Eco_Error_Handler.Log_Error
6113                 (  p_ref_designator_tbl => x_ref_designator_tbl
6114                 ,  p_sub_component_tbl  => x_sub_component_tbl
6115                 ,  p_mesg_token_tbl     => l_mesg_token_tbl
6116                 ,  p_error_status       => Error_Handler.G_STATUS_FATAL
6117                 ,  p_error_scope        => Error_Handler.G_SCOPE_ALL
6118                 ,  p_other_status       => Error_Handler.G_STATUS_FATAL
6119                 ,  p_other_message      => l_other_message
6120                 ,  p_other_token_tbl    => l_other_token_tbl
6121                 ,  p_error_level        => 5
6122                 ,  p_entity_index       => I
6123                 ,  x_eco_rec            => l_eco_rec
6124                 ,  x_eco_revision_tbl   => l_eco_revision_tbl
6125                 ,  x_revised_item_tbl   => l_revised_item_tbl
6126                 ,  x_rev_component_tbl  => l_rev_component_tbl
6127                 ,  x_ref_designator_tbl => x_ref_designator_tbl
6128                 ,  x_sub_component_tbl  => x_sub_component_tbl
6129                 ,  x_rev_operation_tbl   => l_rev_operation_tbl   --L1
6130                 ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl --L1
6131                 ,  x_rev_sub_resource_tbl=> l_rev_sub_resource_tbl--L1
6132                 );
6133 
6134         x_Mesg_Token_Tbl               := l_Mesg_Token_Tbl;
6135         --x_ref_designator_tbl           := l_ref_designator_tbl;
6136         --x_sub_component_tbl            := l_sub_component_tbl;
6137 
6138         l_return_status := 'Q';
6139 
6140        WHEN EXC_UNEXP_SKIP_OBJECT THEN
6141 
6142         Eco_Error_Handler.Log_Error
6143                 (  p_ref_designator_tbl => x_ref_designator_tbl
6144                 ,  p_sub_component_tbl  => x_sub_component_tbl
6145                 ,  p_mesg_token_tbl     => l_mesg_token_tbl
6146                 ,  p_error_status       => Error_Handler.G_STATUS_UNEXPECTED
6147                 ,  p_other_status       => Error_Handler.G_STATUS_NOT_PICKED
6148                 ,  p_other_message      => l_other_message
6149                 ,  p_other_token_tbl    => l_other_token_tbl
6150                 ,  p_error_level        => 5
6151                 ,  x_ECO_rec            => l_ECO_rec
6152                 ,  x_eco_revision_tbl   => l_eco_revision_tbl
6153                 ,  x_revised_item_tbl   => l_revised_item_tbl
6154                 ,  x_rev_component_tbl  => l_rev_component_tbl
6155                 ,  x_ref_designator_tbl => x_ref_designator_tbl
6156                 ,  x_sub_component_tbl  => x_sub_component_tbl
6157                 ,  x_rev_operation_tbl   => l_rev_operation_tbl   --L1
6158                 ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl --L1
6159                 ,  x_rev_sub_resource_tbl=> l_rev_sub_resource_tbl--L1
6160                 );
6161 
6162         --x_ref_designator_tbl           := l_ref_designator_tbl;
6163         --x_sub_component_tbl            := l_sub_component_tbl;
6164         x_Mesg_Token_Tbl               := l_Mesg_Token_Tbl;
6165 
6166         l_return_status := 'U';
6167 
6168         END; -- END block
6169 
6170         IF l_return_status in ('Q', 'U')
6171         THEN
6172                 x_return_status := l_return_status;
6173                 RETURN;
6174         END IF;
6175      END IF; -- End of processing records for which the return status is null
6176      END LOOP; -- END Reference Designator processing loop
6177 
6178     --  Load OUT parameters
6179 
6180      x_return_status            := l_bo_return_status;
6181      --x_ref_designator_tbl       := l_ref_designator_tbl;
6182      --x_sub_component_tbl        := l_sub_component_tbl;
6183      x_Mesg_Token_Tbl           := l_Mesg_Token_Tbl;
6184 
6185 
6186 END Ref_Desgs;
6187 
6188 PROCEDURE Process_Rev_Comp
6189 (   p_validation_level              IN  NUMBER
6190 ,   p_change_notice                 IN  VARCHAR2 := NULL
6191 ,   p_organization_id               IN  NUMBER := NULL
6192 ,   p_revised_item_name             IN  VARCHAR2 := NULL
6193 ,   p_alternate_bom_code            IN  VARCHAR2 := NULL -- Bug 2429272 Change4(cont..of..ENGSVIDB.pls)
6194 ,   p_effectivity_date              IN  DATE := NULL
6195 ,   p_item_revision                 IN  VARCHAR2 := NULL
6196 ,   p_routing_revision              IN  VARCHAR2 := NULL -- Added by MK on 11/02/00
6197 ,   p_from_end_item_number          IN  VARCHAR2 := NULL -- Added by MK on 11/02/00
6198 ,   I                               IN  NUMBER
6199 ,   p_rev_component_rec             IN  BOM_BO_PUB.Rev_Component_Rec_Type
6200 ,   p_ref_designator_tbl            IN  BOM_BO_PUB.Ref_Designator_Tbl_Type
6201 ,   p_sub_component_tbl             IN  BOM_BO_PUB.Sub_Component_Tbl_Type
6202 ,   x_rev_component_tbl             IN OUT NOCOPY BOM_BO_PUB.Rev_Component_Tbl_Type
6203 ,   x_ref_designator_tbl            IN OUT NOCOPY BOM_BO_PUB.Ref_Designator_Tbl_Type
6204 ,   x_sub_component_tbl             IN OUT NOCOPY BOM_BO_PUB.Sub_Component_Tbl_Type
6205 ,   x_rev_comp_unexp_rec            OUT NOCOPY BOM_BO_PUB.Rev_Comp_Unexposed_Rec_Type
6206 ,   x_Mesg_Token_Tbl                OUT NOCOPY Error_Handler.Mesg_Token_Tbl_Type
6207 ,   x_return_status                 OUT NOCOPY VARCHAR2
6208 -- Bug 2941096 // kamohan
6209 ,   x_bill_sequence_id           IN NUMBER := NULL
6210 )
6211 IS
6212 l_Mesg_Token_Tbl        Error_Handler.Mesg_Token_Tbl_Type;
6213 l_other_token_tbl       Error_Handler.Token_Tbl_Type;
6214 l_other_message         VARCHAR2(2000);
6215 l_err_text              VARCHAR2(2000);
6216 l_valid                 BOOLEAN := TRUE;
6217 l_item_parent_exists    BOOLEAN := FALSE;
6218 l_Return_Status         VARCHAR2(1);
6219 l_bo_return_status      VARCHAR2(1);
6220 l_eco_rec               ENG_Eco_PUB.Eco_Rec_Type;
6221 l_eco_revision_tbl      ENG_Eco_PUB.ECO_Revision_Tbl_Type;
6222 l_revised_item_tbl      ENG_Eco_PUB.Revised_Item_Tbl_Type;
6223 l_rev_component_rec     BOM_BO_PUB.Rev_Component_Rec_Type;
6224 --l_rev_component_tbl     BOM_BO_PUB.Rev_Component_Tbl_Type := p_rev_component_tbl;
6225 l_rev_comp_unexp_rec    BOM_BO_PUB.Rev_Comp_Unexposed_Rec_Type;
6226 l_old_rev_component_rec BOM_BO_PUB.Rev_Component_Rec_Type;
6227 l_old_rev_comp_unexp_rec BOM_BO_PUB.Rev_Comp_Unexposed_Rec_Type;
6228 --l_ref_designator_tbl    BOM_BO_PUB.Ref_Designator_Tbl_Type := p_ref_designator_tbl;
6229 --l_sub_component_tbl     BOM_BO_PUB.Sub_Component_Tbl_Type := p_sub_component_tbl;
6230 l_return_value          NUMBER;
6231 l_process_children      BOOLEAN := TRUE;
6232 l_dummy                 NUMBER ;
6233 l_Token_Tbl             Error_Handler.Token_Tbl_Type;
6234 l_structure_type_id     NUMBER ;
6235 l_strc_cp_not_allowed   NUMBER ;
6236 
6237 l_rev_operation_tbl      Bom_Rtg_Pub.Rev_Operation_Tbl_Type;
6238 l_rev_op_resource_tbl    Bom_Rtg_Pub.Rev_Op_Resource_Tbl_Type;
6239 l_rev_sub_resource_tbl   Bom_Rtg_Pub.Rev_Sub_Resource_Tbl_Type;
6240 
6241 EXC_SEV_QUIT_RECORD     EXCEPTION;
6242 EXC_SEV_QUIT_SIBLINGS   EXCEPTION;
6243 EXC_SEV_QUIT_BRANCH     EXCEPTION;
6244 EXC_SEV_SKIP_BRANCH     EXCEPTION;
6245 EXC_FAT_QUIT_OBJECT     EXCEPTION;
6246 EXC_FAT_QUIT_SIBLINGS   EXCEPTION;
6247 EXC_FAT_QUIT_BRANCH     EXCEPTION;
6248 EXC_UNEXP_SKIP_OBJECT   EXCEPTION;
6249 
6250 BEGIN
6251 
6252     l_return_status := FND_API.G_RET_STS_SUCCESS;
6253     l_bo_return_status := FND_API.G_RET_STS_SUCCESS;
6254     x_return_status := FND_API.G_RET_STS_SUCCESS;
6255     x_ref_designator_tbl := p_ref_designator_tbl;
6256     x_sub_component_tbl := p_sub_component_tbl;
6257     l_rev_comp_unexp_rec.organization_id := ENG_GLOBALS.Get_org_id;
6258 
6259     BEGIN
6260 
6261         --
6262         --  Load local records.
6263         --
6264         l_rev_component_rec := x_rev_component_tbl(I);
6265 
6266         l_rev_component_rec.transaction_type :=
6267                 UPPER(l_rev_component_rec.transaction_type);
6268 
6269 
6270         --
6271         -- make sure to set process_children to false at the start of
6272         -- every iteration
6273         --
6274         l_process_children := FALSE;
6275 
6276         --
6277         -- Initialize the Unexposed Record for every iteration of the Loop
6278         -- so that sequence numbers get generated for every new row.
6279         --
6280         l_rev_comp_unexp_rec.Component_Item_Id          := NULL;
6281         l_rev_comp_unexp_rec.Old_Component_Sequence_Id  := NULL;
6282         l_rev_comp_unexp_rec.Component_Sequence_Id      := NULL;
6283         l_rev_comp_unexp_rec.Pick_Components            := NULL;
6284         l_rev_comp_unexp_rec.Supply_Locator_Id          := NULL;
6285         l_rev_comp_unexp_rec.Revised_Item_Sequence_Id   := NULL;
6286         l_rev_comp_unexp_rec.Bom_Item_Type              := NULL;
6287         l_rev_comp_unexp_rec.Revised_Item_Id            := NULL;
6288         l_rev_comp_unexp_rec.Include_On_Bill_Docs       := NULL;
6289 
6290 	-- Bug 2941096 // kamohan
6291 	-- Start changes
6292 
6293 	IF x_bill_sequence_id IS NOT NULL THEN
6294 		l_rev_comp_unexp_rec.Bill_Sequence_Id           := x_bill_sequence_id;
6295 	ELSE
6296 		l_rev_comp_unexp_rec.Bill_Sequence_Id           := NULL;
6297 	END IF;
6298 
6299 	-- End Changes
6300 
6301         IF p_revised_item_name IS NOT NULL AND
6302            p_effectivity_date IS NOT NULL AND
6303            p_change_notice IS NOT NULL AND
6304            p_organization_id IS NOT NULL
6305         THEN
6306                 -- revised item parent exists
6307 
6308                 l_item_parent_exists := TRUE;
6309         END IF;
6310 
6311         -- Process Flow Step 2: Check if record has not yet been processed and
6312         -- that it is the child of the parent that called this procedure
6313         --
6314 
6315         IF --(l_rev_component_rec.return_status IS NULL OR
6316             --l_rev_component_rec.return_status = FND_API.G_MISS_CHAR)
6317            --AND
6318 
6319             -- Did Rev_Items call this procedure, that is,
6320             -- if revised item exists, then is this record a child ?
6321 
6322             (NOT l_item_parent_exists
6323              OR
6324              (l_item_parent_exists AND
6325               (l_rev_component_rec.ECO_Name = p_change_notice AND
6326                l_rev_comp_unexp_rec.organization_id = p_organization_id AND
6327                l_rev_component_rec.revised_item_name = p_revised_item_name AND
6328                NVL(l_rev_component_rec.alternate_bom_code,'NULL') = NVL(p_alternate_bom_code,'NULL') AND
6329                                                                           -- Bug 2429272 Change 4
6330                l_rev_component_rec.start_effective_date = nvl(ENG_Default_Revised_Item.G_OLD_SCHED_DATE,p_effectivity_date) AND -- Bug 6657209
6331                NVL(l_rev_component_rec.new_routing_revision, FND_API.G_MISS_CHAR )
6332                                              =   NVL(p_routing_revision, FND_API.G_MISS_CHAR ) AND -- Added by MK on 11/02/00
6333                NVL(l_rev_component_rec.from_end_item_unit_number, FND_API.G_MISS_CHAR )
6334                                              =   NVL(p_from_end_item_number, FND_API.G_MISS_CHAR ) AND -- Added by MK on 11/02/00
6335                NVL(l_rev_component_rec.new_revised_item_revision, FND_API.G_MISS_CHAR )
6336                                              =   NVL(p_item_revision, FND_API.G_MISS_CHAR) )))
6337 
6338         THEN
6339 
6340            l_return_status := FND_API.G_RET_STS_SUCCESS;
6341 
6342            l_rev_component_rec.return_status := FND_API.G_RET_STS_SUCCESS;
6343 
6344            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Processing component: ' || l_rev_component_rec.component_item_name); END IF;
6345            -- Check if transaction_type is valid
6346            --
6347            -- Bug 6657209
6348            IF (l_item_parent_exists and ENG_Default_Revised_Item.G_OLD_SCHED_DATE is not null ) THEN
6349               l_rev_component_rec.start_effective_date := p_effectivity_date;
6350            END IF;
6351 
6352            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Check transaction_type validity'); END IF;
6353            ENG_GLOBALS.Transaction_Type_Validity
6354            (   p_transaction_type       => l_rev_component_rec.transaction_type
6355            ,   p_entity                 => 'Rev_Comps'
6356            ,   p_entity_id              => l_rev_component_rec.revised_item_name
6357            ,   x_valid                  => l_valid
6358            ,   x_Mesg_Token_Tbl         => l_Mesg_Token_Tbl
6359            );
6360 
6361            IF NOT l_valid
6362            THEN
6363                 RAISE EXC_SEV_QUIT_RECORD;
6364            END IF;
6365 
6366            -- Process Flow step 4(a): Convert user unique index to unique index I
6367            --
6368 
6369            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Converting user unique index to unique index I'); END IF;
6370            Bom_Val_To_Id.Rev_Component_UUI_To_UI
6371                 ( p_rev_component_rec  => l_rev_component_rec
6372                 , p_rev_comp_unexp_rec => l_rev_comp_unexp_rec
6373                 , x_rev_comp_unexp_rec => l_rev_comp_unexp_rec
6374                 , x_Mesg_Token_Tbl     => l_Mesg_Token_Tbl
6375                 , x_Return_Status      => l_return_status
6376                 );
6377 
6378            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
6379 
6380            IF l_return_status = Error_Handler.G_STATUS_ERROR
6381            THEN
6382                 l_other_message := 'BOM_CMP_UUI_SEV_ERROR';
6383                 l_other_token_tbl(1).token_name := 'REVISED_COMPONENT_NAME';
6384                 l_other_token_tbl(1).token_value := l_rev_component_rec.component_item_name;
6385                 RAISE EXC_SEV_QUIT_BRANCH;
6386            ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
6387            THEN
6388                 l_other_message := 'BOM_CMP_UUI_UNEXP_SKIP';
6389                 l_other_token_tbl(1).token_name := 'REVISED_COMPONENT_NAME';
6390                 l_other_token_tbl(1).token_value := l_rev_component_rec.component_item_name;
6391                 RAISE EXC_UNEXP_SKIP_OBJECT;
6392            END IF;
6393 
6394            -- Process Flow step 4(b): Convert user unique index to unique index II
6395            --
6396 
6397            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Converting user unique index to unique index II'); END IF;
6398            Bom_Val_To_Id.Rev_Component_UUI_To_UI2
6399                 ( p_rev_component_rec  => l_rev_component_rec
6400                 , p_rev_comp_unexp_rec => l_rev_comp_unexp_rec
6401                 , x_rev_comp_unexp_rec => l_rev_comp_unexp_rec
6402                 , x_Mesg_Token_Tbl     => l_Mesg_Token_Tbl
6403                 , x_other_message      => l_other_message
6404                 , x_other_token_tbl    => l_other_token_tbl
6405                 , x_Return_Status      => l_return_status
6406                 );
6407 
6408            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
6409 
6410            IF l_return_status = Error_Handler.G_STATUS_ERROR
6411            THEN
6412                 RAISE EXC_SEV_QUIT_SIBLINGS;
6413            ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
6414            THEN
6415                 l_other_message := 'ENG_CMP_UUI_UNEXP_SKIP';
6416                 l_other_token_tbl(1).token_name := 'REVISED_COMPONENT_NAME';
6417                 l_other_token_tbl(1).token_value := l_rev_component_rec.component_item_name;
6418                 RAISE EXC_UNEXP_SKIP_OBJECT;
6419            END IF;
6420 
6421            IF Bom_Globals.Get_Debug = 'Y' THEN
6422            Error_Handler.Write_Debug('Converting user unique index to unique index II for Bill And Rev Seq Id');
6423            END IF;
6424 
6425            ENG_Val_To_Id.BillAndRevitem_UUI_To_UI
6426            ( p_revised_item_name        => l_rev_component_rec.revised_item_name
6427            , p_revised_item_id          => l_rev_comp_unexp_rec.revised_item_id
6428            , p_alternate_bom_code       => l_rev_component_rec.alternate_bom_code -- Bug 2429272 Change 4
6429            , p_item_revision            => l_rev_component_rec.new_revised_item_revision
6430            , p_effective_date           => l_rev_component_rec.start_effective_date
6431            , p_change_notice            => l_rev_component_rec.eco_name
6432            , p_organization_id          => l_rev_comp_unexp_rec.organization_id
6433            , p_new_routing_revision     => l_rev_component_rec.new_routing_revision
6434            , p_from_end_item_number     => l_rev_component_rec.from_end_item_unit_number
6435            , p_entity_processed         => 'RC'
6436            , p_component_item_name      => l_rev_component_rec.component_item_name
6437            , p_transaction_type         => l_rev_component_rec.transaction_type
6438            , x_revised_item_sequence_id => l_rev_comp_unexp_rec.revised_item_sequence_id
6439            , x_bill_sequence_id         => l_rev_comp_unexp_rec.bill_sequence_id
6440            , x_component_sequence_id    => l_dummy
6441            , x_Mesg_Token_Tbl           => l_Mesg_Token_Tbl
6442            , x_other_message            => l_other_message
6443            , x_other_token_tbl          => l_other_token_tbl
6444            , x_Return_Status            => l_return_status
6445           ) ;
6446 
6447            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status) ;
6448            END IF;
6449 
6450            IF l_return_status = Error_Handler.G_STATUS_ERROR
6451            THEN
6452                 RAISE EXC_SEV_QUIT_SIBLINGS;
6453            ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
6454            THEN
6455                 l_other_message := 'ENG_CMP_UUI_UNEXP_SKIP';
6456                 l_other_token_tbl(1).token_name := 'REVISED_COMPONENT_NAME';
6457                 l_other_token_tbl(1).token_value := l_rev_component_rec.component_item_name;
6458                 RAISE EXC_UNEXP_SKIP_OBJECT;
6459            END IF;
6460 
6461 
6462            BOM_Globals.Set_Unit_Controlled_Item
6463            ( p_inventory_item_id => l_rev_comp_unexp_rec.revised_item_id
6464            , p_organization_id  => l_rev_comp_unexp_rec.organization_id
6465            );
6466 
6467            BOM_Globals.Set_Unit_Controlled_Component
6468            ( p_inventory_item_id => l_rev_comp_unexp_rec.component_item_id
6469            , p_organization_id  => l_rev_comp_unexp_rec.organization_id
6470            );
6471 
6472            -- Process Flow step 5: Verify Revised Component's existence
6473            --
6474 
6475            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Check existence'); END IF;
6476            Bom_Validate_Bom_Component.Check_Existence
6477                 (  p_rev_component_rec          => l_rev_component_rec
6478                 ,  p_rev_comp_unexp_rec         => l_rev_comp_unexp_rec
6479                 ,  x_old_rev_component_rec      => l_old_rev_component_rec
6480                 ,  x_old_rev_comp_unexp_rec     => l_old_rev_comp_unexp_rec
6481                 ,  x_Mesg_Token_Tbl             => l_Mesg_Token_Tbl
6482                 ,  x_return_status              => l_Return_Status
6483                 );
6484 
6485            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
6486 
6487            IF l_return_status = Error_Handler.G_STATUS_ERROR
6488            THEN
6489                 l_other_message := 'BOM_CMP_EXS_SEV_ERROR';
6490                 l_other_token_tbl(1).token_name := 'REVISED_COMPONENT_NAME';
6491                 l_other_token_tbl(1).token_value := l_rev_component_rec.component_item_name;
6492                 l_other_token_tbl(2).token_name := 'REVISED_ITEM_NAME';
6493                 l_other_token_tbl(2).token_value := l_rev_component_rec.revised_item_name;
6494                 RAISE EXC_SEV_QUIT_BRANCH;
6495            ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
6496            THEN
6497                 l_other_message := 'BOM_CMP_EXS_UNEXP_SKIP';
6498                 l_other_token_tbl(1).token_name := 'REVISED_COMPONENT_NAME';
6499                 l_other_token_tbl(1).token_value := l_rev_component_rec.component_item_name;
6500                 l_other_token_tbl(2).token_name := 'REVISED_ITEM_NAME';
6501                 l_other_token_tbl(2).token_value := l_rev_component_rec.revised_item_name
6502 ;
6503                 RAISE EXC_UNEXP_SKIP_OBJECT;
6504            END IF;
6505 
6506            -- Process Flow step 6: Check lineage
6507            --
6508 
6509            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Check lineage');          END IF;
6510            Bom_Validate_Bom_Component.Check_Lineage
6511                 (  p_rev_component_rec          => l_rev_component_rec
6512                 ,  p_rev_comp_unexp_rec         => l_rev_comp_unexp_rec
6513                 ,  x_Mesg_Token_Tbl             => l_Mesg_Token_Tbl
6514                 ,  x_return_status              => l_Return_Status
6515                 );
6516 
6517            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
6518 
6519            IF l_return_status = Error_Handler.G_STATUS_ERROR
6520            THEN
6521                    l_other_message := 'BOM_CMP_LIN_SEV_SKIP';
6522                    l_other_token_tbl(1).token_name := 'REVISED_COMPONENT_NAME';
6523                    l_other_token_tbl(1).token_value := l_rev_component_rec.component_item_name;
6524                    RAISE EXC_SEV_QUIT_BRANCH;
6525            ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
6526            THEN
6527                    l_other_message := 'ENG_CMP_LIN_UNEXP_SKIP';
6528                    l_other_token_tbl(1).token_name := 'REVISED_COMPONENT_NAME';
6529                    l_other_token_tbl(1).token_value := l_rev_component_rec.component_item_name;
6530                    RAISE EXC_UNEXP_SKIP_OBJECT;
6531            END IF;
6532 
6533            -- Process Flow step 7: Is Revised Component record an orphan ?
6534 
6535            IF NOT l_item_parent_exists
6536            THEN
6537 
6538                 -- Process Flow step 8(a and b): Is ECO impl/cancl, or in wkflw process ?
6539                 --
6540 
6541                 ENG_Validate_ECO.Check_Access
6542                 (  p_change_notice      => l_rev_component_rec.ECO_Name
6543                 ,  p_organization_id    => l_rev_comp_unexp_rec.organization_id
6544                 , p_Mesg_Token_Tbl      => l_Mesg_Token_Tbl
6545                 , x_Mesg_Token_Tbl      => l_Mesg_Token_Tbl
6546                 , x_Return_Status       => l_return_status
6547                 );
6548 
6549                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
6550 
6551                 IF l_return_status = Error_Handler.G_STATUS_ERROR
6552                 THEN
6553                         l_other_message := 'BOM_CMP_ECOACC_FAT_FATAL';
6554                         l_other_token_tbl(1).token_name := 'REVISED_COMPONENT_NAME';
6555                         l_other_token_tbl(1).token_value := l_rev_component_rec.component_item_name;
6556                         l_return_status := 'F';
6557                         RAISE EXC_FAT_QUIT_OBJECT;
6558                 ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
6559                 THEN
6560                         l_other_message := 'BOM_CMP_ECOACC_UNEXP_SKIP';
6561                         l_other_token_tbl(1).token_name := 'REVISED_COMPONENT_NAME';
6562                         l_other_token_tbl(1).token_value := l_rev_component_rec.component_item_name;
6563                         RAISE EXC_UNEXP_SKIP_OBJECT;
6564                 END IF;
6565 
6566                 -- Process Flow step 9(a and b): check that user has access to revised item
6567                 --
6568 
6569                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Check access'); END IF;
6570                 ENG_Validate_Revised_Item.Check_Access
6571                 (  p_change_notice      => l_rev_component_rec.ECO_Name
6572                 ,  p_organization_id    => l_rev_comp_unexp_rec.organization_id
6573                 ,  p_revised_item_id    => l_rev_comp_unexp_rec.revised_item_id
6574                 ,  p_new_item_revision  => l_rev_component_rec.new_revised_item_revision
6575                 ,  p_effectivity_date   => l_rev_component_rec.start_effective_date
6576                 ,  p_new_routing_revsion   => l_rev_component_rec.new_routing_revision  -- Added by MK on 11/02/00
6577                 ,  p_from_end_item_number  => l_rev_component_rec.from_end_item_unit_number -- Added by MK on 11/02/00
6578                 ,  p_revised_item_name  => l_rev_component_rec.revised_item_name
6579                 ,  p_entity_processed   => 'RC'
6580                 ,  p_alternate_bom_code => l_rev_component_rec.alternate_bom_code -- Bug 4210718
6581                 ,  p_Mesg_Token_Tbl     => l_Mesg_Token_Tbl
6582                 ,  x_Mesg_Token_Tbl     => l_Mesg_Token_Tbl
6583                 ,  x_return_status      => l_Return_Status
6584                 );
6585 
6586                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
6587                 IF l_return_status = Error_Handler.G_STATUS_ERROR
6588                 THEN
6589                         l_other_message := 'BOM_CMP_RITACC_FAT_FATAL';
6590                         l_other_token_tbl(1).token_name := 'REVISED_COMPONENT_NAME';
6591                         l_other_token_tbl(1).token_value := l_rev_component_rec.component_item_name;
6592                         l_return_status := 'F';
6593                         RAISE EXC_FAT_QUIT_SIBLINGS;
6594                 ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
6595                 THEN
6596                         l_other_message := 'BOM_CMP_RITACC_UNEXP_SKIP';
6597                         l_other_token_tbl(1).token_name := 'REVISED_COMPONENT_NAME';
6598                         l_other_token_tbl(1).token_value := l_rev_component_rec.component_item_name;
6599                         RAISE EXC_UNEXP_SKIP_OBJECT;
6600                 END IF;
6601 
6602                 -- Process Flow step 10: check that user has access to revised component
6603                 --
6604 
6605                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Check access'); END IF;
6606                 Bom_Validate_Bom_Component.Check_Access
6607                 (  p_change_notice      => l_rev_component_rec.ECO_Name
6608                 ,  p_organization_id    => l_rev_comp_unexp_rec.organization_id
6609                 ,  p_revised_item_id    => l_rev_comp_unexp_rec.revised_item_id
6610                 ,  p_new_item_revision  => l_rev_component_rec.new_revised_item_revision
6611                 ,  p_effectivity_date   => l_rev_component_rec.start_effective_date
6612                 ,  p_new_routing_revsion  => l_rev_component_rec.new_routing_revision -- Added by MK on 11/02/00
6613                 ,  p_from_end_item_number => l_rev_component_rec.from_end_item_unit_number -- Added by MK on 11/02/00
6614                 ,  p_revised_item_name  => l_rev_component_rec.revised_item_name
6615                 ,  p_component_item_id  => l_rev_comp_unexp_rec.component_item_id
6616                 ,  p_operation_seq_num  => l_rev_component_rec.operation_sequence_number
6617                 ,  p_bill_sequence_id   => l_rev_comp_unexp_rec.bill_sequence_id
6618                 ,  p_component_name     => l_rev_component_rec.component_item_name
6619                 ,  p_Mesg_Token_Tbl     => l_Mesg_Token_Tbl
6620                 ,  x_Mesg_Token_Tbl     => l_Mesg_Token_Tbl
6621                 ,  x_return_status      => l_Return_Status
6622                 );
6623 
6624                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
6625 
6626                 IF l_return_status = Error_Handler.G_STATUS_ERROR
6627                 THEN
6628                         l_other_message := 'BOM_CMP_ACCESS_FAT_FATAL';
6629                         l_other_token_tbl(1).token_name := 'REVISED_COMPONENT_NAME';
6630                         l_other_token_tbl(1).token_value := l_rev_component_rec.component_item_name;
6631                         l_return_status := 'F';
6632                         RAISE EXC_FAT_QUIT_BRANCH;
6633                 ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
6634                 THEN
6635                         l_other_message := 'BOM_CMP_ACCESS_UNEXP_SKIP';
6636                         l_other_token_tbl(1).token_name := 'REVISED_COMPONENT_NAME';
6637                         l_other_token_tbl(1).token_value := l_rev_component_rec.component_item_name;
6638                         RAISE EXC_UNEXP_SKIP_OBJECT;
6639                 END IF;
6640 
6641            ELSE
6642            -- Bug No: 5246049
6643            -- Structure policy check should happen even if parent exists
6644                 l_structure_type_id := NULL;
6645                 l_strc_cp_not_allowed := 2;
6646 
6647                 ENG_Validate_Revised_Item.Check_Structure_Type_Policy
6648                     ( p_inventory_item_id   => l_rev_comp_unexp_rec.revised_item_id
6649                     , p_organization_id     => l_rev_comp_unexp_rec.organization_id
6650                     , p_alternate_bom_code  => l_rev_component_rec.alternate_bom_code
6651                     , x_structure_type_id   => l_structure_type_id
6652                     , x_strc_cp_not_allowed => l_strc_cp_not_allowed
6653                     );
6654                 IF l_strc_cp_not_allowed = 1
6655                 THEN
6656                         l_return_status := Error_Handler.G_STATUS_ERROR ;
6657                         l_Token_Tbl.DELETE;
6658                         l_Token_Tbl(1).token_name := 'STRUCTURE_NAME';
6659                         l_Token_Tbl(1).token_value := l_rev_component_rec.alternate_bom_code;
6660 
6661                         Error_Handler.Add_Error_Token
6662                         ( p_message_name       => 'ENG_BILL_CHANGES_NOT_ALLOWED'
6663                         , p_mesg_token_tbl     => l_Mesg_Token_Tbl
6664                         , p_token_tbl          => l_Token_Tbl
6665                         , x_Mesg_Token_Tbl     => l_Mesg_Token_Tbl
6666                         );
6667 
6668                         l_other_message := 'BOM_CMP_QRY_CSEV_SKIP';
6669                         l_other_token_tbl(1).token_name := 'REVISED_COMPONENT_NAME';
6670                         l_other_token_tbl(1).token_value := l_rev_component_rec.component_item_name;
6671                         RAISE EXC_SEV_SKIP_BRANCH;
6672                 END IF;
6673 
6674 
6675            END IF;
6676 
6677            -- Process Flow step 11: Value to Id conversions
6678            --
6679 
6680            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Value-id conversions'); END IF;
6681            Bom_Val_To_Id.Rev_Component_VID
6682                 ( x_Return_Status       => l_return_status
6683                 , x_Mesg_Token_Tbl      => l_Mesg_Token_Tbl
6684                 , p_rev_comp_unexp_Rec  => l_rev_comp_unexp_rec
6685                 , x_rev_comp_unexp_Rec  => l_rev_comp_unexp_rec
6686                 , p_rev_component_Rec   => l_rev_component_rec
6687                 );
6688 
6689            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
6690 
6691            IF l_return_status = Error_Handler.G_STATUS_ERROR
6692            THEN
6693                 IF l_rev_component_rec.transaction_type = 'CREATE'
6694                 THEN
6695                         l_other_message := 'BOM_CMP_VID_CSEV_SKIP';
6696                         l_other_token_tbl(1).token_name := 'REVISED_COMPONENT_NAME';
6697                         l_other_token_tbl(1).token_value := l_rev_component_rec.component_item_name;
6698                         RAISE EXC_SEV_SKIP_BRANCH;
6699                 ELSE
6700                         RAISE EXC_SEV_QUIT_RECORD;
6701                 END IF;
6702            ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
6703            THEN
6704                 l_other_message := 'BOM_CMP_VID_UNEXP_SKIP';
6705                 l_other_token_tbl(1).token_name := 'REVISED_COMPONENT_NAME';
6706                 l_other_token_tbl(1).token_value := l_rev_component_rec.component_item_name;
6707                 RAISE EXC_UNEXP_SKIP_OBJECT;
6708            ELSIF l_return_status ='S' AND
6709                 l_Mesg_Token_Tbl.COUNT <>0
6710            THEN
6711                 Eco_Error_Handler.Log_Error
6712                 (  p_rev_component_tbl  => x_rev_component_tbl
6713                 ,  p_ref_designator_tbl => x_ref_designator_tbl
6714                 ,  p_sub_component_tbl  => x_sub_component_tbl
6715                 ,  p_mesg_token_tbl     => l_mesg_token_tbl
6716                 ,  p_error_status       => 'W'
6717                 ,  p_error_level        => 4
6718                 ,  p_entity_index       => I
6719                 ,  x_eco_rec            => l_eco_rec
6720                 ,  x_eco_revision_tbl   => l_eco_revision_tbl
6721                 ,  x_revised_item_tbl   => l_revised_item_tbl
6722                 ,  x_rev_component_tbl  => x_rev_component_tbl
6723                 ,  x_ref_designator_tbl => x_ref_designator_tbl
6724                 ,  x_sub_component_tbl  => x_sub_component_tbl
6725                 ,  x_rev_operation_tbl   => l_rev_operation_tbl   --L1
6726                 ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl --L1
6727                 ,  x_rev_sub_resource_tbl=> l_rev_sub_resource_tbl--L1
6728                 );
6729            END IF;
6730 
6731            -- Process Flow step 12: Check required fields exist
6732            -- (also includes conditionally required fields)
6733            --
6734 
6735            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Check required fields'); END IF;
6736            Bom_Validate_Bom_Component.Check_Required
6737                 ( x_return_status              => l_return_status
6738                 , x_Mesg_Token_Tbl             => l_Mesg_Token_Tbl
6739                 , p_rev_component_rec          => l_rev_component_rec
6740                 );
6741 
6742            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
6743 
6744            IF l_return_status = Error_Handler.G_STATUS_ERROR
6745            THEN
6746                 IF l_rev_component_rec.transaction_type = 'CREATE'
6747                 THEN
6748                         l_other_message := 'BOM_CMP_REQ_CSEV_SKIP';
6749                         l_other_token_tbl(1).token_name := 'REVISED_COMPONENT_NAME';
6750                         l_other_token_tbl(1).token_value := l_rev_component_rec.component_item_name;
6751                         RAISE EXC_SEV_SKIP_BRANCH;
6752                 ELSE
6753                         RAISE EXC_SEV_QUIT_RECORD;
6754                 END IF;
6755            ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
6756            THEN
6757                 l_other_message := 'BOM_CMP_REQ_UNEXP_SKIP';
6758                 l_other_token_tbl(1).token_name := 'REVISED_COMPONENT_NAME';
6759                 l_other_token_tbl(1).token_value := l_rev_component_rec.component_item_name;
6760                 RAISE EXC_UNEXP_SKIP_OBJECT;
6761            ELSIF l_return_status ='S' AND
6762                 l_Mesg_Token_Tbl.COUNT <>0
6763            THEN
6764                 Eco_Error_Handler.Log_Error
6765                 (  p_rev_component_tbl  => x_rev_component_tbl
6766                 ,  p_ref_designator_tbl => x_ref_designator_tbl
6767                 ,  p_sub_component_tbl  => x_sub_component_tbl
6768                 ,  p_mesg_token_tbl     => l_mesg_token_tbl
6769                 ,  p_error_status       => 'W'
6770                 ,  p_error_level        => 4
6771                 ,  p_entity_index       => I
6772                 ,  x_eco_rec            => l_eco_rec
6773                 ,  x_eco_revision_tbl   => l_eco_revision_tbl
6774                 ,  x_revised_item_tbl   => l_revised_item_tbl
6775                 ,  x_rev_component_tbl  => x_rev_component_tbl
6776                 ,  x_ref_designator_tbl => x_ref_designator_tbl
6777                 ,  x_sub_component_tbl  => x_sub_component_tbl
6778                 ,  x_rev_operation_tbl   => l_rev_operation_tbl   --L1
6779                 ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl --L1
6780                 ,  x_rev_sub_resource_tbl=> l_rev_sub_resource_tbl--L1
6781                 );
6782            END IF;
6783 
6784            -- Process Flow step 13: Attribute Validation for CREATE and UPDATE
6785            --
6786 
6787            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Attribute Validation'); END IF;
6788            IF l_rev_component_rec.Transaction_Type IN
6789                 (ENG_GLOBALS.G_OPR_CREATE, ENG_GLOBALS.G_OPR_UPDATE)
6790            THEN
6791                 Bom_Validate_Bom_Component.Check_Attributes
6792                 ( x_return_status              => l_return_status
6793                 , x_Mesg_Token_Tbl             => l_Mesg_Token_Tbl
6794                 , p_rev_component_rec          => l_rev_component_rec
6795                 , p_rev_comp_unexp_rec         => l_rev_comp_unexp_rec
6796                 );
6797 
6798                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
6799 
6800                 IF l_return_status = Error_Handler.G_STATUS_ERROR
6801                 THEN
6802                    IF l_rev_component_rec.transaction_type = 'CREATE'
6803                    THEN
6804                         l_other_message := 'BOM_CMP_ATTVAL_CSEV_SKIP';
6805                         l_other_token_tbl(1).token_name := 'REVISED_COMPONENT_NAME';
6806                         l_other_token_tbl(1).token_value := l_rev_component_rec.component_item_name;
6807                         RAISE EXC_SEV_QUIT_BRANCH;
6808                    ELSE
6809                         RAISE EXC_SEV_QUIT_RECORD;
6810                    END IF;
6811                 ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
6812                 THEN
6813                    l_other_message := 'BOM_CMP_ATTVAL_UNEXP_SKIP';
6814                    l_other_token_tbl(1).token_name := 'REVISED_COMPONENT_NAME';
6815                    l_other_token_tbl(1).token_value := l_rev_component_rec.component_item_name;
6816                    RAISE EXC_UNEXP_SKIP_OBJECT;
6817                 ELSIF l_return_status ='S' AND
6818                       l_Mesg_Token_Tbl.COUNT <>0
6819                 THEN
6820                    Eco_Error_Handler.Log_Error
6821                         (  p_rev_component_tbl  => x_rev_component_tbl
6822                         ,  p_ref_designator_tbl => x_ref_designator_tbl
6823                         ,  p_sub_component_tbl  => x_sub_component_tbl
6824                         ,  p_mesg_token_tbl     => l_mesg_token_tbl
6825                         ,  p_error_status       => 'W'
6826                         ,  p_error_level        => 4
6827                         ,  p_entity_index       => I
6828                         ,  x_eco_rec            => l_eco_rec
6829                         ,  x_eco_revision_tbl   => l_eco_revision_tbl
6830                         ,  x_revised_item_tbl   => l_revised_item_tbl
6831                         ,  x_rev_component_tbl  => x_rev_component_tbl
6832                         ,  x_ref_designator_tbl => x_ref_designator_tbl
6833                         ,  x_sub_component_tbl  => x_sub_component_tbl
6834                         ,  x_rev_operation_tbl   => l_rev_operation_tbl   --L1
6835                         ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl --L1
6836                         ,  x_rev_sub_resource_tbl=> l_rev_sub_resource_tbl--L1
6837                         );
6838                 END IF;
6839            END IF;
6840 
6841            IF (l_rev_component_rec.transaction_type = ENG_GLOBALS.G_OPR_CREATE
6842                AND l_rev_component_rec.acd_type IN ( 2, 3 ))
6843            THEN
6844 
6845                 Bom_Bom_Component_Util.Query_Row
6846                    ( p_component_item_id
6847                                 => l_rev_comp_unexp_rec.component_item_id
6848                    , p_operation_sequence_number
6849                                 => l_rev_component_rec.old_operation_sequence_number
6850                    , p_effectivity_date
6851                                 => l_rev_component_rec.old_effectivity_date
6852                    , p_from_end_item_number
6853                                => l_rev_component_rec.old_from_end_item_unit_number
6854                    , p_bill_sequence_id
6855                                 => l_rev_comp_unexp_rec.bill_sequence_id
6856                    , x_Rev_Component_Rec
6857                                 => l_old_rev_component_rec
6858                    , x_Rev_Comp_Unexp_Rec
6859                                 => l_old_rev_comp_unexp_rec
6860                    , x_return_status
6861                                 => l_return_status
6862                    , p_mesg_token_tbl   =>
6863                         l_mesg_token_tbl
6864                    , x_mesg_token_tbl   => l_mesg_token_tbl
6865                    );
6866 
6867                 IF l_return_status <> Eng_Globals.G_RECORD_FOUND
6868                 THEN
6869                         l_return_status := Error_Handler.G_STATUS_ERROR ;
6870                         l_Token_Tbl(1).token_name := 'REVISED_COMPONENT_NAME';
6871                         l_Token_Tbl(1).token_value := l_rev_component_rec.component_item_name;
6872 
6873                         Error_Handler.Add_Error_Token
6874                         ( p_message_name       => 'ENG_CMP_CREATE_REC_NOT_FOUND' --'BOM_CMP_CREATE_REC_NOT_FOUND' -- Bug 3612008 :Modified incorrect message_name
6875                         , p_mesg_token_tbl     => l_Mesg_Token_Tbl
6876                         , p_token_tbl          => l_Token_Tbl
6877                         , x_Mesg_Token_Tbl     => l_Mesg_Token_Tbl
6878                         );
6879 
6880                         l_other_message := 'BOM_CMP_QRY_CSEV_SKIP';
6881                         l_other_token_tbl(1).token_name := 'REVISED_COMPONENT_NAME';
6882                         l_other_token_tbl(1).token_value := l_rev_component_rec.component_item_name;
6883                         RAISE EXC_SEV_SKIP_BRANCH;
6884                 ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
6885                 THEN
6886                         l_other_message := 'BOM_CMP_QRY_UNEXP_SKIP';
6887                         l_other_token_tbl(1).token_name := 'REVISED_COMPONENT_NAME';
6888                         l_other_token_tbl(1).token_value := l_rev_component_rec.component_item_name;
6889                    RAISE EXC_UNEXP_SKIP_OBJECT;
6890                 END IF;
6891             END IF;
6892 
6893             -- Process flow step 15 - Populate NULL columns for Update and
6894             -- Delete, and Creates with ACD_Type 'Add'.
6895 
6896             IF (l_rev_component_rec.transaction_type = ENG_GLOBALS.G_OPR_CREATE
6897                 AND l_rev_component_rec.acd_type = 2)
6898                OR
6899                l_rev_component_rec.transaction_type IN (ENG_GLOBALS.G_OPR_UPDATE,
6900                                                         ENG_GLOBALS.G_OPR_DELETE)
6901             THEN
6902                     IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Populate NULL columns'); END IF;
6903                     Bom_Default_Bom_Component.Populate_Null_Columns
6904                     (   p_rev_component_rec     => l_rev_Component_Rec
6905                     ,   p_old_rev_Component_Rec => l_old_rev_Component_Rec
6906                     ,   p_rev_comp_unexp_rec    => l_rev_comp_unexp_rec
6907                     ,   p_old_rev_comp_unexp_rec=> l_old_rev_comp_unexp_rec
6908                     ,   x_rev_Component_Rec     => l_rev_Component_Rec
6909                     ,   x_rev_comp_unexp_rec    => l_rev_comp_unexp_rec
6910                     );
6911 
6912            ELSIF l_rev_component_rec.Transaction_Type = ENG_GLOBALS.G_OPR_CREATE THEN
6913 
6914                 -- Process Flow step 16: Default missing values for Operation CREATE
6915                 --
6916 
6917                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Attribute Defaulting'); END IF;
6918                 Bom_Default_Bom_Component.Attribute_Defaulting
6919                 (   p_rev_component_rec         => l_rev_component_rec
6920                 ,   p_rev_comp_unexp_rec        => l_rev_comp_unexp_rec
6921                 ,   x_rev_component_rec         => l_rev_component_rec
6922                 ,   x_rev_comp_unexp_rec        => l_rev_comp_unexp_rec
6923                 ,   x_Mesg_Token_Tbl            => l_Mesg_Token_Tbl
6924                 ,   x_return_status             => l_return_status
6925                 );
6926 
6927                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
6928 
6929                 IF l_return_status = Error_Handler.G_STATUS_ERROR
6930                 THEN
6931                         l_other_message := 'BOM_CMP_ATTDEF_CSEV_SKIP';
6932                         l_other_token_tbl(1).token_name := 'REVISED_COMPONENT_NAME';
6933                         l_other_token_tbl(1).token_value := l_rev_component_rec.component_item_name;
6934                         RAISE EXC_SEV_SKIP_BRANCH;
6935                 ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
6936                 THEN
6937                         l_other_message := 'BOM_CMP_ATTDEF_UNEXP_SKIP';
6938                         l_other_token_tbl(1).token_name := 'REVISED_COMPONENT_NAME';
6939                         l_other_token_tbl(1).token_value := l_rev_component_rec.component_item_name;
6940                         RAISE EXC_UNEXP_SKIP_OBJECT;
6941                 ELSIF l_return_status ='S' AND
6942                         l_Mesg_Token_Tbl.COUNT <>0
6943                 THEN
6944                         Eco_Error_Handler.Log_Error
6945                         (  p_rev_component_tbl  => x_rev_component_tbl
6946                         ,  p_ref_designator_tbl => x_ref_designator_tbl
6947                         ,  p_sub_component_tbl  => x_sub_component_tbl
6948                         ,  p_mesg_token_tbl     => l_mesg_token_tbl
6949                         ,  p_error_status       => 'W'
6950                         ,  p_error_level        => 4
6951                         ,  p_entity_index       => I
6952                         ,  x_eco_rec            => l_eco_rec
6953                         ,  x_eco_revision_tbl   => l_eco_revision_tbl
6954                         ,  x_revised_item_tbl   => l_revised_item_tbl
6955                         ,  x_rev_component_tbl  => x_rev_component_tbl
6956                         ,  x_ref_designator_tbl => x_ref_designator_tbl
6957                         ,  x_sub_component_tbl  => x_sub_component_tbl
6958                         ,  x_rev_operation_tbl   => l_rev_operation_tbl   --L1
6959                         ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl --L1
6960                         ,  x_rev_sub_resource_tbl=> l_rev_sub_resource_tbl--L1
6961                         );
6962                 END IF;
6963            END IF;
6964 
6965            -- Process Flow step 17: Entity defaulting for CREATE and UPDATE
6966            --
6967 
6968            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Entity defaulting'); END IF;
6969            IF l_rev_component_rec.Transaction_Type IN
6970                 (ENG_GLOBALS.G_OPR_CREATE, ENG_GLOBALS.G_OPR_UPDATE)
6971            THEN
6972                 Bom_Default_Bom_Component.Entity_Defaulting
6973                 (   p_rev_component_rec         => l_rev_component_rec
6974                 ,   p_old_rev_component_rec     => l_old_rev_component_rec
6975                 ,   x_rev_component_rec         => l_rev_component_rec
6976                 );
6977 
6978                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
6979 
6980                 IF l_return_status = Error_Handler.G_STATUS_ERROR
6981                 THEN
6982                    IF l_rev_component_rec.transaction_type = 'CREATE'
6983                    THEN
6984                         l_other_message := 'BOM_CMP_ENTDEF_CSEV_SKIP';
6985                         l_other_token_tbl(1).token_name := 'REVISED_COMPONENT_NAME';
6986                         l_other_token_tbl(1).token_value := l_rev_component_rec.component_item_name;
6987                         RAISE EXC_SEV_SKIP_BRANCH;
6988                    ELSE
6989                         RAISE EXC_SEV_QUIT_RECORD;
6990                    END IF;
6991                 ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
6992                 THEN
6993                         l_other_message := 'BOM_CMP_ENTDEF_UNEXP_SKIP';
6994                         l_other_token_tbl(1).token_name := 'REVISED_COMPONENT_NAME';
6995                         l_other_token_tbl(1).token_value := l_rev_component_rec.component_item_name;
6996                         RAISE EXC_UNEXP_SKIP_OBJECT;
6997                 ELSIF l_return_status ='S' AND
6998                         l_Mesg_Token_Tbl.COUNT <>0
6999                 THEN
7000                         Eco_Error_Handler.Log_Error
7001                         (  p_rev_component_tbl  => x_rev_component_tbl
7002                         ,  p_ref_designator_tbl => x_ref_designator_tbl
7003                         ,  p_sub_component_tbl  => x_sub_component_tbl
7004                         ,  p_mesg_token_tbl     => l_mesg_token_tbl
7005                         ,  p_error_status       => 'W'
7006                         ,  p_error_level        => 4
7007                         ,  p_entity_index       => I
7008                         ,  x_eco_rec            => l_eco_rec
7009                         ,  x_eco_revision_tbl   => l_eco_revision_tbl
7010                         ,  x_revised_item_tbl   => l_revised_item_tbl
7011                         ,  x_rev_component_tbl  => x_rev_component_tbl
7012                         ,  x_ref_designator_tbl => x_ref_designator_tbl
7013                         ,  x_sub_component_tbl  => x_sub_component_tbl
7014                         ,  x_rev_operation_tbl   => l_rev_operation_tbl   --L1
7015                         ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl --L1
7016                         ,  x_rev_sub_resource_tbl=> l_rev_sub_resource_tbl--L1
7017                         );
7018                 END IF;
7019            END IF;
7020 
7021            -- Process Flow step 18 - Entity Level Validation
7022            --
7023 
7024            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Entity validation'); END IF;
7025            Bom_Validate_Bom_Component.Check_Entity
7026                 (  p_rev_component_rec          => l_rev_component_rec
7027                 ,  p_rev_comp_unexp_rec         => l_rev_comp_unexp_rec
7028                 ,  p_old_rev_component_rec      => l_old_rev_component_rec
7029                 ,  p_old_rev_comp_unexp_rec     => l_old_rev_comp_unexp_rec
7030                 ,  x_Mesg_Token_Tbl             => l_Mesg_Token_Tbl
7031                 ,  x_return_status              => l_Return_Status
7032                 );
7033 
7034            --IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
7035 
7036            IF l_return_status = Error_Handler.G_STATUS_ERROR
7037            THEN
7038                 IF l_rev_component_rec.transaction_type = 'CREATE'
7039                 THEN
7040                         l_other_message := 'BOM_CMP_ENTVAL_CSEV_SKIP';
7041                         l_other_token_tbl(1).token_name := 'REVISED_COMPONENT_NAME';
7042                         l_other_token_tbl(1).token_value := l_rev_component_rec.component_item_name;
7043                         RAISE EXC_SEV_QUIT_BRANCH;
7044                 ELSE
7045                         RAISE EXC_SEV_QUIT_RECORD;
7046                 END IF;
7047            ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
7048            THEN
7049                 l_other_message := 'BOM_CMP_ENTVAL_UNEXP_SKIP';
7050                 l_other_token_tbl(1).token_name := 'REVISED_COMPONENT_NAME';
7051                 l_other_token_tbl(1).token_value := l_rev_component_rec.component_item_name;
7052                 RAISE EXC_UNEXP_SKIP_OBJECT;
7053            ELSIF l_return_status ='S' AND
7054                 l_Mesg_Token_Tbl.COUNT <>0
7055            THEN
7056                 Eco_Error_Handler.Log_Error
7057                 (  p_rev_component_tbl  => x_rev_component_tbl
7058                 ,  p_ref_designator_tbl => x_ref_designator_tbl
7059                 ,  p_sub_component_tbl  => x_sub_component_tbl
7060                 ,  p_mesg_token_tbl     => l_mesg_token_tbl
7061                 ,  p_error_status       => 'W'
7062                 ,  p_error_level        => 4
7063                 ,  p_entity_index       => I
7064                 ,  x_eco_rec            => l_eco_rec
7065                 ,  x_eco_revision_tbl   => l_eco_revision_tbl
7066                 ,  x_revised_item_tbl   => l_revised_item_tbl
7067                 ,  x_rev_component_tbl  => x_rev_component_tbl
7068                 ,  x_ref_designator_tbl => x_ref_designator_tbl
7069                 ,  x_sub_component_tbl  => x_sub_component_tbl
7070                 ,  x_rev_operation_tbl   => l_rev_operation_tbl   --L1
7071                 ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl --L1
7072                 ,  x_rev_sub_resource_tbl=> l_rev_sub_resource_tbl--L1
7073                 );
7074            END IF;
7075 
7076            -- Process Flow step 16 : Database Writes
7077            --
7078 
7079            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Writing to the database'); END IF;
7080            BOM_Globals.Set_BO_Identifier('ECO');  --bug 13849573
7081            Bom_Bom_Component_Util.Perform_Writes
7082                 (   p_rev_component_rec         => l_rev_component_rec
7083                 ,   p_rev_comp_unexp_rec        => l_rev_comp_unexp_rec
7084                 ,   x_Mesg_Token_Tbl            => l_Mesg_Token_Tbl
7085                 ,   x_return_status             => l_return_status
7086                 );
7087 
7088            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
7089 
7090            IF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
7091            THEN
7092                 l_other_message := 'BOM_CMP_WRITES_UNEXP_SKIP';
7093                 l_other_token_tbl(1).token_name := 'REVISED_COMPONENT_NAME';
7094                 l_other_token_tbl(1).token_value := l_rev_component_rec.component_item_name;
7095                 RAISE EXC_UNEXP_SKIP_OBJECT;
7096            ELSIF l_return_status ='S' AND
7097               l_Mesg_Token_Tbl.COUNT <>0
7098            THEN
7099                 Eco_Error_Handler.Log_Error
7100                 (  p_rev_component_tbl  => x_rev_component_tbl
7101                 ,  p_ref_designator_tbl => x_ref_designator_tbl
7102                 ,  p_sub_component_tbl  => x_sub_component_tbl
7103                 ,  p_mesg_token_tbl     => l_mesg_token_tbl
7104                 ,  p_error_status       => 'W'
7105                 ,  p_error_level        => 4
7106                 ,  p_entity_index       => I
7107                 ,  x_eco_rec            => l_eco_rec
7108                 ,  x_eco_revision_tbl   => l_eco_revision_tbl
7109                 ,  x_revised_item_tbl   => l_revised_item_tbl
7110                 ,  x_rev_component_tbl  => x_rev_component_tbl
7111                 ,  x_ref_designator_tbl => x_ref_designator_tbl
7112                 ,  x_sub_component_tbl  => x_sub_component_tbl
7113                 ,  x_rev_operation_tbl   => l_rev_operation_tbl   --L1
7114                 ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl --L1
7115                 ,  x_rev_sub_resource_tbl=> l_rev_sub_resource_tbl--L1
7116                 );
7117            END IF;
7118 
7119 
7120                 -- END IF; -- END IF statement that checks RETURN STATUS
7121 
7122                 --  Load tables.
7123 
7124                 x_rev_component_tbl(I)          := l_rev_component_rec;
7125 
7126                 -- Indicate that children need to be processed
7127 
7128                 l_process_children := TRUE;
7129                 -- END IF;
7130 
7131 
7132         ELSE
7133 
7134 
7135 IF Bom_Globals.Get_Debug = 'Y' THEN
7136     Error_Handler.Write_Debug('This record does not patch with the parent that called it . . .  ') ;
7137     Error_Handler.Write_Debug('so may be this is an comp in another branch . . . '
7138                                || l_rev_component_rec.component_item_name ) ;
7139 END IF ;
7140 
7141                 l_process_children := FALSE;
7142 
7143         END IF; -- END IF statement that checks RETURN STATUS
7144 
7145 
7146     --  For loop exception handler.
7147 
7148 
7149     EXCEPTION
7150 
7151        WHEN EXC_SEV_QUIT_RECORD THEN
7152 
7153         Eco_Error_Handler.Log_Error
7154                 (  p_rev_component_tbl  => x_rev_component_tbl
7155                 ,  p_ref_designator_tbl => x_ref_designator_tbl
7156                 ,  p_sub_component_tbl  => x_sub_component_tbl
7157                 ,  p_mesg_token_tbl     => l_mesg_token_tbl
7158                 ,  p_error_status       => FND_API.G_RET_STS_ERROR
7159                 ,  p_error_scope        => Error_Handler.G_SCOPE_RECORD
7160                 ,  p_error_level        => 4
7161                 ,  p_entity_index       => I
7162                 ,  x_eco_rec            => l_eco_rec
7163                 ,  x_eco_revision_tbl   => l_eco_revision_tbl
7164                 ,  x_revised_item_tbl   => l_revised_item_tbl
7165                 ,  x_rev_component_tbl  => x_rev_component_tbl
7166                 ,  x_ref_designator_tbl => x_ref_designator_tbl
7167                 ,  x_sub_component_tbl  => x_sub_component_tbl
7168                 ,  x_rev_operation_tbl   => l_rev_operation_tbl   --L1
7169                 ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl --L1
7170                 ,  x_rev_sub_resource_tbl=> l_rev_sub_resource_tbl--L1
7171                 );
7172 
7173         l_process_children := TRUE;
7174 
7175         IF l_bo_return_status = 'S'
7176         THEN
7177                 l_bo_return_status     := l_return_status;
7178         END IF;
7179         x_return_status                := l_bo_return_status;
7180         x_Mesg_Token_Tbl               := l_Mesg_Token_Tbl;
7181         x_rev_comp_unexp_rec           := l_rev_comp_unexp_rec;
7182         --x_rev_component_tbl            := l_rev_component_tbl;
7183         --x_ref_designator_tbl           := l_ref_designator_tbl;
7184         --x_sub_component_tbl            := l_sub_component_tbl;
7185 
7186        WHEN EXC_SEV_QUIT_BRANCH THEN
7187 
7188         Eco_Error_Handler.Log_Error
7189                 (  p_rev_component_tbl  => x_rev_component_tbl
7190                 ,  p_ref_designator_tbl => x_ref_designator_tbl
7191                 ,  p_sub_component_tbl  => x_sub_component_tbl
7192                 ,  p_mesg_token_tbl     => l_mesg_token_tbl
7193                 ,  p_error_status       => Error_Handler.G_STATUS_ERROR
7194                 ,  p_error_scope        => Error_Handler.G_SCOPE_CHILDREN
7195                 ,  p_other_status       => Error_Handler.G_STATUS_ERROR
7196                 ,  p_other_message      => l_other_message
7197                 ,  p_other_token_tbl    => l_other_token_tbl
7198                 ,  p_error_level        => 4
7199                 ,  p_entity_index       => I
7200                 ,  x_eco_rec            => l_eco_rec
7201                 ,  x_eco_revision_tbl   => l_eco_revision_tbl
7202                 ,  x_revised_item_tbl   => l_revised_item_tbl
7203                 ,  x_rev_component_tbl  => x_rev_component_tbl
7204                 ,  x_ref_designator_tbl => x_ref_designator_tbl
7205                 ,  x_sub_component_tbl  => x_sub_component_tbl
7206                 ,  x_rev_operation_tbl   => l_rev_operation_tbl   --L1
7207                 ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl --L1
7208                 ,  x_rev_sub_resource_tbl=> l_rev_sub_resource_tbl--L1
7209                 );
7210 
7211         l_process_children := FALSE;
7212 
7213         IF l_bo_return_status = 'S'
7214         THEN
7215                 l_bo_return_status     := l_return_status;
7216         END IF;
7217         x_return_status                := l_bo_return_status;
7218         x_Mesg_Token_Tbl               := l_Mesg_Token_Tbl;
7219         x_rev_comp_unexp_rec           := l_rev_comp_unexp_rec;
7220         --x_rev_component_tbl            := l_rev_component_tbl;
7221         --x_ref_designator_tbl           := l_ref_designator_tbl;
7222         --x_sub_component_tbl            := l_sub_component_tbl;
7223 
7224        WHEN EXC_SEV_SKIP_BRANCH THEN
7225 
7226         Eco_Error_Handler.Log_Error
7227                 (  p_rev_component_tbl  => x_rev_component_tbl
7228                 ,  p_ref_designator_tbl => x_ref_designator_tbl
7229                 ,  p_sub_component_tbl  => x_sub_component_tbl
7230                 ,  p_mesg_token_tbl     => l_mesg_token_tbl
7231                 ,  p_error_status       => Error_Handler.G_STATUS_ERROR
7232                 ,  p_error_scope        => Error_Handler.G_SCOPE_CHILDREN
7233                 ,  p_other_status       => Error_Handler.G_STATUS_NOT_PICKED
7234                 ,  p_other_message      => l_other_message
7235                 ,  p_other_token_tbl    => l_other_token_tbl
7236                 ,  p_error_level        => 4
7237                 ,  p_entity_index       => I
7238                 ,  x_eco_rec            => l_eco_rec
7239                 ,  x_eco_revision_tbl   => l_eco_revision_tbl
7240                 ,  x_revised_item_tbl   => l_revised_item_tbl
7241                 ,  x_rev_component_tbl  => x_rev_component_tbl
7242                 ,  x_ref_designator_tbl => x_ref_designator_tbl
7243                 ,  x_sub_component_tbl  => x_sub_component_tbl
7244                 ,  x_rev_operation_tbl   => l_rev_operation_tbl   --L1
7245                 ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl --L1
7246                 ,  x_rev_sub_resource_tbl=> l_rev_sub_resource_tbl--L1
7247                 );
7248 
7249         l_process_children := FALSE;
7250 
7251         IF l_bo_return_status = 'S'
7252         THEN
7253                 l_bo_return_status     := l_return_status;
7254         END IF;
7255         x_return_status                := l_bo_return_status;
7256         x_Mesg_Token_Tbl               := l_Mesg_Token_Tbl;
7257         x_rev_comp_unexp_rec           := l_rev_comp_unexp_rec;
7258         --x_rev_component_tbl            := l_rev_component_tbl;
7259         --x_ref_designator_tbl           := l_ref_designator_tbl;
7260         --x_sub_component_tbl            := l_sub_component_tbl;
7261 
7262        WHEN EXC_SEV_QUIT_SIBLINGS THEN
7263 
7264         Eco_Error_Handler.Log_Error
7265                 (  p_rev_component_tbl  => x_rev_component_tbl
7266                 ,  p_ref_designator_tbl => x_ref_designator_tbl
7267                 ,  p_sub_component_tbl  => x_sub_component_tbl
7268                 ,  p_mesg_token_tbl     => l_mesg_token_tbl
7269                 ,  p_error_status       => Error_Handler.G_STATUS_ERROR
7270                 ,  p_error_scope        => Error_Handler.G_SCOPE_SIBLINGS
7271                 ,  p_other_status       => Error_Handler.G_STATUS_ERROR
7272                 ,  p_other_message      => l_other_message
7273                 ,  p_other_token_tbl    => l_other_token_tbl
7274                 ,  p_error_level        => 4
7275                 ,  p_entity_index       => I
7276                 ,  x_eco_rec            => l_eco_rec
7277                 ,  x_eco_revision_tbl   => l_eco_revision_tbl
7278                 ,  x_revised_item_tbl   => l_revised_item_tbl
7279                 ,  x_rev_component_tbl  => x_rev_component_tbl
7280                 ,  x_ref_designator_tbl => x_ref_designator_tbl
7281                 ,  x_sub_component_tbl  => x_sub_component_tbl
7282                 ,  x_rev_operation_tbl   => l_rev_operation_tbl   --L1
7283                 ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl --L1
7284                 ,  x_rev_sub_resource_tbl=> l_rev_sub_resource_tbl--L1
7285                 );
7286 
7287         l_process_children := FALSE;
7288 
7289         IF l_bo_return_status = 'S'
7290         THEN
7291                 l_bo_return_status     := l_return_status;
7292         END IF;
7293         x_return_status                := l_bo_return_status;
7294         x_Mesg_Token_Tbl               := l_Mesg_Token_Tbl;
7295         x_rev_comp_unexp_rec           := l_rev_comp_unexp_rec;
7296         --x_rev_component_tbl            := l_rev_component_tbl;
7297         --x_ref_designator_tbl           := l_ref_designator_tbl;
7298         --x_sub_component_tbl            := l_sub_component_tbl;
7299 
7300        WHEN EXC_FAT_QUIT_BRANCH THEN
7301 
7302         Eco_Error_Handler.Log_Error
7303                 (  p_rev_component_tbl  => x_rev_component_tbl
7304                 ,  p_ref_designator_tbl => x_ref_designator_tbl
7305                 ,  p_sub_component_tbl  => x_sub_component_tbl
7306                 ,  p_mesg_token_tbl     => l_mesg_token_tbl
7307                 ,  p_error_status       => Error_Handler.G_STATUS_FATAL
7308                 ,  p_error_scope        => Error_Handler.G_SCOPE_CHILDREN
7309                 ,  p_other_status       => Error_Handler.G_STATUS_FATAL
7310                 ,  p_other_message      => l_other_message
7311                 ,  p_other_token_tbl    => l_other_token_tbl
7312                 ,  p_error_level        => 4
7313                 ,  p_entity_index       => I
7314                 ,  x_eco_rec            => l_eco_rec
7315                 ,  x_eco_revision_tbl   => l_eco_revision_tbl
7316                 ,  x_revised_item_tbl   => l_revised_item_tbl
7317                 ,  x_rev_component_tbl  => x_rev_component_tbl
7318                 ,  x_ref_designator_tbl => x_ref_designator_tbl
7319                 ,  x_sub_component_tbl  => x_sub_component_tbl
7320                 ,  x_rev_operation_tbl   => l_rev_operation_tbl   --L1
7321                 ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl --L1
7322                 ,  x_rev_sub_resource_tbl=> l_rev_sub_resource_tbl--L1
7323                 );
7324 
7325         l_process_children := FALSE;
7326 
7327         x_return_status                := Error_Handler.G_STATUS_FATAL;
7328         x_Mesg_Token_Tbl               := l_Mesg_Token_Tbl;
7329         x_rev_comp_unexp_rec           := l_rev_comp_unexp_rec;
7330         --x_rev_component_tbl            := l_rev_component_tbl;
7331         --x_ref_designator_tbl           := l_ref_designator_tbl;
7332         --x_sub_component_tbl            := l_sub_component_tbl;
7333 
7334        WHEN EXC_FAT_QUIT_SIBLINGS THEN
7335 
7336         Eco_Error_Handler.Log_Error
7337                 (  p_rev_component_tbl  => x_rev_component_tbl
7338                 ,  p_ref_designator_tbl => x_ref_designator_tbl
7339                 ,  p_sub_component_tbl  => x_sub_component_tbl
7340                 ,  p_mesg_token_tbl     => l_mesg_token_tbl
7341                 ,  p_error_status       => Error_Handler.G_STATUS_FATAL
7342                 ,  p_error_scope        => Error_Handler.G_SCOPE_SIBLINGS
7343                 ,  p_other_status       => Error_Handler.G_STATUS_FATAL
7344                 ,  p_other_message      => l_other_message
7345                 ,  p_other_token_tbl    => l_other_token_tbl
7346                 ,  p_error_level        => 4
7347                 ,  p_entity_index       => I
7348                 ,  x_eco_rec            => l_eco_rec
7349                 ,  x_eco_revision_tbl   => l_eco_revision_tbl
7350                 ,  x_revised_item_tbl   => l_revised_item_tbl
7351                 ,  x_rev_component_tbl  => x_rev_component_tbl
7352                 ,  x_ref_designator_tbl => x_ref_designator_tbl
7353                 ,  x_sub_component_tbl  => x_sub_component_tbl
7354                 ,  x_rev_operation_tbl   => l_rev_operation_tbl   --L1
7355                 ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl --L1
7356                 ,  x_rev_sub_resource_tbl=> l_rev_sub_resource_tbl--L1
7357                 );
7358 
7359         l_process_children := FALSE;
7360 
7361         IF l_bo_return_status = 'S'
7362         THEN
7363                 l_bo_return_status     := l_return_status;
7364         END IF;
7365         x_return_status                := Error_Handler.G_STATUS_FATAL;
7366         x_Mesg_Token_Tbl               := l_Mesg_Token_Tbl;
7367         x_rev_comp_unexp_rec           := l_rev_comp_unexp_rec;
7368         --x_rev_component_tbl            := l_rev_component_tbl;
7369         --x_ref_designator_tbl           := l_ref_designator_tbl;
7370         --x_sub_component_tbl            := l_sub_component_tbl;
7371        WHEN EXC_FAT_QUIT_OBJECT THEN
7372 
7373         Eco_Error_Handler.Log_Error
7374                 (  p_rev_component_tbl  => x_rev_component_tbl
7375                 ,  p_ref_designator_tbl => x_ref_designator_tbl
7376                 ,  p_sub_component_tbl  => x_sub_component_tbl
7377                 ,  p_mesg_token_tbl     => l_mesg_token_tbl
7378                 ,  p_error_status       => Error_Handler.G_STATUS_FATAL
7379                 ,  p_error_scope        => Error_Handler.G_SCOPE_ALL
7380                 ,  p_other_status       => Error_Handler.G_STATUS_FATAL
7381                 ,  p_other_message      => l_other_message
7382                 ,  p_other_token_tbl    => l_other_token_tbl
7383                 ,  p_error_level        => 4
7384                 ,  p_entity_index       => I
7385                 ,  x_eco_rec            => l_eco_rec
7386                 ,  x_eco_revision_tbl   => l_eco_revision_tbl
7387                 ,  x_revised_item_tbl   => l_revised_item_tbl
7388                 ,  x_rev_component_tbl  => x_rev_component_tbl
7389                 ,  x_ref_designator_tbl => x_ref_designator_tbl
7390                 ,  x_sub_component_tbl  => x_sub_component_tbl
7391                 ,  x_rev_operation_tbl   => l_rev_operation_tbl   --L1
7392                 ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl --L1
7393                 ,  x_rev_sub_resource_tbl=> l_rev_sub_resource_tbl--L1
7394                 );
7395 
7396         x_Mesg_Token_Tbl               := l_Mesg_Token_Tbl;
7397         --x_rev_component_tbl            := l_rev_component_tbl;
7398         --x_ref_designator_tbl           := l_ref_designator_tbl;
7399         --x_sub_component_tbl            := l_sub_component_tbl;
7400 
7401         l_return_status := 'Q';
7402 
7403        WHEN EXC_UNEXP_SKIP_OBJECT THEN
7404 
7405 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Unexpected error caught in Rev Comps . . . '); END IF;
7406 
7407         Eco_Error_Handler.Log_Error
7408                 (  p_rev_component_tbl  => x_rev_component_tbl
7409                 ,  p_ref_designator_tbl => x_ref_designator_tbl
7410                 ,  p_sub_component_tbl  => x_sub_component_tbl
7411                 ,  p_mesg_token_tbl     => l_mesg_token_tbl
7412                 ,  p_error_status       => Error_Handler.G_STATUS_UNEXPECTED
7413                 ,  p_other_status       => Error_Handler.G_STATUS_NOT_PICKED
7414                 ,  p_other_message      => l_other_message
7415                 ,  p_other_token_tbl    => l_other_token_tbl
7416                 ,  p_error_level        => 4
7417                 ,  p_entity_index       => I
7418                 ,  x_ECO_rec            => l_ECO_rec
7419                 ,  x_eco_revision_tbl   => l_eco_revision_tbl
7420                 ,  x_revised_item_tbl   => l_revised_item_tbl
7421                 ,  x_rev_component_tbl  => x_rev_component_tbl
7422                 ,  x_ref_designator_tbl => x_ref_designator_tbl
7423                 ,  x_sub_component_tbl  => x_sub_component_tbl
7424                 ,  x_rev_operation_tbl   => l_rev_operation_tbl   --L1
7425                 ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl --L1
7426                 ,  x_rev_sub_resource_tbl=> l_rev_sub_resource_tbl--L1
7427                 );
7428 
7429         --x_rev_component_tbl            := l_rev_component_tbl;
7430         --x_ref_designator_tbl           := l_ref_designator_tbl;
7431         --x_sub_component_tbl            := l_sub_component_tbl;
7432         x_Mesg_Token_Tbl               := l_Mesg_Token_Tbl;
7433 
7434         l_return_status := 'U';
7435 
7436 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Unexpected error in Rev Comps . . .'); END IF;
7437 
7438         END; -- END block
7439 
7440         IF l_return_status in ('Q', 'U')
7441         THEN
7442                 x_return_status := l_return_status;
7443 
7444 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Rev Comps returning with status ' || l_return_status ); END IF;
7445 
7446                 RETURN;
7447         END IF;
7448 
7449    IF l_process_children
7450    THEN
7451         -- Process Reference Designators that are direct children of this
7452         -- component
7453 
7454 IF Bom_Globals.Get_Debug = 'Y' THEN
7455     Error_Handler.Write_Debug('***********************************************************') ;
7456     Error_Handler.Write_Debug('Now processing direct children for the Rev Comp '
7457                               || l_rev_component_rec.component_item_name || '. . .'  );
7458     Error_Handler.Write_Debug('Now processing Ref Desig as direct children for the Rev Comp ') ;
7459 END IF;
7460 
7461 
7462         Ref_Desgs
7463         (   p_validation_level          => p_validation_level
7464         ,   p_change_notice             => l_rev_component_rec.ECO_Name
7465         ,   p_organization_id           => l_rev_comp_unexp_rec.organization_id
7466         ,   p_revised_item_name         => l_rev_component_rec.revised_item_name
7467         ,   p_alternate_bom_code        => l_rev_component_rec.alternate_bom_code  -- Bug 3991176
7468         ,   p_effectivity_date          => l_rev_component_rec.start_effective_date
7469         ,   p_item_revision             => l_rev_component_rec.new_revised_item_revision
7470         ,   p_routing_revision          => l_rev_component_rec.new_routing_revision      -- Added by MK on 11/02/00
7471         ,   p_from_end_item_number      => l_rev_component_rec.from_end_item_unit_number -- Added by MK on 11/02/00
7472         ,   p_component_item_name       => l_rev_component_rec.component_item_name
7473         ,   p_operation_seq_num         => l_rev_component_rec.operation_sequence_number
7474         ,   p_ref_designator_tbl        => x_ref_designator_tbl
7475         ,   p_sub_component_tbl         => x_sub_component_tbl
7476         ,   x_ref_designator_tbl        => x_ref_designator_tbl
7477         ,   x_sub_component_tbl         => x_sub_component_tbl
7478         ,   x_Mesg_Token_Tbl            => l_Mesg_Token_Tbl
7479         ,   x_return_status             => l_return_status
7480         );
7481 
7482         IF l_return_status <> FND_API.G_RET_STS_SUCCESS
7483         THEN
7484                 l_bo_return_status := l_return_status;
7485         END IF;
7486 
7487         -- Process Substitute Components that are direct children of this
7488         -- component
7489 
7490 IF Bom_Globals.Get_Debug = 'Y' THEN
7491     Error_Handler.Write_Debug('***********************************************************') ;
7492     Error_Handler.Write_Debug('Now processing Ref Desig as direct children for the Rev Comp ') ;
7493 END IF ;
7494 
7495         Sub_Comps
7496         (   p_validation_level          => p_validation_level
7497         ,   p_change_notice             => l_rev_component_rec.ECO_Name
7498         ,   p_organization_id           => l_rev_comp_unexp_rec.organization_id
7499         ,   p_revised_item_name         => l_rev_component_rec.revised_item_name
7500         ,   p_alternate_bom_code        => l_rev_component_rec.alternate_bom_code  -- Bug 3991176
7501         ,   p_effectivity_date          => l_rev_component_rec.start_effective_date
7502         ,   p_item_revision             => l_rev_component_rec.new_revised_item_revision
7503         ,   p_routing_revision          => l_rev_component_rec.new_routing_revision      -- Added by MK on 11/02/00
7504         ,   p_from_end_item_number      => l_rev_component_rec.from_end_item_unit_number -- Added by MK on 11/02/00
7505         ,   p_component_item_name       => l_rev_component_rec.component_item_name
7506         ,   p_operation_seq_num         => l_rev_component_rec.operation_sequence_number
7507         ,   p_sub_component_tbl         => x_sub_component_tbl
7508         ,   x_sub_component_tbl         => x_sub_component_tbl
7509         ,   x_Mesg_Token_Tbl            => l_Mesg_Token_Tbl
7510         ,   x_return_status             => l_return_status
7511         );
7512 
7513         IF l_return_status <> FND_API.G_RET_STS_SUCCESS
7514         THEN
7515                 l_bo_return_status := l_return_status;
7516         END IF;
7517 
7518         IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Finished processing children for ' || l_rev_component_rec.component_item_name || ' . . . ' || l_return_status ); END IF;
7519 
7520     END IF;  -- Process children
7521     x_return_status            := l_bo_return_status;
7522     x_Mesg_Token_Tbl           := l_Mesg_Token_Tbl;
7523     x_rev_comp_unexp_rec       := l_rev_comp_unexp_rec;
7524 
7525 
7526 END Process_Rev_Comp;
7527 
7528 --  Rev_Comps
7529 
7530 PROCEDURE Rev_Comps
7531 (   p_validation_level              IN  NUMBER
7532 ,   p_change_notice                 IN  VARCHAR2 := NULL
7533 ,   p_organization_id               IN  NUMBER := NULL
7534 ,   p_revised_item_name             IN  VARCHAR2 := NULL
7535 ,   p_alternate_bom_code            IN  VARCHAR2 := NULL -- Bug 2429272 Change4(cont..of..ENGSVIDB.pls)
7536 ,   p_effectivity_date              IN  DATE := NULL
7537 ,   p_item_revision                 IN  VARCHAR2 := NULL
7538 ,   p_routing_revision              IN  VARCHAR2 := NULL -- Added by MK on 11/02/00
7539 ,   p_from_end_item_number          IN  VARCHAR2 := NULL -- Added by MK on 11/02/00
7540 ,   p_rev_component_tbl             IN  BOM_BO_PUB.Rev_Component_Tbl_Type
7541 ,   p_ref_designator_tbl            IN  BOM_BO_PUB.Ref_Designator_Tbl_Type
7542 ,   p_sub_component_tbl             IN  BOM_BO_PUB.Sub_Component_Tbl_Type
7543 ,   x_rev_component_tbl             IN OUT NOCOPY BOM_BO_PUB.Rev_Component_Tbl_Type
7544 ,   x_ref_designator_tbl            IN OUT NOCOPY BOM_BO_PUB.Ref_Designator_Tbl_Type
7545 ,   x_sub_component_tbl             IN OUT NOCOPY BOM_BO_PUB.Sub_Component_Tbl_Type
7546 ,   x_Mesg_Token_Tbl                OUT NOCOPY Error_Handler.Mesg_Token_Tbl_Type
7547 ,   x_return_status                 OUT NOCOPY VARCHAR2
7548 -- Bug 2941096 // kamohan
7549 ,   x_bill_sequence_id           IN NUMBER := NULL
7550 )
7551 IS
7552 l_Mesg_Token_Tbl        Error_Handler.Mesg_Token_Tbl_Type;
7553 l_other_token_tbl       Error_Handler.Token_Tbl_Type;
7554 l_other_message         VARCHAR2(2000);
7555 l_err_text              VARCHAR2(2000);
7556 l_valid                 BOOLEAN := TRUE;
7557 l_item_parent_exists    BOOLEAN := FALSE;
7558 l_Return_Status         VARCHAR2(1);
7559 l_bo_return_status      VARCHAR2(1);
7560 l_eco_rec               ENG_Eco_PUB.Eco_Rec_Type;
7561 l_eco_revision_tbl      ENG_Eco_PUB.ECO_Revision_Tbl_Type;
7562 l_revised_item_tbl      ENG_Eco_PUB.Revised_Item_Tbl_Type;
7563 l_rev_component_rec     BOM_BO_PUB.Rev_Component_Rec_Type;
7564 --l_rev_component_tbl     BOM_BO_PUB.Rev_Component_Tbl_Type := p_rev_component_tbl;
7565 l_rev_comp_unexp_rec    BOM_BO_PUB.Rev_Comp_Unexposed_Rec_Type;
7566 l_old_rev_component_rec BOM_BO_PUB.Rev_Component_Rec_Type;
7567 l_old_rev_comp_unexp_rec BOM_BO_PUB.Rev_Comp_Unexposed_Rec_Type;
7568 --l_ref_designator_tbl    BOM_BO_PUB.Ref_Designator_Tbl_Type := p_ref_designator_tbl;
7569 --l_sub_component_tbl     BOM_BO_PUB.Sub_Component_Tbl_Type := p_sub_component_tbl;
7570 l_return_value          NUMBER;
7571 l_process_children      BOOLEAN := TRUE;
7572 l_dummy                 NUMBER ;
7573 l_Token_Tbl             Error_Handler.Token_Tbl_Type;
7574 l_structure_type_id     NUMBER ;
7575 l_strc_cp_not_allowed   NUMBER ;
7576 
7577 l_rev_operation_tbl      Bom_Rtg_Pub.Rev_Operation_Tbl_Type;
7578 l_rev_op_resource_tbl    Bom_Rtg_Pub.Rev_Op_Resource_Tbl_Type;
7579 l_rev_sub_resource_tbl   Bom_Rtg_Pub.Rev_Sub_Resource_Tbl_Type;
7580 
7581 EXC_SEV_QUIT_RECORD     EXCEPTION;
7582 EXC_SEV_QUIT_SIBLINGS   EXCEPTION;
7583 EXC_SEV_QUIT_BRANCH     EXCEPTION;
7584 EXC_SEV_SKIP_BRANCH     EXCEPTION;
7585 EXC_FAT_QUIT_OBJECT     EXCEPTION;
7586 EXC_FAT_QUIT_SIBLINGS   EXCEPTION;
7587 EXC_FAT_QUIT_BRANCH     EXCEPTION;
7588 EXC_UNEXP_SKIP_OBJECT   EXCEPTION;
7589 
7590 BEGIN
7591 
7592     --  Init local table variables.
7593 
7594     l_return_status := FND_API.G_RET_STS_SUCCESS;
7595     l_bo_return_status := FND_API.G_RET_STS_SUCCESS;
7596 
7597     x_return_status := FND_API.G_RET_STS_SUCCESS;
7598 
7599     --l_rev_component_tbl            := p_rev_component_tbl;
7600     x_rev_component_tbl            := p_rev_component_tbl;
7601     x_ref_designator_tbl           := p_ref_designator_tbl;
7602     x_sub_component_tbl            := p_sub_component_tbl;
7603 
7604     l_rev_comp_unexp_rec.organization_id := ENG_GLOBALS.Get_org_id;
7605 
7606     FOR I IN 1..x_rev_component_tbl.COUNT LOOP
7607     IF (x_rev_component_tbl(I).return_status IS NULL OR
7608          x_rev_component_tbl(I).return_status = FND_API.G_MISS_CHAR) THEN
7609 
7610     BEGIN
7611 
7612         --
7613         --  Load local records.
7614         --
7615         l_rev_component_rec := x_rev_component_tbl(I);
7616 
7617         l_rev_component_rec.transaction_type :=
7618                 UPPER(l_rev_component_rec.transaction_type);
7619 
7620 
7621         --
7622         -- make sure to set process_children to false at the start of
7623         -- every iteration
7624         --
7625         l_process_children := FALSE;
7626 
7627         --
7628         -- Initialize the Unexposed Record for every iteration of the Loop
7629         -- so that sequence numbers get generated for every new row.
7630         --
7631         l_rev_comp_unexp_rec.Component_Item_Id          := NULL;
7632         l_rev_comp_unexp_rec.Old_Component_Sequence_Id  := NULL;
7633         l_rev_comp_unexp_rec.Component_Sequence_Id      := NULL;
7634         l_rev_comp_unexp_rec.Pick_Components            := NULL;
7635         l_rev_comp_unexp_rec.Supply_Locator_Id          := NULL;
7636         l_rev_comp_unexp_rec.Revised_Item_Sequence_Id   := NULL;
7637         l_rev_comp_unexp_rec.Bom_Item_Type              := NULL;
7638         l_rev_comp_unexp_rec.Revised_Item_Id            := NULL;
7639         l_rev_comp_unexp_rec.Include_On_Bill_Docs       := NULL;
7640 
7641 	-- Bug 2941096 // kamohan
7642 	-- Start changes
7643 
7644 	IF x_bill_sequence_id IS NOT NULL THEN
7645 		l_rev_comp_unexp_rec.Bill_Sequence_Id           := x_bill_sequence_id;
7646 	ELSE
7647 		l_rev_comp_unexp_rec.Bill_Sequence_Id           := NULL;
7648 	END IF;
7649 
7650 	-- End Changes
7651 
7652         IF p_revised_item_name IS NOT NULL AND
7653            p_effectivity_date IS NOT NULL AND
7654            p_change_notice IS NOT NULL AND
7655            p_organization_id IS NOT NULL
7656         THEN
7657                 -- revised item parent exists
7658 
7659                 l_item_parent_exists := TRUE;
7660         END IF;
7661 
7662         -- Process Flow Step 2: Check if record has not yet been processed and
7663         -- that it is the child of the parent that called this procedure
7664         --
7665 
7666         IF --(l_rev_component_rec.return_status IS NULL OR
7667             --l_rev_component_rec.return_status = FND_API.G_MISS_CHAR)
7668            --AND
7669 
7670             -- Did Rev_Items call this procedure, that is,
7671             -- if revised item exists, then is this record a child ?
7672 
7673             (NOT l_item_parent_exists
7674              OR
7675              (l_item_parent_exists AND
7676               (l_rev_component_rec.ECO_Name = p_change_notice AND
7677                l_rev_comp_unexp_rec.organization_id = p_organization_id AND
7678                l_rev_component_rec.revised_item_name = p_revised_item_name AND
7679                NVL(l_rev_component_rec.alternate_bom_code,'NULL') = NVL(p_alternate_bom_code,'NULL') AND
7680                                                                           -- Bug 2429272 Change 4
7681                l_rev_component_rec.start_effective_date = nvl(ENG_Default_Revised_Item.G_OLD_SCHED_DATE,p_effectivity_date) AND -- Bug 6657209
7682                NVL(l_rev_component_rec.new_routing_revision, FND_API.G_MISS_CHAR )
7683                                              =   NVL(p_routing_revision, FND_API.G_MISS_CHAR ) AND -- Added by MK on 11/02/00
7684                NVL(l_rev_component_rec.from_end_item_unit_number, FND_API.G_MISS_CHAR )
7685                                              =   NVL(p_from_end_item_number, FND_API.G_MISS_CHAR ) AND -- Added by MK on 11/02/00
7686                NVL(l_rev_component_rec.new_revised_item_revision, FND_API.G_MISS_CHAR )
7687                                              =   NVL(p_item_revision, FND_API.G_MISS_CHAR) )))
7688 
7689         THEN
7690 
7691            l_return_status := FND_API.G_RET_STS_SUCCESS;
7692 
7693            l_rev_component_rec.return_status := FND_API.G_RET_STS_SUCCESS;
7694 
7695            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Processing component: ' || l_rev_component_rec.component_item_name); END IF;
7696            -- Check if transaction_type is valid
7697            --
7698            -- Bug 6657209
7699            IF (l_item_parent_exists and ENG_Default_Revised_Item.G_OLD_SCHED_DATE is not null ) THEN
7700               l_rev_component_rec.start_effective_date := p_effectivity_date;
7701            END IF;
7702 
7703            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Check transaction_type validity'); END IF;
7704            ENG_GLOBALS.Transaction_Type_Validity
7705            (   p_transaction_type       => l_rev_component_rec.transaction_type
7706            ,   p_entity                 => 'Rev_Comps'
7707            ,   p_entity_id              => l_rev_component_rec.revised_item_name
7708            ,   x_valid                  => l_valid
7709            ,   x_Mesg_Token_Tbl         => l_Mesg_Token_Tbl
7710            );
7711 
7712            IF NOT l_valid
7713            THEN
7714                 RAISE EXC_SEV_QUIT_RECORD;
7715            END IF;
7716 
7717            -- Process Flow step 4(a): Convert user unique index to unique index I
7718            --
7719 
7720            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Converting user unique index to unique index I'); END IF;
7721            Bom_Val_To_Id.Rev_Component_UUI_To_UI
7722                 ( p_rev_component_rec  => l_rev_component_rec
7723                 , p_rev_comp_unexp_rec => l_rev_comp_unexp_rec
7724                 , x_rev_comp_unexp_rec => l_rev_comp_unexp_rec
7725                 , x_Mesg_Token_Tbl     => l_Mesg_Token_Tbl
7726                 , x_Return_Status      => l_return_status
7727                 );
7728 
7729            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
7730 
7731            IF l_return_status = Error_Handler.G_STATUS_ERROR
7732            THEN
7733                 l_other_message := 'BOM_CMP_UUI_SEV_ERROR';
7734                 l_other_token_tbl(1).token_name := 'REVISED_COMPONENT_NAME';
7735                 l_other_token_tbl(1).token_value := l_rev_component_rec.component_item_name;
7736                 RAISE EXC_SEV_QUIT_BRANCH;
7737            ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
7738            THEN
7739                 l_other_message := 'BOM_CMP_UUI_UNEXP_SKIP';
7740                 l_other_token_tbl(1).token_name := 'REVISED_COMPONENT_NAME';
7741                 l_other_token_tbl(1).token_value := l_rev_component_rec.component_item_name;
7742                 RAISE EXC_UNEXP_SKIP_OBJECT;
7743            END IF;
7744 
7745            -- Process Flow step 4(b): Convert user unique index to unique index II
7746            --
7747 
7748            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Converting user unique index to unique index II'); END IF;
7749            Bom_Val_To_Id.Rev_Component_UUI_To_UI2
7750                 ( p_rev_component_rec  => l_rev_component_rec
7751                 , p_rev_comp_unexp_rec => l_rev_comp_unexp_rec
7752                 , x_rev_comp_unexp_rec => l_rev_comp_unexp_rec
7753                 , x_Mesg_Token_Tbl     => l_Mesg_Token_Tbl
7754                 , x_other_message      => l_other_message
7755                 , x_other_token_tbl    => l_other_token_tbl
7756                 , x_Return_Status      => l_return_status
7757                 );
7758 
7759            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
7760 
7761            IF l_return_status = Error_Handler.G_STATUS_ERROR
7762            THEN
7763                 RAISE EXC_SEV_QUIT_SIBLINGS;
7764            ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
7765            THEN
7766                 l_other_message := 'ENG_CMP_UUI_UNEXP_SKIP';
7767                 l_other_token_tbl(1).token_name := 'REVISED_COMPONENT_NAME';
7768                 l_other_token_tbl(1).token_value := l_rev_component_rec.component_item_name;
7769                 RAISE EXC_UNEXP_SKIP_OBJECT;
7770            END IF;
7771 
7772            IF Bom_Globals.Get_Debug = 'Y' THEN
7773            Error_Handler.Write_Debug('Converting user unique index to unique index II for Bill And Rev Seq Id');
7774            END IF;
7775 
7776            ENG_Val_To_Id.BillAndRevitem_UUI_To_UI
7777            ( p_revised_item_name        => l_rev_component_rec.revised_item_name
7778            , p_revised_item_id          => l_rev_comp_unexp_rec.revised_item_id
7779            , p_alternate_bom_code       => l_rev_component_rec.alternate_bom_code -- Bug 2429272 Change 4
7780            , p_item_revision            => l_rev_component_rec.new_revised_item_revision
7781            , p_effective_date           => l_rev_component_rec.start_effective_date
7782            , p_change_notice            => l_rev_component_rec.eco_name
7783            , p_organization_id          => l_rev_comp_unexp_rec.organization_id
7784            , p_new_routing_revision     => l_rev_component_rec.new_routing_revision
7785            , p_from_end_item_number     => l_rev_component_rec.from_end_item_unit_number
7786            , p_entity_processed         => 'RC'
7787            , p_component_item_name      => l_rev_component_rec.component_item_name
7788            , p_transaction_type         => l_rev_component_rec.transaction_type
7789            , x_revised_item_sequence_id => l_rev_comp_unexp_rec.revised_item_sequence_id
7790            , x_bill_sequence_id         => l_rev_comp_unexp_rec.bill_sequence_id
7791            , x_component_sequence_id    => l_dummy
7792            , x_Mesg_Token_Tbl           => l_Mesg_Token_Tbl
7793            , x_other_message            => l_other_message
7794            , x_other_token_tbl          => l_other_token_tbl
7795            , x_Return_Status            => l_return_status
7796           ) ;
7797 
7798            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status) ;
7799            END IF;
7800 
7801            IF l_return_status = Error_Handler.G_STATUS_ERROR
7802            THEN
7803                 RAISE EXC_SEV_QUIT_SIBLINGS;
7804            ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
7805            THEN
7806                 l_other_message := 'ENG_CMP_UUI_UNEXP_SKIP';
7807                 l_other_token_tbl(1).token_name := 'REVISED_COMPONENT_NAME';
7808                 l_other_token_tbl(1).token_value := l_rev_component_rec.component_item_name;
7809                 RAISE EXC_UNEXP_SKIP_OBJECT;
7810            END IF;
7811 
7812 
7813            BOM_Globals.Set_Unit_Controlled_Item
7814            ( p_inventory_item_id => l_rev_comp_unexp_rec.revised_item_id
7815            , p_organization_id  => l_rev_comp_unexp_rec.organization_id
7816            );
7817 
7818            BOM_Globals.Set_Unit_Controlled_Component
7819            ( p_inventory_item_id => l_rev_comp_unexp_rec.component_item_id
7820            , p_organization_id  => l_rev_comp_unexp_rec.organization_id
7821            );
7822 
7823            -- Process Flow step 5: Verify Revised Component's existence
7824            --
7825 
7826            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Check existence'); END IF;
7827            Bom_Validate_Bom_Component.Check_Existence
7828                 (  p_rev_component_rec          => l_rev_component_rec
7829                 ,  p_rev_comp_unexp_rec         => l_rev_comp_unexp_rec
7830                 ,  x_old_rev_component_rec      => l_old_rev_component_rec
7831                 ,  x_old_rev_comp_unexp_rec     => l_old_rev_comp_unexp_rec
7832                 ,  x_Mesg_Token_Tbl             => l_Mesg_Token_Tbl
7833                 ,  x_return_status              => l_Return_Status
7834                 );
7835 
7836            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
7837 
7838            IF l_return_status = Error_Handler.G_STATUS_ERROR
7839            THEN
7840                 l_other_message := 'BOM_CMP_EXS_SEV_ERROR';
7841                 l_other_token_tbl(1).token_name := 'REVISED_COMPONENT_NAME';
7842                 l_other_token_tbl(1).token_value := l_rev_component_rec.component_item_name;
7843                 l_other_token_tbl(2).token_name := 'REVISED_ITEM_NAME';
7844                 l_other_token_tbl(2).token_value := l_rev_component_rec.revised_item_name;
7845                 RAISE EXC_SEV_QUIT_BRANCH;
7846            ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
7847            THEN
7848                 l_other_message := 'BOM_CMP_EXS_UNEXP_SKIP';
7849                 l_other_token_tbl(1).token_name := 'REVISED_COMPONENT_NAME';
7850                 l_other_token_tbl(1).token_value := l_rev_component_rec.component_item_name;
7851                 l_other_token_tbl(2).token_name := 'REVISED_ITEM_NAME';
7852                 l_other_token_tbl(2).token_value := l_rev_component_rec.revised_item_name
7853 ;
7854                 RAISE EXC_UNEXP_SKIP_OBJECT;
7855            END IF;
7856 
7857            -- Process Flow step 6: Check lineage
7858            --
7859 
7860            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Check lineage');          END IF;
7861            Bom_Validate_Bom_Component.Check_Lineage
7862                 (  p_rev_component_rec          => l_rev_component_rec
7863                 ,  p_rev_comp_unexp_rec         => l_rev_comp_unexp_rec
7864                 ,  x_Mesg_Token_Tbl             => l_Mesg_Token_Tbl
7865                 ,  x_return_status              => l_Return_Status
7866                 );
7867 
7868            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
7869 
7870            IF l_return_status = Error_Handler.G_STATUS_ERROR
7871            THEN
7872                    l_other_message := 'BOM_CMP_LIN_SEV_SKIP';
7873                    l_other_token_tbl(1).token_name := 'REVISED_COMPONENT_NAME';
7874                    l_other_token_tbl(1).token_value := l_rev_component_rec.component_item_name;
7875                    RAISE EXC_SEV_QUIT_BRANCH;
7876            ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
7877            THEN
7878                    l_other_message := 'ENG_CMP_LIN_UNEXP_SKIP';
7879                    l_other_token_tbl(1).token_name := 'REVISED_COMPONENT_NAME';
7880                    l_other_token_tbl(1).token_value := l_rev_component_rec.component_item_name;
7881                    RAISE EXC_UNEXP_SKIP_OBJECT;
7882            END IF;
7883 
7884            -- Process Flow step 7: Is Revised Component record an orphan ?
7885 
7886            IF NOT l_item_parent_exists
7887            THEN
7888 
7889                 -- Process Flow step 8(a and b): Is ECO impl/cancl, or in wkflw process ?
7890                 --
7891 
7892                 ENG_Validate_ECO.Check_Access
7893                 (  p_change_notice      => l_rev_component_rec.ECO_Name
7894                 ,  p_organization_id    => l_rev_comp_unexp_rec.organization_id
7895                 , p_Mesg_Token_Tbl      => l_Mesg_Token_Tbl
7896                 , x_Mesg_Token_Tbl      => l_Mesg_Token_Tbl
7897                 , x_Return_Status       => l_return_status
7898                 );
7899 
7900                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
7901 
7902                 IF l_return_status = Error_Handler.G_STATUS_ERROR
7903                 THEN
7904                         l_other_message := 'BOM_CMP_ECOACC_FAT_FATAL';
7905                         l_other_token_tbl(1).token_name := 'REVISED_COMPONENT_NAME';
7906                         l_other_token_tbl(1).token_value := l_rev_component_rec.component_item_name;
7907                         l_return_status := 'F';
7908                         RAISE EXC_FAT_QUIT_OBJECT;
7909                 ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
7910                 THEN
7911                         l_other_message := 'BOM_CMP_ECOACC_UNEXP_SKIP';
7912                         l_other_token_tbl(1).token_name := 'REVISED_COMPONENT_NAME';
7913                         l_other_token_tbl(1).token_value := l_rev_component_rec.component_item_name;
7914                         RAISE EXC_UNEXP_SKIP_OBJECT;
7915                 END IF;
7916 
7917                 -- Process Flow step 9(a and b): check that user has access to revised item
7918                 --
7919 
7920                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Check access'); END IF;
7921                 ENG_Validate_Revised_Item.Check_Access
7922                 (  p_change_notice      => l_rev_component_rec.ECO_Name
7923                 ,  p_organization_id    => l_rev_comp_unexp_rec.organization_id
7924                 ,  p_revised_item_id    => l_rev_comp_unexp_rec.revised_item_id
7925                 ,  p_new_item_revision  => l_rev_component_rec.new_revised_item_revision
7926                 ,  p_effectivity_date   => l_rev_component_rec.start_effective_date
7927                 ,  p_new_routing_revsion   => l_rev_component_rec.new_routing_revision  -- Added by MK on 11/02/00
7928                 ,  p_from_end_item_number  => l_rev_component_rec.from_end_item_unit_number -- Added by MK on 11/02/00
7929                 ,  p_revised_item_name  => l_rev_component_rec.revised_item_name
7930                 ,  p_entity_processed   => 'RC'
7931                 ,  p_alternate_bom_code => l_rev_component_rec.alternate_bom_code -- Bug 4210718
7932                 ,  p_Mesg_Token_Tbl     => l_Mesg_Token_Tbl
7933                 ,  x_Mesg_Token_Tbl     => l_Mesg_Token_Tbl
7934                 ,  x_return_status      => l_Return_Status
7935                 );
7936 
7937                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
7938                 IF l_return_status = Error_Handler.G_STATUS_ERROR
7939                 THEN
7940                         l_other_message := 'BOM_CMP_RITACC_FAT_FATAL';
7941                         l_other_token_tbl(1).token_name := 'REVISED_COMPONENT_NAME';
7942                         l_other_token_tbl(1).token_value := l_rev_component_rec.component_item_name;
7943                         l_return_status := 'F';
7944                         RAISE EXC_FAT_QUIT_SIBLINGS;
7945                 ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
7946                 THEN
7947                         l_other_message := 'BOM_CMP_RITACC_UNEXP_SKIP';
7948                         l_other_token_tbl(1).token_name := 'REVISED_COMPONENT_NAME';
7949                         l_other_token_tbl(1).token_value := l_rev_component_rec.component_item_name;
7950                         RAISE EXC_UNEXP_SKIP_OBJECT;
7951                 END IF;
7952 
7953                 -- Process Flow step 10: check that user has access to revised component
7954                 --
7955 
7956                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Check access'); END IF;
7957                 Bom_Validate_Bom_Component.Check_Access
7958                 (  p_change_notice      => l_rev_component_rec.ECO_Name
7959                 ,  p_organization_id    => l_rev_comp_unexp_rec.organization_id
7960                 ,  p_revised_item_id    => l_rev_comp_unexp_rec.revised_item_id
7961                 ,  p_new_item_revision  => l_rev_component_rec.new_revised_item_revision
7962                 ,  p_effectivity_date   => l_rev_component_rec.start_effective_date
7963                 ,  p_new_routing_revsion  => l_rev_component_rec.new_routing_revision -- Added by MK on 11/02/00
7964                 ,  p_from_end_item_number => l_rev_component_rec.from_end_item_unit_number -- Added by MK on 11/02/00
7965                 ,  p_revised_item_name  => l_rev_component_rec.revised_item_name
7966                 ,  p_component_item_id  => l_rev_comp_unexp_rec.component_item_id
7967                 ,  p_operation_seq_num  => l_rev_component_rec.operation_sequence_number
7968                 ,  p_bill_sequence_id   => l_rev_comp_unexp_rec.bill_sequence_id
7969                 ,  p_component_name     => l_rev_component_rec.component_item_name
7970                 ,  p_Mesg_Token_Tbl     => l_Mesg_Token_Tbl
7971                 ,  x_Mesg_Token_Tbl     => l_Mesg_Token_Tbl
7972                 ,  x_return_status      => l_Return_Status
7973                 );
7974 
7975                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
7976 
7977                 IF l_return_status = Error_Handler.G_STATUS_ERROR
7978                 THEN
7979                         l_other_message := 'BOM_CMP_ACCESS_FAT_FATAL';
7980                         l_other_token_tbl(1).token_name := 'REVISED_COMPONENT_NAME';
7981                         l_other_token_tbl(1).token_value := l_rev_component_rec.component_item_name;
7982                         l_return_status := 'F';
7983                         RAISE EXC_FAT_QUIT_BRANCH;
7984                 ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
7985                 THEN
7986                         l_other_message := 'BOM_CMP_ACCESS_UNEXP_SKIP';
7987                         l_other_token_tbl(1).token_name := 'REVISED_COMPONENT_NAME';
7988                         l_other_token_tbl(1).token_value := l_rev_component_rec.component_item_name;
7989                         RAISE EXC_UNEXP_SKIP_OBJECT;
7990                 END IF;
7991 
7992            ELSE
7993            -- Bug No: 5246049
7994            -- Structure policy check should happen even if parent exists
7995                 l_structure_type_id := NULL;
7996                 l_strc_cp_not_allowed := 2;
7997 
7998                 ENG_Validate_Revised_Item.Check_Structure_Type_Policy
7999                     ( p_inventory_item_id   => l_rev_comp_unexp_rec.revised_item_id
8000                     , p_organization_id     => l_rev_comp_unexp_rec.organization_id
8001                     , p_alternate_bom_code  => l_rev_component_rec.alternate_bom_code
8002                     , x_structure_type_id   => l_structure_type_id
8003                     , x_strc_cp_not_allowed => l_strc_cp_not_allowed
8004                     );
8005                 IF l_strc_cp_not_allowed = 1
8006                 THEN
8007                         l_return_status := Error_Handler.G_STATUS_ERROR ;
8008                         l_Token_Tbl.DELETE;
8009                         l_Token_Tbl(1).token_name := 'STRUCTURE_NAME';
8010                         l_Token_Tbl(1).token_value := l_rev_component_rec.alternate_bom_code;
8011 
8012                         Error_Handler.Add_Error_Token
8013                         ( p_message_name       => 'ENG_BILL_CHANGES_NOT_ALLOWED'
8014                         , p_mesg_token_tbl     => l_Mesg_Token_Tbl
8015                         , p_token_tbl          => l_Token_Tbl
8016                         , x_Mesg_Token_Tbl     => l_Mesg_Token_Tbl
8017                         );
8018 
8019                         l_other_message := 'BOM_CMP_QRY_CSEV_SKIP';
8020                         l_other_token_tbl(1).token_name := 'REVISED_COMPONENT_NAME';
8021                         l_other_token_tbl(1).token_value := l_rev_component_rec.component_item_name;
8022                         RAISE EXC_SEV_SKIP_BRANCH;
8023                 END IF;
8024            END IF;
8025 
8026            -- Process Flow step 11: Value to Id conversions
8027            --
8028 
8029            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Value-id conversions'); END IF;
8030            Bom_Val_To_Id.Rev_Component_VID
8031                 ( x_Return_Status       => l_return_status
8032                 , x_Mesg_Token_Tbl      => l_Mesg_Token_Tbl
8033                 , p_rev_comp_unexp_Rec  => l_rev_comp_unexp_rec
8034                 , x_rev_comp_unexp_Rec  => l_rev_comp_unexp_rec
8035                 , p_rev_component_Rec   => l_rev_component_rec
8036                 );
8037 
8038            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
8039 
8040            IF l_return_status = Error_Handler.G_STATUS_ERROR
8041            THEN
8042                 IF l_rev_component_rec.transaction_type = 'CREATE'
8043                 THEN
8044                         l_other_message := 'BOM_CMP_VID_CSEV_SKIP';
8045                         l_other_token_tbl(1).token_name := 'REVISED_COMPONENT_NAME';
8046                         l_other_token_tbl(1).token_value := l_rev_component_rec.component_item_name;
8047                         RAISE EXC_SEV_SKIP_BRANCH;
8048                 ELSE
8049                         RAISE EXC_SEV_QUIT_RECORD;
8050                 END IF;
8051            ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
8052            THEN
8053                 l_other_message := 'BOM_CMP_VID_UNEXP_SKIP';
8054                 l_other_token_tbl(1).token_name := 'REVISED_COMPONENT_NAME';
8055                 l_other_token_tbl(1).token_value := l_rev_component_rec.component_item_name;
8056                 RAISE EXC_UNEXP_SKIP_OBJECT;
8057            ELSIF l_return_status ='S' AND
8058                 l_Mesg_Token_Tbl.COUNT <>0
8059            THEN
8060                 Eco_Error_Handler.Log_Error
8061                 (  p_rev_component_tbl  => x_rev_component_tbl
8062                 ,  p_ref_designator_tbl => x_ref_designator_tbl
8063                 ,  p_sub_component_tbl  => x_sub_component_tbl
8064                 ,  p_mesg_token_tbl     => l_mesg_token_tbl
8065                 ,  p_error_status       => 'W'
8066                 ,  p_error_level        => 4
8067                 ,  p_entity_index       => I
8068                 ,  x_eco_rec            => l_eco_rec
8069                 ,  x_eco_revision_tbl   => l_eco_revision_tbl
8070                 ,  x_revised_item_tbl   => l_revised_item_tbl
8071                 ,  x_rev_component_tbl  => x_rev_component_tbl
8072                 ,  x_ref_designator_tbl => x_ref_designator_tbl
8073                 ,  x_sub_component_tbl  => x_sub_component_tbl
8074                 ,  x_rev_operation_tbl   => l_rev_operation_tbl   --L1
8075                 ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl --L1
8076                 ,  x_rev_sub_resource_tbl=> l_rev_sub_resource_tbl--L1
8077                 );
8078            END IF;
8079 
8080            -- Process Flow step 12: Check required fields exist
8081            -- (also includes conditionally required fields)
8082            --
8083 
8084            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Check required fields'); END IF;
8085            Bom_Validate_Bom_Component.Check_Required
8086                 ( x_return_status              => l_return_status
8087                 , x_Mesg_Token_Tbl             => l_Mesg_Token_Tbl
8088                 , p_rev_component_rec          => l_rev_component_rec
8089                 );
8090 
8091            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
8092 
8093            IF l_return_status = Error_Handler.G_STATUS_ERROR
8094            THEN
8095                 IF l_rev_component_rec.transaction_type = 'CREATE'
8096                 THEN
8097                         l_other_message := 'BOM_CMP_REQ_CSEV_SKIP';
8098                         l_other_token_tbl(1).token_name := 'REVISED_COMPONENT_NAME';
8099                         l_other_token_tbl(1).token_value := l_rev_component_rec.component_item_name;
8100                         RAISE EXC_SEV_SKIP_BRANCH;
8101                 ELSE
8102                         RAISE EXC_SEV_QUIT_RECORD;
8103                 END IF;
8104            ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
8105            THEN
8106                 l_other_message := 'BOM_CMP_REQ_UNEXP_SKIP';
8107                 l_other_token_tbl(1).token_name := 'REVISED_COMPONENT_NAME';
8108                 l_other_token_tbl(1).token_value := l_rev_component_rec.component_item_name;
8109                 RAISE EXC_UNEXP_SKIP_OBJECT;
8110            ELSIF l_return_status ='S' AND
8111                 l_Mesg_Token_Tbl.COUNT <>0
8112            THEN
8113                 Eco_Error_Handler.Log_Error
8114                 (  p_rev_component_tbl  => x_rev_component_tbl
8115                 ,  p_ref_designator_tbl => x_ref_designator_tbl
8116                 ,  p_sub_component_tbl  => x_sub_component_tbl
8117                 ,  p_mesg_token_tbl     => l_mesg_token_tbl
8118                 ,  p_error_status       => 'W'
8119                 ,  p_error_level        => 4
8120                 ,  p_entity_index       => I
8121                 ,  x_eco_rec            => l_eco_rec
8122                 ,  x_eco_revision_tbl   => l_eco_revision_tbl
8123                 ,  x_revised_item_tbl   => l_revised_item_tbl
8124                 ,  x_rev_component_tbl  => x_rev_component_tbl
8125                 ,  x_ref_designator_tbl => x_ref_designator_tbl
8126                 ,  x_sub_component_tbl  => x_sub_component_tbl
8127                 ,  x_rev_operation_tbl   => l_rev_operation_tbl   --L1
8128                 ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl --L1
8129                 ,  x_rev_sub_resource_tbl=> l_rev_sub_resource_tbl--L1
8130                 );
8131            END IF;
8132 
8133            -- Process Flow step 13: Attribute Validation for CREATE and UPDATE
8134            --
8135 
8136            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Attribute Validation'); END IF;
8137            IF l_rev_component_rec.Transaction_Type IN
8138                 (ENG_GLOBALS.G_OPR_CREATE, ENG_GLOBALS.G_OPR_UPDATE)
8139            THEN
8140                 Bom_Validate_Bom_Component.Check_Attributes
8141                 ( x_return_status              => l_return_status
8142                 , x_Mesg_Token_Tbl             => l_Mesg_Token_Tbl
8143                 , p_rev_component_rec          => l_rev_component_rec
8144                 , p_rev_comp_unexp_rec         => l_rev_comp_unexp_rec
8145                 );
8146 
8147                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
8148 
8149                 IF l_return_status = Error_Handler.G_STATUS_ERROR
8150                 THEN
8151                    IF l_rev_component_rec.transaction_type = 'CREATE'
8152                    THEN
8153                         l_other_message := 'BOM_CMP_ATTVAL_CSEV_SKIP';
8154                         l_other_token_tbl(1).token_name := 'REVISED_COMPONENT_NAME';
8155                         l_other_token_tbl(1).token_value := l_rev_component_rec.component_item_name;
8156                         RAISE EXC_SEV_QUIT_BRANCH;
8157                    ELSE
8158                         RAISE EXC_SEV_QUIT_RECORD;
8159                    END IF;
8160                 ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
8161                 THEN
8162                    l_other_message := 'BOM_CMP_ATTVAL_UNEXP_SKIP';
8163                    l_other_token_tbl(1).token_name := 'REVISED_COMPONENT_NAME';
8164                    l_other_token_tbl(1).token_value := l_rev_component_rec.component_item_name;
8165                    RAISE EXC_UNEXP_SKIP_OBJECT;
8166                 ELSIF l_return_status ='S' AND
8167                       l_Mesg_Token_Tbl.COUNT <>0
8168                 THEN
8169                    Eco_Error_Handler.Log_Error
8170                         (  p_rev_component_tbl  => x_rev_component_tbl
8171                         ,  p_ref_designator_tbl => x_ref_designator_tbl
8172                         ,  p_sub_component_tbl  => x_sub_component_tbl
8173                         ,  p_mesg_token_tbl     => l_mesg_token_tbl
8174                         ,  p_error_status       => 'W'
8175                         ,  p_error_level        => 4
8176                         ,  p_entity_index       => I
8177                         ,  x_eco_rec            => l_eco_rec
8178                         ,  x_eco_revision_tbl   => l_eco_revision_tbl
8179                         ,  x_revised_item_tbl   => l_revised_item_tbl
8180                         ,  x_rev_component_tbl  => x_rev_component_tbl
8181                         ,  x_ref_designator_tbl => x_ref_designator_tbl
8182                         ,  x_sub_component_tbl  => x_sub_component_tbl
8183                         ,  x_rev_operation_tbl   => l_rev_operation_tbl   --L1
8184                         ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl --L1
8185                         ,  x_rev_sub_resource_tbl=> l_rev_sub_resource_tbl--L1
8186                         );
8187                 END IF;
8188            END IF;
8189 
8190            IF (l_rev_component_rec.transaction_type = ENG_GLOBALS.G_OPR_CREATE
8191                AND l_rev_component_rec.acd_type IN ( 2, 3 ))
8192            THEN
8193 
8194                 Bom_Bom_Component_Util.Query_Row
8195                    ( p_component_item_id
8196                                 => l_rev_comp_unexp_rec.component_item_id
8197                    , p_operation_sequence_number
8198                                 => l_rev_component_rec.old_operation_sequence_number
8199                    , p_effectivity_date
8200                                 => l_rev_component_rec.old_effectivity_date
8201                    , p_from_end_item_number
8202                                => l_rev_component_rec.old_from_end_item_unit_number
8203                    , p_bill_sequence_id
8204                                 => l_rev_comp_unexp_rec.bill_sequence_id
8205                    , x_Rev_Component_Rec
8206                                 => l_old_rev_component_rec
8207                    , x_Rev_Comp_Unexp_Rec
8208                                 => l_old_rev_comp_unexp_rec
8209                    , x_return_status
8210                                 => l_return_status
8211                    , p_mesg_token_tbl   =>
8212                         l_mesg_token_tbl
8213                    , x_mesg_token_tbl   => l_mesg_token_tbl
8214                    );
8215 
8216                 IF l_return_status <> Eng_Globals.G_RECORD_FOUND
8217                 THEN
8218                         l_return_status := Error_Handler.G_STATUS_ERROR ;
8219                         l_Token_Tbl(1).token_name := 'REVISED_COMPONENT_NAME';
8220                         l_Token_Tbl(1).token_value := l_rev_component_rec.component_item_name;
8221 
8222                         Error_Handler.Add_Error_Token
8223                         ( p_message_name       => 'ENG_CMP_CREATE_REC_NOT_FOUND' --'BOM_CMP_CREATE_REC_NOT_FOUND' -- Bug 3612008 :Modified incorrect message_name
8224                         , p_mesg_token_tbl     => l_Mesg_Token_Tbl
8225                         , p_token_tbl          => l_Token_Tbl
8226                         , x_Mesg_Token_Tbl     => l_Mesg_Token_Tbl
8227                         );
8228 
8229                         l_other_message := 'BOM_CMP_QRY_CSEV_SKIP';
8230                         l_other_token_tbl(1).token_name := 'REVISED_COMPONENT_NAME';
8231                         l_other_token_tbl(1).token_value := l_rev_component_rec.component_item_name;
8232                         RAISE EXC_SEV_SKIP_BRANCH;
8233                 ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
8234                 THEN
8235                         l_other_message := 'BOM_CMP_QRY_UNEXP_SKIP';
8236                         l_other_token_tbl(1).token_name := 'REVISED_COMPONENT_NAME';
8237                         l_other_token_tbl(1).token_value := l_rev_component_rec.component_item_name;
8238                    RAISE EXC_UNEXP_SKIP_OBJECT;
8239                 END IF;
8240             END IF;
8241 
8242             -- Process flow step 15 - Populate NULL columns for Update and
8243             -- Delete, and Creates with ACD_Type 'Add'.
8244 
8245             IF (l_rev_component_rec.transaction_type = ENG_GLOBALS.G_OPR_CREATE
8246                 AND l_rev_component_rec.acd_type = 2)
8247                OR
8248                l_rev_component_rec.transaction_type IN (ENG_GLOBALS.G_OPR_UPDATE,
8249                                                         ENG_GLOBALS.G_OPR_DELETE)
8250             THEN
8251                     IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Populate NULL columns'); END IF;
8252                     Bom_Default_Bom_Component.Populate_Null_Columns
8253                     (   p_rev_component_rec     => l_rev_Component_Rec
8254                     ,   p_old_rev_Component_Rec => l_old_rev_Component_Rec
8255                     ,   p_rev_comp_unexp_rec    => l_rev_comp_unexp_rec
8256                     ,   p_old_rev_comp_unexp_rec=> l_old_rev_comp_unexp_rec
8257                     ,   x_rev_Component_Rec     => l_rev_Component_Rec
8258                     ,   x_rev_comp_unexp_rec    => l_rev_comp_unexp_rec
8259                     );
8260 
8261            ELSIF l_rev_component_rec.Transaction_Type = ENG_GLOBALS.G_OPR_CREATE THEN
8262 
8263                 -- Process Flow step 16: Default missing values for Operation CREATE
8264                 --
8265 
8266                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Attribute Defaulting'); END IF;
8267                 Bom_Default_Bom_Component.Attribute_Defaulting
8268                 (   p_rev_component_rec         => l_rev_component_rec
8269                 ,   p_rev_comp_unexp_rec        => l_rev_comp_unexp_rec
8270                 ,   x_rev_component_rec         => l_rev_component_rec
8271                 ,   x_rev_comp_unexp_rec        => l_rev_comp_unexp_rec
8272                 ,   x_Mesg_Token_Tbl            => l_Mesg_Token_Tbl
8273                 ,   x_return_status             => l_return_status
8274                 );
8275 
8276                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
8277 
8278                 IF l_return_status = Error_Handler.G_STATUS_ERROR
8279                 THEN
8280                         l_other_message := 'BOM_CMP_ATTDEF_CSEV_SKIP';
8281                         l_other_token_tbl(1).token_name := 'REVISED_COMPONENT_NAME';
8282                         l_other_token_tbl(1).token_value := l_rev_component_rec.component_item_name;
8283                         RAISE EXC_SEV_SKIP_BRANCH;
8284                 ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
8285                 THEN
8286                         l_other_message := 'BOM_CMP_ATTDEF_UNEXP_SKIP';
8287                         l_other_token_tbl(1).token_name := 'REVISED_COMPONENT_NAME';
8288                         l_other_token_tbl(1).token_value := l_rev_component_rec.component_item_name;
8289                         RAISE EXC_UNEXP_SKIP_OBJECT;
8290                 ELSIF l_return_status ='S' AND
8291                         l_Mesg_Token_Tbl.COUNT <>0
8292                 THEN
8293                         Eco_Error_Handler.Log_Error
8294                         (  p_rev_component_tbl  => x_rev_component_tbl
8295                         ,  p_ref_designator_tbl => x_ref_designator_tbl
8296                         ,  p_sub_component_tbl  => x_sub_component_tbl
8297                         ,  p_mesg_token_tbl     => l_mesg_token_tbl
8298                         ,  p_error_status       => 'W'
8299                         ,  p_error_level        => 4
8300                         ,  p_entity_index       => I
8301                         ,  x_eco_rec            => l_eco_rec
8302                         ,  x_eco_revision_tbl   => l_eco_revision_tbl
8303                         ,  x_revised_item_tbl   => l_revised_item_tbl
8304                         ,  x_rev_component_tbl  => x_rev_component_tbl
8305                         ,  x_ref_designator_tbl => x_ref_designator_tbl
8306                         ,  x_sub_component_tbl  => x_sub_component_tbl
8307                         ,  x_rev_operation_tbl   => l_rev_operation_tbl   --L1
8308                         ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl --L1
8309                         ,  x_rev_sub_resource_tbl=> l_rev_sub_resource_tbl--L1
8310                         );
8311                 END IF;
8312            END IF;
8313 
8314            -- Process Flow step 17: Entity defaulting for CREATE and UPDATE
8315            --
8316 
8317            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Entity defaulting'); END IF;
8318            IF l_rev_component_rec.Transaction_Type IN
8319                 (ENG_GLOBALS.G_OPR_CREATE, ENG_GLOBALS.G_OPR_UPDATE)
8320            THEN
8321                 Bom_Default_Bom_Component.Entity_Defaulting
8322                 (   p_rev_component_rec         => l_rev_component_rec
8323                 ,   p_old_rev_component_rec     => l_old_rev_component_rec
8324                 ,   x_rev_component_rec         => l_rev_component_rec
8325                 );
8326 
8327                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
8328 
8329                 IF l_return_status = Error_Handler.G_STATUS_ERROR
8330                 THEN
8331                    IF l_rev_component_rec.transaction_type = 'CREATE'
8332                    THEN
8333                         l_other_message := 'BOM_CMP_ENTDEF_CSEV_SKIP';
8334                         l_other_token_tbl(1).token_name := 'REVISED_COMPONENT_NAME';
8335                         l_other_token_tbl(1).token_value := l_rev_component_rec.component_item_name;
8336                         RAISE EXC_SEV_SKIP_BRANCH;
8337                    ELSE
8338                         RAISE EXC_SEV_QUIT_RECORD;
8339                    END IF;
8340                 ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
8341                 THEN
8342                         l_other_message := 'BOM_CMP_ENTDEF_UNEXP_SKIP';
8343                         l_other_token_tbl(1).token_name := 'REVISED_COMPONENT_NAME';
8344                         l_other_token_tbl(1).token_value := l_rev_component_rec.component_item_name;
8345                         RAISE EXC_UNEXP_SKIP_OBJECT;
8346                 ELSIF l_return_status ='S' AND
8347                         l_Mesg_Token_Tbl.COUNT <>0
8348                 THEN
8349                         Eco_Error_Handler.Log_Error
8350                         (  p_rev_component_tbl  => x_rev_component_tbl
8351                         ,  p_ref_designator_tbl => x_ref_designator_tbl
8352                         ,  p_sub_component_tbl  => x_sub_component_tbl
8353                         ,  p_mesg_token_tbl     => l_mesg_token_tbl
8354                         ,  p_error_status       => 'W'
8355                         ,  p_error_level        => 4
8356                         ,  p_entity_index       => I
8357                         ,  x_eco_rec            => l_eco_rec
8358                         ,  x_eco_revision_tbl   => l_eco_revision_tbl
8359                         ,  x_revised_item_tbl   => l_revised_item_tbl
8360                         ,  x_rev_component_tbl  => x_rev_component_tbl
8361                         ,  x_ref_designator_tbl => x_ref_designator_tbl
8362                         ,  x_sub_component_tbl  => x_sub_component_tbl
8363                         ,  x_rev_operation_tbl   => l_rev_operation_tbl   --L1
8364                         ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl --L1
8365                         ,  x_rev_sub_resource_tbl=> l_rev_sub_resource_tbl--L1
8366                         );
8367                 END IF;
8368            END IF;
8369 
8370            -- Process Flow step 18 - Entity Level Validation
8371            --
8372 
8373            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Entity validation'); END IF;
8374            Bom_Validate_Bom_Component.Check_Entity
8375                 (  p_rev_component_rec          => l_rev_component_rec
8376                 ,  p_rev_comp_unexp_rec         => l_rev_comp_unexp_rec
8377                 ,  p_old_rev_component_rec      => l_old_rev_component_rec
8378                 ,  p_old_rev_comp_unexp_rec     => l_old_rev_comp_unexp_rec
8379                 ,  x_Mesg_Token_Tbl             => l_Mesg_Token_Tbl
8380                 ,  x_return_status              => l_Return_Status
8381                 );
8382 
8383            --IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
8384 
8385            IF l_return_status = Error_Handler.G_STATUS_ERROR
8386            THEN
8387                 IF l_rev_component_rec.transaction_type = 'CREATE'
8388                 THEN
8389                         l_other_message := 'BOM_CMP_ENTVAL_CSEV_SKIP';
8390                         l_other_token_tbl(1).token_name := 'REVISED_COMPONENT_NAME';
8391                         l_other_token_tbl(1).token_value := l_rev_component_rec.component_item_name;
8392                         RAISE EXC_SEV_QUIT_BRANCH;
8393                 ELSE
8394                         RAISE EXC_SEV_QUIT_RECORD;
8395                 END IF;
8396            ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
8397            THEN
8398                 l_other_message := 'BOM_CMP_ENTVAL_UNEXP_SKIP';
8399                 l_other_token_tbl(1).token_name := 'REVISED_COMPONENT_NAME';
8400                 l_other_token_tbl(1).token_value := l_rev_component_rec.component_item_name;
8401                 RAISE EXC_UNEXP_SKIP_OBJECT;
8402            ELSIF l_return_status ='S' AND
8403                 l_Mesg_Token_Tbl.COUNT <>0
8404            THEN
8405                 Eco_Error_Handler.Log_Error
8406                 (  p_rev_component_tbl  => x_rev_component_tbl
8407                 ,  p_ref_designator_tbl => x_ref_designator_tbl
8408                 ,  p_sub_component_tbl  => x_sub_component_tbl
8409                 ,  p_mesg_token_tbl     => l_mesg_token_tbl
8410                 ,  p_error_status       => 'W'
8411                 ,  p_error_level        => 4
8412                 ,  p_entity_index       => I
8413                 ,  x_eco_rec            => l_eco_rec
8414                 ,  x_eco_revision_tbl   => l_eco_revision_tbl
8415                 ,  x_revised_item_tbl   => l_revised_item_tbl
8416                 ,  x_rev_component_tbl  => x_rev_component_tbl
8417                 ,  x_ref_designator_tbl => x_ref_designator_tbl
8418                 ,  x_sub_component_tbl  => x_sub_component_tbl
8419                 ,  x_rev_operation_tbl   => l_rev_operation_tbl   --L1
8420                 ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl --L1
8421                 ,  x_rev_sub_resource_tbl=> l_rev_sub_resource_tbl--L1
8422                 );
8423            END IF;
8424 
8425            -- Process Flow step 16 : Database Writes
8426            --
8427 
8428            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Writing to the database'); END IF;
8429            BOM_Globals.Set_BO_Identifier('ECO');  --bug 13849573
8430            Bom_Bom_Component_Util.Perform_Writes
8431                 (   p_rev_component_rec         => l_rev_component_rec
8432                 ,   p_rev_comp_unexp_rec        => l_rev_comp_unexp_rec
8433                 ,   x_Mesg_Token_Tbl            => l_Mesg_Token_Tbl
8434                 ,   x_return_status             => l_return_status
8435                 );
8436 
8437            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
8438 
8439            IF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
8440            THEN
8441                 l_other_message := 'BOM_CMP_WRITES_UNEXP_SKIP';
8442                 l_other_token_tbl(1).token_name := 'REVISED_COMPONENT_NAME';
8443                 l_other_token_tbl(1).token_value := l_rev_component_rec.component_item_name;
8444                 RAISE EXC_UNEXP_SKIP_OBJECT;
8445            ELSIF l_return_status ='S' AND
8446               l_Mesg_Token_Tbl.COUNT <>0
8447            THEN
8448                 Eco_Error_Handler.Log_Error
8449                 (  p_rev_component_tbl  => x_rev_component_tbl
8450                 ,  p_ref_designator_tbl => x_ref_designator_tbl
8451                 ,  p_sub_component_tbl  => x_sub_component_tbl
8452                 ,  p_mesg_token_tbl     => l_mesg_token_tbl
8453                 ,  p_error_status       => 'W'
8454                 ,  p_error_level        => 4
8455                 ,  p_entity_index       => I
8456                 ,  x_eco_rec            => l_eco_rec
8457                 ,  x_eco_revision_tbl   => l_eco_revision_tbl
8458                 ,  x_revised_item_tbl   => l_revised_item_tbl
8459                 ,  x_rev_component_tbl  => x_rev_component_tbl
8460                 ,  x_ref_designator_tbl => x_ref_designator_tbl
8461                 ,  x_sub_component_tbl  => x_sub_component_tbl
8462                 ,  x_rev_operation_tbl   => l_rev_operation_tbl   --L1
8463                 ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl --L1
8464                 ,  x_rev_sub_resource_tbl=> l_rev_sub_resource_tbl--L1
8465                 );
8466            END IF;
8467 
8468 
8469                 -- END IF; -- END IF statement that checks RETURN STATUS
8470 
8471                 --  Load tables.
8472 
8473                 x_rev_component_tbl(I)          := l_rev_component_rec;
8474 
8475                 -- Indicate that children need to be processed
8476 
8477                 l_process_children := TRUE;
8478                 -- END IF;
8479 
8480 
8481         ELSE
8482 
8483 
8484 IF Bom_Globals.Get_Debug = 'Y' THEN
8485     Error_Handler.Write_Debug('This record does not patch with the parent that called it . . .  ') ;
8486     Error_Handler.Write_Debug('so may be this is an comp in another branch . . . '
8487                                || l_rev_component_rec.component_item_name ) ;
8488 END IF ;
8489 
8490                 l_process_children := FALSE;
8491 
8492         END IF; -- END IF statement that checks RETURN STATUS
8493 
8494 
8495     --  For loop exception handler.
8496 
8497 
8498     EXCEPTION
8499 
8500        WHEN EXC_SEV_QUIT_RECORD THEN
8501 
8502         Eco_Error_Handler.Log_Error
8503                 (  p_rev_component_tbl  => x_rev_component_tbl
8504                 ,  p_ref_designator_tbl => x_ref_designator_tbl
8505                 ,  p_sub_component_tbl  => x_sub_component_tbl
8506                 ,  p_mesg_token_tbl     => l_mesg_token_tbl
8507                 ,  p_error_status       => FND_API.G_RET_STS_ERROR
8508                 ,  p_error_scope        => Error_Handler.G_SCOPE_RECORD
8509                 ,  p_error_level        => 4
8510                 ,  p_entity_index       => I
8511                 ,  x_eco_rec            => l_eco_rec
8512                 ,  x_eco_revision_tbl   => l_eco_revision_tbl
8513                 ,  x_revised_item_tbl   => l_revised_item_tbl
8514                 ,  x_rev_component_tbl  => x_rev_component_tbl
8515                 ,  x_ref_designator_tbl => x_ref_designator_tbl
8516                 ,  x_sub_component_tbl  => x_sub_component_tbl
8517                 ,  x_rev_operation_tbl   => l_rev_operation_tbl   --L1
8518                 ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl --L1
8519                 ,  x_rev_sub_resource_tbl=> l_rev_sub_resource_tbl--L1
8520                 );
8521 
8522         l_process_children := TRUE;
8523 
8524         IF l_bo_return_status = 'S'
8525         THEN
8526                 l_bo_return_status     := l_return_status;
8527         END IF;
8528         x_return_status                := l_bo_return_status;
8529         x_Mesg_Token_Tbl               := l_Mesg_Token_Tbl;
8530         --x_rev_component_tbl            := l_rev_component_tbl;
8531         --x_ref_designator_tbl           := l_ref_designator_tbl;
8532         --x_sub_component_tbl            := l_sub_component_tbl;
8533 
8534        WHEN EXC_SEV_QUIT_BRANCH THEN
8535 
8536         Eco_Error_Handler.Log_Error
8537                 (  p_rev_component_tbl  => x_rev_component_tbl
8538                 ,  p_ref_designator_tbl => x_ref_designator_tbl
8539                 ,  p_sub_component_tbl  => x_sub_component_tbl
8540                 ,  p_mesg_token_tbl     => l_mesg_token_tbl
8541                 ,  p_error_status       => Error_Handler.G_STATUS_ERROR
8542                 ,  p_error_scope        => Error_Handler.G_SCOPE_CHILDREN
8543                 ,  p_other_status       => Error_Handler.G_STATUS_ERROR
8544                 ,  p_other_message      => l_other_message
8545                 ,  p_other_token_tbl    => l_other_token_tbl
8546                 ,  p_error_level        => 4
8547                 ,  p_entity_index       => I
8548                 ,  x_eco_rec            => l_eco_rec
8549                 ,  x_eco_revision_tbl   => l_eco_revision_tbl
8550                 ,  x_revised_item_tbl   => l_revised_item_tbl
8551                 ,  x_rev_component_tbl  => x_rev_component_tbl
8552                 ,  x_ref_designator_tbl => x_ref_designator_tbl
8553                 ,  x_sub_component_tbl  => x_sub_component_tbl
8554                 ,  x_rev_operation_tbl   => l_rev_operation_tbl   --L1
8555                 ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl --L1
8556                 ,  x_rev_sub_resource_tbl=> l_rev_sub_resource_tbl--L1
8557                 );
8558 
8559         l_process_children := FALSE;
8560 
8561         IF l_bo_return_status = 'S'
8562         THEN
8563                 l_bo_return_status     := l_return_status;
8564         END IF;
8565         x_return_status                := l_bo_return_status;
8566         x_Mesg_Token_Tbl               := l_Mesg_Token_Tbl;
8567         --x_rev_component_tbl            := l_rev_component_tbl;
8568         --x_ref_designator_tbl           := l_ref_designator_tbl;
8569         --x_sub_component_tbl            := l_sub_component_tbl;
8570 
8571        WHEN EXC_SEV_SKIP_BRANCH THEN
8572 
8573         Eco_Error_Handler.Log_Error
8574                 (  p_rev_component_tbl  => x_rev_component_tbl
8575                 ,  p_ref_designator_tbl => x_ref_designator_tbl
8576                 ,  p_sub_component_tbl  => x_sub_component_tbl
8577                 ,  p_mesg_token_tbl     => l_mesg_token_tbl
8578                 ,  p_error_status       => Error_Handler.G_STATUS_ERROR
8579                 ,  p_error_scope        => Error_Handler.G_SCOPE_CHILDREN
8580                 ,  p_other_status       => Error_Handler.G_STATUS_NOT_PICKED
8581                 ,  p_other_message      => l_other_message
8582                 ,  p_other_token_tbl    => l_other_token_tbl
8583                 ,  p_error_level        => 4
8584                 ,  p_entity_index       => I
8585                 ,  x_eco_rec            => l_eco_rec
8586                 ,  x_eco_revision_tbl   => l_eco_revision_tbl
8587                 ,  x_revised_item_tbl   => l_revised_item_tbl
8588                 ,  x_rev_component_tbl  => x_rev_component_tbl
8589                 ,  x_ref_designator_tbl => x_ref_designator_tbl
8590                 ,  x_sub_component_tbl  => x_sub_component_tbl
8591                 ,  x_rev_operation_tbl   => l_rev_operation_tbl   --L1
8592                 ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl --L1
8593                 ,  x_rev_sub_resource_tbl=> l_rev_sub_resource_tbl--L1
8594                 );
8595 
8596         l_process_children := FALSE;
8597 
8598         IF l_bo_return_status = 'S'
8599         THEN
8600                 l_bo_return_status     := l_return_status;
8601         END IF;
8602         x_return_status                := l_bo_return_status;
8603         x_Mesg_Token_Tbl               := l_Mesg_Token_Tbl;
8604         --x_rev_component_tbl            := l_rev_component_tbl;
8605         --x_ref_designator_tbl           := l_ref_designator_tbl;
8606         --x_sub_component_tbl            := l_sub_component_tbl;
8607 
8608        WHEN EXC_SEV_QUIT_SIBLINGS THEN
8609 
8610         Eco_Error_Handler.Log_Error
8611                 (  p_rev_component_tbl  => x_rev_component_tbl
8612                 ,  p_ref_designator_tbl => x_ref_designator_tbl
8613                 ,  p_sub_component_tbl  => x_sub_component_tbl
8614                 ,  p_mesg_token_tbl     => l_mesg_token_tbl
8615                 ,  p_error_status       => Error_Handler.G_STATUS_ERROR
8616                 ,  p_error_scope        => Error_Handler.G_SCOPE_SIBLINGS
8617                 ,  p_other_status       => Error_Handler.G_STATUS_ERROR
8618                 ,  p_other_message      => l_other_message
8619                 ,  p_other_token_tbl    => l_other_token_tbl
8620                 ,  p_error_level        => 4
8621                 ,  p_entity_index       => I
8622                 ,  x_eco_rec            => l_eco_rec
8623                 ,  x_eco_revision_tbl   => l_eco_revision_tbl
8624                 ,  x_revised_item_tbl   => l_revised_item_tbl
8625                 ,  x_rev_component_tbl  => x_rev_component_tbl
8626                 ,  x_ref_designator_tbl => x_ref_designator_tbl
8627                 ,  x_sub_component_tbl  => x_sub_component_tbl
8628                 ,  x_rev_operation_tbl   => l_rev_operation_tbl   --L1
8629                 ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl --L1
8630                 ,  x_rev_sub_resource_tbl=> l_rev_sub_resource_tbl--L1
8631                 );
8632 
8633         l_process_children := FALSE;
8634 
8635         IF l_bo_return_status = 'S'
8636         THEN
8637                 l_bo_return_status     := l_return_status;
8638         END IF;
8639         x_return_status                := l_bo_return_status;
8640         x_Mesg_Token_Tbl               := l_Mesg_Token_Tbl;
8641         --x_rev_component_tbl            := l_rev_component_tbl;
8642         --x_ref_designator_tbl           := l_ref_designator_tbl;
8643         --x_sub_component_tbl            := l_sub_component_tbl;
8644 
8645        WHEN EXC_FAT_QUIT_BRANCH THEN
8646 
8647         Eco_Error_Handler.Log_Error
8648                 (  p_rev_component_tbl  => x_rev_component_tbl
8649                 ,  p_ref_designator_tbl => x_ref_designator_tbl
8650                 ,  p_sub_component_tbl  => x_sub_component_tbl
8651                 ,  p_mesg_token_tbl     => l_mesg_token_tbl
8652                 ,  p_error_status       => Error_Handler.G_STATUS_FATAL
8653                 ,  p_error_scope        => Error_Handler.G_SCOPE_CHILDREN
8654                 ,  p_other_status       => Error_Handler.G_STATUS_FATAL
8655                 ,  p_other_message      => l_other_message
8656                 ,  p_other_token_tbl    => l_other_token_tbl
8657                 ,  p_error_level        => 4
8658                 ,  p_entity_index       => I
8659                 ,  x_eco_rec            => l_eco_rec
8660                 ,  x_eco_revision_tbl   => l_eco_revision_tbl
8661                 ,  x_revised_item_tbl   => l_revised_item_tbl
8662                 ,  x_rev_component_tbl  => x_rev_component_tbl
8663                 ,  x_ref_designator_tbl => x_ref_designator_tbl
8664                 ,  x_sub_component_tbl  => x_sub_component_tbl
8665                 ,  x_rev_operation_tbl   => l_rev_operation_tbl   --L1
8666                 ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl --L1
8667                 ,  x_rev_sub_resource_tbl=> l_rev_sub_resource_tbl--L1
8668                 );
8669 
8670         l_process_children := FALSE;
8671 
8672         x_return_status                := Error_Handler.G_STATUS_FATAL;
8673         x_Mesg_Token_Tbl               := l_Mesg_Token_Tbl;
8674         --x_rev_component_tbl            := l_rev_component_tbl;
8675         --x_ref_designator_tbl           := l_ref_designator_tbl;
8676         --x_sub_component_tbl            := l_sub_component_tbl;
8677 
8678        WHEN EXC_FAT_QUIT_SIBLINGS THEN
8679 
8680         Eco_Error_Handler.Log_Error
8681                 (  p_rev_component_tbl  => x_rev_component_tbl
8682                 ,  p_ref_designator_tbl => x_ref_designator_tbl
8683                 ,  p_sub_component_tbl  => x_sub_component_tbl
8684                 ,  p_mesg_token_tbl     => l_mesg_token_tbl
8685                 ,  p_error_status       => Error_Handler.G_STATUS_FATAL
8686                 ,  p_error_scope        => Error_Handler.G_SCOPE_SIBLINGS
8687                 ,  p_other_status       => Error_Handler.G_STATUS_FATAL
8688                 ,  p_other_message      => l_other_message
8689                 ,  p_other_token_tbl    => l_other_token_tbl
8690                 ,  p_error_level        => 4
8691                 ,  p_entity_index       => I
8692                 ,  x_eco_rec            => l_eco_rec
8693                 ,  x_eco_revision_tbl   => l_eco_revision_tbl
8694                 ,  x_revised_item_tbl   => l_revised_item_tbl
8695                 ,  x_rev_component_tbl  => x_rev_component_tbl
8696                 ,  x_ref_designator_tbl => x_ref_designator_tbl
8697                 ,  x_sub_component_tbl  => x_sub_component_tbl
8698                 ,  x_rev_operation_tbl   => l_rev_operation_tbl   --L1
8699                 ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl --L1
8700                 ,  x_rev_sub_resource_tbl=> l_rev_sub_resource_tbl--L1
8701                 );
8702 
8703         l_process_children := FALSE;
8704 
8705         x_return_status                := Error_Handler.G_STATUS_FATAL;
8706         x_Mesg_Token_Tbl               := l_Mesg_Token_Tbl;
8707         --x_rev_component_tbl            := l_rev_component_tbl;
8708         --x_ref_designator_tbl           := l_ref_designator_tbl;
8709         --x_sub_component_tbl            := l_sub_component_tbl;
8710 
8711        WHEN EXC_FAT_QUIT_OBJECT THEN
8712 
8713         Eco_Error_Handler.Log_Error
8714                 (  p_rev_component_tbl  => x_rev_component_tbl
8715                 ,  p_ref_designator_tbl => x_ref_designator_tbl
8716                 ,  p_sub_component_tbl  => x_sub_component_tbl
8717                 ,  p_mesg_token_tbl     => l_mesg_token_tbl
8718                 ,  p_error_status       => Error_Handler.G_STATUS_FATAL
8719                 ,  p_error_scope        => Error_Handler.G_SCOPE_ALL
8720                 ,  p_other_status       => Error_Handler.G_STATUS_FATAL
8721                 ,  p_other_message      => l_other_message
8722                 ,  p_other_token_tbl    => l_other_token_tbl
8723                 ,  p_error_level        => 4
8724                 ,  p_entity_index       => I
8725                 ,  x_eco_rec            => l_eco_rec
8726                 ,  x_eco_revision_tbl   => l_eco_revision_tbl
8727                 ,  x_revised_item_tbl   => l_revised_item_tbl
8728                 ,  x_rev_component_tbl  => x_rev_component_tbl
8729                 ,  x_ref_designator_tbl => x_ref_designator_tbl
8730                 ,  x_sub_component_tbl  => x_sub_component_tbl
8731                 ,  x_rev_operation_tbl   => l_rev_operation_tbl   --L1
8732                 ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl --L1
8733                 ,  x_rev_sub_resource_tbl=> l_rev_sub_resource_tbl--L1
8734                 );
8735 
8736         x_Mesg_Token_Tbl               := l_Mesg_Token_Tbl;
8737         --x_rev_component_tbl            := l_rev_component_tbl;
8738         --x_ref_designator_tbl           := l_ref_designator_tbl;
8739         --x_sub_component_tbl            := l_sub_component_tbl;
8740 
8741         l_return_status := 'Q';
8742 
8743        WHEN EXC_UNEXP_SKIP_OBJECT THEN
8744 
8745 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Unexpected error caught in Rev Comps . . . '); END IF;
8746 
8747         Eco_Error_Handler.Log_Error
8748                 (  p_rev_component_tbl  => x_rev_component_tbl
8749                 ,  p_ref_designator_tbl => x_ref_designator_tbl
8750                 ,  p_sub_component_tbl  => x_sub_component_tbl
8751                 ,  p_mesg_token_tbl     => l_mesg_token_tbl
8752                 ,  p_error_status       => Error_Handler.G_STATUS_UNEXPECTED
8753                 ,  p_other_status       => Error_Handler.G_STATUS_NOT_PICKED
8754                 ,  p_other_message      => l_other_message
8755                 ,  p_other_token_tbl    => l_other_token_tbl
8756                 ,  p_error_level        => 4
8757                 ,  p_entity_index       => I
8758                 ,  x_ECO_rec            => l_ECO_rec
8759                 ,  x_eco_revision_tbl   => l_eco_revision_tbl
8760                 ,  x_revised_item_tbl   => l_revised_item_tbl
8761                 ,  x_rev_component_tbl  => x_rev_component_tbl
8762                 ,  x_ref_designator_tbl => x_ref_designator_tbl
8763                 ,  x_sub_component_tbl  => x_sub_component_tbl
8764                 ,  x_rev_operation_tbl   => l_rev_operation_tbl   --L1
8765                 ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl --L1
8766                 ,  x_rev_sub_resource_tbl=> l_rev_sub_resource_tbl--L1
8767                 );
8768 
8769         --x_rev_component_tbl            := l_rev_component_tbl;
8770         --x_ref_designator_tbl           := l_ref_designator_tbl;
8771         --x_sub_component_tbl            := l_sub_component_tbl;
8772         x_Mesg_Token_Tbl               := l_Mesg_Token_Tbl;
8773 
8774         l_return_status := 'U';
8775 
8776 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Unexpected error in Rev Comps . . .'); END IF;
8777 
8778         END; -- END block
8779 
8780         IF l_return_status in ('Q', 'U')
8781         THEN
8782                 x_return_status := l_return_status;
8783 
8784 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Rev Comps returning with status ' || l_return_status ); END IF;
8785 
8786                 RETURN;
8787         END IF;
8788 
8789    IF l_process_children
8790    THEN
8791         -- Process Reference Designators that are direct children of this
8792         -- component
8793 
8794 IF Bom_Globals.Get_Debug = 'Y' THEN
8795     Error_Handler.Write_Debug('***********************************************************') ;
8796     Error_Handler.Write_Debug('Now processing direct children for the Rev Comp '
8797                               || l_rev_component_rec.component_item_name || '. . .'  );
8798     Error_Handler.Write_Debug('Now processing Ref Desig as direct children for the Rev Comp ') ;
8799 END IF;
8800 
8801 
8802         Ref_Desgs
8803         (   p_validation_level          => p_validation_level
8804         ,   p_change_notice             => l_rev_component_rec.ECO_Name
8805         ,   p_organization_id           => l_rev_comp_unexp_rec.organization_id
8806         ,   p_revised_item_name         => l_rev_component_rec.revised_item_name
8807         ,   p_alternate_bom_code        => l_rev_component_rec.alternate_bom_code  -- Bug 3991176
8808         ,   p_effectivity_date          => l_rev_component_rec.start_effective_date
8809         ,   p_item_revision             => l_rev_component_rec.new_revised_item_revision
8810         ,   p_routing_revision          => l_rev_component_rec.new_routing_revision      -- Added by MK on 11/02/00
8811         ,   p_from_end_item_number      => l_rev_component_rec.from_end_item_unit_number -- Added by MK on 11/02/00
8812         ,   p_component_item_name       => l_rev_component_rec.component_item_name
8813         ,   p_operation_seq_num         => l_rev_component_rec.operation_sequence_number
8814         ,   p_ref_designator_tbl        => x_ref_designator_tbl
8815         ,   p_sub_component_tbl         => x_sub_component_tbl
8816         ,   x_ref_designator_tbl        => x_ref_designator_tbl
8817         ,   x_sub_component_tbl         => x_sub_component_tbl
8818         ,   x_Mesg_Token_Tbl            => l_Mesg_Token_Tbl
8819         ,   x_return_status             => l_return_status
8820         );
8821 
8822         IF l_return_status <> FND_API.G_RET_STS_SUCCESS
8823         THEN
8824                 l_bo_return_status := l_return_status;
8825         END IF;
8826 
8827         -- Process Substitute Components that are direct children of this
8828         -- component
8829 
8830 IF Bom_Globals.Get_Debug = 'Y' THEN
8831     Error_Handler.Write_Debug('***********************************************************') ;
8832     Error_Handler.Write_Debug('Now processing Ref Desig as direct children for the Rev Comp ') ;
8833 END IF ;
8834 
8835         Sub_Comps
8836         (   p_validation_level          => p_validation_level
8837         ,   p_change_notice             => l_rev_component_rec.ECO_Name
8838         ,   p_organization_id           => l_rev_comp_unexp_rec.organization_id
8839         ,   p_revised_item_name         => l_rev_component_rec.revised_item_name
8840         ,   p_alternate_bom_code        => l_rev_component_rec.alternate_bom_code  -- Bug 3991176
8841         ,   p_effectivity_date          => l_rev_component_rec.start_effective_date
8842         ,   p_item_revision             => l_rev_component_rec.new_revised_item_revision
8843         ,   p_routing_revision          => l_rev_component_rec.new_routing_revision      -- Added by MK on 11/02/00
8844         ,   p_from_end_item_number      => l_rev_component_rec.from_end_item_unit_number -- Added by MK on 11/02/00
8845         ,   p_component_item_name       => l_rev_component_rec.component_item_name
8846         ,   p_operation_seq_num         => l_rev_component_rec.operation_sequence_number
8847         ,   p_sub_component_tbl         => x_sub_component_tbl
8848         ,   x_sub_component_tbl         => x_sub_component_tbl
8849         ,   x_Mesg_Token_Tbl            => l_Mesg_Token_Tbl
8850         ,   x_return_status             => l_return_status
8851         );
8852 
8853         IF l_return_status <> FND_API.G_RET_STS_SUCCESS
8854         THEN
8855                 l_bo_return_status := l_return_status;
8856         END IF;
8857 
8858         IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Finished processing children for ' || l_rev_component_rec.component_item_name || ' . . . ' || l_return_status ); END IF;
8859 
8860     END IF;  -- Process children
8861     END IF; -- End of processing records for which the return status is null
8862     END LOOP; -- END Revised Components processing loop
8863 
8864     --  Load OUT parameters
8865 
8866         IF NVL(l_bo_return_status, 'S') <> 'S'
8867      THEN
8868 IF Bom_Globals.Get_Debug = 'Y' THEN
8869         Error_Handler.write_Debug('Return status before returning from Rev Comps: ' || l_bo_return_status);
8870 END IF;
8871         x_return_status     := l_bo_return_status;
8872 
8873      END IF;
8874 
8875      --x_rev_component_tbl        := l_rev_component_tbl;
8876      --x_ref_designator_tbl       := l_ref_designator_tbl;
8877      --x_sub_component_tbl        := l_sub_component_tbl;
8878      x_Mesg_Token_Tbl           := l_Mesg_Token_Tbl;
8879 
8880 END Rev_Comps;
8881 
8882 --  Process_Rev_Item
8883 PROCEDURE Process_Rev_Item
8884 (   p_validation_level              IN  NUMBER
8885 ,   p_change_notice                 IN  VARCHAR2 := NULL
8886 ,   p_organization_id               IN  NUMBER := NULL
8887 ,   I                               IN  NUMBER
8888 ,   p_revised_item_rec              IN  ENG_Eco_PUB.Revised_Item_Rec_Type
8889 ,   p_rev_component_tbl             IN  BOM_BO_PUB.Rev_Component_Tbl_Type
8890 ,   p_ref_designator_tbl            IN  BOM_BO_PUB.Ref_Designator_Tbl_Type
8891 ,   p_sub_component_tbl             IN  BOM_BO_PUB.Sub_Component_Tbl_Type
8892 ,   p_rev_operation_tbl             IN  Bom_Rtg_Pub.Rev_Operation_Tbl_Type   --L1
8893 ,   p_rev_op_resource_tbl           IN  Bom_Rtg_Pub.Rev_Op_Resource_Tbl_Type --L1
8894 ,   p_rev_sub_resource_tbl          IN  Bom_Rtg_Pub.Rev_Sub_Resource_Tbl_Type--L1
8895 ,   x_revised_item_tbl              IN OUT NOCOPY ENG_Eco_PUB.Revised_Item_Tbl_Type
8896 ,   x_rev_component_tbl             IN OUT NOCOPY BOM_BO_PUB.Rev_Component_Tbl_Type
8897 ,   x_ref_designator_tbl            IN OUT NOCOPY BOM_BO_PUB.Ref_Designator_Tbl_Type
8898 ,   x_sub_component_tbl             IN OUT NOCOPY BOM_BO_PUB.Sub_Component_Tbl_Type
8899 ,   x_rev_operation_tbl             IN OUT NOCOPY Bom_Rtg_Pub.Rev_Operation_Tbl_Type   --L1
8900 ,   x_rev_op_resource_tbl           IN OUT NOCOPY Bom_Rtg_Pub.Rev_Op_Resource_Tbl_Type --L1
8901 ,   x_rev_sub_resource_tbl          IN OUT NOCOPY Bom_Rtg_Pub.Rev_Sub_Resource_Tbl_Type--L1
8902 ,   x_revised_item_unexp_rec        OUT NOCOPY ENG_Eco_PUB.Rev_Item_Unexposed_Rec_Type
8903 ,   x_Mesg_Token_Tbl                OUT NOCOPY Error_Handler.Mesg_Token_Tbl_Type
8904 ,   x_return_status                 OUT NOCOPY VARCHAR2
8905 ,   x_disable_revision              OUT NOCOPY NUMBER --Bug no:3034642
8906 )
8907 IS
8908 l_Mesg_Token_Tbl        Error_Handler.Mesg_Token_Tbl_Type;
8909 l_other_token_tbl       Error_Handler.Token_Tbl_Type;
8910 l_other_message         VARCHAR2(2000);
8911 l_err_text              VARCHAR2(2000);
8912 l_valid                 BOOLEAN := TRUE;
8913 l_eco_parent_exists     BOOLEAN := FALSE;
8914 l_Return_Status         VARCHAR2(1);
8915 l_bo_return_status      VARCHAR2(1);
8916 l_eco_rec               ENG_Eco_PUB.Eco_Rec_Type;
8917 l_old_eco_rec           ENG_Eco_PUB.Eco_Rec_Type;
8918 l_old_eco_unexp_rec     ENG_Eco_PUB.Eco_Unexposed_Rec_Type;
8919 l_eco_revision_tbl      ENG_Eco_PUB.ECO_Revision_Tbl_Type;
8920 l_revised_item_rec      ENG_Eco_PUB.Revised_Item_Rec_Type;
8921 --l_revised_item_tbl      ENG_Eco_PUB.Revised_Item_Tbl_Type := p_revised_item_tbl;
8922 l_rev_item_unexp_rec    ENG_Eco_PUB.Rev_Item_Unexposed_Rec_Type;
8923 l_rev_item_miss_rec     ENG_Eco_PUB.Rev_Item_Unexposed_Rec_Type;
8924 l_old_revised_item_rec  ENG_Eco_PUB.Revised_Item_Rec_Type;
8925 l_old_rev_item_unexp_rec ENG_Eco_PUB.Rev_Item_Unexposed_Rec_Type;
8926 --l_rev_component_tbl     BOM_BO_PUB.Rev_Component_Tbl_Type := p_rev_component_tbl;
8927 --l_ref_designator_tbl    BOM_BO_PUB.Ref_Designator_Tbl_Type := p_ref_designator_tbl;
8928 --l_sub_component_tbl     BOM_BO_PUB.Sub_Component_Tbl_Type := p_sub_component_tbl;
8929 --l_rev_operation_tbl     Bom_Rtg_Pub.Rev_Operation_Tbl_Type := p_rev_operation_tbl;  --L1
8930 --l_rev_op_resource_tbl   Bom_Rtg_Pub.Rev_Op_Resource_Tbl_Type :=p_rev_op_resource_tbl; --L1
8931 --l_rev_sub_resource_tbl  Bom_Rtg_Pub.Rev_Sub_Resource_Tbl_Type :=p_rev_sub_resource_tbl; --L1
8932 l_return_value          NUMBER;
8933 l_Token_Tbl             Error_Handler.Token_Tbl_Type;
8934 
8935 l_process_children      BOOLEAN := TRUE;
8936 
8937 EXC_SEV_QUIT_RECORD     EXCEPTION;
8938 EXC_SEV_QUIT_SIBLINGS   EXCEPTION;
8939 EXC_SEV_QUIT_BRANCH     EXCEPTION;
8940 EXC_SEV_QUIT_OBJECT     EXCEPTION;
8941 EXC_SEV_SKIP_BRANCH     EXCEPTION;
8942 EXC_FAT_QUIT_OBJECT     EXCEPTION;
8943 EXC_FAT_QUIT_BRANCH     EXCEPTION;
8944 EXC_UNEXP_SKIP_OBJECT   EXCEPTION;
8945 
8946 	-- Bug 2918350 // kamohan
8947 	-- Start Changes
8948 
8949 	l_chk_co_sch eng_engineering_changes.status_type%TYPE;
8950 
8951 	-- End Changes
8952 
8953 BEGIN
8954     l_return_status := FND_API.G_RET_STS_SUCCESS;
8955     l_bo_return_status := FND_API.G_RET_STS_SUCCESS;
8956     x_return_status := FND_API.G_RET_STS_SUCCESS;
8957 
8958     x_rev_component_tbl    := p_rev_component_tbl;
8959     x_ref_designator_tbl   := p_ref_designator_tbl;
8960     x_sub_component_tbl    := p_sub_component_tbl;
8961     x_rev_operation_tbl    := p_rev_operation_tbl;  --L1
8962     x_rev_op_resource_tbl  := p_rev_op_resource_tbl; --L1
8963     x_rev_sub_resource_tbl := p_rev_sub_resource_tbl; --L1
8964     BEGIN
8965         --  Load local records.
8966 
8967         l_revised_item_rec := p_revised_item_rec;
8968 
8969 
8970 
8971         -- make sure that the unexposed record does not have remains of
8972         -- any previous processing. This could be possible in the consequent
8973         -- iterations of this loop
8974         l_rev_item_unexp_rec := l_rev_item_miss_rec;
8975         l_Rev_Item_Unexp_Rec.organization_id := ENG_GLOBALS.Get_org_id;
8976 
8977 
8978         l_revised_item_rec.transaction_type :=
8979                 UPPER(l_revised_item_rec.transaction_type);
8980 
8981         --
8982         -- be sure to set the process_children to false at the start of each
8983         -- iteration to avoid faulty processing of children at the end of the loop
8984         --
8985         l_process_children := FALSE;
8986 
8987         IF p_change_notice IS NOT NULL AND
8988            p_organization_id IS NOT NULL
8989         THEN
8990                 l_eco_parent_exists := TRUE;
8991         END IF;
8992 
8993         -- Process Flow Step 2: Check if record has not yet been processed and
8994         -- that it is the child of the parent that called this procedure
8995         --
8996 
8997 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Processing Revised Item . . . ' || l_revised_item_rec.revised_item_name); END IF;
8998 
8999         IF --(l_revised_item_rec.return_status IS NULL OR
9000             --l_revised_item_rec.return_status = FND_API.G_MISS_CHAR)
9001            --AND
9002            (NOT l_eco_parent_exists
9003             OR
9004             (l_eco_parent_exists AND
9005              (l_revised_item_rec.ECO_Name = p_change_notice AND
9006               l_rev_item_unexp_rec.organization_id = p_organization_id)))
9007         THEN
9008 
9009            l_return_status := FND_API.G_RET_STS_SUCCESS;
9010 
9011            l_revised_item_rec.return_status := FND_API.G_RET_STS_SUCCESS;
9012 
9013            -- Check if transaction_type is valid
9014            --
9015 
9016            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Check transaction_type validity'); END IF;
9017            ENG_GLOBALS.Transaction_Type_Validity
9018            (   p_transaction_type       => l_revised_item_rec.transaction_type
9019            ,   p_entity                 => 'Rev_Items'
9020            ,   p_entity_id              => l_revised_item_rec.revised_item_name
9021            ,   x_valid                  => l_valid
9022            ,   x_Mesg_Token_Tbl         => l_Mesg_Token_Tbl
9023            );
9024 
9025            IF NOT l_valid
9026            THEN
9027                 l_return_status := Error_Handler.G_STATUS_ERROR;
9028                 RAISE EXC_SEV_QUIT_RECORD;
9029            END IF;
9030 
9031            -- Process Flow step 4: Convert user unique index to unique index
9032            --
9033 
9034            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Converting user unique index to unique index'); END IF;
9035            ENG_Val_To_Id.Revised_Item_UUI_To_UI
9036                 ( p_revised_item_rec   => l_revised_item_rec
9037                 , p_rev_item_unexp_rec => l_rev_item_unexp_rec
9038                 , x_rev_item_unexp_rec => l_rev_item_unexp_rec
9039                 , x_Mesg_Token_Tbl     => l_Mesg_Token_Tbl
9040                 , x_Return_Status      => l_return_status
9041                 );
9042 
9043            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
9044 
9045            IF l_return_status = Error_Handler.G_STATUS_ERROR
9046            THEN
9047                 l_other_message := 'ENG_RIT_UUI_SEV_ERROR';
9048                 l_other_token_tbl(1).token_name := 'REVISED_ITEM_NAME';
9049                 l_other_token_tbl(1).token_value := l_revised_item_rec.revised_item_name;
9050                 RAISE EXC_SEV_QUIT_BRANCH;
9051            ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
9052            THEN
9053                 l_other_message := 'ENG_RIT_UUI_UNEXP_SKIP';
9054                 l_other_token_tbl(1).token_name := 'REVISED_ITEM_NAME';
9055                 l_other_token_tbl(1).token_value := l_revised_item_rec.revised_item_name;
9056                 RAISE EXC_UNEXP_SKIP_OBJECT;
9057            END IF;
9058 
9059            BOM_Globals.Set_Unit_Controlled_Item
9060            ( p_inventory_item_id => l_rev_item_unexp_rec.revised_item_id
9061            , p_organization_id  => l_rev_item_unexp_rec.organization_id
9062            );
9063 
9064            -- Process Flow step 5: Verify ECO's existence in database, if
9065            -- the revised item is being created on an ECO and the business
9066            -- object does not carry the ECO header
9067 
9068            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Check parent existence'); END IF;
9069 
9070            IF l_revised_item_rec.transaction_type = ENG_GLOBALS.G_OPR_CREATE
9071               AND
9072               NOT l_eco_parent_exists
9073            THEN
9074                 ENG_Validate_ECO.Check_Existence
9075                 ( p_change_notice       => l_revised_item_rec.ECO_Name
9076                 , p_organization_id     => l_rev_item_unexp_rec.organization_id
9077                 , p_organization_code   => l_revised_item_rec.organization_code
9078                 , p_calling_entity      => 'CHILD'
9079                 , p_transaction_type    => 'XXX'
9080                 , x_eco_rec             => l_old_eco_rec
9081                 , x_eco_unexp_rec       => l_old_eco_unexp_rec
9082                 , x_Mesg_Token_Tbl      => l_Mesg_Token_Tbl
9083                 , x_return_status       => l_Return_Status
9084                 );
9085 
9086                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
9087 
9088                 IF l_return_status = Error_Handler.G_STATUS_ERROR
9089                 THEN
9090                    l_other_message := 'ENG_PARENTECO_NOT_EXIST';
9091                    l_other_token_tbl(1).token_name := 'ECO_NAME';
9092                    l_other_token_tbl(1).token_value := l_revised_item_rec.ECO_Name;
9093                    l_other_token_tbl(2).token_name := 'ORGANIZATION_CODE';
9094                    l_other_token_tbl(2).token_value := l_revised_item_rec.organization_code;
9095                    RAISE EXC_SEV_QUIT_OBJECT;
9096                 ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
9097                 THEN
9098                    l_other_message := 'ENG_RIT_LIN_UNEXP_SKIP';
9099                    l_other_token_tbl(1).token_name := 'REVISED_ITEM_NAME';
9100                    l_other_token_tbl(1).token_value := l_revised_item_rec.revised_item_name;
9101                    RAISE EXC_UNEXP_SKIP_OBJECT;
9102                 END IF;
9103            END IF;
9104 
9105          IF l_revised_item_rec.Transaction_Type IN
9106                 (ENG_GLOBALS.G_OPR_UPDATE, ENG_GLOBALS.G_OPR_DELETE)
9107            THEN
9108 
9109 	-- Bug 2918350
9110 	-- Start Changes
9111 	IF p_change_notice IS NOT NULL AND p_organization_id IS NOT NULL THEN
9112 		l_chk_co_sch := ret_co_status ( p_change_notice, p_organization_id);
9113 	ELSE
9114 		l_chk_co_sch := ret_co_status ( l_revised_item_rec.eco_name, l_rev_item_unexp_rec.organization_id);
9115 	END IF;
9116 
9117 	IF l_chk_co_sch = 4 THEN
9118 		l_return_status := error_handler.g_status_error;
9119 		error_handler.add_error_token (p_message_name        => 'ENG_REV_ITM_NOT_UPD',
9120 			p_mesg_token_tbl      => l_mesg_token_tbl,
9121 			x_mesg_token_tbl      => l_mesg_token_tbl,
9122 			p_token_tbl           => l_token_tbl
9123 			);
9124 		RAISE exc_sev_quit_record;
9125 	END IF;
9126 
9127 	-- End Changes
9128        END IF;
9129 
9130           -- Bug No.:3614144 added by sseraphi to convert  new revision in small case to upper case while import
9131           -- adding this conversion before validations start.
9132 	   IF l_revised_item_rec.New_Revised_Item_Revision IS NOT null
9133 	   THEN
9134                 l_revised_item_rec.New_Revised_Item_Revision := UPPER(l_revised_item_rec.New_Revised_Item_Revision);
9135 	   END IF;
9136 	    IF l_revised_item_rec.Updated_Revised_Item_Revision IS NOT null
9137 	   THEN
9138                 l_revised_item_rec.Updated_Revised_Item_Revision := UPPER(l_revised_item_rec.Updated_Revised_Item_Revision);
9139 	   END IF;
9140            -- Process Flow step 5: Verify Revised Item's existence
9141            --
9142 
9143 	   IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Check existence'); END IF;
9144            ENG_Validate_Revised_Item.Check_Existence
9145                 (  p_revised_item_rec           => l_revised_item_rec
9146                 ,  p_rev_item_unexp_rec         => l_rev_item_unexp_rec
9147                 ,  x_old_revised_item_rec       => l_old_revised_item_rec
9148                 ,  x_old_rev_item_unexp_rec     => l_old_rev_item_unexp_rec
9149                 ,  x_Mesg_Token_Tbl             => l_Mesg_Token_Tbl
9150                 ,  x_return_status              => l_Return_Status
9151 		,  x_disable_revision           => x_disable_revision  --BUG 3034642
9152                 );
9153 
9154            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
9155 
9156            IF l_return_status = Error_Handler.G_STATUS_ERROR
9157            THEN
9158                 l_other_message := 'ENG_RIT_EXS_SEV_ERROR';
9159                 l_other_token_tbl(1).token_name := 'REVISED_ITEM_NAME';
9160                 l_other_token_tbl(1).token_value := l_revised_item_rec.revised_item_name;
9161                 l_other_token_tbl(2).token_name := 'ECO_NAME';
9162                 l_other_token_tbl(2).token_value := l_revised_item_rec.eco_name;
9163                 RAISE EXC_SEV_QUIT_BRANCH;
9164            ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
9165            THEN
9166                 l_other_message := 'ENG_RIT_EXS_UNEXP_SKIP';
9167                 l_other_token_tbl(1).token_name := 'REVISED_ITEM_NAME';
9168                 l_other_token_tbl(1).token_value := l_revised_item_rec.revised_item_name;
9169                 l_other_token_tbl(2).token_name := 'ECO_NAME';
9170                 l_other_token_tbl(2).token_value := l_revised_item_rec.eco_name;
9171                 RAISE EXC_UNEXP_SKIP_OBJECT;
9172            END IF;
9173 
9174 
9175            -- Process Flow step 6: Is Revised Item record an orphan ?
9176 
9177            IF NOT l_eco_parent_exists
9178            THEN
9179 
9180                 -- Process Flow step 7(a): Is ECO impl/cancl, or in wkflw process ?
9181                 --
9182 
9183                 ENG_Validate_ECO.Check_Access
9184                 ( p_change_notice       => l_revised_item_rec.ECO_Name
9185                 , p_organization_id     => l_rev_item_unexp_rec.organization_id
9186                 , p_Mesg_Token_Tbl      => l_Mesg_Token_Tbl
9187                 , x_Mesg_Token_Tbl      => l_Mesg_Token_Tbl
9188                 , x_Return_Status       => l_return_status
9189                 );
9190 
9191                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
9192 
9193                 IF l_return_status = Error_Handler.G_STATUS_ERROR
9194                 THEN
9195                         l_other_message := 'ENG_RIT_ECOACC_FAT_FATAL';
9196                         l_other_token_tbl(1).token_name := 'REVISED_ITEM_NAME';
9197                         l_other_token_tbl(1).token_value := l_revised_item_rec.revised_item_name;
9198                         l_return_status := 'F';
9199                         RAISE EXC_FAT_QUIT_OBJECT;
9200                 ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
9201                 THEN
9202                         l_other_message := 'ENG_RIT_ECOACC_UNEXP_SKIP';
9203                         l_other_token_tbl(1).token_name := 'REVISED_ITEM_NAME';
9204                         l_other_token_tbl(1).token_value := l_revised_item_rec.revised_item_name;
9205                         RAISE EXC_UNEXP_SKIP_OBJECT;
9206                 END IF;
9207 
9208                 -- Process Flow step 7(b): check that user has access to revised item
9209                 --
9210 
9211                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Check access'); END IF;
9212                 ENG_Validate_Revised_Item.Check_Access
9213                 (  p_change_notice      => l_revised_item_rec.ECO_Name
9214                 ,  p_organization_id    => l_rev_item_unexp_rec.organization_id
9215                 ,  p_revised_item_id    => l_rev_item_unexp_rec.revised_item_id
9216                 ,  p_new_item_revision  => l_revised_item_rec.new_revised_item_revision
9217                 ,  p_effectivity_date   => l_revised_item_rec.start_effective_date
9218                 ,  p_new_routing_revsion   => l_revised_item_rec.new_routing_revision  -- Added by MK on 11/02/00
9219                 ,  p_from_end_item_number  => l_revised_item_rec.from_end_item_unit_number -- Added by MK on 11/02/00
9220                 ,  p_revised_item_name  => l_revised_item_rec.revised_item_name
9221                 ,  p_Mesg_Token_Tbl     => l_Mesg_Token_Tbl
9222                 ,  x_Mesg_Token_Tbl     => l_Mesg_Token_Tbl
9223                 ,  x_return_status      => l_Return_Status
9224                 );
9225 
9226                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
9227 
9228                 IF l_return_status = Error_Handler.G_STATUS_ERROR
9229                 THEN
9230                         l_other_message := 'ENG_RIT_ACCESS_FAT_FATAL';
9231                         l_other_token_tbl(1).token_name := 'REVISED_ITEM_NAME';
9232                         l_other_token_tbl(1).token_value := l_revised_item_rec.revised_item_name;
9233                         l_return_status := 'F';
9234                         RAISE EXC_FAT_QUIT_BRANCH;
9235                 ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
9236                 THEN
9237                         l_other_message := 'ENG_RIT_ACCESS_UNEXP_SKIP';
9238                         l_other_token_tbl(1).token_name := 'REVISED_ITEM_NAME';
9239                         l_other_token_tbl(1).token_value := l_revised_item_rec.revised_item_name;
9240                         RAISE EXC_UNEXP_SKIP_OBJECT;
9241                 END IF;
9242 
9243            END IF;
9244 
9245            /****  Following Process Flow is for ECO Routing ***/
9246            --
9247            -- Process Flow step 8:  Flow Routing's operability for routing.
9248            -- (for future release, flow routing is not supported in current release
9249            -- Added by MK on 08/24/2000
9250            --
9251            /* Comment out for current release
9252            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Check Non-Flow Routing'); END IF;
9253 
9254            Bom_Validate_Rtg_Header.Check_flow_routing_operability ;
9255            (  p_assembly_item_name  =>  l_revised_item_rec.revised_item_name
9256             , p_cfm_routing_flag    =>  l_rev_item_unexp_rec.cfm_routing_flag
9257                                         -- in future, this shoud be exposed column
9258             , p_organization_id     =>  l_rev_item_unexp_rec.organization_id
9259             , x_mesg_token_tbl      =>  l_mesg_token_tbl
9260             , x_return_status       =>  l_return_status
9261             );
9262 
9263            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
9264 
9265 
9266            IF l_return_status = Error_Handler.G_STATUS_ERROR
9267            THEN
9268                 l_other_message := 'BOM_RTG_FRACC_ERROR';
9269                 l_other_token_tbl(1).token_name := 'ASSEMBLY_ITEM_NAME';
9270                 l_other_token_tbl(1).token_value :=
9271                                         l_revised_item_rec.revised_item_name;
9272                 RAISE EXC_SEV_QUIT_BRANCH;
9273            ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
9274            THEN
9275                 l_other_message := 'BOM_RTG_FRACC_UNEXP_SKIP';
9276                 l_other_token_tbl(1).token_name := 'ASSEMBLY_ITEM_NAME';
9277                 l_other_token_tbl(1).token_value :=
9278                                         l_revised_item_rec.revised_item_name;
9279                 RAISE EXC_UNEXP_SKIP_OBJECT;
9280            END IF;
9281            */
9282 
9283 
9284 
9285            -- Process Flow step 9: Value to Id conversions
9286            --
9287 
9288            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Value-id conversions'); END IF;
9289            ENG_Val_To_Id.Revised_Item_VID
9290                 ( x_Return_Status       => l_return_status
9291                 , x_Mesg_Token_Tbl      => l_Mesg_Token_Tbl
9292                 , p_rev_item_unexp_Rec  => l_rev_item_unexp_rec
9293                 , x_rev_item_unexp_Rec  => l_rev_item_unexp_rec
9294                 , p_revised_item_Rec    => l_revised_item_rec
9295                 );
9296 
9297            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
9298 
9299            IF l_return_status = Error_Handler.G_STATUS_ERROR
9300            THEN
9301                 IF l_revised_item_rec.transaction_type = 'CREATE'
9302                 THEN
9303                         l_other_message := 'ENG_RIT_VID_CSEV_SKIP';
9304                         l_other_token_tbl(1).token_name := 'REVISED_ITEM_NAME';
9305                         l_other_token_tbl(1).token_value := l_revised_item_rec.revised_item_name;
9306                         RAISE EXC_SEV_SKIP_BRANCH;
9307                 ELSE
9308                         RAISE EXC_SEV_QUIT_RECORD;
9309                 END IF;
9310            ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
9311            THEN
9312                 RAISE EXC_UNEXP_SKIP_OBJECT;
9313            ELSIF l_return_status ='S' AND
9314                 l_Mesg_Token_Tbl.COUNT <>0
9315            THEN
9316                 Eco_Error_Handler.Log_Error
9317                 (  p_revised_item_tbl   => x_revised_item_tbl
9318                 ,  p_rev_component_tbl  => x_rev_component_tbl
9319                 ,  p_ref_designator_tbl => x_ref_designator_tbl
9320                 ,  p_sub_component_tbl  => x_sub_component_tbl
9321                 ,  p_rev_operation_tbl      => x_rev_operation_tbl    --L1
9322                 ,  p_rev_op_resource_tbl    => x_rev_op_resource_tbl  --L1
9323                 ,  p_rev_sub_resource_tbl   => x_rev_sub_resource_tbl --L1
9324                 ,  p_mesg_token_tbl     => l_mesg_token_tbl
9325                 ,  p_error_status       => 'W'
9326                 ,  p_error_level        => 3
9327                 ,  p_entity_index       => I
9328                 ,  x_eco_rec            => l_eco_rec
9329                 ,  x_eco_revision_tbl   => l_eco_revision_tbl
9330                 ,  x_revised_item_tbl   => x_revised_item_tbl
9331                 ,  x_rev_component_tbl  => x_rev_component_tbl
9332                 ,  x_ref_designator_tbl => x_ref_designator_tbl
9333                 ,  x_sub_component_tbl  => x_sub_component_tbl
9334                 ,  x_rev_operation_tbl      => x_rev_operation_tbl    --L1
9335                 ,  x_rev_op_resource_tbl    => x_rev_op_resource_tbl  --L1
9336                 ,  x_rev_sub_resource_tbl   => x_rev_sub_resource_tbl --L1
9337                 );
9338            END IF;
9339 
9340 	   -- Process Flow step 10: Attribute Validation for CREATE and UPDATE
9341            --
9342 
9343 
9344            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Attribute Validation'); END IF;
9345            IF l_revised_item_rec.Transaction_Type IN
9346                 (ENG_GLOBALS.G_OPR_CREATE, ENG_GLOBALS.G_OPR_UPDATE)
9347            THEN
9348                 ENG_Validate_Revised_Item.Check_Attributes
9349                 ( x_return_status              => l_return_status
9350                 , x_Mesg_Token_Tbl             => l_Mesg_Token_Tbl
9351                 , p_revised_item_rec           => l_revised_item_rec
9352                 , p_rev_item_unexp_rec         => l_rev_item_unexp_rec
9353                 , p_old_revised_item_rec       => l_old_revised_item_rec
9354                 , p_old_rev_item_unexp_rec     => l_old_rev_item_unexp_rec
9355                 );
9356 
9357                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
9358 
9359                 IF l_return_status = Error_Handler.G_STATUS_ERROR
9360                 THEN
9361                    IF l_revised_item_rec.transaction_type = 'CREATE'
9362                    THEN
9363                         l_other_message := 'ENG_RIT_ATTVAL_CSEV_SKIP';
9364                         l_other_token_tbl(1).token_name := 'REVISED_ITEM_NAME';
9365                         l_other_token_tbl(1).token_value := l_revised_item_rec.revised_item_name;
9366                         RAISE EXC_SEV_SKIP_BRANCH;
9367                    ELSE
9368                         RAISE EXC_SEV_QUIT_RECORD;
9369                    END IF;
9370                 ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
9371                 THEN
9372                    l_other_message := 'ENG_RIT_ATTVAL_UNEXP_SKIP';
9373                    l_other_token_tbl(1).token_name := 'REVISED_ITEM_NAME';
9374                    l_other_token_tbl(1).token_value := l_revised_item_rec.revised_item_name;
9375                    RAISE EXC_UNEXP_SKIP_OBJECT;
9376                 ELSIF l_return_status ='S' AND
9377                       l_Mesg_Token_Tbl.COUNT <>0
9378                 THEN
9379                    Eco_Error_Handler.Log_Error
9380                         (  p_revised_item_tbl   => x_revised_item_tbl
9381                         ,  p_rev_component_tbl  => x_rev_component_tbl
9382                         ,  p_ref_designator_tbl => x_ref_designator_tbl
9383                         ,  p_sub_component_tbl  => x_sub_component_tbl
9384                         ,  p_rev_operation_tbl   => x_rev_operation_tbl    --L1
9385                         ,  p_rev_op_resource_tbl => x_rev_op_resource_tbl  --L1
9386                         ,  p_rev_sub_resource_tbl=> x_rev_sub_resource_tbl --L1
9387                         ,  p_mesg_token_tbl     =>  l_mesg_token_tbl
9388                         ,  p_error_status       => 'W'
9389                         ,  p_error_level        => 3
9390                         ,  p_entity_index       => I
9391                         ,  x_eco_rec            => l_eco_rec
9392                         ,  x_eco_revision_tbl   => l_eco_revision_tbl
9393                         ,  x_revised_item_tbl   => x_revised_item_tbl
9394                         ,  x_rev_component_tbl  => x_rev_component_tbl
9395                         ,  x_ref_designator_tbl => x_ref_designator_tbl
9396                         ,  x_sub_component_tbl  => x_sub_component_tbl
9397                         ,  x_rev_operation_tbl   => x_rev_operation_tbl    --L1
9398                         ,  x_rev_op_resource_tbl => x_rev_op_resource_tbl  --L1
9399                         ,  x_rev_sub_resource_tbl=> x_rev_sub_resource_tbl --L1
9400                         );
9401                 END IF;
9402            END IF;
9403 
9404            IF l_revised_item_rec.Transaction_Type IN
9405                 (ENG_GLOBALS.G_OPR_UPDATE, ENG_GLOBALS.G_OPR_DELETE)
9406            THEN
9407 
9408                 -- Process flow step 11 - Populate NULL columns for Update and
9409                 -- Delete.
9410 
9411                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Populating NULL Columns'); END IF;
9412                 Eng_Default_Revised_Item.Populate_NULL_Columns
9413                 (   p_revised_item_rec          => l_revised_item_rec
9414                 ,   p_old_revised_item_rec      => l_old_revised_item_rec
9415                 ,   p_rev_item_unexp_rec        => l_rev_item_unexp_rec
9416                 ,   p_old_rev_item_unexp_rec    => l_old_rev_item_unexp_rec
9417                 ,   x_revised_item_rec          => l_revised_item_rec
9418                 ,   x_rev_item_unexp_rec        => l_rev_item_unexp_rec
9419                 );
9420 
9421            ELSIF l_revised_item_rec.Transaction_Type = ENG_GLOBALS.G_OPR_CREATE THEN
9422 
9423                 -- Process Flow step 12: Default missing values for Operation CREATE
9424                 --
9425 
9426                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Attribute Defaulting'); END IF;
9427                 Eng_Default_Revised_Item.Attribute_Defaulting
9428                 (   p_revised_item_rec          => l_revised_item_rec
9429                 ,   p_rev_item_unexp_rec        => l_rev_item_unexp_rec
9430                 ,   x_revised_item_rec          => l_revised_item_rec
9431                 ,   x_rev_item_unexp_rec        => l_rev_item_unexp_rec
9432                 ,   x_Mesg_Token_Tbl            => l_Mesg_Token_Tbl
9433                 ,   x_return_status             => l_return_status
9434                 );
9435 
9436                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
9437 
9438                 IF l_return_status = Error_Handler.G_STATUS_ERROR
9439                 THEN
9440                         l_other_message := 'ENG_RIT_ATTDEF_SEV_SKIP';
9441                         l_other_token_tbl(1).token_name := 'REVISED_ITEM_NAME';
9442                         l_other_token_tbl(1).token_value := l_revised_item_rec.revised_item_name;
9443                         RAISE EXC_SEV_SKIP_BRANCH;
9444                 ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
9445                 THEN
9446                         l_other_message := 'ENG_RIT_ATTDEF_UNEXP_SKIP';
9447                         l_other_token_tbl(1).token_name := 'REVISED_ITEM_NAME';
9448                         l_other_token_tbl(1).token_value := l_revised_item_rec.revised_item_name;
9449                         RAISE EXC_UNEXP_SKIP_OBJECT;
9450                 ELSIF l_return_status ='S' AND
9451                         l_Mesg_Token_Tbl.COUNT <>0
9452                 THEN
9453                         Eco_Error_Handler.Log_Error
9454                         (  p_revised_item_tbl   => x_revised_item_tbl
9455                         ,  p_rev_component_tbl  => x_rev_component_tbl
9456                         ,  p_ref_designator_tbl => x_ref_designator_tbl
9457                         ,  p_sub_component_tbl  => x_sub_component_tbl
9458                         ,  p_rev_operation_tbl   => x_rev_operation_tbl    --L1
9459                         ,  p_rev_op_resource_tbl => x_rev_op_resource_tbl  --L1
9460                         ,  p_rev_sub_resource_tbl=> x_rev_sub_resource_tbl --L1
9461                         ,  p_mesg_token_tbl     => l_mesg_token_tbl
9462                         ,  p_error_status       => 'S'
9463                         ,  p_error_level        => 3
9464                         ,  p_entity_index       => I
9465                         ,  x_eco_rec            => l_eco_rec
9466                         ,  x_eco_revision_tbl   => l_eco_revision_tbl
9467                         ,  x_revised_item_tbl   => x_revised_item_tbl
9468                         ,  x_rev_component_tbl  => x_rev_component_tbl
9469                         ,  x_ref_designator_tbl => x_ref_designator_tbl
9470                         ,  x_sub_component_tbl  => x_sub_component_tbl
9471                         ,  x_rev_operation_tbl   => x_rev_operation_tbl    --L1
9472                         ,  x_rev_op_resource_tbl => x_rev_op_resource_tbl  --L1
9473                         ,  x_rev_sub_resource_tbl=> x_rev_sub_resource_tbl --L1
9474                         );
9475                 END IF;
9476            END IF;
9477 
9478            -- Process Flow step 13 - Conditionally required attributes check
9479            --
9480 
9481            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Conditionally required attributes check'); END IF;
9482 
9483            --
9484            -- Put conditionally required check procedure here
9485            --
9486 
9487            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
9488 
9489            ENG_Validate_Revised_Item.Check_Required
9490                 ( x_return_status              => l_return_status
9491                 , x_Mesg_Token_Tbl             => l_Mesg_Token_Tbl
9492                 , p_revised_item_rec           => l_revised_item_rec
9493                 );
9494 
9495            IF l_return_status = Error_Handler.G_STATUS_ERROR
9496            THEN
9497                 IF l_revised_item_rec.transaction_type = 'CREATE'
9498                 THEN
9499                         l_other_message := 'ENG_RIT_CONREQ_CSEV_SKIP';
9500                         l_other_token_tbl(1).token_name := 'REVISED_ITEM_NAME';
9501                         l_other_token_tbl(1).token_value := l_revised_item_rec.revised_item_name;
9502                         RAISE EXC_SEV_SKIP_BRANCH;
9503                 ELSE
9504                         RAISE EXC_SEV_QUIT_RECORD;
9505                 END IF;
9506            ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
9507            THEN
9508                 l_other_message := 'ENG_RIT_CONREQ_UNEXP_SKIP';
9509                 l_other_token_tbl(1).token_name := 'REVISED_ITEM_NAME';
9510                 l_other_token_tbl(1).token_value := l_revised_item_rec.revised_item_name;
9511                 RAISE EXC_UNEXP_SKIP_OBJECT;
9512            ELSIF l_return_status ='S' AND
9513                 l_Mesg_Token_Tbl.COUNT <>0
9514            THEN
9515                 Eco_Error_Handler.Log_Error
9516                 (  p_revised_item_tbl       => x_revised_item_tbl
9517                 ,  p_rev_component_tbl      => x_rev_component_tbl
9518                 ,  p_ref_designator_tbl     => x_ref_designator_tbl
9519                 ,  p_sub_component_tbl      => x_sub_component_tbl
9520                 ,  p_rev_operation_tbl      => x_rev_operation_tbl    --L1
9521                 ,  p_rev_op_resource_tbl    => x_rev_op_resource_tbl  --L1
9522                 ,  p_rev_sub_resource_tbl   => x_rev_sub_resource_tbl --L1
9523                 ,  p_mesg_token_tbl         => l_mesg_token_tbl
9524                 ,  p_error_status           => 'W'
9525                 ,  p_error_level            => 3
9526                 ,  p_entity_index           => I
9527                 ,  x_eco_rec                => l_eco_rec
9528                 ,  x_eco_revision_tbl       => l_eco_revision_tbl
9529                 ,  x_revised_item_tbl       => x_revised_item_tbl
9530                 ,  x_rev_component_tbl      => x_rev_component_tbl
9531                 ,  x_ref_designator_tbl     => x_ref_designator_tbl
9532                 ,  x_sub_component_tbl      => x_sub_component_tbl
9533                 ,  x_rev_operation_tbl      => x_rev_operation_tbl    --L1
9534                 ,  x_rev_op_resource_tbl    => x_rev_op_resource_tbl  --L1
9535                 ,  x_rev_sub_resource_tbl   => x_rev_sub_resource_tbl --L1
9536                 );
9537            END IF;
9538 
9539            -- Process Flow step 14: Entity defaulting for CREATE and UPDATE
9540            --
9541 
9542            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Entity defaulting'); END IF;
9543            IF l_revised_item_rec.Transaction_Type IN
9544                 (ENG_GLOBALS.G_OPR_CREATE, ENG_GLOBALS.G_OPR_UPDATE)
9545            THEN
9546                 ENG_Default_Revised_Item.Entity_Defaulting
9547                 (   p_revised_item_rec          => l_revised_item_rec
9548                 ,   p_rev_item_unexp_rec        => l_rev_item_unexp_rec
9549                 ,   p_old_revised_item_rec      => l_old_revised_item_rec
9550                 ,   p_old_rev_item_unexp_rec    => l_old_rev_item_unexp_rec
9551                 ,   x_revised_item_rec          => l_revised_item_rec
9552                 ,   x_rev_item_unexp_rec        => l_rev_item_unexp_rec
9553                 ,   x_Mesg_Token_Tbl            => l_Mesg_Token_Tbl
9554                 ,   x_return_status             => l_return_status
9555                 );
9556 
9557                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
9558 
9559                 IF l_return_status = Error_Handler.G_STATUS_ERROR
9560                 THEN
9561                    IF l_revised_item_rec.transaction_type = 'CREATE'
9562                    THEN
9563                         l_other_message := 'ENG_RIT_ENTDEF_CSEV_SKIP';
9564                         l_other_token_tbl(1).token_name := 'REVISED_ITEM_NAME';
9565                         l_other_token_tbl(1).token_value := l_revised_item_rec.revised_item_name;
9566                         RAISE EXC_SEV_SKIP_BRANCH;
9567                    ELSE
9568                         RAISE EXC_SEV_QUIT_RECORD;
9569                    END IF;
9570                 ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
9571                 THEN
9572                         l_other_message := 'ENG_RIT_ENTDEF_UNEXP_SKIP';
9573                         l_other_token_tbl(1).token_name := 'REVISED_ITEM_NAME';
9574                         l_other_token_tbl(1).token_value := l_revised_item_rec.revised_item_name;
9575                         RAISE EXC_UNEXP_SKIP_OBJECT;
9576                 ELSIF l_return_status ='S' AND
9577                         l_Mesg_Token_Tbl.COUNT <>0
9578                 THEN
9579                         Eco_Error_Handler.Log_Error
9580                         (  p_revised_item_tbl    => x_revised_item_tbl
9581                         ,  p_rev_component_tbl   => x_rev_component_tbl
9582                         ,  p_ref_designator_tbl  => x_ref_designator_tbl
9583                         ,  p_sub_component_tbl   => x_sub_component_tbl
9584                         ,  p_rev_operation_tbl   => x_rev_operation_tbl    --L1
9585                         ,  p_rev_op_resource_tbl => x_rev_op_resource_tbl  --L1
9586                         ,  p_rev_sub_resource_tbl=> x_rev_sub_resource_tbl --L1
9587                         ,  p_mesg_token_tbl      => l_mesg_token_tbl
9588                         ,  p_error_status        => 'W'
9589                         ,  p_error_level         => 3
9590                         ,  p_entity_index        => I
9591                         ,  x_eco_rec             => l_eco_rec
9592                         ,  x_eco_revision_tbl    => l_eco_revision_tbl
9593                         ,  x_revised_item_tbl    => x_revised_item_tbl
9594                         ,  x_rev_component_tbl   => x_rev_component_tbl
9595                         ,  x_ref_designator_tbl  => x_ref_designator_tbl
9596                         ,  x_sub_component_tbl   => x_sub_component_tbl
9597                         ,  x_rev_operation_tbl   => x_rev_operation_tbl    --L1
9598                         ,  x_rev_op_resource_tbl => x_rev_op_resource_tbl  --L1
9599                         ,  x_rev_sub_resource_tbl=> x_rev_sub_resource_tbl --L1
9600                         );
9601                 END IF;
9602            END IF;
9603 
9604            -- Process Flow step 15 - Entity Level Validation
9605            --
9606 
9607            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Entity validation'); END IF;
9608 
9609            IF l_revised_item_rec.transaction_type = 'DELETE'
9610            THEN
9611                 Eng_Validate_Revised_Item.Check_Entity_Delete
9612                 (  p_revised_item_rec     => l_revised_item_rec
9613                 ,  p_rev_item_unexp_rec   => l_rev_item_unexp_rec
9614                 ,  x_Mesg_Token_Tbl       => l_Mesg_Token_Tbl
9615                 ,  x_return_status        => l_Return_Status
9616                 );
9617            ELSE
9618                 Eng_Validate_Revised_Item.Check_Entity
9619                 (  p_revised_item_rec     => l_revised_item_rec
9620                 ,  p_rev_item_unexp_rec   => l_rev_item_unexp_rec
9621                 ,  p_old_revised_item_rec => l_old_revised_item_rec
9622                 ,  p_old_rev_item_unexp_rec => l_old_rev_item_unexp_rec
9623                 ,  x_Mesg_Token_Tbl       => l_Mesg_Token_Tbl
9624                 ,  x_return_status        => l_Return_Status
9625                 );
9626            END IF;
9627 
9628            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
9629 
9630            IF l_return_status = Error_Handler.G_STATUS_ERROR
9631            THEN
9632                 IF l_revised_item_rec.transaction_type = 'CREATE'
9633                 THEN
9634                         l_other_message := 'ENG_RIT_ENTVAL_CSEV_SKIP';
9635                         l_other_token_tbl(1).token_name := 'REVISED_ITEM_NAME';
9636                         l_other_token_tbl(1).token_value := l_revised_item_rec.revised_item_name;
9637                         RAISE EXC_SEV_SKIP_BRANCH;
9638                 ELSE
9639                         RAISE EXC_SEV_QUIT_RECORD;
9640                 END IF;
9641            ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
9642            THEN
9643                 l_other_message := 'ENG_RIT_ENTVAL_UNEXP_SKIP';
9644                 l_other_token_tbl(1).token_name := 'REVISED_ITEM_NAME';
9645                 l_other_token_tbl(1).token_value := l_revised_item_rec.revised_item_name;
9646                 RAISE EXC_UNEXP_SKIP_OBJECT;
9647            ELSIF l_return_status ='S' AND
9648                 l_Mesg_Token_Tbl.COUNT <>0
9649            THEN
9650                 Eco_Error_Handler.Log_Error
9651                 (  p_revised_item_tbl       => x_revised_item_tbl
9652                 ,  p_rev_component_tbl      => x_rev_component_tbl
9653                 ,  p_ref_designator_tbl     => x_ref_designator_tbl
9654                 ,  p_sub_component_tbl      => x_sub_component_tbl
9655                 ,  p_rev_operation_tbl      => x_rev_operation_tbl    --L1
9656                 ,  p_rev_op_resource_tbl    => x_rev_op_resource_tbl  --L1
9657                 ,  p_rev_sub_resource_tbl   => x_rev_sub_resource_tbl --L1
9658                 ,  p_mesg_token_tbl         => l_mesg_token_tbl
9659                 ,  p_error_status           => 'W'
9660                 ,  p_error_level            => 3
9661                 ,  p_entity_index           => I
9662                 ,  x_eco_rec                => l_eco_rec
9663                 ,  x_eco_revision_tbl       => l_eco_revision_tbl
9664                 ,  x_revised_item_tbl       => x_revised_item_tbl
9665                 ,  x_rev_component_tbl      => x_rev_component_tbl
9666                 ,  x_ref_designator_tbl     => x_ref_designator_tbl
9667                 ,  x_sub_component_tbl      => x_sub_component_tbl
9668                 ,  x_rev_operation_tbl      => x_rev_operation_tbl    --L1
9669                 ,  x_rev_op_resource_tbl    => x_rev_op_resource_tbl  --L1
9670                 ,  x_rev_sub_resource_tbl   => x_rev_sub_resource_tbl --L1
9671                 );
9672            END IF;
9673 
9674            -- Process Flow step 16 : Database Writes
9675            --
9676 
9677            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Writing to the database'); END IF;
9678            ENG_Revised_Item_Util.Perform_Writes
9679                 (   p_revised_item_rec          => l_revised_item_rec
9680                 ,   p_rev_item_unexp_rec        => l_rev_item_unexp_rec
9681                 ,   x_Mesg_Token_Tbl            => l_Mesg_Token_Tbl
9682                 ,   x_return_status             => l_return_status
9683                 );
9684 
9685            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
9686 
9687            IF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
9688            THEN
9689                 l_other_message := 'ENG_RIT_WRITES_UNEXP_SKIP';
9690                 l_other_token_tbl(1).token_name := 'REVISED_ITEM_NAME';
9691                 l_other_token_tbl(1).token_value := l_revised_item_rec.revised_item_name;
9692                 RAISE EXC_UNEXP_SKIP_OBJECT;
9693            ELSIF l_return_status ='S' AND
9694               l_Mesg_Token_Tbl.COUNT <>0
9695            THEN
9696                 Eco_Error_Handler.Log_Error
9697                 (  p_revised_item_tbl       => x_revised_item_tbl
9698                 ,  p_rev_component_tbl      => x_rev_component_tbl
9699                 ,  p_ref_designator_tbl     => x_ref_designator_tbl
9700                 ,  p_sub_component_tbl      => x_sub_component_tbl
9701                 ,  p_rev_operation_tbl      => x_rev_operation_tbl    --L1
9702                 ,  p_rev_op_resource_tbl    => x_rev_op_resource_tbl  --L1
9703                 ,  p_rev_sub_resource_tbl   => x_rev_sub_resource_tbl --L1
9704                 ,  p_mesg_token_tbl         => l_mesg_token_tbl
9705                 ,  p_error_status           => 'W'
9706                 ,  p_error_level            => 3
9707                 ,  p_entity_index           => I
9708                 ,  x_eco_rec                => l_eco_rec
9709                 ,  x_eco_revision_tbl       => l_eco_revision_tbl
9710                 ,  x_revised_item_tbl       => x_revised_item_tbl
9711                 ,  x_rev_component_tbl      => x_rev_component_tbl
9712                 ,  x_ref_designator_tbl     => x_ref_designator_tbl
9713                 ,  x_sub_component_tbl      => x_sub_component_tbl
9714                 ,  x_rev_operation_tbl      => x_rev_operation_tbl    --L1
9715                 ,  x_rev_op_resource_tbl    => x_rev_op_resource_tbl  --L1
9716                 ,  x_rev_sub_resource_tbl   => x_rev_sub_resource_tbl --L1
9717                 );
9718            END IF;
9719 
9720 IF Bom_Globals.Get_Debug = 'Y' THEN
9721      Error_Handler.Write_Debug('Writing to the database for Rev Item is completed with '||l_return_status );
9722 END IF;
9723 
9724         END IF; -- END IF statement that checks RETURN STATUS
9725 
9726         --  Load tables.
9727 
9728         x_revised_item_tbl(I)          := l_revised_item_rec;
9729 
9730         --
9731         -- If everything goes well then, process children
9732         --
9733         l_process_children := TRUE;
9734 
9735      -- Reset system_information flags
9736 
9737      ENG_GLOBALS.Set_RITEM_Impl( p_ritem_impl   => NULL);
9738      ENG_GLOBALS.Set_RITEM_Cancl( p_ritem_cancl => NULL);
9739      ENG_GLOBALS.Set_Bill_Sequence_Id( p_bill_sequence_id => NULL);
9740      ENG_GLOBALS.Set_Current_Revision( p_current_revision => NULL);
9741 
9742     --  For loop exception handler.
9743 
9744 
9745     EXCEPTION
9746 
9747        WHEN EXC_SEV_QUIT_RECORD THEN
9748 
9749         Eco_Error_Handler.Log_Error
9750                 (  p_revised_item_tbl       => x_revised_item_tbl
9751                 ,  p_rev_component_tbl      => x_rev_component_tbl
9752                 ,  p_ref_designator_tbl     => x_ref_designator_tbl
9753                 ,  p_sub_component_tbl      => x_sub_component_tbl
9754                 ,  p_rev_operation_tbl      => x_rev_operation_tbl    --L1
9755                 ,  p_rev_op_resource_tbl    => x_rev_op_resource_tbl  --L1
9756                 ,  p_rev_sub_resource_tbl   => x_rev_sub_resource_tbl --L1
9757                 ,  p_mesg_token_tbl         => l_mesg_token_tbl
9758                 ,  p_error_status           => FND_API.G_RET_STS_ERROR
9759                 ,  p_error_scope            => Error_Handler.G_SCOPE_RECORD
9760                 ,  p_error_level            => 3
9761                 ,  p_entity_index           => I
9762                 ,  x_eco_rec                => l_eco_rec
9763                 ,  x_eco_revision_tbl       => l_eco_revision_tbl
9764                 ,  x_revised_item_tbl       => x_revised_item_tbl
9765                 ,  x_rev_component_tbl      => x_rev_component_tbl
9766                 ,  x_ref_designator_tbl     => x_ref_designator_tbl
9767                 ,  x_sub_component_tbl      => x_sub_component_tbl
9768                 ,  x_rev_operation_tbl      => x_rev_operation_tbl    --L1
9769                 ,  x_rev_op_resource_tbl    => x_rev_op_resource_tbl  --L1
9770                 ,  x_rev_sub_resource_tbl   => x_rev_sub_resource_tbl --L1
9771                 );
9772 
9773         l_process_children := TRUE;
9774 
9775         IF l_bo_return_status = 'S'
9776         THEN
9777                 l_bo_return_status     := l_return_status;
9778         END IF;
9779         x_return_status                := l_bo_return_status;
9780         x_Mesg_Token_Tbl               := l_Mesg_Token_Tbl;
9781         --x_revised_item_tbl             := l_revised_item_tbl;
9782         --x_rev_component_tbl            := l_rev_component_tbl;
9783         --x_ref_designator_tbl           := l_ref_designator_tbl;
9784         --x_sub_component_tbl            := l_sub_component_tbl;
9785         --x_rev_operation_tbl            := l_rev_operation_tbl;     --L1
9786         --x_rev_op_resource_tbl          := l_rev_op_resource_tbl;   --L1
9787         --x_rev_sub_resource_tbl         := l_rev_sub_resource_tbl;  --L1
9788 
9789         -- Reset system_information flags
9790 
9791      ENG_GLOBALS.Set_RITEM_Impl( p_ritem_impl   => NULL);
9792      ENG_GLOBALS.Set_RITEM_Cancl( p_ritem_cancl => NULL);
9793      ENG_GLOBALS.Set_Bill_Sequence_Id( p_bill_sequence_id => NULL);
9794      ENG_GLOBALS.Set_Current_Revision( p_current_revision => NULL);
9795 
9796        WHEN EXC_SEV_QUIT_BRANCH THEN
9797 
9798         Eco_Error_Handler.Log_Error
9799                 (  p_revised_item_tbl    => x_revised_item_tbl
9800                 ,  p_rev_component_tbl   => x_rev_component_tbl
9801                 ,  p_ref_designator_tbl  => x_ref_designator_tbl
9802                 ,  p_sub_component_tbl   => x_sub_component_tbl
9803                 ,  p_rev_operation_tbl   => x_rev_operation_tbl    --L1
9804                 ,  p_rev_op_resource_tbl => x_rev_op_resource_tbl  --L1
9805                 ,  p_rev_sub_resource_tbl=> x_rev_sub_resource_tbl --L1
9806                 ,  p_mesg_token_tbl      => l_mesg_token_tbl
9807                 ,  p_error_status        => Error_Handler.G_STATUS_ERROR
9808                 ,  p_error_scope         => Error_Handler.G_SCOPE_CHILDREN
9809                 ,  p_other_status        => Error_Handler.G_STATUS_ERROR
9810                 ,  p_other_message       => l_other_message
9811                 ,  p_other_token_tbl     => l_other_token_tbl
9812                 ,  p_error_level         => 3
9813                 ,  p_entity_index        => I
9814                 ,  x_eco_rec             => l_eco_rec
9815                 ,  x_eco_revision_tbl    => l_eco_revision_tbl
9816                 ,  x_revised_item_tbl    => x_revised_item_tbl
9817                 ,  x_rev_component_tbl   => x_rev_component_tbl
9818                 ,  x_ref_designator_tbl  => x_ref_designator_tbl
9819                 ,  x_sub_component_tbl   => x_sub_component_tbl
9820                 ,  x_rev_operation_tbl   => x_rev_operation_tbl    --L1
9821                 ,  x_rev_op_resource_tbl => x_rev_op_resource_tbl  --L1
9822                 ,  x_rev_sub_resource_tbl=> x_rev_sub_resource_tbl --L1
9823                 );
9824 
9825         l_process_children := FALSE;
9826 
9827         IF l_bo_return_status = 'S'
9828         THEN
9829                 l_bo_return_status     := l_return_status;
9830         END IF;
9831         x_return_status                := l_bo_return_status;
9832         x_Mesg_Token_Tbl               := l_Mesg_Token_Tbl;
9833         --x_revised_item_tbl             := l_revised_item_tbl;
9834         --x_rev_component_tbl            := l_rev_component_tbl;
9835         --x_ref_designator_tbl           := l_ref_designator_tbl;
9836         --x_sub_component_tbl            := l_sub_component_tbl;
9837         --x_rev_operation_tbl            := l_rev_operation_tbl;     --L1
9838         --x_rev_op_resource_tbl          := l_rev_op_resource_tbl;   --L1
9839         --x_rev_sub_resource_tbl         := l_rev_sub_resource_tbl;  --L1
9840 
9841         -- Reset system_information flags
9842 
9843      ENG_GLOBALS.Set_RITEM_Impl( p_ritem_impl   => NULL);
9844      ENG_GLOBALS.Set_RITEM_Cancl( p_ritem_cancl => NULL);
9845      ENG_GLOBALS.Set_Bill_Sequence_Id( p_bill_sequence_id => NULL);
9846      ENG_GLOBALS.Set_Current_Revision( p_current_revision => NULL);
9847 
9848        WHEN EXC_SEV_SKIP_BRANCH THEN
9849 
9850         Eco_Error_Handler.Log_Error
9851                 (  p_revised_item_tbl    => x_revised_item_tbl
9852                 ,  p_rev_component_tbl   => x_rev_component_tbl
9853                 ,  p_ref_designator_tbl  => x_ref_designator_tbl
9854                 ,  p_sub_component_tbl   => x_sub_component_tbl
9855                 ,  p_rev_operation_tbl   => x_rev_operation_tbl    --L1
9856                 ,  p_rev_op_resource_tbl => x_rev_op_resource_tbl  --L1
9857                 ,  p_rev_sub_resource_tbl=> x_rev_sub_resource_tbl --L1
9858                 ,  p_mesg_token_tbl      => l_mesg_token_tbl
9859                 ,  p_error_status        => Error_Handler.G_STATUS_ERROR
9860                 ,  p_error_scope         => Error_Handler.G_SCOPE_CHILDREN
9861                 ,  p_other_status        => Error_Handler.G_STATUS_NOT_PICKED
9862                 ,  p_other_message       => l_other_message
9863                 ,  p_other_token_tbl     => l_other_token_tbl
9864                 ,  p_error_level         => 3
9865                 ,  p_entity_index        => I
9866                 ,  x_eco_rec             => l_eco_rec
9867                 ,  x_eco_revision_tbl    => l_eco_revision_tbl
9868                 ,  x_revised_item_tbl    => x_revised_item_tbl
9869                 ,  x_rev_component_tbl   => x_rev_component_tbl
9870                 ,  x_ref_designator_tbl  => x_ref_designator_tbl
9871                 ,  x_sub_component_tbl   => x_sub_component_tbl
9872                 ,  x_rev_operation_tbl   => x_rev_operation_tbl    --L1
9873                 ,  x_rev_op_resource_tbl => x_rev_op_resource_tbl  --L1
9874                 ,  x_rev_sub_resource_tbl=> x_rev_sub_resource_tbl --L1
9875                 );
9876 
9877         l_process_children := FALSE;
9878 
9879         IF l_bo_return_status = 'S'
9880         THEN
9881                 l_bo_return_status     := l_return_status;
9882         END IF;
9883         x_return_status                := l_bo_return_status;
9884         x_Mesg_Token_Tbl               := l_Mesg_Token_Tbl;
9885         --x_revised_item_tbl             := l_revised_item_tbl;
9886         --x_rev_component_tbl            := l_rev_component_tbl;
9887         --x_ref_designator_tbl           := l_ref_designator_tbl;
9888         --x_sub_component_tbl            := l_sub_component_tbl;
9889         --x_rev_operation_tbl            := l_rev_operation_tbl;     --L1
9890         --x_rev_op_resource_tbl          := l_rev_op_resource_tbl;   --L1
9891         --x_rev_sub_resource_tbl         := l_rev_sub_resource_tbl;  --L1
9892 
9893         -- Reset system_information flags
9894 
9895      ENG_GLOBALS.Set_RITEM_Impl( p_ritem_impl   => NULL);
9896      ENG_GLOBALS.Set_RITEM_Cancl( p_ritem_cancl => NULL);
9897      ENG_GLOBALS.Set_Bill_Sequence_Id( p_bill_sequence_id => NULL);
9898      ENG_GLOBALS.Set_Current_Revision( p_current_revision => NULL);
9899 
9900         WHEN EXC_SEV_QUIT_OBJECT THEN
9901 
9902         Eco_Error_Handler.Log_Error
9903             (  p_revised_item_tbl       => x_revised_item_tbl
9904              , p_rev_component_tbl      => x_rev_component_tbl
9905              , p_ref_designator_tbl     => x_ref_designator_tbl
9906              , p_sub_component_tbl      => x_sub_component_tbl
9907              , p_rev_operation_tbl      => x_rev_operation_tbl    --L1
9908              , p_rev_op_resource_tbl    => x_rev_op_resource_tbl  --L1
9909              , p_rev_sub_resource_tbl   => x_rev_sub_resource_tbl --L1
9910              , p_error_status           => Error_Handler.G_STATUS_ERROR
9911              , p_error_scope            => Error_Handler.G_SCOPE_ALL
9912              , p_error_level            => Error_Handler.G_BO_LEVEL
9913              , p_other_message          => l_other_message
9914              , p_other_status           => Error_Handler.G_STATUS_ERROR
9915              , p_other_token_tbl        => l_other_token_tbl
9916              , x_eco_rec                => l_eco_rec
9917              , x_eco_revision_tbl       => l_eco_revision_tbl
9918              , x_revised_item_tbl       => x_revised_item_tbl
9919              , x_rev_component_tbl      => x_rev_component_tbl
9920              , x_ref_designator_tbl     => x_ref_designator_tbl
9921              , x_sub_component_tbl      => x_sub_component_tbl
9922              , x_rev_operation_tbl   => x_rev_operation_tbl    --L1
9923              , x_rev_op_resource_tbl => x_rev_op_resource_tbl  --L1
9924              , x_rev_sub_resource_tbl=> x_rev_sub_resource_tbl --L1
9925              );
9926 
9927         IF l_bo_return_status = 'S'
9928         THEN
9929                 l_bo_return_status     := l_return_status;
9930         END IF;
9931         x_return_status                := l_bo_return_status;
9932         x_Mesg_Token_Tbl               := l_Mesg_Token_Tbl;
9933         --x_revised_item_tbl             := l_revised_item_tbl;
9934         --x_rev_component_tbl            := l_rev_component_tbl;
9935         --x_ref_designator_tbl           := l_ref_designator_tbl;
9936         --x_sub_component_tbl            := l_sub_component_tbl;
9937         --x_rev_operation_tbl            := l_rev_operation_tbl;     --L1
9938         --x_rev_op_resource_tbl          := l_rev_op_resource_tbl;   --L1
9939         --x_rev_sub_resource_tbl         := l_rev_sub_resource_tbl;  --L1
9940 
9941         -- Reset system_information flags
9942 
9943      ENG_GLOBALS.Set_RITEM_Impl( p_ritem_impl   => NULL);
9944      ENG_GLOBALS.Set_RITEM_Cancl( p_ritem_cancl => NULL);
9945      ENG_GLOBALS.Set_Bill_Sequence_Id( p_bill_sequence_id => NULL);
9946      ENG_GLOBALS.Set_Current_Revision( p_current_revision => NULL);
9947 
9948        WHEN EXC_FAT_QUIT_BRANCH THEN
9949 
9950         Eco_Error_Handler.Log_Error
9951                 (  p_revised_item_tbl    => x_revised_item_tbl
9952                 ,  p_rev_component_tbl   => x_rev_component_tbl
9953                 ,  p_ref_designator_tbl  => x_ref_designator_tbl
9954                 ,  p_sub_component_tbl   => x_sub_component_tbl
9955                 ,  p_rev_operation_tbl   => x_rev_operation_tbl    --L1
9956                 ,  p_rev_op_resource_tbl => x_rev_op_resource_tbl  --L1
9957                 ,  p_rev_sub_resource_tbl=> x_rev_sub_resource_tbl --L1
9958                 ,  p_mesg_token_tbl      => l_mesg_token_tbl
9959                 ,  p_error_status        => Error_Handler.G_STATUS_FATAL
9960                 ,  p_error_scope         => Error_Handler.G_SCOPE_CHILDREN
9961                 ,  p_other_status        => Error_Handler.G_STATUS_FATAL
9962                 ,  p_other_message       => l_other_message
9963                 ,  p_other_token_tbl     => l_other_token_tbl
9964                 ,  p_error_level         => 3
9965                 ,  p_entity_index        => I
9966                 ,  x_eco_rec             => l_eco_rec
9967                 ,  x_eco_revision_tbl    => l_eco_revision_tbl
9968                 ,  x_revised_item_tbl    => x_revised_item_tbl
9969                 ,  x_rev_component_tbl   => x_rev_component_tbl
9970                 ,  x_ref_designator_tbl  => x_ref_designator_tbl
9971                 ,  x_sub_component_tbl   => x_sub_component_tbl
9972                 ,  x_rev_operation_tbl   => x_rev_operation_tbl    --L1
9973                 ,  x_rev_op_resource_tbl => x_rev_op_resource_tbl  --L1
9974                 ,  x_rev_sub_resource_tbl=> x_rev_sub_resource_tbl --L1
9975                 );
9976 
9977         l_process_children := FALSE;
9978 
9979         x_return_status                := Error_Handler.G_STATUS_FATAL;
9980         x_Mesg_Token_Tbl               := l_Mesg_Token_Tbl;
9981         --x_revised_item_tbl             := l_revised_item_tbl;
9982         --x_rev_component_tbl            := l_rev_component_tbl;
9983         --x_ref_designator_tbl           := l_ref_designator_tbl;
9984         --x_sub_component_tbl            := l_sub_component_tbl;
9985         --x_rev_operation_tbl            := l_rev_operation_tbl;     --L1
9986         --x_rev_op_resource_tbl          := l_rev_op_resource_tbl;   --L1
9987         --x_rev_sub_resource_tbl         := l_rev_sub_resource_tbl;  --L1
9988 
9989         -- Reset system_information flags
9990 
9991      ENG_GLOBALS.Set_RITEM_Impl( p_ritem_impl   => NULL);
9992      ENG_GLOBALS.Set_RITEM_Cancl( p_ritem_cancl => NULL);
9993      ENG_GLOBALS.Set_Bill_Sequence_Id( p_bill_sequence_id => NULL);
9994      ENG_GLOBALS.Set_Current_Revision( p_current_revision => NULL);
9995 
9996        WHEN EXC_FAT_QUIT_OBJECT THEN
9997 
9998         Eco_Error_Handler.Log_Error
9999                 (  p_revised_item_tbl    => x_revised_item_tbl
10000                 ,  p_rev_component_tbl   => x_rev_component_tbl
10001                 ,  p_ref_designator_tbl  => x_ref_designator_tbl
10002                 ,  p_sub_component_tbl   => x_sub_component_tbl
10003                 ,  p_rev_operation_tbl   => x_rev_operation_tbl    --L1
10004                 ,  p_rev_op_resource_tbl => x_rev_op_resource_tbl  --L1
10005                 ,  p_rev_sub_resource_tbl=> x_rev_sub_resource_tbl --L1
10006                 ,  p_mesg_token_tbl      => l_mesg_token_tbl
10007                 ,  p_error_status        => Error_Handler.G_STATUS_FATAL
10008                 ,  p_error_scope         => Error_Handler.G_SCOPE_ALL
10009                 ,  p_other_status        => Error_Handler.G_STATUS_FATAL
10010                 ,  p_other_message       => l_other_message
10011                 ,  p_other_token_tbl     => l_other_token_tbl
10012                 ,  p_error_level         => 3
10013                 ,  p_entity_index        => I
10014                 ,  x_eco_rec             => l_eco_rec
10015                 ,  x_eco_revision_tbl    => l_eco_revision_tbl
10016                 ,  x_revised_item_tbl    => x_revised_item_tbl
10017                 ,  x_rev_component_tbl   => x_rev_component_tbl
10018                 ,  x_ref_designator_tbl  => x_ref_designator_tbl
10019                 ,  x_sub_component_tbl   => x_sub_component_tbl
10020                 ,  x_rev_operation_tbl   => x_rev_operation_tbl    --L1
10021                 ,  x_rev_op_resource_tbl => x_rev_op_resource_tbl  --L1
10022                 ,  x_rev_sub_resource_tbl=> x_rev_sub_resource_tbl --L1
10023                 );
10024 
10025         x_Mesg_Token_Tbl               := l_Mesg_Token_Tbl;
10026         --x_revised_item_tbl             := l_revised_item_tbl;
10027         --x_rev_component_tbl            := l_rev_component_tbl;
10028         --x_ref_designator_tbl           := l_ref_designator_tbl;
10029         --x_sub_component_tbl            := l_sub_component_tbl;
10030         --x_rev_operation_tbl            := l_rev_operation_tbl;     --L1
10031         --x_rev_op_resource_tbl          := l_rev_op_resource_tbl;   --L1
10032         --x_rev_sub_resource_tbl         := l_rev_sub_resource_tbl;  --L1
10033 
10034         -- Reset system_information flags
10035 
10036      ENG_GLOBALS.Set_RITEM_Impl( p_ritem_impl   => NULL);
10037      ENG_GLOBALS.Set_RITEM_Cancl( p_ritem_cancl => NULL);
10038      ENG_GLOBALS.Set_Bill_Sequence_Id( p_bill_sequence_id => NULL);
10039      ENG_GLOBALS.Set_Current_Revision( p_current_revision => NULL);
10040 
10041         l_return_status := 'Q';
10042 
10043        WHEN EXC_UNEXP_SKIP_OBJECT THEN
10044 
10045         Eco_Error_Handler.Log_Error
10046                 (  p_revised_item_tbl    => x_revised_item_tbl
10047                 ,  p_rev_component_tbl   => x_rev_component_tbl
10048                 ,  p_ref_designator_tbl  => x_ref_designator_tbl
10049                 ,  p_sub_component_tbl   => x_sub_component_tbl
10050                 ,  p_rev_operation_tbl   => x_rev_operation_tbl    --L1
10051                 ,  p_rev_op_resource_tbl => x_rev_op_resource_tbl  --L1
10052                 ,  p_rev_sub_resource_tbl=> x_rev_sub_resource_tbl --L1
10053                 ,  p_mesg_token_tbl      => l_mesg_token_tbl
10054                 ,  p_error_status        => Error_Handler.G_STATUS_UNEXPECTED
10055                 ,  p_other_status        => Error_Handler.G_STATUS_NOT_PICKED
10056                 ,  p_other_message       => l_other_message
10057                 ,  p_other_token_tbl     => l_other_token_tbl
10058                 ,  p_error_level         => 3
10059                 ,  x_ECO_rec             => l_ECO_rec
10060                 ,  x_eco_revision_tbl    => l_eco_revision_tbl
10061                 ,  x_revised_item_tbl    => x_revised_item_tbl
10062                 ,  x_rev_component_tbl   => x_rev_component_tbl
10063                 ,  x_ref_designator_tbl  => x_ref_designator_tbl
10064                 ,  x_sub_component_tbl   => x_sub_component_tbl
10065                 ,  x_rev_operation_tbl   => x_rev_operation_tbl    --L1
10066                 ,  x_rev_op_resource_tbl => x_rev_op_resource_tbl  --L1
10067                 ,  x_rev_sub_resource_tbl=> x_rev_sub_resource_tbl --L1
10068                 );
10069 
10070         x_Mesg_Token_Tbl               := l_Mesg_Token_Tbl;
10071         --x_revised_item_tbl             := l_revised_item_tbl;
10072         --x_rev_component_tbl            := l_rev_component_tbl;
10073         --x_ref_designator_tbl           := l_ref_designator_tbl;
10074         --x_sub_component_tbl            := l_sub_component_tbl;
10075         --x_rev_operation_tbl            := l_rev_operation_tbl;     --L1
10076         --x_rev_op_resource_tbl          := l_rev_op_resource_tbl;   --L1
10077         --x_rev_sub_resource_tbl         := l_rev_sub_resource_tbl;  --L1
10078 
10079         -- Reset system_information flags
10080 
10081      ENG_GLOBALS.Set_RITEM_Impl( p_ritem_impl   => NULL);
10082      ENG_GLOBALS.Set_RITEM_Cancl( p_ritem_cancl => NULL);
10083      ENG_GLOBALS.Set_Bill_Sequence_Id( p_bill_sequence_id => NULL);
10084      ENG_GLOBALS.Set_Current_Revision( p_current_revision => NULL);
10085 
10086         l_return_status := 'U';
10087 
10088         END; -- END block
10089 
10090         IF l_return_status in ('Q', 'U')
10091         THEN
10092                 x_return_status := l_return_status;
10093                 RETURN;
10094         END IF;
10095 
10096     IF l_process_children
10097     THEN
10098 
10099 
10100         -- L1: The following is for ECO enhancement
10101         -- Process operations that are orphans
10102         -- (without immediate revised component parents) but are
10103         -- indirect children of this item
10104         --
10105         -- Modified by MK on 11/30/00 Moved eco for routing procedure before BOMs.
10106         --
10107 
10108 -- IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Processing Rev Op children of Revised item . . . ' || l_revised_item_rec.revised_item_name); END IF;
10109 
10110         Rev_Operation_Sequences
10111         (   p_validation_level          => p_validation_level
10112         ,   p_change_notice             => l_revised_item_rec.ECO_Name
10113         ,   p_organization_id           => l_rev_item_unexp_rec.organization_id
10114         ,   p_revised_item_name         => l_revised_item_rec.revised_item_name
10115         ,   p_effectivity_date          => l_revised_item_rec.start_effective_date
10116         ,   p_item_revision             => l_revised_item_rec.new_revised_item_revision -- Added by MK on 11/02/00
10117         ,   p_routing_revision          => l_revised_item_rec.new_routing_revision      -- Added by MK on 11/02/00
10118         ,   p_from_end_item_number      => l_revised_item_rec.from_end_item_unit_number -- Added by MK on 11/02/00
10119         ,   p_alternate_routing_code    => l_revised_item_rec.alternate_bom_code        -- Added for bug 13440461
10120         ,   p_rev_operation_tbl         => x_rev_operation_tbl
10121         ,   p_rev_op_resource_tbl       => x_rev_op_resource_tbl
10122         ,   p_rev_sub_resource_tbl      => x_rev_sub_resource_tbl
10123         ,   x_rev_operation_tbl         => x_rev_operation_tbl
10124         ,   x_rev_op_resource_tbl       => x_rev_op_resource_tbl
10125         ,   x_rev_sub_resource_tbl      => x_rev_sub_resource_tbl
10126         ,   x_Mesg_Token_Tbl            => l_Mesg_Token_Tbl
10127         ,   x_return_status             => l_return_status
10128         );
10129 
10130         IF l_return_status <> FND_API.G_RET_STS_SUCCESS
10131         THEN
10132                 l_bo_return_status := l_return_status;
10133         END IF;
10134 
10135 
10136 
10137         -- Process resource that are orphans
10138         -- (without immediate revised component parents) but are
10139         -- indirect children of this item
10140 
10141 -- IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Processing Rev Op Res children of Revised item . . . ' || l_revised_item_rec.revised_item_name); END IF;
10142 
10143 
10144         Rev_Operation_Resources
10145         (   p_validation_level          => p_validation_level
10146         ,   p_change_notice             => l_revised_item_rec.ECO_Name
10147         ,   p_organization_id           => l_rev_item_unexp_rec.organization_id
10148         ,   p_revised_item_name         => l_revised_item_rec.revised_item_name
10149         ,   p_effectivity_date          => l_revised_item_rec.start_effective_date
10150         ,   p_item_revision             => l_revised_item_rec.new_revised_item_revision -- Added by MK on 11/02/00
10151         ,   p_routing_revision          => l_revised_item_rec.new_routing_revision      -- Added by MK on 11/02/00
10152         ,   p_from_end_item_number      => l_revised_item_rec.from_end_item_unit_number -- Added by MK on 11/02/00
10153         ,   p_alternate_routing_code    => l_revised_item_rec.alternate_bom_code        -- Added for bug 13440461
10154         ,   p_rev_op_resource_tbl       => x_rev_op_resource_tbl
10155         ,   p_rev_sub_resource_tbl      => x_rev_sub_resource_tbl
10156         ,   x_rev_op_resource_tbl       => x_rev_op_resource_tbl
10157         ,   x_rev_sub_resource_tbl      => x_rev_sub_resource_tbl
10158         ,   x_Mesg_Token_Tbl            => l_Mesg_Token_Tbl
10159         ,   x_return_status             => l_return_status
10160         );
10161        IF l_return_status <> FND_API.G_RET_STS_SUCCESS
10162        THEN
10163                 l_bo_return_status := l_return_status;
10164        END IF;
10165 
10166         -- Process substitute resources that are orphans
10167         -- (without immediate revised component parents) but are
10168         -- indirect children of this item
10169 
10170 -- IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Processing Rev Sub Op Res children of Revised item . . . ' || l_revised_item_rec.revised_item_name); END IF;
10171 
10172 
10173        Rev_Sub_Operation_Resources
10174         (   p_validation_level          => p_validation_level
10175         ,   p_change_notice             => l_revised_item_rec.ECO_Name
10176         ,   p_organization_id           => l_rev_item_unexp_rec.organization_id
10177         ,   p_revised_item_name         => l_revised_item_rec.revised_item_name
10178         ,   p_effectivity_date          => l_revised_item_rec.start_effective_date
10179         ,   p_item_revision             => l_revised_item_rec.new_revised_item_revision -- Added by MK on 11/02/00
10180         ,   p_routing_revision          => l_revised_item_rec.new_routing_revision      -- Added by MK on 11/02/00
10181         ,   p_from_end_item_number      => l_revised_item_rec.from_end_item_unit_number -- Added by MK on 11/02/00
10182         ,   p_alternate_routing_code    => l_revised_item_rec.alternate_bom_code        -- Added for bug 13440461
10183         ,   p_rev_sub_resource_tbl      => x_rev_sub_resource_tbl
10184         ,   x_rev_sub_resource_tbl      => x_rev_sub_resource_tbl
10185         ,   x_Mesg_Token_Tbl            => l_Mesg_Token_Tbl
10186         ,   x_return_status             => l_return_status
10187         );
10188         IF l_return_status <> FND_API.G_RET_STS_SUCCESS
10189         THEN
10190                 l_bo_return_status := l_return_status;
10191         END IF;
10192 
10193         -- L1: The above is for ECO enhancement
10194 
10195 
10196         -- Process Revised Components that are direct children of this item
10197 
10198 IF Bom_Globals.Get_Debug = 'Y' THEN
10199     Error_Handler.Write_Debug('***********************************************************') ;
10200     Error_Handler.Write_Debug('Now processing direct children for the Rev Item '
10201                               || l_revised_item_rec.revised_item_name || '. . .'  );
10202     Error_Handler.Write_Debug('Processing Rev Comp as children of Revised item ' || l_revised_item_rec.revised_item_name);
10203 END IF;
10204 
10205         Rev_Comps
10206         (   p_validation_level          => p_validation_level
10207         ,   p_change_notice             => l_revised_item_rec.ECO_Name
10208         ,   p_organization_id           => l_rev_item_unexp_rec.organization_id
10209         ,   p_revised_item_name         => l_revised_item_rec.revised_item_name
10210         ,   p_alternate_bom_code        => l_revised_item_rec.alternate_bom_code -- Bug 2429272 Change 4
10211         ,   p_effectivity_date          => l_revised_item_rec.start_effective_date
10212         ,   p_item_revision             => l_revised_item_rec.new_revised_item_revision
10213         ,   p_routing_revision          => l_revised_item_rec.new_routing_revision      -- Added by MK on 11/02/00
10214         ,   p_from_end_item_number      => l_revised_item_rec.from_end_item_unit_number -- Added by MK on 11/02/00
10215         ,   p_rev_component_tbl         => x_rev_component_tbl
10216         ,   p_ref_designator_tbl        => x_ref_designator_tbl
10217         ,   p_sub_component_tbl         => x_sub_component_tbl
10218         ,   x_rev_component_tbl         => x_rev_component_tbl
10219         ,   x_ref_designator_tbl        => x_ref_designator_tbl
10220         ,   x_sub_component_tbl         => x_sub_component_tbl
10221         ,   x_Mesg_Token_Tbl            => l_Mesg_Token_Tbl
10222         ,   x_return_status             => l_return_status
10223 	,   x_bill_sequence_id          => l_rev_item_unexp_rec.bill_sequence_id
10224         );
10225 
10226 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Rev_Comps return status ' || l_return_status); END IF;
10227 
10228         IF l_return_status <> FND_API.G_RET_STS_SUCCESS
10229         THEN
10230 
10231 IF Bom_Globals.Get_Debug = 'Y' THEN
10232         Error_Handler.Write_Debug('Rev_Comps returned in Rev_Items . . .BO Status: ' || l_return_status);
10233 END IF;
10234 
10235                 l_bo_return_status := l_return_status;
10236         END IF;
10237 
10238         -- Process Reference Designators that are orphans
10239         -- (without immediate revised component parents) but are
10240         -- indirect children of this item
10241 
10242 IF Bom_Globals.Get_Debug = 'Y' THEN
10243     Error_Handler.Write_Debug('***********************************************************') ;
10244     Error_Handler.Write_Debug('Processing Ref Desgs as children of Revised item ' || l_revised_item_rec.revised_item_name);
10245 END IF;
10246 
10247 
10248         Ref_Desgs
10249         (   p_validation_level          => p_validation_level
10250         ,   p_change_notice             => l_revised_item_rec.ECO_Name
10251         ,   p_organization_id           => l_rev_item_unexp_rec.organization_id
10252         ,   p_revised_item_name         => l_revised_item_rec.revised_item_name
10253         ,   p_alternate_bom_code        => l_revised_item_rec.alternate_bom_code  -- Bug 3991176
10254         ,   p_effectivity_date          => l_revised_item_rec.start_effective_date
10255         ,   p_item_revision             => l_revised_item_rec.new_revised_item_revision
10256         ,   p_routing_revision          => l_revised_item_rec.new_routing_revision      -- Added by MK on 11/02/00
10257         ,   p_from_end_item_number      => l_revised_item_rec.from_end_item_unit_number -- Added by MK on 11/02/00
10258         ,   p_ref_designator_tbl        => x_ref_designator_tbl
10259         ,   p_sub_component_tbl         => x_sub_component_tbl
10260         ,   x_ref_designator_tbl        => x_ref_designator_tbl
10261         ,   x_sub_component_tbl         => x_sub_component_tbl
10262         ,   x_Mesg_Token_Tbl            => l_Mesg_Token_Tbl
10263         ,   x_return_status             => l_return_status
10264         );
10265 
10266         -- Process Substitute Components that are orphans
10267         -- (without immediate revised component parents) but are
10268         -- indirect children of this item
10269 
10270         IF l_return_status <> FND_API.G_RET_STS_SUCCESS
10271         THEN
10272                 l_bo_return_status := l_return_status;
10273         END IF;
10274 
10275 IF Bom_Globals.Get_Debug = 'Y' THEN
10276     Error_Handler.Write_Debug('***********************************************************') ;
10277     Error_Handler.Write_Debug('Processing Sub Comps children of Revised item ' || l_revised_item_rec.revised_item_name);
10278 END IF;
10279 
10280         Sub_Comps
10281         (   p_validation_level          => p_validation_level
10282         ,   p_change_notice             => l_revised_item_rec.ECO_Name
10283         ,   p_organization_id           => l_rev_item_unexp_rec.organization_id
10284         ,   p_revised_item_name         => l_revised_item_rec.revised_item_name
10285         ,   p_alternate_bom_code        => l_revised_item_rec.alternate_bom_code  -- Bug 3991176
10286         ,   p_effectivity_date          => l_revised_item_rec.start_effective_date
10287         ,   p_item_revision             => l_revised_item_rec.new_revised_item_revision
10288         ,   p_routing_revision          => l_revised_item_rec.new_routing_revision      -- Added by MK on 11/02/00
10289         ,   p_from_end_item_number      => l_revised_item_rec.from_end_item_unit_number -- Added by MK on 11/02/00
10290         ,   p_sub_component_tbl         => x_sub_component_tbl
10291         ,   x_sub_component_tbl         => x_sub_component_tbl
10292         ,   x_Mesg_Token_Tbl            => l_Mesg_Token_Tbl
10293         ,   x_return_status             => l_return_status
10294         );
10295 
10296         IF l_return_status <> FND_API.G_RET_STS_SUCCESS
10297         THEN
10298                 l_bo_return_status := l_return_status;
10299         END IF;
10300 
10301 
10302     END IF; -- END Process children
10303     x_revised_item_unexp_rec := l_rev_item_unexp_rec;
10304     x_return_status := l_bo_return_status;
10305 
10306 END Process_Rev_Item;
10307 
10308 
10309 --  Rev_Items
10310 
10311 PROCEDURE Rev_Items
10312 (   p_validation_level              IN  NUMBER
10313 ,   p_change_notice                 IN  VARCHAR2 := NULL
10314 ,   p_organization_id               IN  NUMBER := NULL
10315 ,   p_revised_item_tbl              IN  ENG_Eco_PUB.Revised_Item_Tbl_Type
10316 ,   p_rev_component_tbl             IN  BOM_BO_PUB.Rev_Component_Tbl_Type
10317 ,   p_ref_designator_tbl            IN  BOM_BO_PUB.Ref_Designator_Tbl_Type
10318 ,   p_sub_component_tbl             IN  BOM_BO_PUB.Sub_Component_Tbl_Type
10319 ,   p_rev_operation_tbl             IN  Bom_Rtg_Pub.Rev_Operation_Tbl_Type   --L1
10320 ,   p_rev_op_resource_tbl           IN  Bom_Rtg_Pub.Rev_Op_Resource_Tbl_Type --L1
10321 ,   p_rev_sub_resource_tbl          IN  Bom_Rtg_Pub.Rev_Sub_Resource_Tbl_Type--L1
10322 ,   x_revised_item_tbl              IN OUT NOCOPY ENG_Eco_PUB.Revised_Item_Tbl_Type
10323 ,   x_rev_component_tbl             IN OUT NOCOPY BOM_BO_PUB.Rev_Component_Tbl_Type
10324 ,   x_ref_designator_tbl            IN OUT NOCOPY BOM_BO_PUB.Ref_Designator_Tbl_Type
10325 ,   x_sub_component_tbl             IN OUT NOCOPY BOM_BO_PUB.Sub_Component_Tbl_Type
10326 ,   x_rev_operation_tbl             IN OUT NOCOPY Bom_Rtg_Pub.Rev_Operation_Tbl_Type   --L1
10327 ,   x_rev_op_resource_tbl           IN OUT NOCOPY Bom_Rtg_Pub.Rev_Op_Resource_Tbl_Type --L1
10328 ,   x_rev_sub_resource_tbl          IN OUT NOCOPY Bom_Rtg_Pub.Rev_Sub_Resource_Tbl_Type--L1
10329 ,   x_Mesg_Token_Tbl                OUT NOCOPY Error_Handler.Mesg_Token_Tbl_Type
10330 ,   x_return_status                 OUT NOCOPY VARCHAR2
10331 ,   x_disable_revision              OUT NOCOPY NUMBER --Bug no:3034642
10332 )
10333 IS
10334 l_Mesg_Token_Tbl        Error_Handler.Mesg_Token_Tbl_Type;
10335 l_other_token_tbl       Error_Handler.Token_Tbl_Type;
10336 l_other_message         VARCHAR2(2000);
10337 l_err_text              VARCHAR2(2000);
10338 l_valid                 BOOLEAN := TRUE;
10339 l_eco_parent_exists     BOOLEAN := FALSE;
10340 l_Return_Status         VARCHAR2(1);
10341 l_bo_return_status      VARCHAR2(1);
10342 l_eco_rec               ENG_Eco_PUB.Eco_Rec_Type;
10343 l_old_eco_rec           ENG_Eco_PUB.Eco_Rec_Type;
10344 l_old_eco_unexp_rec     ENG_Eco_PUB.Eco_Unexposed_Rec_Type;
10345 l_eco_revision_tbl      ENG_Eco_PUB.ECO_Revision_Tbl_Type;
10346 l_revised_item_rec      ENG_Eco_PUB.Revised_Item_Rec_Type;
10347 --l_revised_item_tbl      ENG_Eco_PUB.Revised_Item_Tbl_Type := p_revised_item_tbl;
10348 l_rev_item_unexp_rec    ENG_Eco_PUB.Rev_Item_Unexposed_Rec_Type;
10349 l_rev_item_miss_rec     ENG_Eco_PUB.Rev_Item_Unexposed_Rec_Type;
10350 l_old_revised_item_rec  ENG_Eco_PUB.Revised_Item_Rec_Type;
10351 l_old_rev_item_unexp_rec ENG_Eco_PUB.Rev_Item_Unexposed_Rec_Type;
10352 --l_rev_component_tbl     BOM_BO_PUB.Rev_Component_Tbl_Type := p_rev_component_tbl;
10353 --l_ref_designator_tbl    BOM_BO_PUB.Ref_Designator_Tbl_Type := p_ref_designator_tbl;
10354 --l_sub_component_tbl     BOM_BO_PUB.Sub_Component_Tbl_Type := p_sub_component_tbl;
10355 --l_rev_operation_tbl     Bom_Rtg_Pub.Rev_Operation_Tbl_Type := p_rev_operation_tbl;  --L1
10356 --l_rev_op_resource_tbl   Bom_Rtg_Pub.Rev_Op_Resource_Tbl_Type :=p_rev_op_resource_tbl; --L1
10357 --l_rev_sub_resource_tbl  Bom_Rtg_Pub.Rev_Sub_Resource_Tbl_Type :=p_rev_sub_resource_tbl; --L1
10358 l_return_value          NUMBER;
10359 l_Token_Tbl             Error_Handler.Token_Tbl_Type;
10360 
10361 l_rev_comp_flag         VARCHAR2(1);
10362 
10363 l_process_children      BOOLEAN := TRUE;
10364 
10365 EXC_SEV_QUIT_RECORD     EXCEPTION;
10366 EXC_SEV_QUIT_SIBLINGS   EXCEPTION;
10367 EXC_SEV_QUIT_BRANCH     EXCEPTION;
10368 EXC_SEV_QUIT_OBJECT     EXCEPTION;
10369 EXC_SEV_SKIP_BRANCH     EXCEPTION;
10370 EXC_FAT_QUIT_OBJECT     EXCEPTION;
10371 EXC_FAT_QUIT_BRANCH     EXCEPTION;
10372 EXC_UNEXP_SKIP_OBJECT   EXCEPTION;
10373 
10374 	-- Bug 2918350 // kamohan
10375 	-- Start Changes
10376 
10377 	l_chk_co_sch eng_engineering_changes.status_type%TYPE;
10378 
10379 	-- End Changes
10380 
10381 BEGIN
10382 
10383     --  Init local table variables.
10384 
10385     l_return_status := FND_API.G_RET_STS_SUCCESS;
10386     l_bo_return_status := FND_API.G_RET_STS_SUCCESS;
10387     x_return_status := FND_API.G_RET_STS_SUCCESS;
10388 
10389     x_revised_item_tbl             := p_revised_item_tbl;
10390     x_rev_component_tbl            := p_rev_component_tbl;
10391     x_ref_designator_tbl           := p_ref_designator_tbl;
10392     x_sub_component_tbl            := p_sub_component_tbl;
10393     x_rev_operation_tbl            := p_rev_operation_tbl;  --L1
10394     x_rev_op_resource_tbl          := p_rev_op_resource_tbl; --L1
10395     x_rev_sub_resource_tbl         := p_rev_sub_resource_tbl; --L1
10396 
10397     -- l_Rev_Item_Unexp_Rec.organization_id := ENG_GLOBALS.Get_org_id;
10398 
10399     FOR I IN 1..x_revised_item_tbl.COUNT LOOP
10400     IF (x_revised_item_tbl(I).return_status IS NULL OR
10401          x_revised_item_tbl(I).return_status = FND_API.G_MISS_CHAR) THEN
10402 
10403     BEGIN
10404 
10405         --  Load local records.
10406 
10407         l_revised_item_rec := x_revised_item_tbl(I);
10408 
10409 
10410 
10411         -- make sure that the unexposed record does not have remains of
10412         -- any previous processing. This could be possible in the consequent
10413         -- iterations of this loop
10414         l_rev_item_unexp_rec := l_rev_item_miss_rec;
10415         l_Rev_Item_Unexp_Rec.organization_id := ENG_GLOBALS.Get_org_id;
10416 
10417 
10418         l_revised_item_rec.transaction_type :=
10419                 UPPER(l_revised_item_rec.transaction_type);
10420 
10421         --
10422         -- be sure to set the process_children to false at the start of each
10423         -- iteration to avoid faulty processing of children at the end of the loop
10424         --
10425         l_process_children := FALSE;
10426 
10427         IF p_change_notice IS NOT NULL AND
10428            p_organization_id IS NOT NULL
10429         THEN
10430                 l_eco_parent_exists := TRUE;
10431         END IF;
10432 
10433         -- Process Flow Step 2: Check if record has not yet been processed and
10434         -- that it is the child of the parent that called this procedure
10435         --
10436 
10437 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Processing Revised Item . . . ' || l_revised_item_rec.revised_item_name); END IF;
10438 
10439         IF --(l_revised_item_rec.return_status IS NULL OR
10440             --l_revised_item_rec.return_status = FND_API.G_MISS_CHAR)
10441            --AND
10442            (NOT l_eco_parent_exists
10443             OR
10444             (l_eco_parent_exists AND
10445              (l_revised_item_rec.ECO_Name = p_change_notice AND
10446               l_rev_item_unexp_rec.organization_id = p_organization_id)))
10447         THEN
10448 
10449            l_return_status := FND_API.G_RET_STS_SUCCESS;
10450 
10451            l_revised_item_rec.return_status := FND_API.G_RET_STS_SUCCESS;
10452 
10453            -- Check if transaction_type is valid
10454            --
10455 
10456            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Check transaction_type validity'); END IF;
10457            ENG_GLOBALS.Transaction_Type_Validity
10458            (   p_transaction_type       => l_revised_item_rec.transaction_type
10459            ,   p_entity                 => 'Rev_Items'
10460            ,   p_entity_id              => l_revised_item_rec.revised_item_name
10461            ,   x_valid                  => l_valid
10462            ,   x_Mesg_Token_Tbl         => l_Mesg_Token_Tbl
10463            );
10464 
10465            IF NOT l_valid
10466            THEN
10467                 l_return_status := Error_Handler.G_STATUS_ERROR;
10468                 RAISE EXC_SEV_QUIT_RECORD;
10469            END IF;
10470 
10471            -- Process Flow step 4: Convert user unique index to unique index
10472            --
10473 
10474            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Converting user unique index to unique index'); END IF;
10475            ENG_Val_To_Id.Revised_Item_UUI_To_UI
10476                 ( p_revised_item_rec   => l_revised_item_rec
10477                 , p_rev_item_unexp_rec => l_rev_item_unexp_rec
10478                 , x_rev_item_unexp_rec => l_rev_item_unexp_rec
10479                 , x_Mesg_Token_Tbl     => l_Mesg_Token_Tbl
10480                 , x_Return_Status      => l_return_status
10481                 );
10482 
10483            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
10484 
10485            IF l_return_status = Error_Handler.G_STATUS_ERROR
10486            THEN
10487                 l_other_message := 'ENG_RIT_UUI_SEV_ERROR';
10488                 l_other_token_tbl(1).token_name := 'REVISED_ITEM_NAME';
10489                 l_other_token_tbl(1).token_value := l_revised_item_rec.revised_item_name;
10490                 RAISE EXC_SEV_QUIT_BRANCH;
10491            ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
10492            THEN
10493                 l_other_message := 'ENG_RIT_UUI_UNEXP_SKIP';
10494                 l_other_token_tbl(1).token_name := 'REVISED_ITEM_NAME';
10495                 l_other_token_tbl(1).token_value := l_revised_item_rec.revised_item_name;
10496                 RAISE EXC_UNEXP_SKIP_OBJECT;
10497            END IF;
10498 
10499            BOM_Globals.Set_Unit_Controlled_Item
10500            ( p_inventory_item_id => l_rev_item_unexp_rec.revised_item_id
10501            , p_organization_id  => l_rev_item_unexp_rec.organization_id
10502            );
10503 
10504            -- Process Flow step 5: Verify ECO's existence in database, if
10505            -- the revised item is being created on an ECO and the business
10506            -- object does not carry the ECO header
10507 
10508            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Check parent existence'); END IF;
10509 
10510            IF l_revised_item_rec.transaction_type = ENG_GLOBALS.G_OPR_CREATE
10511               AND
10512               NOT l_eco_parent_exists
10513            THEN
10514                 ENG_Validate_ECO.Check_Existence
10515                 ( p_change_notice       => l_revised_item_rec.ECO_Name
10516                 , p_organization_id     => l_rev_item_unexp_rec.organization_id
10517                 , p_organization_code   => l_revised_item_rec.organization_code
10518                 , p_calling_entity      => 'CHILD'
10519                 , p_transaction_type    => 'XXX'
10520                 , x_eco_rec             => l_old_eco_rec
10521                 , x_eco_unexp_rec       => l_old_eco_unexp_rec
10522                 , x_Mesg_Token_Tbl      => l_Mesg_Token_Tbl
10523                 , x_return_status       => l_Return_Status
10524                 );
10525 
10526                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
10527 
10528                 IF l_return_status = Error_Handler.G_STATUS_ERROR
10529                 THEN
10530                    l_other_message := 'ENG_PARENTECO_NOT_EXIST';
10531                    l_other_token_tbl(1).token_name := 'ECO_NAME';
10532                    l_other_token_tbl(1).token_value := l_revised_item_rec.ECO_Name;
10533                    l_other_token_tbl(2).token_name := 'ORGANIZATION_CODE';
10534                    l_other_token_tbl(2).token_value := l_revised_item_rec.organization_code;
10535                    RAISE EXC_SEV_QUIT_OBJECT;
10536                 ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
10537                 THEN
10538                    l_other_message := 'ENG_RIT_LIN_UNEXP_SKIP';
10539                    l_other_token_tbl(1).token_name := 'REVISED_ITEM_NAME';
10540                    l_other_token_tbl(1).token_value := l_revised_item_rec.revised_item_name;
10541                    RAISE EXC_UNEXP_SKIP_OBJECT;
10542                 END IF;
10543            END IF;
10544 
10545          IF l_revised_item_rec.Transaction_Type IN
10546                 (ENG_GLOBALS.G_OPR_UPDATE, ENG_GLOBALS.G_OPR_DELETE)
10547            THEN
10548 
10549 	-- Bug 2918350
10550 	-- Start Changes
10551 	IF p_change_notice IS NOT NULL AND p_organization_id IS NOT NULL THEN
10552 		l_chk_co_sch := ret_co_status ( p_change_notice, p_organization_id);
10553 	ELSE
10554 		l_chk_co_sch := ret_co_status ( l_revised_item_rec.eco_name, l_rev_item_unexp_rec.organization_id);
10555 	END IF;
10556 
10557 	-- Added for bug 5756870
10558 	-- The update case when the CO is in scheduled status is handled saperately
10559 	IF  (l_revised_item_rec.Transaction_Type <> ENG_GLOBALS.G_OPR_UPDATE )
10560 		AND (l_chk_co_sch = 4) THEN
10561 		l_return_status := error_handler.g_status_error;
10562 		error_handler.add_error_token (p_message_name        => 'ENG_REV_ITM_NOT_UPD',
10563 			p_mesg_token_tbl      => l_mesg_token_tbl,
10564 			x_mesg_token_tbl      => l_mesg_token_tbl,
10565 			p_token_tbl           => l_token_tbl
10566 			);
10567 		RAISE exc_sev_quit_record;
10568 	END IF;
10569 
10570 	-- End Changes
10571        END IF;
10572 
10573           -- Bug No.:3614144 added by sseraphi to convert  new revision in small case to upper case while import
10574           -- adding this conversion before validations start.
10575 	   IF l_revised_item_rec.New_Revised_Item_Revision IS NOT null
10576 	   THEN
10577                 l_revised_item_rec.New_Revised_Item_Revision := UPPER(l_revised_item_rec.New_Revised_Item_Revision);
10578 	   END IF;
10579 	    IF l_revised_item_rec.Updated_Revised_Item_Revision IS NOT null
10580 	   THEN
10581                 l_revised_item_rec.Updated_Revised_Item_Revision := UPPER(l_revised_item_rec.Updated_Revised_Item_Revision);
10582 	   END IF;
10583            -- Process Flow step 5: Verify Revised Item's existence
10584            --
10585 
10586 	   IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Check existence'); END IF;
10587            ENG_Validate_Revised_Item.Check_Existence
10588                 (  p_revised_item_rec           => l_revised_item_rec
10589                 ,  p_rev_item_unexp_rec         => l_rev_item_unexp_rec
10590                 ,  x_old_revised_item_rec       => l_old_revised_item_rec
10591                 ,  x_old_rev_item_unexp_rec     => l_old_rev_item_unexp_rec
10592                 ,  x_Mesg_Token_Tbl             => l_Mesg_Token_Tbl
10593                 ,  x_return_status              => l_Return_Status
10594 		,  x_disable_revision           => x_disable_revision  --BUG 3034642
10595                 );
10596 
10597            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
10598 
10599            IF l_return_status = Error_Handler.G_STATUS_ERROR
10600            THEN
10601                 l_other_message := 'ENG_RIT_EXS_SEV_ERROR';
10602                 l_other_token_tbl(1).token_name := 'REVISED_ITEM_NAME';
10603                 l_other_token_tbl(1).token_value := l_revised_item_rec.revised_item_name;
10604                 l_other_token_tbl(2).token_name := 'ECO_NAME';
10605                 l_other_token_tbl(2).token_value := l_revised_item_rec.eco_name;
10606                 RAISE EXC_SEV_QUIT_BRANCH;
10607            ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
10608            THEN
10609                 l_other_message := 'ENG_RIT_EXS_UNEXP_SKIP';
10610                 l_other_token_tbl(1).token_name := 'REVISED_ITEM_NAME';
10611                 l_other_token_tbl(1).token_value := l_revised_item_rec.revised_item_name;
10612                 l_other_token_tbl(2).token_name := 'ECO_NAME';
10613                 l_other_token_tbl(2).token_value := l_revised_item_rec.eco_name;
10614                 RAISE EXC_UNEXP_SKIP_OBJECT;
10615            END IF;
10616 
10617 
10618            -- Process Flow step 6: Is Revised Item record an orphan ?
10619 
10620            IF NOT l_eco_parent_exists
10621            THEN
10622 
10623                 -- Process Flow step 7(a): Is ECO impl/cancl, or in wkflw process ?
10624                 --
10625 		-- Added for bug 5756870
10626 		-- In case if the transaciton is update, pass parameter to avoid scheduled date validations
10627 		IF  (l_revised_item_rec.Transaction_Type = ENG_GLOBALS.G_OPR_UPDATE ) THEN
10628 			ENG_Validate_ECO.Check_Access
10629 			( p_change_notice       => l_revised_item_rec.ECO_Name
10630 			, p_organization_id     => l_rev_item_unexp_rec.organization_id
10631 			, p_Mesg_Token_Tbl      => l_Mesg_Token_Tbl
10632 			, x_Mesg_Token_Tbl      => l_Mesg_Token_Tbl
10633 			, x_Return_Status       => l_return_status
10634 			, p_check_scheduled_status  => FALSE -- bug 5756870 , don't check for scheduled date validation..
10635 			);
10636 		ELSE
10637 
10638 			-- If the transaction is not update, fire the default validations...
10639 			ENG_Validate_ECO.Check_Access
10640 			( p_change_notice       => l_revised_item_rec.ECO_Name
10641 			, p_organization_id     => l_rev_item_unexp_rec.organization_id
10642 			, p_Mesg_Token_Tbl      => l_Mesg_Token_Tbl
10643 			, x_Mesg_Token_Tbl      => l_Mesg_Token_Tbl
10644 			, x_Return_Status       => l_return_status
10645 			, p_check_scheduled_status  => TRUE -- bug 5756870
10646 			);
10647 		END IF;
10648 
10649                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
10650 
10651                 IF l_return_status = Error_Handler.G_STATUS_ERROR
10652                 THEN
10653                         l_other_message := 'ENG_RIT_ECOACC_FAT_FATAL';
10654                         l_other_token_tbl(1).token_name := 'REVISED_ITEM_NAME';
10655                         l_other_token_tbl(1).token_value := l_revised_item_rec.revised_item_name;
10656                         l_return_status := 'F';
10657                         RAISE EXC_FAT_QUIT_OBJECT;
10658                 ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
10659                 THEN
10660                         l_other_message := 'ENG_RIT_ECOACC_UNEXP_SKIP';
10661                         l_other_token_tbl(1).token_name := 'REVISED_ITEM_NAME';
10662                         l_other_token_tbl(1).token_value := l_revised_item_rec.revised_item_name;
10663                         RAISE EXC_UNEXP_SKIP_OBJECT;
10664                 END IF;
10665            END IF;
10666 
10667            -- Process Flow step 7(b): check that user has access to revised item
10668            --
10669            -- Bug No: 5246049
10670            -- Moved validation outside 'IF NOT l_eco_parent_exists' as validation should happen in all cases
10671 
10672            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Check access'); END IF;
10673 		IF  (l_revised_item_rec.Transaction_Type = ENG_GLOBALS.G_OPR_UPDATE ) THEN
10674 		   ENG_Validate_Revised_Item.Check_Access
10675 		   (  p_change_notice      => l_revised_item_rec.ECO_Name
10676 		   ,  p_organization_id    => l_rev_item_unexp_rec.organization_id
10677 		   ,  p_revised_item_id    => l_rev_item_unexp_rec.revised_item_id
10678 		   ,  p_new_item_revision  => l_revised_item_rec.new_revised_item_revision
10679 		   ,  p_effectivity_date   => l_revised_item_rec.start_effective_date
10680 		   ,  p_new_routing_revsion   => l_revised_item_rec.new_routing_revision  -- Added by MK on 11/02/00
10681 		   ,  p_from_end_item_number  => l_revised_item_rec.from_end_item_unit_number -- Added by MK on 11/02/00
10682 		   ,  p_revised_item_name  => l_revised_item_rec.revised_item_name
10683 		   ,  p_Mesg_Token_Tbl     => l_Mesg_Token_Tbl
10684 		   ,  x_Mesg_Token_Tbl     => l_Mesg_Token_Tbl
10685 		   ,  x_return_status      => l_Return_Status
10686 		   , p_check_scheduled_status  => FALSE -- bug 5756870 , don't check for scheduled date validation..
10687 		   );
10688 		ELSE
10689 			ENG_Validate_Revised_Item.Check_Access
10690 		   (  p_change_notice      => l_revised_item_rec.ECO_Name
10691 		   ,  p_organization_id    => l_rev_item_unexp_rec.organization_id
10692 		   ,  p_revised_item_id    => l_rev_item_unexp_rec.revised_item_id
10693 		   ,  p_new_item_revision  => l_revised_item_rec.new_revised_item_revision
10694 		   ,  p_effectivity_date   => l_revised_item_rec.start_effective_date
10695 		   ,  p_new_routing_revsion   => l_revised_item_rec.new_routing_revision  -- Added by MK on 11/02/00
10696 		   ,  p_from_end_item_number  => l_revised_item_rec.from_end_item_unit_number -- Added by MK on 11/02/00
10697 		   ,  p_revised_item_name  => l_revised_item_rec.revised_item_name
10698 		   ,  p_Mesg_Token_Tbl     => l_Mesg_Token_Tbl
10699 		   ,  x_Mesg_Token_Tbl     => l_Mesg_Token_Tbl
10700 		   ,  x_return_status      => l_Return_Status
10701 		   , p_check_scheduled_status  => TRUE -- bug 5756870 , don't check for scheduled date validation..
10702 		   );
10703 
10704 		END IF;
10705 
10706 
10707            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
10708 
10709            IF l_return_status = Error_Handler.G_STATUS_ERROR
10710            THEN
10711                    l_other_message := 'ENG_RIT_ACCESS_FAT_FATAL';
10712                    l_other_token_tbl(1).token_name := 'REVISED_ITEM_NAME';
10713                    l_other_token_tbl(1).token_value := l_revised_item_rec.revised_item_name;
10714                    l_return_status := 'F';
10715                    RAISE EXC_FAT_QUIT_BRANCH;
10716            ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
10717            THEN
10718                    l_other_message := 'ENG_RIT_ACCESS_UNEXP_SKIP';
10719                    l_other_token_tbl(1).token_name := 'REVISED_ITEM_NAME';
10720                    l_other_token_tbl(1).token_value := l_revised_item_rec.revised_item_name;
10721                    RAISE EXC_UNEXP_SKIP_OBJECT;
10722            END IF;
10723 
10724 
10725 
10726            /****  Following Process Flow is for ECO Routing ***/
10727            --
10728            -- Process Flow step 8:  Flow Routing's operability for routing.
10729            -- (for future release, flow routing is not supported in current release
10730            -- Added by MK on 08/24/2000
10731            --
10732            /* Comment out for current release
10733            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Check Non-Flow Routing'); END IF;
10734 
10735            Bom_Validate_Rtg_Header.Check_flow_routing_operability ;
10736            (  p_assembly_item_name  =>  l_revised_item_rec.revised_item_name
10737             , p_cfm_routing_flag    =>  l_rev_item_unexp_rec.cfm_routing_flag
10738                                         -- in future, this shoud be exposed column
10739             , p_organization_id     =>  l_rev_item_unexp_rec.organization_id
10740             , x_mesg_token_tbl      =>  l_mesg_token_tbl
10741             , x_return_status       =>  l_return_status
10742             );
10743 
10744            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
10745 
10746 
10747            IF l_return_status = Error_Handler.G_STATUS_ERROR
10748            THEN
10749                 l_other_message := 'BOM_RTG_FRACC_ERROR';
10750                 l_other_token_tbl(1).token_name := 'ASSEMBLY_ITEM_NAME';
10751                 l_other_token_tbl(1).token_value :=
10752                                         l_revised_item_rec.revised_item_name;
10753                 RAISE EXC_SEV_QUIT_BRANCH;
10754            ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
10755            THEN
10756                 l_other_message := 'BOM_RTG_FRACC_UNEXP_SKIP';
10757                 l_other_token_tbl(1).token_name := 'ASSEMBLY_ITEM_NAME';
10758                 l_other_token_tbl(1).token_value :=
10759                                         l_revised_item_rec.revised_item_name;
10760                 RAISE EXC_UNEXP_SKIP_OBJECT;
10761            END IF;
10762            */
10763 
10764 
10765 
10766            -- Process Flow step 9: Value to Id conversions
10767            --
10768 
10769            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Value-id conversions'); END IF;
10770            ENG_Val_To_Id.Revised_Item_VID
10771                 ( x_Return_Status       => l_return_status
10772                 , x_Mesg_Token_Tbl      => l_Mesg_Token_Tbl
10773                 , p_rev_item_unexp_Rec  => l_rev_item_unexp_rec
10774                 , x_rev_item_unexp_Rec  => l_rev_item_unexp_rec
10775                 , p_revised_item_Rec    => l_revised_item_rec
10776                 );
10777 
10778            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
10779 
10780            IF l_return_status = Error_Handler.G_STATUS_ERROR
10781            THEN
10782                 IF l_revised_item_rec.transaction_type = 'CREATE'
10783                 THEN
10784                         l_other_message := 'ENG_RIT_VID_CSEV_SKIP';
10785                         l_other_token_tbl(1).token_name := 'REVISED_ITEM_NAME';
10786                         l_other_token_tbl(1).token_value := l_revised_item_rec.revised_item_name;
10787                         RAISE EXC_SEV_SKIP_BRANCH;
10788                 ELSE
10789                         RAISE EXC_SEV_QUIT_RECORD;
10790                 END IF;
10791            ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
10792            THEN
10793                 RAISE EXC_UNEXP_SKIP_OBJECT;
10794            ELSIF l_return_status ='S' AND
10795                 l_Mesg_Token_Tbl.COUNT <>0
10796            THEN
10797                 Eco_Error_Handler.Log_Error
10798                 (  p_revised_item_tbl   => x_revised_item_tbl
10799                 ,  p_rev_component_tbl  => x_rev_component_tbl
10800                 ,  p_ref_designator_tbl => x_ref_designator_tbl
10801                 ,  p_sub_component_tbl  => x_sub_component_tbl
10802                 ,  p_rev_operation_tbl      => x_rev_operation_tbl    --L1
10803                 ,  p_rev_op_resource_tbl    => x_rev_op_resource_tbl  --L1
10804                 ,  p_rev_sub_resource_tbl   => x_rev_sub_resource_tbl --L1
10805                 ,  p_mesg_token_tbl     => l_mesg_token_tbl
10806                 ,  p_error_status       => 'W'
10807                 ,  p_error_level        => 3
10808                 ,  p_entity_index       => I
10809                 ,  x_eco_rec            => l_eco_rec
10810                 ,  x_eco_revision_tbl   => l_eco_revision_tbl
10811                 ,  x_revised_item_tbl   => x_revised_item_tbl
10812                 ,  x_rev_component_tbl  => x_rev_component_tbl
10813                 ,  x_ref_designator_tbl => x_ref_designator_tbl
10814                 ,  x_sub_component_tbl  => x_sub_component_tbl
10815                 ,  x_rev_operation_tbl      => x_rev_operation_tbl    --L1
10816                 ,  x_rev_op_resource_tbl    => x_rev_op_resource_tbl  --L1
10817                 ,  x_rev_sub_resource_tbl   => x_rev_sub_resource_tbl --L1
10818                 );
10819            END IF;
10820 
10821 	     -- Check for access if the status is scheduled...
10822 	   -- Added for bug 5756870
10823 	   --Note: we need not check if the transaction type is anything other than update
10824 	   -- because it has been check above, and execution will not make it to this line in such cases
10825 
10826 	   IF(l_chk_co_sch = 4 OR l_old_revised_item_rec.status_type = 4) THEN
10827 		   ENG_Validate_Revised_Item.Check_Access_Scheduled(
10828 			  x_Return_Status       => l_return_status
10829 			, x_Mesg_Token_Tbl      => l_Mesg_Token_Tbl
10830 			, p_rev_item_unexp_Rec  => l_rev_item_unexp_rec
10831 			, p_revised_item_Rec    => l_revised_item_rec
10832 			);
10833 
10834 
10835 			   IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
10836 
10837 			   IF l_return_status = Error_Handler.G_STATUS_ERROR
10838 			   THEN
10839 
10840 				   l_other_message := 'ENG_RIT_SCHEDULE_ACCESS_FATAL';
10841 				   l_other_token_tbl(1).token_name := 'REVISED_ITEM_NAME';
10842 				   l_other_token_tbl(1).token_value := l_revised_item_rec.revised_item_name;
10843 				   l_return_status := 'F';
10844 				   RAISE EXC_FAT_QUIT_BRANCH;
10845 			   ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
10846 			   THEN
10847 
10848 				   l_other_message := 'ENG_RIT_SCHEDULE_ACCESS_UNEXP';
10849 				   l_other_token_tbl(1).token_name := 'REVISED_ITEM_NAME';
10850 				   l_other_token_tbl(1).token_value := l_revised_item_rec.revised_item_name;
10851 				   RAISE EXC_UNEXP_SKIP_OBJECT;
10852 			   END IF;
10853 
10854 			   if( p_rev_component_tbl.COUNT <> 0
10855 			      OR   p_ref_designator_tbl.COUNT<> 0
10856 			      OR   p_sub_component_tbl.COUNT<> 0
10857 			      OR   p_rev_operation_tbl.COUNT<> 0
10858 			      OR    p_rev_op_resource_tbl.COUNT<> 0
10859 			      OR   p_rev_sub_resource_tbl.COUNT<> 0 ) THEN
10860 
10861 				l_other_message := 'ENG_RIT_NO_CHILD_IN_SCHEDULED';
10862 				l_other_token_tbl(1).token_name := 'REVISED_ITEM_NAME';
10863 				l_other_token_tbl(1).token_value := l_revised_item_rec.revised_item_name;
10864 				l_return_status := 'F';
10865 				RAISE EXC_FAT_QUIT_BRANCH;
10866 			   END IF;
10867 
10868 	   END IF;
10869 
10870 
10871 	   -- Process Flow step 10: Attribute Validation for CREATE and UPDATE
10872            --
10873 
10874 
10875            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Attribute Validation'); END IF;
10876            IF l_revised_item_rec.Transaction_Type IN
10877                 (ENG_GLOBALS.G_OPR_CREATE, ENG_GLOBALS.G_OPR_UPDATE)
10878            THEN
10879                 ENG_Validate_Revised_Item.Check_Attributes
10880                 ( x_return_status              => l_return_status
10881                 , x_Mesg_Token_Tbl             => l_Mesg_Token_Tbl
10882                 , p_revised_item_rec           => l_revised_item_rec
10883                 , p_rev_item_unexp_rec         => l_rev_item_unexp_rec
10884                 , p_old_revised_item_rec       => l_old_revised_item_rec
10885                 , p_old_rev_item_unexp_rec     => l_old_rev_item_unexp_rec
10886                 );
10887 
10888                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
10889 
10890                 IF l_return_status = Error_Handler.G_STATUS_ERROR
10891                 THEN
10892                    IF l_revised_item_rec.transaction_type = 'CREATE'
10893                    THEN
10894                         l_other_message := 'ENG_RIT_ATTVAL_CSEV_SKIP';
10895                         l_other_token_tbl(1).token_name := 'REVISED_ITEM_NAME';
10896                         l_other_token_tbl(1).token_value := l_revised_item_rec.revised_item_name;
10897                         RAISE EXC_SEV_SKIP_BRANCH;
10898                    ELSE
10899                         RAISE EXC_SEV_QUIT_RECORD;
10900                    END IF;
10901                 ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
10902                 THEN
10903                    l_other_message := 'ENG_RIT_ATTVAL_UNEXP_SKIP';
10904                    l_other_token_tbl(1).token_name := 'REVISED_ITEM_NAME';
10905                    l_other_token_tbl(1).token_value := l_revised_item_rec.revised_item_name;
10906                    RAISE EXC_UNEXP_SKIP_OBJECT;
10907                 ELSIF l_return_status ='S' AND
10908                       l_Mesg_Token_Tbl.COUNT <>0
10909                 THEN
10910                    Eco_Error_Handler.Log_Error
10911                         (  p_revised_item_tbl   => x_revised_item_tbl
10912                         ,  p_rev_component_tbl  => x_rev_component_tbl
10913                         ,  p_ref_designator_tbl => x_ref_designator_tbl
10914                         ,  p_sub_component_tbl  => x_sub_component_tbl
10915                         ,  p_rev_operation_tbl   => x_rev_operation_tbl    --L1
10916                         ,  p_rev_op_resource_tbl => x_rev_op_resource_tbl  --L1
10917                         ,  p_rev_sub_resource_tbl=> x_rev_sub_resource_tbl --L1
10918                         ,  p_mesg_token_tbl     =>  l_mesg_token_tbl
10919                         ,  p_error_status       => 'W'
10920                         ,  p_error_level        => 3
10921                         ,  p_entity_index       => I
10922                         ,  x_eco_rec            => l_eco_rec
10923                         ,  x_eco_revision_tbl   => l_eco_revision_tbl
10924                         ,  x_revised_item_tbl   => x_revised_item_tbl
10925                         ,  x_rev_component_tbl  => x_rev_component_tbl
10926                         ,  x_ref_designator_tbl => x_ref_designator_tbl
10927                         ,  x_sub_component_tbl  => x_sub_component_tbl
10928                         ,  x_rev_operation_tbl   => x_rev_operation_tbl    --L1
10929                         ,  x_rev_op_resource_tbl => x_rev_op_resource_tbl  --L1
10930                         ,  x_rev_sub_resource_tbl=> x_rev_sub_resource_tbl --L1
10931                         );
10932                 END IF;
10933            END IF;
10934 
10935            IF l_revised_item_rec.Transaction_Type IN
10936                 (ENG_GLOBALS.G_OPR_UPDATE, ENG_GLOBALS.G_OPR_DELETE)
10937            THEN
10938 
10939                 -- Process flow step 11 - Populate NULL columns for Update and
10940                 -- Delete.
10941 
10942                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Populating NULL Columns'); END IF;
10943                 Eng_Default_Revised_Item.Populate_NULL_Columns
10944                 (   p_revised_item_rec          => l_revised_item_rec
10945                 ,   p_old_revised_item_rec      => l_old_revised_item_rec
10946                 ,   p_rev_item_unexp_rec        => l_rev_item_unexp_rec
10947                 ,   p_old_rev_item_unexp_rec    => l_old_rev_item_unexp_rec
10948                 ,   x_revised_item_rec          => l_revised_item_rec
10949                 ,   x_rev_item_unexp_rec        => l_rev_item_unexp_rec
10950                 );
10951 
10952            ELSIF l_revised_item_rec.Transaction_Type = ENG_GLOBALS.G_OPR_CREATE THEN
10953 
10954                 -- Process Flow step 12: Default missing values for Operation CREATE
10955                 --
10956 
10957                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Attribute Defaulting'); END IF;
10958                 Eng_Default_Revised_Item.Attribute_Defaulting
10959                 (   p_revised_item_rec          => l_revised_item_rec
10960                 ,   p_rev_item_unexp_rec        => l_rev_item_unexp_rec
10961                 ,   x_revised_item_rec          => l_revised_item_rec
10962                 ,   x_rev_item_unexp_rec        => l_rev_item_unexp_rec
10963                 ,   x_Mesg_Token_Tbl            => l_Mesg_Token_Tbl
10964                 ,   x_return_status             => l_return_status
10965                 );
10966 
10967                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
10968 
10969                 IF l_return_status = Error_Handler.G_STATUS_ERROR
10970                 THEN
10971                         l_other_message := 'ENG_RIT_ATTDEF_SEV_SKIP';
10972                         l_other_token_tbl(1).token_name := 'REVISED_ITEM_NAME';
10973                         l_other_token_tbl(1).token_value := l_revised_item_rec.revised_item_name;
10974                         RAISE EXC_SEV_SKIP_BRANCH;
10975                 ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
10976                 THEN
10977                         l_other_message := 'ENG_RIT_ATTDEF_UNEXP_SKIP';
10978                         l_other_token_tbl(1).token_name := 'REVISED_ITEM_NAME';
10979                         l_other_token_tbl(1).token_value := l_revised_item_rec.revised_item_name;
10980                         RAISE EXC_UNEXP_SKIP_OBJECT;
10981                 ELSIF l_return_status ='S' AND
10982                         l_Mesg_Token_Tbl.COUNT <>0
10983                 THEN
10984                         Eco_Error_Handler.Log_Error
10985                         (  p_revised_item_tbl   => x_revised_item_tbl
10986                         ,  p_rev_component_tbl  => x_rev_component_tbl
10987                         ,  p_ref_designator_tbl => x_ref_designator_tbl
10988                         ,  p_sub_component_tbl  => x_sub_component_tbl
10989                         ,  p_rev_operation_tbl   => x_rev_operation_tbl    --L1
10990                         ,  p_rev_op_resource_tbl => x_rev_op_resource_tbl  --L1
10991                         ,  p_rev_sub_resource_tbl=> x_rev_sub_resource_tbl --L1
10992                         ,  p_mesg_token_tbl     => l_mesg_token_tbl
10993                         ,  p_error_status       => 'S'
10994                         ,  p_error_level        => 3
10995                         ,  p_entity_index       => I
10996                         ,  x_eco_rec            => l_eco_rec
10997                         ,  x_eco_revision_tbl   => l_eco_revision_tbl
10998                         ,  x_revised_item_tbl   => x_revised_item_tbl
10999                         ,  x_rev_component_tbl  => x_rev_component_tbl
11000                         ,  x_ref_designator_tbl => x_ref_designator_tbl
11001                         ,  x_sub_component_tbl  => x_sub_component_tbl
11002                         ,  x_rev_operation_tbl   => x_rev_operation_tbl    --L1
11003                         ,  x_rev_op_resource_tbl => x_rev_op_resource_tbl  --L1
11004                         ,  x_rev_sub_resource_tbl=> x_rev_sub_resource_tbl --L1
11005                         );
11006                 END IF;
11007            END IF;
11008 
11009            -- Process Flow step 13 - Conditionally required attributes check
11010            --
11011 
11012            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Conditionally required attributes check'); END IF;
11013 
11014            --
11015            -- Put conditionally required check procedure here
11016            --
11017 
11018            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
11019 
11020            ENG_Validate_Revised_Item.Check_Required
11021                 ( x_return_status              => l_return_status
11022                 , x_Mesg_Token_Tbl             => l_Mesg_Token_Tbl
11023                 , p_revised_item_rec           => l_revised_item_rec
11024                 );
11025 
11026            IF l_return_status = Error_Handler.G_STATUS_ERROR
11027            THEN
11028                 IF l_revised_item_rec.transaction_type = 'CREATE'
11029                 THEN
11030                         l_other_message := 'ENG_RIT_CONREQ_CSEV_SKIP';
11031                         l_other_token_tbl(1).token_name := 'REVISED_ITEM_NAME';
11032                         l_other_token_tbl(1).token_value := l_revised_item_rec.revised_item_name;
11033                         RAISE EXC_SEV_SKIP_BRANCH;
11034                 ELSE
11035                         RAISE EXC_SEV_QUIT_RECORD;
11036                 END IF;
11037            ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
11038            THEN
11039                 l_other_message := 'ENG_RIT_CONREQ_UNEXP_SKIP';
11040                 l_other_token_tbl(1).token_name := 'REVISED_ITEM_NAME';
11041                 l_other_token_tbl(1).token_value := l_revised_item_rec.revised_item_name;
11042                 RAISE EXC_UNEXP_SKIP_OBJECT;
11043            ELSIF l_return_status ='S' AND
11044                 l_Mesg_Token_Tbl.COUNT <>0
11045            THEN
11046                 Eco_Error_Handler.Log_Error
11047                 (  p_revised_item_tbl       => x_revised_item_tbl
11048                 ,  p_rev_component_tbl      => x_rev_component_tbl
11049                 ,  p_ref_designator_tbl     => x_ref_designator_tbl
11050                 ,  p_sub_component_tbl      => x_sub_component_tbl
11051                 ,  p_rev_operation_tbl      => x_rev_operation_tbl    --L1
11052                 ,  p_rev_op_resource_tbl    => x_rev_op_resource_tbl  --L1
11053                 ,  p_rev_sub_resource_tbl   => x_rev_sub_resource_tbl --L1
11054                 ,  p_mesg_token_tbl         => l_mesg_token_tbl
11055                 ,  p_error_status           => 'W'
11056                 ,  p_error_level            => 3
11057                 ,  p_entity_index           => I
11058                 ,  x_eco_rec                => l_eco_rec
11059                 ,  x_eco_revision_tbl       => l_eco_revision_tbl
11060                 ,  x_revised_item_tbl       => x_revised_item_tbl
11061                 ,  x_rev_component_tbl      => x_rev_component_tbl
11062                 ,  x_ref_designator_tbl     => x_ref_designator_tbl
11063                 ,  x_sub_component_tbl      => x_sub_component_tbl
11064                 ,  x_rev_operation_tbl      => x_rev_operation_tbl    --L1
11065                 ,  x_rev_op_resource_tbl    => x_rev_op_resource_tbl  --L1
11066                 ,  x_rev_sub_resource_tbl   => x_rev_sub_resource_tbl --L1
11067                 );
11068            END IF;
11069 
11070            -- Process Flow step 14: Entity defaulting for CREATE and UPDATE
11071            --
11072 
11073            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Entity defaulting'); END IF;
11074            IF l_revised_item_rec.Transaction_Type IN
11075                 (ENG_GLOBALS.G_OPR_CREATE, ENG_GLOBALS.G_OPR_UPDATE)
11076            THEN
11077                 ENG_Default_Revised_Item.Entity_Defaulting
11078                 (   p_revised_item_rec          => l_revised_item_rec
11079                 ,   p_rev_item_unexp_rec        => l_rev_item_unexp_rec
11080                 ,   p_old_revised_item_rec      => l_old_revised_item_rec
11081                 ,   p_old_rev_item_unexp_rec    => l_old_rev_item_unexp_rec
11082                 ,   x_revised_item_rec          => l_revised_item_rec
11083                 ,   x_rev_item_unexp_rec        => l_rev_item_unexp_rec
11084                 ,   x_Mesg_Token_Tbl            => l_Mesg_Token_Tbl
11085                 ,   x_return_status             => l_return_status
11086                 );
11087 
11088                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
11089 
11090                 IF l_return_status = Error_Handler.G_STATUS_ERROR
11091                 THEN
11092                    IF l_revised_item_rec.transaction_type = 'CREATE'
11093                    THEN
11094                         l_other_message := 'ENG_RIT_ENTDEF_CSEV_SKIP';
11095                         l_other_token_tbl(1).token_name := 'REVISED_ITEM_NAME';
11096                         l_other_token_tbl(1).token_value := l_revised_item_rec.revised_item_name;
11097                         RAISE EXC_SEV_SKIP_BRANCH;
11098                    ELSE
11099                         RAISE EXC_SEV_QUIT_RECORD;
11100                    END IF;
11101                 ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
11102                 THEN
11103                         l_other_message := 'ENG_RIT_ENTDEF_UNEXP_SKIP';
11104                         l_other_token_tbl(1).token_name := 'REVISED_ITEM_NAME';
11105                         l_other_token_tbl(1).token_value := l_revised_item_rec.revised_item_name;
11106                         RAISE EXC_UNEXP_SKIP_OBJECT;
11107                 ELSIF l_return_status ='S' AND
11108                         l_Mesg_Token_Tbl.COUNT <>0
11109                 THEN
11110                         Eco_Error_Handler.Log_Error
11111                         (  p_revised_item_tbl    => x_revised_item_tbl
11112                         ,  p_rev_component_tbl   => x_rev_component_tbl
11113                         ,  p_ref_designator_tbl  => x_ref_designator_tbl
11114                         ,  p_sub_component_tbl   => x_sub_component_tbl
11115                         ,  p_rev_operation_tbl   => x_rev_operation_tbl    --L1
11116                         ,  p_rev_op_resource_tbl => x_rev_op_resource_tbl  --L1
11117                         ,  p_rev_sub_resource_tbl=> x_rev_sub_resource_tbl --L1
11118                         ,  p_mesg_token_tbl      => l_mesg_token_tbl
11119                         ,  p_error_status        => 'W'
11120                         ,  p_error_level         => 3
11121                         ,  p_entity_index        => I
11122                         ,  x_eco_rec             => l_eco_rec
11123                         ,  x_eco_revision_tbl    => l_eco_revision_tbl
11124                         ,  x_revised_item_tbl    => x_revised_item_tbl
11125                         ,  x_rev_component_tbl   => x_rev_component_tbl
11126                         ,  x_ref_designator_tbl  => x_ref_designator_tbl
11127                         ,  x_sub_component_tbl   => x_sub_component_tbl
11128                         ,  x_rev_operation_tbl   => x_rev_operation_tbl    --L1
11129                         ,  x_rev_op_resource_tbl => x_rev_op_resource_tbl  --L1
11130                         ,  x_rev_sub_resource_tbl=> x_rev_sub_resource_tbl --L1
11131                         );
11132                 END IF;
11133            END IF;
11134 
11135            -- Process Flow step 15 - Entity Level Validation
11136            --
11137 
11138            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Entity validation'); END IF;
11139 
11140            IF l_revised_item_rec.transaction_type = 'DELETE'
11141            THEN
11142                 Eng_Validate_Revised_Item.Check_Entity_Delete
11143                 (  p_revised_item_rec     => l_revised_item_rec
11144                 ,  p_rev_item_unexp_rec   => l_rev_item_unexp_rec
11145                 ,  x_Mesg_Token_Tbl       => l_Mesg_Token_Tbl
11146                 ,  x_return_status        => l_Return_Status
11147                 );
11148            ELSE
11149                 Eng_Validate_Revised_Item.Check_Entity
11150                 (  p_revised_item_rec     => l_revised_item_rec
11151                 ,  p_rev_item_unexp_rec   => l_rev_item_unexp_rec
11152                 ,  p_old_revised_item_rec => l_old_revised_item_rec
11153                 ,  p_old_rev_item_unexp_rec => l_old_rev_item_unexp_rec
11154                 ,  x_Mesg_Token_Tbl       => l_Mesg_Token_Tbl
11155                 ,  x_return_status        => l_Return_Status
11156                 );
11157            END IF;
11158 
11159            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
11160 
11161            IF l_return_status = Error_Handler.G_STATUS_ERROR
11162            THEN
11163                 IF l_revised_item_rec.transaction_type = 'CREATE'
11164                 THEN
11165                         l_other_message := 'ENG_RIT_ENTVAL_CSEV_SKIP';
11166                         l_other_token_tbl(1).token_name := 'REVISED_ITEM_NAME';
11167                         l_other_token_tbl(1).token_value := l_revised_item_rec.revised_item_name;
11168                         RAISE EXC_SEV_SKIP_BRANCH;
11169                 ELSE
11170                         RAISE EXC_SEV_QUIT_RECORD;
11171                 END IF;
11172            ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
11173            THEN
11174                 l_other_message := 'ENG_RIT_ENTVAL_UNEXP_SKIP';
11175                 l_other_token_tbl(1).token_name := 'REVISED_ITEM_NAME';
11176                 l_other_token_tbl(1).token_value := l_revised_item_rec.revised_item_name;
11177                 RAISE EXC_UNEXP_SKIP_OBJECT;
11178            ELSIF l_return_status ='S' AND
11179                 l_Mesg_Token_Tbl.COUNT <>0
11180            THEN
11181                 Eco_Error_Handler.Log_Error
11182                 (  p_revised_item_tbl       => x_revised_item_tbl
11183                 ,  p_rev_component_tbl      => x_rev_component_tbl
11184                 ,  p_ref_designator_tbl     => x_ref_designator_tbl
11185                 ,  p_sub_component_tbl      => x_sub_component_tbl
11186                 ,  p_rev_operation_tbl      => x_rev_operation_tbl    --L1
11187                 ,  p_rev_op_resource_tbl    => x_rev_op_resource_tbl  --L1
11188                 ,  p_rev_sub_resource_tbl   => x_rev_sub_resource_tbl --L1
11189                 ,  p_mesg_token_tbl         => l_mesg_token_tbl
11190                 ,  p_error_status           => 'W'
11191                 ,  p_error_level            => 3
11192                 ,  p_entity_index           => I
11193                 ,  x_eco_rec                => l_eco_rec
11194                 ,  x_eco_revision_tbl       => l_eco_revision_tbl
11195                 ,  x_revised_item_tbl       => x_revised_item_tbl
11196                 ,  x_rev_component_tbl      => x_rev_component_tbl
11197                 ,  x_ref_designator_tbl     => x_ref_designator_tbl
11198                 ,  x_sub_component_tbl      => x_sub_component_tbl
11199                 ,  x_rev_operation_tbl      => x_rev_operation_tbl    --L1
11200                 ,  x_rev_op_resource_tbl    => x_rev_op_resource_tbl  --L1
11201                 ,  x_rev_sub_resource_tbl   => x_rev_sub_resource_tbl --L1
11202                 );
11203            END IF;
11204      /*      -- Fixed Bug 12870702 begin --commented by bug 14571849
11205            l_rev_comp_flag := 'N';
11206 
11207            FOR rev_comp_index IN 1..x_rev_component_tbl.COUNT LOOP
11208              IF (x_rev_component_tbl(rev_comp_index).eco_name = x_revised_item_tbl(I).eco_name
11209                   AND x_rev_component_tbl(rev_comp_index).organization_code = x_revised_item_tbl(I).organization_code
11210                   AND x_rev_component_tbl(rev_comp_index).revised_item_name = x_revised_item_tbl(I).revised_item_name
11211                   AND NVL(x_rev_component_tbl(rev_comp_index).new_revised_item_revision, FND_API.G_MISS_CHAR) = NVL(x_revised_item_tbl(I).new_revised_item_revision, FND_API.G_MISS_CHAR) -- Bug: 13451729
11212                   AND (x_rev_component_tbl(rev_comp_index).component_item_name is not NULL
11213                         or x_rev_component_tbl(rev_comp_index).component_item_name <> FND_API.G_MISS_CHAR)
11214                  ) THEN
11215                     l_rev_comp_flag := 'Y';
11216                     EXIT;
11217               END IF;
11218            END LOOP;
11219 
11220            -- Bug 12870702, if there is no revised component, the bill_sequence_id = null, and save null into Eng_revised_items.bill_sequence_id
11221            IF l_rev_comp_flag = 'N' THEN
11222              l_rev_item_unexp_rec.bill_sequence_id := NULL;
11223            END IF;
11224 
11225            -- Fixed Bug 12870702 end;  */
11226            -- Process Flow step 16 : Database Writes
11227            --
11228 
11229            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Writing to the database'); END IF;
11230            ENG_Revised_Item_Util.Perform_Writes
11231                 (   p_revised_item_rec          => l_revised_item_rec
11232                 ,   p_rev_item_unexp_rec        => l_rev_item_unexp_rec
11233                 ,   x_Mesg_Token_Tbl            => l_Mesg_Token_Tbl
11234                 ,   x_return_status             => l_return_status
11235                 );
11236 
11237            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
11238 
11239            IF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
11240            THEN
11241                 l_other_message := 'ENG_RIT_WRITES_UNEXP_SKIP';
11242                 l_other_token_tbl(1).token_name := 'REVISED_ITEM_NAME';
11243                 l_other_token_tbl(1).token_value := l_revised_item_rec.revised_item_name;
11244                 RAISE EXC_UNEXP_SKIP_OBJECT;
11245            ELSIF l_return_status ='S' AND
11246               l_Mesg_Token_Tbl.COUNT <>0
11247            THEN
11248                 Eco_Error_Handler.Log_Error
11249                 (  p_revised_item_tbl       => x_revised_item_tbl
11250                 ,  p_rev_component_tbl      => x_rev_component_tbl
11251                 ,  p_ref_designator_tbl     => x_ref_designator_tbl
11252                 ,  p_sub_component_tbl      => x_sub_component_tbl
11253                 ,  p_rev_operation_tbl      => x_rev_operation_tbl    --L1
11254                 ,  p_rev_op_resource_tbl    => x_rev_op_resource_tbl  --L1
11255                 ,  p_rev_sub_resource_tbl   => x_rev_sub_resource_tbl --L1
11256                 ,  p_mesg_token_tbl         => l_mesg_token_tbl
11257                 ,  p_error_status           => 'W'
11258                 ,  p_error_level            => 3
11259                 ,  p_entity_index           => I
11260                 ,  x_eco_rec                => l_eco_rec
11261                 ,  x_eco_revision_tbl       => l_eco_revision_tbl
11262                 ,  x_revised_item_tbl       => x_revised_item_tbl
11263                 ,  x_rev_component_tbl      => x_rev_component_tbl
11264                 ,  x_ref_designator_tbl     => x_ref_designator_tbl
11265                 ,  x_sub_component_tbl      => x_sub_component_tbl
11266                 ,  x_rev_operation_tbl      => x_rev_operation_tbl    --L1
11267                 ,  x_rev_op_resource_tbl    => x_rev_op_resource_tbl  --L1
11268                 ,  x_rev_sub_resource_tbl   => x_rev_sub_resource_tbl --L1
11269                 );
11270            END IF;
11271 
11272 IF Bom_Globals.Get_Debug = 'Y' THEN
11273      Error_Handler.Write_Debug('Writing to the database for Rev Item is completed with '||l_return_status );
11274 END IF;
11275 
11276         END IF; -- END IF statement that checks RETURN STATUS
11277 
11278         --  Load tables.
11279 
11280         x_revised_item_tbl(I)          := l_revised_item_rec;
11281 
11282         --
11283         -- If everything goes well then, process children
11284         --
11285         l_process_children := TRUE;
11286 
11287      -- Reset system_information flags
11288 
11289      ENG_GLOBALS.Set_RITEM_Impl( p_ritem_impl   => NULL);
11290      ENG_GLOBALS.Set_RITEM_Cancl( p_ritem_cancl => NULL);
11291      ENG_GLOBALS.Set_Bill_Sequence_Id( p_bill_sequence_id => NULL);
11292      ENG_GLOBALS.Set_Current_Revision( p_current_revision => NULL);
11293 
11294     --  For loop exception handler.
11295 
11296 
11297     EXCEPTION
11298 
11299        WHEN EXC_SEV_QUIT_RECORD THEN
11300 
11301         Eco_Error_Handler.Log_Error
11302                 (  p_revised_item_tbl       => x_revised_item_tbl
11303                 ,  p_rev_component_tbl      => x_rev_component_tbl
11304                 ,  p_ref_designator_tbl     => x_ref_designator_tbl
11305                 ,  p_sub_component_tbl      => x_sub_component_tbl
11306                 ,  p_rev_operation_tbl      => x_rev_operation_tbl    --L1
11307                 ,  p_rev_op_resource_tbl    => x_rev_op_resource_tbl  --L1
11308                 ,  p_rev_sub_resource_tbl   => x_rev_sub_resource_tbl --L1
11309                 ,  p_mesg_token_tbl         => l_mesg_token_tbl
11310                 ,  p_error_status           => FND_API.G_RET_STS_ERROR
11311                 ,  p_error_scope            => Error_Handler.G_SCOPE_RECORD
11312                 ,  p_error_level            => 3
11313                 ,  p_entity_index           => I
11314                 ,  x_eco_rec                => l_eco_rec
11315                 ,  x_eco_revision_tbl       => l_eco_revision_tbl
11316                 ,  x_revised_item_tbl       => x_revised_item_tbl
11317                 ,  x_rev_component_tbl      => x_rev_component_tbl
11318                 ,  x_ref_designator_tbl     => x_ref_designator_tbl
11319                 ,  x_sub_component_tbl      => x_sub_component_tbl
11320                 ,  x_rev_operation_tbl      => x_rev_operation_tbl    --L1
11321                 ,  x_rev_op_resource_tbl    => x_rev_op_resource_tbl  --L1
11322                 ,  x_rev_sub_resource_tbl   => x_rev_sub_resource_tbl --L1
11323                 );
11324 
11325         l_process_children := TRUE;
11326 
11327         IF l_bo_return_status = 'S'
11328         THEN
11329                 l_bo_return_status     := l_return_status;
11330         END IF;
11331         x_return_status                := l_bo_return_status;
11332         x_Mesg_Token_Tbl               := l_Mesg_Token_Tbl;
11333         --x_revised_item_tbl             := l_revised_item_tbl;
11334         --x_rev_component_tbl            := l_rev_component_tbl;
11335         --x_ref_designator_tbl           := l_ref_designator_tbl;
11336         --x_sub_component_tbl            := l_sub_component_tbl;
11337         --x_rev_operation_tbl            := l_rev_operation_tbl;     --L1
11338         --x_rev_op_resource_tbl          := l_rev_op_resource_tbl;   --L1
11339         --x_rev_sub_resource_tbl         := l_rev_sub_resource_tbl;  --L1
11340 
11341         -- Reset system_information flags
11342 
11343      ENG_GLOBALS.Set_RITEM_Impl( p_ritem_impl   => NULL);
11344      ENG_GLOBALS.Set_RITEM_Cancl( p_ritem_cancl => NULL);
11345      ENG_GLOBALS.Set_Bill_Sequence_Id( p_bill_sequence_id => NULL);
11346      ENG_GLOBALS.Set_Current_Revision( p_current_revision => NULL);
11347 
11348        WHEN EXC_SEV_QUIT_BRANCH THEN
11349 
11350         Eco_Error_Handler.Log_Error
11351                 (  p_revised_item_tbl    => x_revised_item_tbl
11352                 ,  p_rev_component_tbl   => x_rev_component_tbl
11353                 ,  p_ref_designator_tbl  => x_ref_designator_tbl
11354                 ,  p_sub_component_tbl   => x_sub_component_tbl
11355                 ,  p_rev_operation_tbl   => x_rev_operation_tbl    --L1
11356                 ,  p_rev_op_resource_tbl => x_rev_op_resource_tbl  --L1
11357                 ,  p_rev_sub_resource_tbl=> x_rev_sub_resource_tbl --L1
11358                 ,  p_mesg_token_tbl      => l_mesg_token_tbl
11359                 ,  p_error_status        => Error_Handler.G_STATUS_ERROR
11360                 ,  p_error_scope         => Error_Handler.G_SCOPE_CHILDREN
11361                 ,  p_other_status        => Error_Handler.G_STATUS_ERROR
11362                 ,  p_other_message       => l_other_message
11363                 ,  p_other_token_tbl     => l_other_token_tbl
11364                 ,  p_error_level         => 3
11365                 ,  p_entity_index        => I
11366                 ,  x_eco_rec             => l_eco_rec
11367                 ,  x_eco_revision_tbl    => l_eco_revision_tbl
11368                 ,  x_revised_item_tbl    => x_revised_item_tbl
11369                 ,  x_rev_component_tbl   => x_rev_component_tbl
11370                 ,  x_ref_designator_tbl  => x_ref_designator_tbl
11371                 ,  x_sub_component_tbl   => x_sub_component_tbl
11372                 ,  x_rev_operation_tbl   => x_rev_operation_tbl    --L1
11373                 ,  x_rev_op_resource_tbl => x_rev_op_resource_tbl  --L1
11374                 ,  x_rev_sub_resource_tbl=> x_rev_sub_resource_tbl --L1
11375                 );
11376 
11377         l_process_children := FALSE;
11378 
11379         IF l_bo_return_status = 'S'
11380         THEN
11381                 l_bo_return_status     := l_return_status;
11382         END IF;
11383         x_return_status                := l_bo_return_status;
11384         x_Mesg_Token_Tbl               := l_Mesg_Token_Tbl;
11385         --x_revised_item_tbl             := l_revised_item_tbl;
11386         --x_rev_component_tbl            := l_rev_component_tbl;
11387         --x_ref_designator_tbl           := l_ref_designator_tbl;
11388         --x_sub_component_tbl            := l_sub_component_tbl;
11389         --x_rev_operation_tbl            := l_rev_operation_tbl;     --L1
11390         --x_rev_op_resource_tbl          := l_rev_op_resource_tbl;   --L1
11391         --x_rev_sub_resource_tbl         := l_rev_sub_resource_tbl;  --L1
11392 
11393         -- Reset system_information flags
11394 
11395      ENG_GLOBALS.Set_RITEM_Impl( p_ritem_impl   => NULL);
11396      ENG_GLOBALS.Set_RITEM_Cancl( p_ritem_cancl => NULL);
11397      ENG_GLOBALS.Set_Bill_Sequence_Id( p_bill_sequence_id => NULL);
11398      ENG_GLOBALS.Set_Current_Revision( p_current_revision => NULL);
11399 
11400        WHEN EXC_SEV_SKIP_BRANCH THEN
11401 
11402         Eco_Error_Handler.Log_Error
11403                 (  p_revised_item_tbl    => x_revised_item_tbl
11404                 ,  p_rev_component_tbl   => x_rev_component_tbl
11405                 ,  p_ref_designator_tbl  => x_ref_designator_tbl
11406                 ,  p_sub_component_tbl   => x_sub_component_tbl
11407                 ,  p_rev_operation_tbl   => x_rev_operation_tbl    --L1
11408                 ,  p_rev_op_resource_tbl => x_rev_op_resource_tbl  --L1
11409                 ,  p_rev_sub_resource_tbl=> x_rev_sub_resource_tbl --L1
11410                 ,  p_mesg_token_tbl      => l_mesg_token_tbl
11411                 ,  p_error_status        => Error_Handler.G_STATUS_ERROR
11412                 ,  p_error_scope         => Error_Handler.G_SCOPE_CHILDREN
11413                 ,  p_other_status        => Error_Handler.G_STATUS_NOT_PICKED
11414                 ,  p_other_message       => l_other_message
11415                 ,  p_other_token_tbl     => l_other_token_tbl
11416                 ,  p_error_level         => 3
11417                 ,  p_entity_index        => I
11418                 ,  x_eco_rec             => l_eco_rec
11419                 ,  x_eco_revision_tbl    => l_eco_revision_tbl
11420                 ,  x_revised_item_tbl    => x_revised_item_tbl
11421                 ,  x_rev_component_tbl   => x_rev_component_tbl
11422                 ,  x_ref_designator_tbl  => x_ref_designator_tbl
11423                 ,  x_sub_component_tbl   => x_sub_component_tbl
11424                 ,  x_rev_operation_tbl   => x_rev_operation_tbl    --L1
11425                 ,  x_rev_op_resource_tbl => x_rev_op_resource_tbl  --L1
11426                 ,  x_rev_sub_resource_tbl=> x_rev_sub_resource_tbl --L1
11427                 );
11428 
11429         l_process_children := FALSE;
11430 
11431         IF l_bo_return_status = 'S'
11432         THEN
11433                 l_bo_return_status     := l_return_status;
11434         END IF;
11435         x_return_status                := l_bo_return_status;
11436         x_Mesg_Token_Tbl               := l_Mesg_Token_Tbl;
11437         --x_revised_item_tbl             := l_revised_item_tbl;
11438         --x_rev_component_tbl            := l_rev_component_tbl;
11439         --x_ref_designator_tbl           := l_ref_designator_tbl;
11440         --x_sub_component_tbl            := l_sub_component_tbl;
11441         --x_rev_operation_tbl            := l_rev_operation_tbl;     --L1
11442         --x_rev_op_resource_tbl          := l_rev_op_resource_tbl;   --L1
11443         --x_rev_sub_resource_tbl         := l_rev_sub_resource_tbl;  --L1
11444 
11445         -- Reset system_information flags
11446 
11447      ENG_GLOBALS.Set_RITEM_Impl( p_ritem_impl   => NULL);
11448      ENG_GLOBALS.Set_RITEM_Cancl( p_ritem_cancl => NULL);
11449      ENG_GLOBALS.Set_Bill_Sequence_Id( p_bill_sequence_id => NULL);
11450      ENG_GLOBALS.Set_Current_Revision( p_current_revision => NULL);
11451 
11452         WHEN EXC_SEV_QUIT_OBJECT THEN
11453 
11454         Eco_Error_Handler.Log_Error
11455             (  p_revised_item_tbl       => x_revised_item_tbl
11456              , p_rev_component_tbl      => x_rev_component_tbl
11457              , p_ref_designator_tbl     => x_ref_designator_tbl
11458              , p_sub_component_tbl      => x_sub_component_tbl
11459              , p_rev_operation_tbl      => x_rev_operation_tbl    --L1
11460              , p_rev_op_resource_tbl    => x_rev_op_resource_tbl  --L1
11461              , p_rev_sub_resource_tbl   => x_rev_sub_resource_tbl --L1
11462              , p_error_status           => Error_Handler.G_STATUS_ERROR
11463              , p_error_scope            => Error_Handler.G_SCOPE_ALL
11464              , p_error_level            => Error_Handler.G_BO_LEVEL
11465              , p_other_message          => l_other_message
11466              , p_other_status           => Error_Handler.G_STATUS_ERROR
11467              , p_other_token_tbl        => l_other_token_tbl
11468              , x_eco_rec                => l_eco_rec
11469              , x_eco_revision_tbl       => l_eco_revision_tbl
11470              , x_revised_item_tbl       => x_revised_item_tbl
11471              , x_rev_component_tbl      => x_rev_component_tbl
11472              , x_ref_designator_tbl     => x_ref_designator_tbl
11473              , x_sub_component_tbl      => x_sub_component_tbl
11474              , x_rev_operation_tbl   => x_rev_operation_tbl    --L1
11475              , x_rev_op_resource_tbl => x_rev_op_resource_tbl  --L1
11476              , x_rev_sub_resource_tbl=> x_rev_sub_resource_tbl --L1
11477              );
11478 
11479         IF l_bo_return_status = 'S'
11480         THEN
11481                 l_bo_return_status     := l_return_status;
11482         END IF;
11483         x_return_status                := l_bo_return_status;
11484         x_Mesg_Token_Tbl               := l_Mesg_Token_Tbl;
11485         --x_revised_item_tbl             := l_revised_item_tbl;
11486         --x_rev_component_tbl            := l_rev_component_tbl;
11487         --x_ref_designator_tbl           := l_ref_designator_tbl;
11488         --x_sub_component_tbl            := l_sub_component_tbl;
11489         --x_rev_operation_tbl            := l_rev_operation_tbl;     --L1
11490         --x_rev_op_resource_tbl          := l_rev_op_resource_tbl;   --L1
11491         --x_rev_sub_resource_tbl         := l_rev_sub_resource_tbl;  --L1
11492 
11493         -- Reset system_information flags
11494 
11495      ENG_GLOBALS.Set_RITEM_Impl( p_ritem_impl   => NULL);
11496      ENG_GLOBALS.Set_RITEM_Cancl( p_ritem_cancl => NULL);
11497      ENG_GLOBALS.Set_Bill_Sequence_Id( p_bill_sequence_id => NULL);
11498      ENG_GLOBALS.Set_Current_Revision( p_current_revision => NULL);
11499 
11500        WHEN EXC_FAT_QUIT_BRANCH THEN
11501 
11502         Eco_Error_Handler.Log_Error
11503                 (  p_revised_item_tbl    => x_revised_item_tbl
11504                 ,  p_rev_component_tbl   => x_rev_component_tbl
11505                 ,  p_ref_designator_tbl  => x_ref_designator_tbl
11506                 ,  p_sub_component_tbl   => x_sub_component_tbl
11507                 ,  p_rev_operation_tbl   => x_rev_operation_tbl    --L1
11508                 ,  p_rev_op_resource_tbl => x_rev_op_resource_tbl  --L1
11509                 ,  p_rev_sub_resource_tbl=> x_rev_sub_resource_tbl --L1
11510                 ,  p_mesg_token_tbl      => l_mesg_token_tbl
11511                 ,  p_error_status        => Error_Handler.G_STATUS_FATAL
11512                 ,  p_error_scope         => Error_Handler.G_SCOPE_CHILDREN
11513                 ,  p_other_status        => Error_Handler.G_STATUS_FATAL
11514                 ,  p_other_message       => l_other_message
11515                 ,  p_other_token_tbl     => l_other_token_tbl
11516                 ,  p_error_level         => 3
11517                 ,  p_entity_index        => I
11518                 ,  x_eco_rec             => l_eco_rec
11519                 ,  x_eco_revision_tbl    => l_eco_revision_tbl
11520                 ,  x_revised_item_tbl    => x_revised_item_tbl
11521                 ,  x_rev_component_tbl   => x_rev_component_tbl
11522                 ,  x_ref_designator_tbl  => x_ref_designator_tbl
11523                 ,  x_sub_component_tbl   => x_sub_component_tbl
11524                 ,  x_rev_operation_tbl   => x_rev_operation_tbl    --L1
11525                 ,  x_rev_op_resource_tbl => x_rev_op_resource_tbl  --L1
11526                 ,  x_rev_sub_resource_tbl=> x_rev_sub_resource_tbl --L1
11527                 );
11528 
11529         l_process_children := FALSE;
11530 
11531         x_return_status                := Error_Handler.G_STATUS_FATAL;
11532         x_Mesg_Token_Tbl               := l_Mesg_Token_Tbl;
11533         --x_revised_item_tbl             := l_revised_item_tbl;
11534         --x_rev_component_tbl            := l_rev_component_tbl;
11535         --x_ref_designator_tbl           := l_ref_designator_tbl;
11536         --x_sub_component_tbl            := l_sub_component_tbl;
11537         --x_rev_operation_tbl            := l_rev_operation_tbl;     --L1
11538         --x_rev_op_resource_tbl          := l_rev_op_resource_tbl;   --L1
11539         --x_rev_sub_resource_tbl         := l_rev_sub_resource_tbl;  --L1
11540 
11541         -- Reset system_information flags
11542 
11543      ENG_GLOBALS.Set_RITEM_Impl( p_ritem_impl   => NULL);
11544      ENG_GLOBALS.Set_RITEM_Cancl( p_ritem_cancl => NULL);
11545      ENG_GLOBALS.Set_Bill_Sequence_Id( p_bill_sequence_id => NULL);
11546      ENG_GLOBALS.Set_Current_Revision( p_current_revision => NULL);
11547 
11548        WHEN EXC_FAT_QUIT_OBJECT THEN
11549 
11550         Eco_Error_Handler.Log_Error
11551                 (  p_revised_item_tbl    => x_revised_item_tbl
11552                 ,  p_rev_component_tbl   => x_rev_component_tbl
11553                 ,  p_ref_designator_tbl  => x_ref_designator_tbl
11554                 ,  p_sub_component_tbl   => x_sub_component_tbl
11555                 ,  p_rev_operation_tbl   => x_rev_operation_tbl    --L1
11556                 ,  p_rev_op_resource_tbl => x_rev_op_resource_tbl  --L1
11557                 ,  p_rev_sub_resource_tbl=> x_rev_sub_resource_tbl --L1
11558                 ,  p_mesg_token_tbl      => l_mesg_token_tbl
11559                 ,  p_error_status        => Error_Handler.G_STATUS_FATAL
11560                 ,  p_error_scope         => Error_Handler.G_SCOPE_ALL
11561                 ,  p_other_status        => Error_Handler.G_STATUS_FATAL
11562                 ,  p_other_message       => l_other_message
11563                 ,  p_other_token_tbl     => l_other_token_tbl
11564                 ,  p_error_level         => 3
11565                 ,  p_entity_index        => I
11566                 ,  x_eco_rec             => l_eco_rec
11567                 ,  x_eco_revision_tbl    => l_eco_revision_tbl
11568                 ,  x_revised_item_tbl    => x_revised_item_tbl
11569                 ,  x_rev_component_tbl   => x_rev_component_tbl
11570                 ,  x_ref_designator_tbl  => x_ref_designator_tbl
11571                 ,  x_sub_component_tbl   => x_sub_component_tbl
11572                 ,  x_rev_operation_tbl   => x_rev_operation_tbl    --L1
11573                 ,  x_rev_op_resource_tbl => x_rev_op_resource_tbl  --L1
11574                 ,  x_rev_sub_resource_tbl=> x_rev_sub_resource_tbl --L1
11575                 );
11576 
11577         x_Mesg_Token_Tbl               := l_Mesg_Token_Tbl;
11578         --x_revised_item_tbl             := l_revised_item_tbl;
11579         --x_rev_component_tbl            := l_rev_component_tbl;
11580         --x_ref_designator_tbl           := l_ref_designator_tbl;
11581         --x_sub_component_tbl            := l_sub_component_tbl;
11582         --x_rev_operation_tbl            := l_rev_operation_tbl;     --L1
11583         --x_rev_op_resource_tbl          := l_rev_op_resource_tbl;   --L1
11584         --x_rev_sub_resource_tbl         := l_rev_sub_resource_tbl;  --L1
11585 
11586         -- Reset system_information flags
11587 
11588      ENG_GLOBALS.Set_RITEM_Impl( p_ritem_impl   => NULL);
11589      ENG_GLOBALS.Set_RITEM_Cancl( p_ritem_cancl => NULL);
11590      ENG_GLOBALS.Set_Bill_Sequence_Id( p_bill_sequence_id => NULL);
11591      ENG_GLOBALS.Set_Current_Revision( p_current_revision => NULL);
11592 
11593         l_return_status := 'Q';
11594 
11595        WHEN EXC_UNEXP_SKIP_OBJECT THEN
11596 
11597         Eco_Error_Handler.Log_Error
11598                 (  p_revised_item_tbl    => x_revised_item_tbl
11599                 ,  p_rev_component_tbl   => x_rev_component_tbl
11600                 ,  p_ref_designator_tbl  => x_ref_designator_tbl
11601                 ,  p_sub_component_tbl   => x_sub_component_tbl
11602                 ,  p_rev_operation_tbl   => x_rev_operation_tbl    --L1
11603                 ,  p_rev_op_resource_tbl => x_rev_op_resource_tbl  --L1
11604                 ,  p_rev_sub_resource_tbl=> x_rev_sub_resource_tbl --L1
11605                 ,  p_mesg_token_tbl      => l_mesg_token_tbl
11606                 ,  p_error_status        => Error_Handler.G_STATUS_UNEXPECTED
11607                 ,  p_other_status        => Error_Handler.G_STATUS_NOT_PICKED
11608                 ,  p_other_message       => l_other_message
11609                 ,  p_other_token_tbl     => l_other_token_tbl
11610                 ,  p_error_level         => 3
11611                 ,  x_ECO_rec             => l_ECO_rec
11612                 ,  x_eco_revision_tbl    => l_eco_revision_tbl
11613                 ,  x_revised_item_tbl    => x_revised_item_tbl
11614                 ,  x_rev_component_tbl   => x_rev_component_tbl
11615                 ,  x_ref_designator_tbl  => x_ref_designator_tbl
11616                 ,  x_sub_component_tbl   => x_sub_component_tbl
11617                 ,  x_rev_operation_tbl   => x_rev_operation_tbl    --L1
11618                 ,  x_rev_op_resource_tbl => x_rev_op_resource_tbl  --L1
11619                 ,  x_rev_sub_resource_tbl=> x_rev_sub_resource_tbl --L1
11620                 );
11621 
11622         x_Mesg_Token_Tbl               := l_Mesg_Token_Tbl;
11623         --x_revised_item_tbl             := l_revised_item_tbl;
11624         --x_rev_component_tbl            := l_rev_component_tbl;
11625         --x_ref_designator_tbl           := l_ref_designator_tbl;
11626         --x_sub_component_tbl            := l_sub_component_tbl;
11627         --x_rev_operation_tbl            := l_rev_operation_tbl;     --L1
11628         --x_rev_op_resource_tbl          := l_rev_op_resource_tbl;   --L1
11629         --x_rev_sub_resource_tbl         := l_rev_sub_resource_tbl;  --L1
11630 
11631         -- Reset system_information flags
11632 
11633      ENG_GLOBALS.Set_RITEM_Impl( p_ritem_impl   => NULL);
11634      ENG_GLOBALS.Set_RITEM_Cancl( p_ritem_cancl => NULL);
11635      ENG_GLOBALS.Set_Bill_Sequence_Id( p_bill_sequence_id => NULL);
11636      ENG_GLOBALS.Set_Current_Revision( p_current_revision => NULL);
11637 
11638         l_return_status := 'U';
11639 
11640         END; -- END block
11641 
11642         IF l_return_status in ('Q', 'U')
11643         THEN
11644                 x_return_status := l_return_status;
11645                 RETURN;
11646         END IF;
11647 
11648     IF l_process_children
11649     THEN
11650 
11651 
11652         -- L1: The following is for ECO enhancement
11653         -- Process operations that are orphans
11654         -- (without immediate revised component parents) but are
11655         -- indirect children of this item
11656         --
11657         -- Modified by MK on 11/30/00 Moved eco for routing procedure before BOMs.
11658         --
11659 
11660 -- IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Processing Rev Op children of Revised item . . . ' || l_revised_item_rec.revised_item_name); END IF;
11661 
11662         Rev_Operation_Sequences
11663         (   p_validation_level          => p_validation_level
11664         ,   p_change_notice             => l_revised_item_rec.ECO_Name
11665         ,   p_organization_id           => l_rev_item_unexp_rec.organization_id
11666         ,   p_revised_item_name         => l_revised_item_rec.revised_item_name
11667         ,   p_effectivity_date          => l_revised_item_rec.start_effective_date
11668         ,   p_item_revision             => l_revised_item_rec.new_revised_item_revision -- Added by MK on 11/02/00
11669         ,   p_routing_revision          => l_revised_item_rec.new_routing_revision      -- Added by MK on 11/02/00
11670         ,   p_from_end_item_number      => l_revised_item_rec.from_end_item_unit_number -- Added by MK on 11/02/00
11671         ,   p_alternate_routing_code    => l_revised_item_rec.alternate_bom_code        -- Added for bug 13440461
11672         ,   p_rev_operation_tbl         => x_rev_operation_tbl
11673         ,   p_rev_op_resource_tbl       => x_rev_op_resource_tbl
11674         ,   p_rev_sub_resource_tbl      => x_rev_sub_resource_tbl
11675         ,   x_rev_operation_tbl         => x_rev_operation_tbl
11676         ,   x_rev_op_resource_tbl       => x_rev_op_resource_tbl
11677         ,   x_rev_sub_resource_tbl      => x_rev_sub_resource_tbl
11678         ,   x_Mesg_Token_Tbl            => l_Mesg_Token_Tbl
11679         ,   x_return_status             => l_return_status
11680         );
11681 
11682         IF l_return_status <> FND_API.G_RET_STS_SUCCESS
11683         THEN
11684                 l_bo_return_status := l_return_status;
11685         END IF;
11686 
11687 
11688 
11689         -- Process resource that are orphans
11690         -- (without immediate revised component parents) but are
11691         -- indirect children of this item
11692 
11693 -- IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Processing Rev Op Res children of Revised item . . . ' || l_revised_item_rec.revised_item_name); END IF;
11694 
11695 
11696         Rev_Operation_Resources
11697         (   p_validation_level          => p_validation_level
11698         ,   p_change_notice             => l_revised_item_rec.ECO_Name
11699         ,   p_organization_id           => l_rev_item_unexp_rec.organization_id
11700         ,   p_revised_item_name         => l_revised_item_rec.revised_item_name
11701         ,   p_effectivity_date          => l_revised_item_rec.start_effective_date
11702         ,   p_item_revision             => l_revised_item_rec.new_revised_item_revision -- Added by MK on 11/02/00
11703         ,   p_routing_revision          => l_revised_item_rec.new_routing_revision      -- Added by MK on 11/02/00
11704         ,   p_from_end_item_number      => l_revised_item_rec.from_end_item_unit_number -- Added by MK on 11/02/00
11705         ,   p_alternate_routing_code    => l_revised_item_rec.alternate_bom_code        -- Added for bug 13440461
11706         ,   p_rev_op_resource_tbl       => x_rev_op_resource_tbl
11707         ,   p_rev_sub_resource_tbl      => x_rev_sub_resource_tbl
11708         ,   x_rev_op_resource_tbl       => x_rev_op_resource_tbl
11709         ,   x_rev_sub_resource_tbl      => x_rev_sub_resource_tbl
11710         ,   x_Mesg_Token_Tbl            => l_Mesg_Token_Tbl
11711         ,   x_return_status             => l_return_status
11712         );
11713        IF l_return_status <> FND_API.G_RET_STS_SUCCESS
11714        THEN
11715                 l_bo_return_status := l_return_status;
11716        END IF;
11717 
11718         -- Process substitute resources that are orphans
11719         -- (without immediate revised component parents) but are
11720         -- indirect children of this item
11721 
11722 -- IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Processing Rev Sub Op Res children of Revised item . . . ' || l_revised_item_rec.revised_item_name); END IF;
11723 
11724 
11725        Rev_Sub_Operation_Resources
11726         (   p_validation_level          => p_validation_level
11727         ,   p_change_notice             => l_revised_item_rec.ECO_Name
11728         ,   p_organization_id           => l_rev_item_unexp_rec.organization_id
11729         ,   p_revised_item_name         => l_revised_item_rec.revised_item_name
11730         ,   p_effectivity_date          => l_revised_item_rec.start_effective_date
11731         ,   p_item_revision             => l_revised_item_rec.new_revised_item_revision -- Added by MK on 11/02/00
11732         ,   p_routing_revision          => l_revised_item_rec.new_routing_revision      -- Added by MK on 11/02/00
11733         ,   p_from_end_item_number      => l_revised_item_rec.from_end_item_unit_number -- Added by MK on 11/02/00
11734         ,   p_alternate_routing_code    => l_revised_item_rec.alternate_bom_code        -- Added for bug 13440461
11735         ,   p_rev_sub_resource_tbl      => x_rev_sub_resource_tbl
11736         ,   x_rev_sub_resource_tbl      => x_rev_sub_resource_tbl
11737         ,   x_Mesg_Token_Tbl            => l_Mesg_Token_Tbl
11738         ,   x_return_status             => l_return_status
11739         );
11740         IF l_return_status <> FND_API.G_RET_STS_SUCCESS
11741         THEN
11742                 l_bo_return_status := l_return_status;
11743         END IF;
11744 
11745         -- L1: The above is for ECO enhancement
11746 
11747 
11748         -- Process Revised Components that are direct children of this item
11749 
11750 IF Bom_Globals.Get_Debug = 'Y' THEN
11751     Error_Handler.Write_Debug('***********************************************************') ;
11752     Error_Handler.Write_Debug('Now processing direct children for the Rev Item '
11753                               || l_revised_item_rec.revised_item_name || '. . .'  );
11754     Error_Handler.Write_Debug('Processing Rev Comp as children of Revised item ' || l_revised_item_rec.revised_item_name);
11755 END IF;
11756 
11757         Rev_Comps
11758         (   p_validation_level          => p_validation_level
11759         ,   p_change_notice             => l_revised_item_rec.ECO_Name
11760         ,   p_organization_id           => l_rev_item_unexp_rec.organization_id
11761         ,   p_revised_item_name         => l_revised_item_rec.revised_item_name
11762         ,   p_alternate_bom_code        => l_revised_item_rec.alternate_bom_code -- Bug 2429272 Change 4
11763         ,   p_effectivity_date          => l_revised_item_rec.start_effective_date
11764         ,   p_item_revision             => l_revised_item_rec.new_revised_item_revision
11765         ,   p_routing_revision          => l_revised_item_rec.new_routing_revision      -- Added by MK on 11/02/00
11766         ,   p_from_end_item_number      => l_revised_item_rec.from_end_item_unit_number -- Added by MK on 11/02/00
11767         ,   p_rev_component_tbl         => x_rev_component_tbl
11768         ,   p_ref_designator_tbl        => x_ref_designator_tbl
11769         ,   p_sub_component_tbl         => x_sub_component_tbl
11770         ,   x_rev_component_tbl         => x_rev_component_tbl
11771         ,   x_ref_designator_tbl        => x_ref_designator_tbl
11772         ,   x_sub_component_tbl         => x_sub_component_tbl
11773         ,   x_Mesg_Token_Tbl            => l_Mesg_Token_Tbl
11774         ,   x_return_status             => l_return_status
11775 	,   x_bill_sequence_id          => l_rev_item_unexp_rec.bill_sequence_id
11776         );
11777 
11778 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Rev_Comps return status ' || l_return_status); END IF;
11779 
11780         IF l_return_status <> FND_API.G_RET_STS_SUCCESS
11781         THEN
11782 
11783 IF Bom_Globals.Get_Debug = 'Y' THEN
11784         Error_Handler.Write_Debug('Rev_Comps returned in Rev_Items . . .BO Status: ' || l_return_status);
11785 END IF;
11786 
11787                 l_bo_return_status := l_return_status;
11788         END IF;
11789 
11790         -- Process Reference Designators that are orphans
11791         -- (without immediate revised component parents) but are
11792         -- indirect children of this item
11793 
11794 IF Bom_Globals.Get_Debug = 'Y' THEN
11795     Error_Handler.Write_Debug('***********************************************************') ;
11796     Error_Handler.Write_Debug('Processing Ref Desgs as children of Revised item ' || l_revised_item_rec.revised_item_name);
11797 END IF;
11798 
11799 
11800         Ref_Desgs
11801         (   p_validation_level          => p_validation_level
11802         ,   p_change_notice             => l_revised_item_rec.ECO_Name
11803         ,   p_organization_id           => l_rev_item_unexp_rec.organization_id
11804         ,   p_revised_item_name         => l_revised_item_rec.revised_item_name
11805         ,   p_alternate_bom_code        => l_revised_item_rec.alternate_bom_code  -- Bug 3991176
11806         ,   p_effectivity_date          => l_revised_item_rec.start_effective_date
11807         ,   p_item_revision             => l_revised_item_rec.new_revised_item_revision
11808         ,   p_routing_revision          => l_revised_item_rec.new_routing_revision      -- Added by MK on 11/02/00
11809         ,   p_from_end_item_number      => l_revised_item_rec.from_end_item_unit_number -- Added by MK on 11/02/00
11810         ,   p_ref_designator_tbl        => x_ref_designator_tbl
11811         ,   p_sub_component_tbl         => x_sub_component_tbl
11812         ,   x_ref_designator_tbl        => x_ref_designator_tbl
11813         ,   x_sub_component_tbl         => x_sub_component_tbl
11814         ,   x_Mesg_Token_Tbl            => l_Mesg_Token_Tbl
11815         ,   x_return_status             => l_return_status
11816         );
11817 
11818         -- Process Substitute Components that are orphans
11819         -- (without immediate revised component parents) but are
11820         -- indirect children of this item
11821 
11822         IF l_return_status <> FND_API.G_RET_STS_SUCCESS
11823         THEN
11824                 l_bo_return_status := l_return_status;
11825         END IF;
11826 
11827 IF Bom_Globals.Get_Debug = 'Y' THEN
11828     Error_Handler.Write_Debug('***********************************************************') ;
11829     Error_Handler.Write_Debug('Processing Sub Comps children of Revised item ' || l_revised_item_rec.revised_item_name);
11830 END IF;
11831 
11832         Sub_Comps
11833         (   p_validation_level          => p_validation_level
11834         ,   p_change_notice             => l_revised_item_rec.ECO_Name
11835         ,   p_organization_id           => l_rev_item_unexp_rec.organization_id
11836         ,   p_revised_item_name         => l_revised_item_rec.revised_item_name
11837         ,   p_alternate_bom_code        => l_revised_item_rec.alternate_bom_code  -- Bug 3991176
11838         ,   p_effectivity_date          => l_revised_item_rec.start_effective_date
11839         ,   p_item_revision             => l_revised_item_rec.new_revised_item_revision
11840         ,   p_routing_revision          => l_revised_item_rec.new_routing_revision      -- Added by MK on 11/02/00
11841         ,   p_from_end_item_number      => l_revised_item_rec.from_end_item_unit_number -- Added by MK on 11/02/00
11842         ,   p_sub_component_tbl         => x_sub_component_tbl
11843         ,   x_sub_component_tbl         => x_sub_component_tbl
11844         ,   x_Mesg_Token_Tbl            => l_Mesg_Token_Tbl
11845         ,   x_return_status             => l_return_status
11846         );
11847 
11848         IF l_return_status <> FND_API.G_RET_STS_SUCCESS
11849         THEN
11850                 l_bo_return_status := l_return_status;
11851         END IF;
11852 
11853 
11854     END IF; -- END Process children
11855     END IF; -- End of processing records for which the return status is null
11856     END LOOP; -- END Revised Items processing loop
11857 
11858     --  Load OUT parameters
11859 
11860     IF NVL(l_bo_return_status, 'S') <> 'S'
11861     THEN
11862         x_return_status        := l_bo_return_status;
11863 
11864 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Rev Items returning with ' || l_bo_return_status); END IF;
11865 
11866     END IF;
11867     --x_revised_item_tbl         := l_revised_item_tbl;
11868     --x_rev_component_tbl        := l_rev_component_tbl;
11869     --x_ref_designator_tbl       := l_ref_designator_tbl;
11870     --x_sub_component_tbl        := l_sub_component_tbl;
11871     --x_rev_operation_tbl        := l_rev_operation_tbl;     --L1
11872     --x_rev_op_resource_tbl      := l_rev_op_resource_tbl;   --L1
11873     --x_rev_sub_resource_tbl     := l_rev_sub_resource_tbl;  --L1
11874     x_Mesg_Token_Tbl           := l_Mesg_Token_Tbl;
11875 
11876 END Rev_Items;
11877 
11878 
11879 -- Eng Change Enhancement: Change Line
11880 /****************************************************************************
11881 * Procedure : Change_Line
11882 * Parameters IN   : Change Line Table and all the other entities
11883 * Parameters OUT  : Change Line Table and all the other entities
11884 * Purpose   : This procedure will process all the Change Line records.
11885 *****************************************************************************/
11886 PROCEDURE Change_Line
11887 (   p_validation_level            IN  NUMBER
11888 ,   p_change_notice               IN  VARCHAR2 := NULL
11889 ,   p_organization_id             IN  NUMBER := NULL
11890 ,   p_change_line_tbl             IN  ENG_Eco_PUB.Change_Line_Tbl_Type -- Eng Change
11891 ,   p_revised_item_tbl            IN  ENG_Eco_PUB.Revised_Item_Tbl_Type
11892 ,   p_rev_component_tbl           IN  BOM_BO_PUB.Rev_Component_Tbl_Type
11893 ,   p_ref_designator_tbl          IN  BOM_BO_PUB.Ref_Designator_Tbl_Type
11894 ,   p_sub_component_tbl           IN  BOM_BO_PUB.Sub_Component_Tbl_Type
11895 ,   p_rev_operation_tbl           IN  Bom_Rtg_Pub.Rev_Operation_Tbl_Type   --L1
11896 ,   p_rev_op_resource_tbl         IN  Bom_Rtg_Pub.Rev_Op_Resource_Tbl_Type --L1
11897 ,   p_rev_sub_resource_tbl        IN  Bom_Rtg_Pub.Rev_Sub_Resource_Tbl_Type--L1
11898 ,   x_change_line_tbl             IN OUT NOCOPY ENG_Eco_PUB.Change_Line_Tbl_Type      -- Eng Change
11899 ,   x_revised_item_tbl            IN OUT NOCOPY ENG_Eco_PUB.Revised_Item_Tbl_Type
11900 ,   x_rev_component_tbl           IN OUT NOCOPY BOM_BO_PUB.Rev_Component_Tbl_Type
11901 ,   x_ref_designator_tbl          IN OUT NOCOPY BOM_BO_PUB.Ref_Designator_Tbl_Type
11902 ,   x_sub_component_tbl           IN OUT NOCOPY BOM_BO_PUB.Sub_Component_Tbl_Type
11903 ,   x_rev_operation_tbl           IN OUT NOCOPY Bom_Rtg_Pub.Rev_Operation_Tbl_Type    --L1--
11904 ,   x_rev_op_resource_tbl         IN OUT NOCOPY Bom_Rtg_Pub.Rev_Op_Resource_Tbl_Type  --L1--
11905 ,   x_rev_sub_resource_tbl        IN OUT NOCOPY Bom_Rtg_Pub.Rev_Sub_Resource_Tbl_Type --L1--
11906 ,   x_Mesg_Token_Tbl              OUT NOCOPY Error_Handler.Mesg_Token_Tbl_Type
11907 ,   x_return_status               OUT NOCOPY VARCHAR2
11908 )
11909 IS
11910 
11911 /* Exposed and Unexposed record */
11912 l_eco_rec               ENG_Eco_PUB.Eco_Rec_Type;
11913 l_eco_revision_tbl      ENG_Eco_PUB.ECO_Revision_Tbl_Type;
11914 
11915 l_change_line_rec            Eng_Eco_Pub.Change_Line_Rec_Type ;
11916 l_change_line_unexp_rec      Eng_Eco_Pub.Change_Line_Unexposed_Rec_Type;
11917 l_old_change_line_rec        Eng_Eco_Pub.Change_Line_Rec_Type ;
11918 l_old_change_line_unexp_rec  Eng_Eco_Pub.Change_Line_Unexposed_Rec_Type;
11919 
11920 /* Error Handling Variables */
11921 l_token_tbl             Error_Handler.Token_Tbl_Type ;
11922 l_mesg_token_tbl        Error_Handler.Mesg_Token_Tbl_Type;
11923 l_other_token_tbl       Error_Handler.Token_Tbl_Type;
11924 l_other_message         VARCHAR2(2000);
11925 l_err_text              VARCHAR2(2000);
11926 
11927 /* Others */
11928 l_old_eco_rec           ENG_Eco_PUB.Eco_Rec_Type;
11929 l_old_eco_unexp_rec     ENG_Eco_PUB.Eco_Unexposed_Rec_Type;
11930 
11931 l_return_status         VARCHAR2(1);
11932 l_bo_return_status      VARCHAR2(1);
11933 l_eco_parent_exists     BOOLEAN := FALSE;
11934 l_process_children      BOOLEAN := TRUE;
11935 l_valid                 BOOLEAN := TRUE;
11936 
11937 /* Error handler definations */
11938 EXC_SEV_QUIT_RECORD     EXCEPTION ;
11939 EXC_SEV_QUIT_BRANCH     EXCEPTION ;
11940 EXC_SEV_SKIP_BRANCH     EXCEPTION ;
11941 EXC_FAT_QUIT_OBJECT     EXCEPTION ;
11942 EXC_UNEXP_SKIP_OBJECT   EXCEPTION ;
11943 
11944 EXC_FAT_QUIT_BRANCH     EXCEPTION ;
11945 EXC_SEV_QUIT_OBJECT     EXCEPTION;
11946 
11947 l_chk_co_sch eng_engineering_changes.status_type%TYPE;
11948 l_change_subject_unexp_rec  Eng_Eco_Pub.Change_Subject_Unexp_Rec_Type;
11949 
11950 BEGIN
11951 
11952 
11953   --  Init local table variables.
11954   l_return_status        := FND_API.G_RET_STS_SUCCESS ;
11955   l_bo_return_status     := FND_API.G_RET_STS_SUCCESS ;
11956   --l_change_line_tbl      := p_change_line_tbl ;
11957   x_change_line_tbl      := p_change_line_tbl;
11958   x_revised_item_tbl     := p_revised_item_tbl;
11959   x_rev_component_tbl    := p_rev_component_tbl;
11960   x_ref_designator_tbl   := p_ref_designator_tbl;
11961   x_sub_component_tbl    := p_sub_component_tbl ;
11962   x_rev_operation_tbl    := p_rev_operation_tbl;
11963   x_rev_op_resource_tbl  := p_rev_op_resource_tbl;
11964   x_rev_sub_resource_tbl := p_rev_sub_resource_tbl;
11965 
11966 
11967   -- Begin block that processes Change Lines. This block holds the exception handlers
11968   -- for change line errors.
11969   FOR I IN 1..x_change_line_tbl.COUNT LOOP
11970   -- Process Flow Step 2: Check if record has not yet been processed and
11971   -- that it is the child of the parent that called this procedure
11972   --
11973   IF (x_change_line_tbl(I).return_status IS NULL OR
11974        x_change_line_tbl(I).return_status = FND_API.G_MISS_CHAR)
11975   THEN
11976 
11977   BEGIN
11978 
11979         --  Load local records.
11980         l_change_line_rec := x_change_line_tbl(I);
11981         l_change_line_rec.transaction_type :=
11982         UPPER(l_change_line_rec.transaction_type);
11983         --l_change_line_unexp_rec.organization_id := Eng_Globals.Get_Org_Id;
11984 
11985         --
11986         -- Initialize the Unexposed Record for every iteration of the Loop
11987         -- so that sequence numbers get generated for every new row.
11988         --
11989 
11990              l_change_line_unexp_rec := NULL;
11991 
11992         --l_change_line_unexp_rec.change_line_id   := NULL ;
11993         --l_change_line_unexp_rec.change_type_id   := NULL ;
11994         --l_change_line_unexp_rec.item_id          := NULL ;
11995         --l_change_line_unexp_rec.item_revision_id := NULL ;
11996 
11997           --Organization_id is required for validations when we attach revised_items/lines to already existing ECO's
11998           l_change_line_unexp_rec.organization_id := Eng_Globals.Get_Org_Id;
11999 
12000 
12001 
12002         --
12003         -- be sure to set the process_children to false at the start of each
12004         -- iteration to avoid faulty processing of children at the end of the loop
12005         --
12006         l_process_children := FALSE;
12007 
12008         IF p_change_notice IS NOT NULL AND
12009            p_organization_id IS NOT NULL
12010         THEN
12011                 l_eco_parent_exists := TRUE;
12012         END IF;
12013 
12014         -- Process Flow Step 2: Check if record has not yet been processed and
12015         -- that it is the child of the parent that called this procedure
12016         --
12017 
12018 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Processing Change Line . . . ' || l_change_line_rec.name); END IF;
12019 
12020         --IF (l_change_line_rec.return_status IS NULL OR
12021             --l_change_line_rec.return_status = FND_API.G_MISS_CHAR)
12022         --THEN
12023 
12024            l_return_status := FND_API.G_RET_STS_SUCCESS;
12025            l_change_line_rec.return_status := FND_API.G_RET_STS_SUCCESS;
12026 
12027            -- Check if transaction_type is valid
12028            --
12029 
12030 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Check transaction_type validity'); END IF;
12031 
12032            ENG_GLOBALS.Transaction_Type_Validity
12033            (   p_transaction_type       => l_change_line_rec.transaction_type
12034            ,   p_entity                 => 'Change_Lines'
12035            ,   p_entity_id              => l_change_line_rec.name
12036            ,   x_valid                  => l_valid
12037            ,   x_Mesg_Token_Tbl         => l_Mesg_Token_Tbl
12038            );
12039 
12040            IF NOT l_valid
12041            THEN
12042                 l_return_status := Error_Handler.G_STATUS_ERROR;
12043                 RAISE EXC_SEV_QUIT_RECORD;
12044            END IF;
12045 
12046            --
12047            -- Process Flow step 4: Convert user unique index to unique index
12048            --
12049 
12050 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Converting user unique index to unique index'); END IF;
12051 
12052            ENG_Val_To_Id.Change_Line_UUI_To_UI
12053            ( p_change_line_rec       => l_change_line_rec
12054            , p_change_line_unexp_rec => l_change_line_unexp_rec
12055            , x_change_line_unexp_rec => l_change_line_unexp_rec
12056            , x_Mesg_Token_Tbl        => l_Mesg_Token_Tbl
12057            , x_Return_Status         => l_return_status
12058            );
12059 
12060 
12061 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
12062 
12063            IF l_return_status = Error_Handler.G_STATUS_ERROR
12064            THEN
12065 
12066                 l_other_message := 'ENG_CL_UUI_SEV_ERROR';
12067                 l_other_token_tbl(1).token_name := 'LINE_NAME';
12068                 l_other_token_tbl(1).token_value := l_change_line_rec.name ;
12069                 RAISE EXC_SEV_QUIT_BRANCH;
12070 
12071            ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
12072            THEN
12073                 l_other_message := 'ENG_CL_UUI_UNEXP_SKIP';
12074                 l_other_token_tbl(1).token_name := 'LINE_NAME';
12075                 l_other_token_tbl(1).token_value := l_change_line_rec.name ;
12076                 RAISE EXC_UNEXP_SKIP_OBJECT;
12077 
12078            END IF;
12079 
12080            --
12081            -- Process Flow step 4(b): Check required fields exist
12082            --
12083 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Check Required'); END IF;
12084            ENG_Validate_Change_Line.Check_Required
12085                 ( x_return_status        => l_return_status
12086                 , x_Mesg_Token_Tbl       => l_Mesg_Token_Tbl
12087                 , p_change_line_rec      => l_change_line_rec
12088                 );
12089 
12090            IF l_return_status = Error_Handler.G_STATUS_ERROR
12091            THEN
12092                 IF l_change_line_rec.transaction_type = ENG_GLOBALS.G_OPR_CREATE
12093                 THEN
12094                         l_other_message := 'ENG_CL_REQ_CSEV_SKIP';
12095                         l_other_token_tbl(1).token_name := 'LINE_NAME';
12096                         l_other_token_tbl(1).token_value := l_change_line_rec.name;
12097                         RAISE EXC_SEV_SKIP_BRANCH;
12098                 ELSE
12099                         RAISE EXC_SEV_QUIT_RECORD;
12100                 END IF;
12101            ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
12102            THEN
12103                 l_other_message := 'ENG_CL_REQ_UNEXP_SKIP';
12104                         l_other_token_tbl(1).token_name := 'LINE_NAME';
12105                         l_other_token_tbl(1).token_value := l_change_line_rec.name;
12106                 RAISE EXC_UNEXP_SKIP_OBJECT;
12107 
12108            ELSIF l_return_status ='S' AND
12109                  l_Mesg_Token_Tbl.COUNT <>0
12110            THEN
12111                     Eco_Error_Handler.Log_Error
12112                     (  p_change_line_tbl     => x_change_line_tbl -- Eng Change
12113                     ,  p_revised_item_tbl    => x_revised_item_tbl
12114                     ,  p_rev_component_tbl   => x_rev_component_tbl
12115                     ,  p_ref_designator_tbl  => x_ref_designator_tbl
12116                     ,  p_sub_component_tbl   => x_sub_component_tbl
12117                     ,  p_rev_operation_tbl   => x_rev_operation_tbl    --L1
12118                     ,  p_rev_op_resource_tbl => x_rev_op_resource_tbl  --L1
12119                     ,  p_rev_sub_resource_tbl=> x_rev_sub_resource_tbl --L1
12120                     ,  p_mesg_token_tbl      => l_mesg_token_tbl
12121                     ,  p_error_status        => 'W'
12122                     ,  p_error_level         => ECO_Error_Handler.G_CL_LEVEL
12123                     ,  p_entity_index        => I
12124                     ,  x_ECO_rec             => l_eco_rec
12125                     ,  x_eco_revision_tbl    => l_eco_revision_tbl
12126                     ,  x_change_line_tbl     => x_change_line_tbl -- Eng Change
12127                     ,  x_revised_item_tbl    => x_revised_item_tbl
12128                     ,  x_rev_component_tbl   => x_rev_component_tbl
12129                     ,  x_ref_designator_tbl  => x_ref_designator_tbl
12130                     ,  x_sub_component_tbl   => x_sub_component_tbl
12131                     ,  x_rev_operation_tbl   => x_rev_operation_tbl    --L1
12132                     ,  x_rev_op_resource_tbl => x_rev_op_resource_tbl  --L1
12133                     ,  x_rev_sub_resource_tbl=> x_rev_sub_resource_tbl --L1
12134                     );
12135 
12136            END IF;
12137 
12138 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
12139 
12140 
12141            -- Process Flow step 5: Verify ECO's existence in database, if
12142            -- the revised item is being created on an ECO and the business
12143            -- object does not carry the ECO header
12144 
12145 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Check parent existence'); END IF;
12146 
12147            IF l_change_line_rec.transaction_type = ENG_GLOBALS.G_OPR_CREATE
12148            AND  NOT l_eco_parent_exists
12149            THEN
12150                 ENG_Validate_ECO.Check_Existence
12151                 ( p_change_notice       => l_change_line_rec.eco_name
12152                 , p_organization_id     => l_change_line_unexp_rec.organization_id
12153                 , p_organization_code   => l_change_line_rec.organization_code
12154                 , p_calling_entity      => 'CHILD'
12155                 , p_transaction_type    => 'XXX'
12156                 , x_eco_rec             => l_old_eco_rec
12157                 , x_eco_unexp_rec       => l_old_eco_unexp_rec
12158                 , x_Mesg_Token_Tbl      => l_Mesg_Token_Tbl
12159                 , x_return_status       => l_Return_Status
12160                 );
12161 
12162 		IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
12163 
12164                 IF l_return_status = Error_Handler.G_STATUS_ERROR
12165                 THEN
12166                    l_other_message := 'ENG_PARENTECO_NOT_EXIST';
12167                    l_other_token_tbl(1).token_name := 'ECO_NAME';
12168                    l_other_token_tbl(1).token_value := l_change_line_rec.ECO_Name;
12169                    l_other_token_tbl(2).token_name := 'ORGANIZATION_CODE';
12170                    l_other_token_tbl(2).token_value := l_change_line_rec.organization_code;
12171                    RAISE EXC_SEV_QUIT_OBJECT;
12172                 ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
12173                 THEN
12174                    l_other_message := 'ENG_CL_LIN_UNEXP_SKIP';
12175                    l_other_token_tbl(1).token_name := 'LINE_NAME';
12176                    l_other_token_tbl(1).token_value := l_change_line_rec.name;
12177                    RAISE EXC_UNEXP_SKIP_OBJECT;
12178                 END IF;
12179 
12180            END IF;
12181 
12182 	   IF l_change_line_rec.Transaction_Type IN
12183                 (ENG_GLOBALS.G_OPR_UPDATE, ENG_GLOBALS.G_OPR_DELETE)
12184            THEN
12185 		-- Bug 2918350
12186 		-- Start Changes
12187 
12188 		IF p_change_notice IS NOT NULL AND p_organization_id IS NOT NULL THEN
12189 			l_chk_co_sch := ret_co_status ( p_change_notice, p_organization_id);
12190 		ELSE
12191 			l_chk_co_sch := ret_co_status (l_change_line_rec.eco_name, l_change_line_unexp_rec.organization_id);
12192 		END IF;
12193 
12194 		IF l_chk_co_sch = 4 THEN
12195 			l_return_status := error_handler.g_status_error;
12196 			error_handler.add_error_token (p_message_name        => 'ENG_CHG_LN_NOT_UPD',
12197 				p_mesg_token_tbl      => l_mesg_token_tbl,
12198 				x_mesg_token_tbl      => l_mesg_token_tbl,
12199 				p_token_tbl           => l_token_tbl
12200 			);
12201 			RAISE exc_sev_quit_record;
12202 		END IF;
12203     	  END IF;
12204 		-- End Changes
12205 
12206 		-- Process Flow step 5: Verify Revised Item's existence
12207 	        --
12208 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Check existence'); END IF;
12209 
12210            ENG_Validate_Change_Line.Check_Existence
12211                 (  p_change_line_rec            => l_change_line_rec
12212                 ,  p_change_line_unexp_rec      => l_change_line_unexp_rec
12213                 ,  x_old_change_line_rec        => l_old_change_line_rec
12214                 ,  x_old_change_line_unexp_rec  => l_old_change_line_unexp_rec
12215                 ,  x_Mesg_Token_Tbl             => l_Mesg_Token_Tbl
12216                 ,  x_return_status              => l_Return_Status
12217                 );
12218 
12219 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
12220 
12221            IF l_return_status = Error_Handler.G_STATUS_ERROR
12222            THEN
12223                 l_other_message := 'ENG_CL_EXS_SEV_ERROR';
12224                 l_other_token_tbl(1).token_name := 'LINE_NAME';
12225                 l_other_token_tbl(1).token_value := l_change_line_rec.name;
12226                 l_other_token_tbl(2).token_name := 'ECO_NAME';
12227                 l_other_token_tbl(2).token_value := l_change_line_rec.eco_name;
12228                 RAISE EXC_SEV_QUIT_BRANCH;
12229            ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
12230            THEN
12231                 l_other_message := 'ENG_CL_EXS_UNEXP_SKIP';
12232                 l_other_token_tbl(1).token_name := 'LINE_NAME';
12233                 l_other_token_tbl(1).token_value := l_change_line_rec.name;
12234                 l_other_token_tbl(2).token_name := 'ECO_NAME';
12235                 l_other_token_tbl(2).token_value := l_change_line_rec.eco_name;
12236                 RAISE EXC_UNEXP_SKIP_OBJECT;
12237            END IF;
12238 
12239 
12240            -- Process Flow step 6: Is Revised Item record an orphan ?
12241 
12242            IF NOT l_eco_parent_exists
12243            THEN
12244 
12245                 -- Process Flow step 7: Is ECO impl/cancl, or in wkflw process ?
12246                 --
12247 
12248                 ENG_Validate_ECO.Check_Access
12249                 ( p_change_notice       => l_change_line_rec.ECO_Name
12250                 , p_organization_id     => l_change_line_unexp_rec.organization_id
12251                 , p_Mesg_Token_Tbl      => l_Mesg_Token_Tbl
12252                 , x_Mesg_Token_Tbl      => l_Mesg_Token_Tbl
12253                 , x_Return_Status       => l_return_status
12254                 );
12255 
12256 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
12257 
12258                 IF l_return_status = Error_Handler.G_STATUS_ERROR
12259                 THEN
12260                         l_other_message := 'ENG_CL_ECOACC_FAT_FATAL';
12261                         l_other_token_tbl(1).token_name := 'LINE_NAME';
12262                         l_other_token_tbl(1).token_value := l_change_line_rec.name;
12263                         l_return_status := 'F';
12264                         RAISE EXC_FAT_QUIT_OBJECT;
12265                 ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
12266                 THEN
12267                         l_other_message := 'ENG_RIT_ECOACC_UNEXP_SKIP';
12268                         l_other_token_tbl(1).token_name := 'LINE_NAME';
12269                         l_other_token_tbl(1).token_value := l_change_line_rec.name;
12270                         RAISE EXC_UNEXP_SKIP_OBJECT;
12271                 END IF;
12272 
12273            END IF;
12274 
12275 
12276            -- Process Flow step 7: Value to Id conversions
12277            --
12278 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Value-id conversions'); END IF;
12279 
12280            ENG_Val_To_Id.Change_Line_VID
12281                 ( p_change_line_rec       => l_change_line_rec
12282                 , p_change_line_unexp_rec => l_change_line_unexp_rec
12283                 , x_change_line_unexp_rec => l_change_line_unexp_rec
12284                 , x_Mesg_Token_Tbl        => l_Mesg_Token_Tbl
12285                 , x_Return_Status         => l_return_status
12286                 );
12287 
12288 
12289 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
12290 
12291            IF l_return_status = Error_Handler.G_STATUS_ERROR
12292            THEN
12293                 IF l_change_line_rec.transaction_type = ENG_GLOBALS.G_OPR_CREATE
12294                 THEN
12295                         l_other_message := 'ENG_RIT_VID_CSEV_SKIP';
12296                         l_other_token_tbl(1).token_name := 'LINE_NAME';
12297                         l_other_token_tbl(1).token_value := l_change_line_rec.name;
12298                         RAISE EXC_SEV_SKIP_BRANCH;
12299                 ELSE
12300                         RAISE EXC_SEV_QUIT_RECORD;
12301                 END IF;
12302            ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
12303            THEN
12304                 RAISE EXC_UNEXP_SKIP_OBJECT;
12305            ELSIF l_return_status ='S' AND
12306                 l_Mesg_Token_Tbl.COUNT <>0
12307            THEN
12308                 Eco_Error_Handler.Log_Error
12309                 (  p_change_line_tbl     => x_change_line_tbl -- Eng Change
12310                 ,  p_revised_item_tbl    => x_revised_item_tbl
12311                 ,  p_rev_component_tbl   => x_rev_component_tbl
12312                 ,  p_ref_designator_tbl  => x_ref_designator_tbl
12313                 ,  p_sub_component_tbl   => x_sub_component_tbl
12314                 ,  p_rev_operation_tbl   => x_rev_operation_tbl    --L1
12315                 ,  p_rev_op_resource_tbl => x_rev_op_resource_tbl  --L1
12316                 ,  p_rev_sub_resource_tbl=> x_rev_sub_resource_tbl --L1
12317                 ,  p_mesg_token_tbl      => l_mesg_token_tbl
12318                 ,  p_error_status        => 'W'
12319                 ,  p_error_level         => ECO_Error_Handler.G_CL_LEVEL
12320                 ,  p_entity_index        => I
12321                 ,  x_ECO_rec             => l_eco_rec
12322                 ,  x_eco_revision_tbl    => l_eco_revision_tbl
12323                 ,  x_change_line_tbl     => x_change_line_tbl -- Eng Change
12324                 ,  x_revised_item_tbl    => x_revised_item_tbl
12325                 ,  x_rev_component_tbl   => x_rev_component_tbl
12326                 ,  x_ref_designator_tbl  => x_ref_designator_tbl
12327                 ,  x_sub_component_tbl   => x_sub_component_tbl
12328                 ,  x_rev_operation_tbl   => x_rev_operation_tbl    --L1
12329                 ,  x_rev_op_resource_tbl => x_rev_op_resource_tbl  --L1
12330                 ,  x_rev_sub_resource_tbl=> x_rev_sub_resource_tbl --L1
12331                 );
12332 
12333            END IF;
12334 
12335 
12336            -- Process Flow step8: check that user has access to item associated to change line
12337            --
12338 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Check access'); END IF;
12339            IF l_change_line_unexp_rec.pk1_value IS NOT NULL THEN
12340 
12341                 ENG_Validate_Change_Line.Check_Access
12342                 (  p_change_line_rec        => l_change_line_rec
12343                 ,  p_change_line_unexp_rec  => l_change_line_unexp_rec
12344                 ,  p_Mesg_Token_Tbl         => l_Mesg_Token_Tbl
12345                 ,  x_Mesg_Token_Tbl         => l_Mesg_Token_Tbl
12346                 ,  x_return_status          => l_Return_Status
12347                 );
12348 
12349 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
12350 
12351                 IF l_return_status = Error_Handler.G_STATUS_ERROR
12352                 THEN
12353                         l_other_message := 'ENG_CL_ACCESS_FAT_FATAL';
12354                         l_other_token_tbl(1).token_name := 'OBJECT_NAME';
12355                         l_other_token_tbl(1).token_value := l_change_line_rec.pk1_name;
12356                         l_other_token_tbl(2).token_name := 'LINE_NAME';
12357                         l_other_token_tbl(2).token_value := l_change_line_rec.name;
12358                         l_return_status := 'F';
12359                         RAISE EXC_FAT_QUIT_BRANCH;
12360                 ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
12361                 THEN
12362                         l_other_message := 'ENG_CL_ACCESS_UNEXP_SKIP';
12363                         l_other_token_tbl(1).token_name := 'OBJECT_NAME';
12364                         l_other_token_tbl(1).token_value := l_change_line_rec.pk1_name;
12365                         l_other_token_tbl(2).token_name := 'LINE_NAME';
12366                         l_other_token_tbl(2).token_value := l_change_line_rec.name;
12367                         RAISE EXC_UNEXP_SKIP_OBJECT;
12368                 END IF;
12369 
12370            END IF ;
12371 
12372            --
12373            -- Process Flow step 10: Attribute Validation for CREATE and UPDATE
12374            --
12375 
12376 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Attribute Validation'); END IF;
12377            IF l_change_line_rec.Transaction_Type IN
12378                 (ENG_GLOBALS.G_OPR_CREATE, ENG_GLOBALS.G_OPR_UPDATE)
12379            THEN
12380                 ENG_Validate_Change_Line.Check_Attributes
12381                 ( x_return_status             => l_return_status
12382                 , x_Mesg_Token_Tbl            => l_Mesg_Token_Tbl
12383                 , p_change_line_rec           => l_change_line_rec
12384                 , p_change_line_unexp_rec     => l_change_line_unexp_rec
12385                 , p_old_change_line_rec       => l_old_change_line_rec
12386                 , p_old_change_line_unexp_rec => l_old_change_line_unexp_rec
12387                 );
12388 
12389 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
12390 
12391                 IF l_return_status = Error_Handler.G_STATUS_ERROR
12392                 THEN
12393                    IF l_change_line_rec.transaction_type = ENG_GLOBALS.G_OPR_CREATE
12394                    THEN
12395                         l_other_message := 'ENG_RIT_ATTVAL_CSEV_SKIP';
12396                         l_other_token_tbl(1).token_name := 'LINE_NAME';
12397                         l_other_token_tbl(1).token_value := l_change_line_rec.name;
12398 
12399                         RAISE EXC_SEV_SKIP_BRANCH;
12400                    ELSE
12401                         RAISE EXC_SEV_QUIT_RECORD;
12402                    END IF;
12403                 ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
12404                 THEN
12405 
12406                    l_other_message := 'ENG_RIT_ATTVAL_UNEXP_SKIP';
12407                    l_other_token_tbl(1).token_name := 'LINE_NAME';
12408                    l_other_token_tbl(1).token_value := l_change_line_rec.name;
12409 
12410                    RAISE EXC_UNEXP_SKIP_OBJECT;
12411 
12412                 ELSIF l_return_status ='S' AND
12413                       l_Mesg_Token_Tbl.COUNT <>0
12414                 THEN
12415 
12416                     Eco_Error_Handler.Log_Error
12417                     (  p_change_line_tbl     => x_change_line_tbl -- Eng Change
12418                     ,  p_revised_item_tbl    => x_revised_item_tbl
12419                     ,  p_rev_component_tbl   => x_rev_component_tbl
12420                     ,  p_ref_designator_tbl  => x_ref_designator_tbl
12421                     ,  p_sub_component_tbl   => x_sub_component_tbl
12422                     ,  p_rev_operation_tbl   => x_rev_operation_tbl    --L1
12423                     ,  p_rev_op_resource_tbl => x_rev_op_resource_tbl  --L1
12424                     ,  p_rev_sub_resource_tbl=> x_rev_sub_resource_tbl --L1
12425                     ,  p_mesg_token_tbl      => l_mesg_token_tbl
12426                     ,  p_error_status        => 'W'
12427                     ,  p_error_level         => ECO_Error_Handler.G_CL_LEVEL
12428                     ,  p_entity_index        => I
12429                     ,  x_ECO_rec             => l_eco_rec
12430                     ,  x_eco_revision_tbl    => l_eco_revision_tbl
12431                     ,  x_change_line_tbl     => x_change_line_tbl -- Eng Change
12432                     ,  x_revised_item_tbl    => x_revised_item_tbl
12433                     ,  x_rev_component_tbl   => x_rev_component_tbl
12434                     ,  x_ref_designator_tbl  => x_ref_designator_tbl
12435                     ,  x_sub_component_tbl   => x_sub_component_tbl
12436                     ,  x_rev_operation_tbl   => x_rev_operation_tbl    --L1
12437                     ,  x_rev_op_resource_tbl => x_rev_op_resource_tbl  --L1
12438                     ,  x_rev_sub_resource_tbl=> x_rev_sub_resource_tbl --L1
12439                     );
12440 
12441                 END IF;
12442 
12443            END IF;
12444 
12445            IF l_change_line_rec.Transaction_Type IN
12446                 (ENG_GLOBALS.G_OPR_UPDATE, ENG_GLOBALS.G_OPR_DELETE)
12447            THEN
12448 
12449                 -- Process flow step 11 - Populate NULL columns for Update and
12450                 -- Delete.
12451 
12452 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Populating NULL Columns'); END IF;
12453 
12454                 Eng_Default_Change_Line.Populate_NULL_Columns
12455                 ( p_change_line_rec           => l_change_line_rec
12456                 , p_change_line_unexp_rec     => l_change_line_unexp_rec
12457                 , p_old_change_line_rec       => l_old_change_line_rec
12458                 , p_old_change_line_unexp_rec => l_old_change_line_unexp_rec
12459                 , x_change_line_rec           => l_change_line_rec
12460                 , x_change_line_unexp_rec     => l_change_line_unexp_rec
12461                 );
12462 
12463            ELSIF l_change_line_rec.Transaction_Type = ENG_GLOBALS.G_OPR_CREATE THEN
12464 
12465                 -- Process Flow step 12: Default missing values for Operation CREATE
12466                 --
12467 
12468 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Attribute Defaulting'); END IF;
12469                 Eng_Default_Change_Line.Attribute_Defaulting
12470                 ( p_change_line_rec           => l_change_line_rec
12471                 , p_change_line_unexp_rec     => l_change_line_unexp_rec
12472                 , x_change_line_rec           => l_change_line_rec
12473                 , x_change_line_unexp_rec     => l_change_line_unexp_rec
12474                 , x_Mesg_Token_Tbl            => l_Mesg_Token_Tbl
12475                 , x_return_status             => l_return_status
12476                 );
12477 
12478 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
12479 
12480                 IF l_return_status = Error_Handler.G_STATUS_ERROR
12481                 THEN
12482                         l_other_message := 'ENG_CL_ATTDEF_SEV_SKIP';
12483                         l_other_token_tbl(1).token_name := 'LINE_NAME';
12484                         l_other_token_tbl(1).token_value := l_change_line_rec.name;
12485                         RAISE EXC_SEV_SKIP_BRANCH;
12486                 ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
12487                 THEN
12488                         l_other_message := 'ENG_CL_ATTDEF_UNEXP_SKIP';
12489                         l_other_token_tbl(1).token_name := 'LINE_NAME';
12490                         l_other_token_tbl(1).token_value := l_change_line_rec.name;
12491 
12492                         RAISE EXC_UNEXP_SKIP_OBJECT;
12493                 ELSIF l_return_status ='S' AND
12494                         l_Mesg_Token_Tbl.COUNT <>0
12495                 THEN
12496                     Eco_Error_Handler.Log_Error
12497                     (  p_change_line_tbl     => x_change_line_tbl -- Eng Change
12498                     ,  p_revised_item_tbl    => x_revised_item_tbl
12499                     ,  p_rev_component_tbl   => x_rev_component_tbl
12500                     ,  p_ref_designator_tbl  => x_ref_designator_tbl
12501                     ,  p_sub_component_tbl   => x_sub_component_tbl
12502                     ,  p_rev_operation_tbl   => x_rev_operation_tbl    --L1
12503                     ,  p_rev_op_resource_tbl => x_rev_op_resource_tbl  --L1
12504                     ,  p_rev_sub_resource_tbl=> x_rev_sub_resource_tbl --L1
12505                     ,  p_mesg_token_tbl      => l_mesg_token_tbl
12506                     ,  p_error_status        => 'W'
12507                     ,  p_error_level         => ECO_Error_Handler.G_CL_LEVEL
12508                     ,  p_entity_index        => I
12509                     ,  x_ECO_rec             => l_eco_rec
12510                     ,  x_eco_revision_tbl    => l_eco_revision_tbl
12511                     ,  x_change_line_tbl     => x_change_line_tbl -- Eng Change
12512                     ,  x_revised_item_tbl    => x_revised_item_tbl
12513                     ,  x_rev_component_tbl   => x_rev_component_tbl
12514                     ,  x_ref_designator_tbl  => x_ref_designator_tbl
12515                     ,  x_sub_component_tbl   => x_sub_component_tbl
12516                     ,  x_rev_operation_tbl   => x_rev_operation_tbl    --L1
12517                     ,  x_rev_op_resource_tbl => x_rev_op_resource_tbl  --L1
12518                     ,  x_rev_sub_resource_tbl=> x_rev_sub_resource_tbl --L1
12519                     );
12520 
12521                 END IF;
12522            END IF;
12523 
12524            -- Process Flow step 13 - Conditionally required attributes check
12525            --
12526 
12527 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Conditionally required attributes check'); END IF;
12528 
12529            --
12530            -- Put conditionally required check procedure here
12531            --
12532 
12533 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
12534 
12535            ENG_Validate_Change_Line.Check_Conditionally_Required
12536                (  p_change_line_rec           => l_change_line_rec
12537                 , p_change_line_unexp_rec     => l_change_line_unexp_rec
12538                 , x_Mesg_Token_Tbl            => l_Mesg_Token_Tbl
12539                 , x_return_status             => l_return_status
12540                 );
12541 
12542            IF l_return_status = Error_Handler.G_STATUS_ERROR
12543            THEN
12544                 IF l_change_line_rec.transaction_type = ENG_GLOBALS.G_OPR_CREATE
12545                 THEN
12546                         l_other_message := 'ENG_CL_CONREQ_CSEV_SKIP';
12547                         l_other_token_tbl(1).token_name := 'LINE_NAME';
12548                         l_other_token_tbl(1).token_value := l_change_line_rec.name;
12549                         RAISE EXC_SEV_SKIP_BRANCH;
12550                 ELSE
12551                         RAISE EXC_SEV_QUIT_RECORD;
12552                 END IF;
12553            ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
12554            THEN
12555                 l_other_message := 'ENG_CL_CONREQ_UNEXP_SKIP';
12556                 l_other_token_tbl(1).token_name := 'LINE_NAME';
12557                 l_other_token_tbl(1).token_value := l_change_line_rec.name;
12558                 RAISE EXC_UNEXP_SKIP_OBJECT;
12559 
12560            ELSIF l_return_status ='S' AND
12561                 l_Mesg_Token_Tbl.COUNT <>0
12562            THEN
12563                     Eco_Error_Handler.Log_Error
12564                     (  p_change_line_tbl     => x_change_line_tbl -- Eng Change
12565                     ,  p_revised_item_tbl    => x_revised_item_tbl
12566                     ,  p_rev_component_tbl   => x_rev_component_tbl
12567                     ,  p_ref_designator_tbl  => x_ref_designator_tbl
12568                     ,  p_sub_component_tbl   => x_sub_component_tbl
12569                     ,  p_rev_operation_tbl   => x_rev_operation_tbl    --L1
12570                     ,  p_rev_op_resource_tbl => x_rev_op_resource_tbl  --L1
12571                     ,  p_rev_sub_resource_tbl=> x_rev_sub_resource_tbl --L1
12572                     ,  p_mesg_token_tbl      => l_mesg_token_tbl
12573                     ,  p_error_status        => 'W'
12574                     ,  p_error_level         => ECO_Error_Handler.G_CL_LEVEL
12575                     ,  p_entity_index        => I
12576                     ,  x_ECO_rec             => l_eco_rec
12577                     ,  x_eco_revision_tbl    => l_eco_revision_tbl
12578                     ,  x_change_line_tbl     => x_change_line_tbl -- Eng Change
12579                     ,  x_revised_item_tbl    => x_revised_item_tbl
12580                     ,  x_rev_component_tbl   => x_rev_component_tbl
12581                     ,  x_ref_designator_tbl  => x_ref_designator_tbl
12582                     ,  x_sub_component_tbl   => x_sub_component_tbl
12583                     ,  x_rev_operation_tbl   => x_rev_operation_tbl    --L1
12584                     ,  x_rev_op_resource_tbl => x_rev_op_resource_tbl  --L1
12585                     ,  x_rev_sub_resource_tbl=> x_rev_sub_resource_tbl --L1
12586                     );
12587 
12588            END IF;
12589 
12590            -- Process Flow step 14: Entity defaulting for CREATE and UPDATE
12591            --
12592 
12593 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Entity defaulting'); END IF;
12594 
12595            IF l_change_line_rec.Transaction_Type IN
12596                 (ENG_GLOBALS.G_OPR_CREATE, ENG_GLOBALS.G_OPR_UPDATE)
12597            THEN
12598 
12599                 ENG_Default_Change_Line.Entity_Defaulting
12600                 ( p_change_line_rec           => l_change_line_rec
12601                 , p_change_line_unexp_rec     => l_change_line_unexp_rec
12602                 , p_old_change_line_rec       => l_old_change_line_rec
12603                 , p_old_change_line_unexp_rec => l_old_change_line_unexp_rec
12604                 , x_change_line_rec           => l_change_line_rec
12605                 , x_change_line_unexp_rec     => l_change_line_unexp_rec
12606                 , x_Mesg_Token_Tbl            => l_Mesg_Token_Tbl
12607                 , x_return_status             => l_return_status
12608                 );
12609 
12610 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
12611 
12612                 IF l_return_status = Error_Handler.G_STATUS_ERROR
12613                 THEN
12614                    IF l_change_line_rec.transaction_type = ENG_GLOBALS.G_OPR_CREATE
12615                    THEN
12616                         l_other_message := 'ENG_CL_ENTDEF_CSEV_SKIP';
12617                         l_other_token_tbl(1).token_name := 'LINE_NAME';
12618                         l_other_token_tbl(1).token_value := l_change_line_rec.name;
12619                         RAISE EXC_SEV_SKIP_BRANCH;
12620                    ELSE
12621                         RAISE EXC_SEV_QUIT_RECORD;
12622                    END IF;
12623                 ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
12624                 THEN
12625                         l_other_message := 'ENG_CL_ENTDEF_UNEXP_SKIP';
12626                         l_other_token_tbl(1).token_name := 'LINE_NAME';
12627                         l_other_token_tbl(1).token_value := l_change_line_rec.name;
12628                         RAISE EXC_UNEXP_SKIP_OBJECT;
12629                 ELSIF l_return_status ='S' AND
12630                         l_Mesg_Token_Tbl.COUNT <>0
12631                 THEN
12632                     Eco_Error_Handler.Log_Error
12633                     (  p_change_line_tbl     => x_change_line_tbl -- Eng Change
12634                     ,  p_revised_item_tbl    => x_revised_item_tbl
12635                     ,  p_rev_component_tbl   => x_rev_component_tbl
12636                     ,  p_ref_designator_tbl  => x_ref_designator_tbl
12637                     ,  p_sub_component_tbl   => x_sub_component_tbl
12638                     ,  p_rev_operation_tbl   => x_rev_operation_tbl    --L1
12639                     ,  p_rev_op_resource_tbl => x_rev_op_resource_tbl  --L1
12640                     ,  p_rev_sub_resource_tbl=> x_rev_sub_resource_tbl --L1
12641                     ,  p_mesg_token_tbl      => l_mesg_token_tbl
12642                     ,  p_error_status        => 'W'
12643                     ,  p_error_level         => ECO_Error_Handler.G_CL_LEVEL
12644                     ,  p_entity_index        => I
12645                     ,  x_ECO_rec             => l_eco_rec
12646                     ,  x_eco_revision_tbl    => l_eco_revision_tbl
12647                     ,  x_change_line_tbl     => x_change_line_tbl -- Eng Change
12648                     ,  x_revised_item_tbl    => x_revised_item_tbl
12649                     ,  x_rev_component_tbl   => x_rev_component_tbl
12650                     ,  x_ref_designator_tbl  => x_ref_designator_tbl
12651                     ,  x_sub_component_tbl   => x_sub_component_tbl
12652                     ,  x_rev_operation_tbl   => x_rev_operation_tbl    --L1
12653                     ,  x_rev_op_resource_tbl => x_rev_op_resource_tbl  --L1
12654                     ,  x_rev_sub_resource_tbl=> x_rev_sub_resource_tbl --L1
12655                     );
12656 
12657                 END IF;
12658            END IF;
12659 
12660            -- Process Flow step 15 - Entity Level Validation
12661            --
12662 
12663 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Entity validation'); END IF;
12664 
12665            IF l_change_line_rec.transaction_type = ENG_GLOBALS.G_OPR_DELETE
12666            THEN
12667                 ENG_Validate_Change_Line.Check_Entity_Delete
12668                 (  p_change_line_rec       => l_change_line_rec
12669                 ,  p_change_line_unexp_rec => l_change_line_unexp_rec
12670                 ,  x_Mesg_Token_Tbl        => l_Mesg_Token_Tbl
12671                 ,  x_return_status         => l_Return_Status
12672                 );
12673            ELSE
12674                 ENG_Validate_Change_Line.Check_Entity
12675                 (  p_change_line_rec           => l_change_line_rec
12676                 ,  p_change_line_unexp_rec     => l_change_line_unexp_rec
12677                 ,  p_old_change_line_rec       => l_old_change_line_rec
12678                 ,  p_old_change_line_unexp_rec => l_old_change_line_unexp_rec
12679                 ,  x_Mesg_Token_Tbl            => l_Mesg_Token_Tbl
12680                 ,  x_return_status             => l_Return_Status
12681                 );
12682            END IF;
12683 
12684 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
12685 
12686            IF l_return_status = Error_Handler.G_STATUS_ERROR
12687            THEN
12688                 IF l_change_line_rec.transaction_type = ENG_GLOBALS.G_OPR_CREATE
12689                 THEN
12690                         l_other_message := 'ENG_CL_ENTVAL_CSEV_SKIP';
12691                         l_other_token_tbl(1).token_name := 'LINE_NAME';
12692                         l_other_token_tbl(1).token_value := l_change_line_rec.name;
12693                         RAISE EXC_SEV_SKIP_BRANCH;
12694                 ELSE
12695                         RAISE EXC_SEV_QUIT_RECORD;
12696                 END IF;
12697            ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
12698            THEN
12699                 l_other_message := 'ENG_CL_ENTVAL_UNEXP_SKIP';
12700                 l_other_token_tbl(1).token_name := 'LINE_NAME';
12701                 l_other_token_tbl(1).token_value := l_change_line_rec.name;
12702                 RAISE EXC_UNEXP_SKIP_OBJECT;
12703            ELSIF l_return_status ='S' AND
12704                 l_Mesg_Token_Tbl.COUNT <>0
12705            THEN
12706                     Eco_Error_Handler.Log_Error
12707                     (  p_change_line_tbl     => x_change_line_tbl -- Eng Change
12708                     ,  p_revised_item_tbl    => x_revised_item_tbl
12709                     ,  p_rev_component_tbl   => x_rev_component_tbl
12710                     ,  p_ref_designator_tbl  => x_ref_designator_tbl
12711                     ,  p_sub_component_tbl   => x_sub_component_tbl
12712                     ,  p_rev_operation_tbl   => x_rev_operation_tbl    --L1
12713                     ,  p_rev_op_resource_tbl => x_rev_op_resource_tbl  --L1
12714                     ,  p_rev_sub_resource_tbl=> x_rev_sub_resource_tbl --L1
12715                     ,  p_mesg_token_tbl      => l_mesg_token_tbl
12716                     ,  p_error_status        => 'W'
12717                     ,  p_error_level         => ECO_Error_Handler.G_CL_LEVEL
12718                     ,  p_entity_index        => I
12719                     ,  x_ECO_rec             => l_eco_rec
12720                     ,  x_eco_revision_tbl    => l_eco_revision_tbl
12721                     ,  x_change_line_tbl     => x_change_line_tbl -- Eng Change
12722                     ,  x_revised_item_tbl    => x_revised_item_tbl
12723                     ,  x_rev_component_tbl   => x_rev_component_tbl
12724                     ,  x_ref_designator_tbl  => x_ref_designator_tbl
12725                     ,  x_sub_component_tbl   => x_sub_component_tbl
12726                     ,  x_rev_operation_tbl   => x_rev_operation_tbl    --L1
12727                     ,  x_rev_op_resource_tbl => x_rev_op_resource_tbl  --L1
12728                     ,  x_rev_sub_resource_tbl=> x_rev_sub_resource_tbl --L1
12729                     );
12730 
12731            END IF;
12732 
12733            -- Process Flow step 16 : Database Writes
12734            --
12735 
12736            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Writing to the database'); END IF;
12737 
12738            ENG_Change_Line_Util.Perform_Writes
12739                 (  p_change_line_rec       => l_change_line_rec
12740                 ,  p_change_line_unexp_rec => l_change_line_unexp_rec
12741                 ,  x_Mesg_Token_Tbl        => l_Mesg_Token_Tbl
12742                 ,  x_return_status         => l_Return_Status
12743                 );
12744            IF l_return_status ='S' THEN
12745                --11.5.10 subjects
12746                ENG_Change_Line_Util.Change_Subjects(
12747                    p_change_line_rec          => l_change_line_rec
12748                  , p_change_line_unexp_rec    => l_change_line_unexp_rec
12749                  , x_change_subject_unexp_rec => l_change_subject_unexp_rec
12750                  , x_Mesg_Token_Tbl           => l_Mesg_Token_Tbl
12751                  , x_return_status            => l_Return_Status);
12752                --11.5.10
12753            END IF;
12754            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
12755            -- Bug 4033384: Added error handling for subject validation for l_return_status G_STATUS_ERROR
12756            IF l_return_status = Error_Handler.G_STATUS_ERROR
12757            THEN
12758                 IF l_change_line_rec.transaction_type = ENG_GLOBALS.G_OPR_CREATE
12759                 THEN
12760                     l_other_message := 'ENG_CL_ENTVAL_CSEV_SKIP';
12761                     l_other_token_tbl(1).token_name := 'LINE_NAME';
12762                     l_other_token_tbl(1).token_value := l_change_line_rec.name;
12763                     RAISE EXC_SEV_SKIP_BRANCH;
12764                 ELSE
12765                     RAISE EXC_SEV_QUIT_RECORD;
12766                 END IF;
12767            ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
12768            THEN
12769                 l_other_message := 'ENG_CL_WRITES_UNEXP_SKIP';
12770                 l_other_token_tbl(1).token_name := 'LINE_NAME';
12771                 l_other_token_tbl(1).token_value := l_change_line_rec.name;
12772                 RAISE EXC_UNEXP_SKIP_OBJECT;
12773            ELSIF l_return_status ='S' AND
12774               l_Mesg_Token_Tbl.COUNT <>0
12775            THEN
12776                     Eco_Error_Handler.Log_Error
12777                     (  p_change_line_tbl     => x_change_line_tbl -- Eng Change
12778                     ,  p_revised_item_tbl    => x_revised_item_tbl
12779                     ,  p_rev_component_tbl   => x_rev_component_tbl
12780                     ,  p_ref_designator_tbl  => x_ref_designator_tbl
12781                     ,  p_sub_component_tbl   => x_sub_component_tbl
12782                     ,  p_rev_operation_tbl   => x_rev_operation_tbl    --L1
12783                     ,  p_rev_op_resource_tbl => x_rev_op_resource_tbl  --L1
12784                     ,  p_rev_sub_resource_tbl=> x_rev_sub_resource_tbl --L1
12785                     ,  p_mesg_token_tbl      => l_mesg_token_tbl
12786                     ,  p_error_status        => 'W'
12787                     ,  p_error_level         => ECO_Error_Handler.G_CL_LEVEL
12788                     ,  p_entity_index        => I
12789                     ,  x_ECO_rec             => l_eco_rec
12790                     ,  x_eco_revision_tbl    => l_eco_revision_tbl
12791                     ,  x_change_line_tbl     => x_change_line_tbl -- Eng Change
12792                     ,  x_revised_item_tbl    => x_revised_item_tbl
12793                     ,  x_rev_component_tbl   => x_rev_component_tbl
12794                     ,  x_ref_designator_tbl  => x_ref_designator_tbl
12795                     ,  x_sub_component_tbl   => x_sub_component_tbl
12796                     ,  x_rev_operation_tbl   => x_rev_operation_tbl    --L1
12797                     ,  x_rev_op_resource_tbl => x_rev_op_resource_tbl  --L1
12798                     ,  x_rev_sub_resource_tbl=> x_rev_sub_resource_tbl --L1
12799                     );
12800 
12801            END IF;
12802 
12803 IF Bom_Globals.Get_Debug = 'Y' THEN
12804      Error_Handler.Write_Debug('Writing to the database for Change Line is completed with '||l_return_status );
12805 END IF;
12806 
12807         --END IF; -- END IF statement that checks RETURN STATUS
12808 
12809         --  Load tables.
12810 
12811         x_change_line_tbl(I)          := l_change_line_rec;
12812 
12813   --  For loop exception handler.
12814 
12815   EXCEPTION
12816 
12817     WHEN EXC_SEV_QUIT_RECORD THEN
12818 
12819         Eco_Error_Handler.Log_Error
12820         (  p_change_line_tbl     => x_change_line_tbl -- Eng Change
12821         ,  p_revised_item_tbl    => x_revised_item_tbl
12822         ,  p_rev_component_tbl   => x_rev_component_tbl
12823         ,  p_ref_designator_tbl  => x_ref_designator_tbl
12824         ,  p_sub_component_tbl   => x_sub_component_tbl
12825         ,  p_rev_operation_tbl   => x_rev_operation_tbl    --L1
12826         ,  p_rev_op_resource_tbl => x_rev_op_resource_tbl  --L1
12827         ,  p_rev_sub_resource_tbl=> x_rev_sub_resource_tbl --L1
12828         ,  p_mesg_token_tbl      => l_mesg_token_tbl
12829         ,  p_error_status        => FND_API.G_RET_STS_ERROR
12830         ,  p_error_scope         => Error_Handler.G_SCOPE_RECORD
12831         ,  p_error_level         => ECO_Error_Handler.G_CL_LEVEL
12832         ,  p_entity_index        => I
12833         ,  x_ECO_rec             => l_ECO_rec
12834         ,  x_eco_revision_tbl    => l_eco_revision_tbl
12835         ,  x_change_line_tbl     => x_change_line_tbl -- Eng Change
12836         ,  x_revised_item_tbl    => x_revised_item_tbl
12837         ,  x_rev_component_tbl   => x_rev_component_tbl
12838         ,  x_ref_designator_tbl  => x_ref_designator_tbl
12839         ,  x_sub_component_tbl   => x_sub_component_tbl
12840         ,  x_rev_operation_tbl   => x_rev_operation_tbl    --L1
12841         ,  x_rev_op_resource_tbl => x_rev_op_resource_tbl  --L1
12842         ,  x_rev_sub_resource_tbl=> x_rev_sub_resource_tbl --L1
12843         );
12844 
12845 
12846         IF l_bo_return_status = 'S'
12847         THEN
12848             l_bo_return_status  := l_return_status;
12849         END IF;
12850 
12851         x_return_status                := l_bo_return_status;
12852         x_Mesg_Token_Tbl               := l_Mesg_Token_Tbl;
12853 
12854         --x_change_line_tbl              := l_change_line_tbl ;      -- Eng Change
12855         --x_revised_item_tbl             := l_revised_item_tbl;
12856         --x_rev_component_tbl            := l_rev_component_tbl;
12857         --x_ref_designator_tbl           := l_ref_designator_tbl;
12858         --x_sub_component_tbl            := l_sub_component_tbl;
12859         --x_rev_operation_tbl            := l_rev_operation_tbl;     --L1
12860         --x_rev_op_resource_tbl          := l_rev_op_resource_tbl;   --L1
12861         --x_rev_sub_resource_tbl         := l_rev_sub_resource_tbl;  --L1
12862 
12863     WHEN EXC_SEV_QUIT_BRANCH THEN
12864 
12865         Eco_Error_Handler.Log_Error
12866         (  p_change_line_tbl     => x_change_line_tbl -- Eng Change
12867         ,  p_revised_item_tbl    => x_revised_item_tbl
12868         ,  p_rev_component_tbl   => x_rev_component_tbl
12869         ,  p_ref_designator_tbl  => x_ref_designator_tbl
12870         ,  p_sub_component_tbl   => x_sub_component_tbl
12871         ,  p_rev_operation_tbl   => x_rev_operation_tbl    --L1
12872         ,  p_rev_op_resource_tbl => x_rev_op_resource_tbl  --L1
12873         ,  p_rev_sub_resource_tbl=> x_rev_sub_resource_tbl --L1
12874         ,  p_mesg_token_tbl      => l_mesg_token_tbl
12875         ,  p_error_status        => Error_Handler.G_STATUS_ERROR
12876         ,  p_error_scope         => Error_Handler.G_SCOPE_CHILDREN
12877         ,  p_other_status        => Error_Handler.G_STATUS_ERROR
12878         ,  p_other_message       => l_other_message
12879         ,  p_other_token_tbl     => l_other_token_tbl
12880         ,  p_error_level         => ECO_Error_Handler.G_CL_LEVEL
12881         ,  p_entity_index        => I
12882         ,  x_eco_rec             => l_eco_rec
12883         ,  x_eco_revision_tbl    => l_eco_revision_tbl
12884         ,  x_change_line_tbl     => x_change_line_tbl -- Eng Change
12885         ,  x_revised_item_tbl    => x_revised_item_tbl
12886         ,  x_rev_component_tbl   => x_rev_component_tbl
12887         ,  x_ref_designator_tbl  => x_ref_designator_tbl
12888         ,  x_sub_component_tbl   => x_sub_component_tbl
12889         ,  x_rev_operation_tbl   => x_rev_operation_tbl    --L1
12890         ,  x_rev_op_resource_tbl => x_rev_op_resource_tbl  --L1
12891         ,  x_rev_sub_resource_tbl=> x_rev_sub_resource_tbl --L1
12892         );
12893 
12894         IF l_bo_return_status = 'S'
12895         THEN
12896             l_bo_return_status  := l_return_status;
12897         END IF;
12898 
12899 
12900         x_return_status                := l_bo_return_status;
12901         x_Mesg_Token_Tbl               := l_Mesg_Token_Tbl;
12902 
12903         --x_change_line_tbl              := l_change_line_tbl ;      -- Eng Change
12904         --x_revised_item_tbl             := l_revised_item_tbl;
12905         --x_rev_component_tbl            := l_rev_component_tbl;
12906         --x_ref_designator_tbl           := l_ref_designator_tbl;
12907         --x_sub_component_tbl            := l_sub_component_tbl;
12908         --x_rev_operation_tbl            := l_rev_operation_tbl;     --L1
12909         --x_rev_op_resource_tbl          := l_rev_op_resource_tbl;   --L1
12910         --x_rev_sub_resource_tbl         := l_rev_sub_resource_tbl;  --L1
12911 
12912         RETURN;
12913 
12914     WHEN EXC_SEV_SKIP_BRANCH THEN
12915 
12916         Eco_Error_Handler.Log_Error
12917         (  p_change_line_tbl     => x_change_line_tbl -- Eng Change
12918         ,  p_revised_item_tbl    => x_revised_item_tbl
12919         ,  p_rev_component_tbl   => x_rev_component_tbl
12920         ,  p_ref_designator_tbl  => x_ref_designator_tbl
12921         ,  p_sub_component_tbl   => x_sub_component_tbl
12922         ,  p_rev_operation_tbl   => x_rev_operation_tbl    --L1
12923         ,  p_rev_op_resource_tbl => x_rev_op_resource_tbl  --L1
12924         ,  p_rev_sub_resource_tbl=> x_rev_sub_resource_tbl --L1
12925         ,  p_mesg_token_tbl      => l_mesg_token_tbl
12926         ,  p_error_status        => Error_Handler.G_STATUS_ERROR
12927         ,  p_error_scope         => Error_Handler.G_SCOPE_CHILDREN
12928         ,  p_other_message       => l_other_message
12929         ,  p_other_token_tbl     => l_other_token_tbl
12930         ,  p_other_status        => Error_Handler.G_STATUS_NOT_PICKED
12931         ,  p_error_level         => ECO_Error_Handler.G_CL_LEVEL
12932         ,  p_entity_index        => I
12933         ,  x_ECO_rec             => l_ECO_rec
12934         ,  x_eco_revision_tbl    => l_eco_revision_tbl
12935         ,  x_change_line_tbl     => x_change_line_tbl -- Eng Change
12936         ,  x_revised_item_tbl    => x_revised_item_tbl
12937         ,  x_rev_component_tbl   => x_rev_component_tbl
12938         ,  x_ref_designator_tbl  => x_ref_designator_tbl
12939         ,  x_sub_component_tbl   => x_sub_component_tbl
12940         ,  x_rev_operation_tbl   => x_rev_operation_tbl    --L1
12941         ,  x_rev_op_resource_tbl => x_rev_op_resource_tbl  --L1
12942         ,  x_rev_sub_resource_tbl=> x_rev_sub_resource_tbl --L1
12943         );
12944 
12945         IF l_bo_return_status = 'S'
12946         THEN
12947            l_bo_return_status          := l_return_status ;
12948         END IF;
12949 
12950         x_return_status                := l_bo_return_status;
12951         x_Mesg_Token_Tbl               := l_Mesg_Token_Tbl;
12952 
12953         --x_change_line_tbl              := l_change_line_tbl ;      -- Eng Change
12954         --x_revised_item_tbl             := l_revised_item_tbl;
12955         --x_rev_component_tbl            := l_rev_component_tbl;
12956         --x_ref_designator_tbl           := l_ref_designator_tbl;
12957         --x_sub_component_tbl            := l_sub_component_tbl;
12958         --x_rev_operation_tbl            := l_rev_operation_tbl;     --L1
12959         --x_rev_op_resource_tbl          := l_rev_op_resource_tbl;   --L1
12960         --x_rev_sub_resource_tbl         := l_rev_sub_resource_tbl;  --L1
12961 
12962         RETURN;
12963 
12964     WHEN EXC_FAT_QUIT_OBJECT THEN
12965 
12966         Eco_Error_Handler.Log_Error
12967         (  p_change_line_tbl     => x_change_line_tbl -- Eng Change
12968         ,  p_revised_item_tbl    => x_revised_item_tbl
12969         ,  p_rev_component_tbl   => x_rev_component_tbl
12970         ,  p_ref_designator_tbl  => x_ref_designator_tbl
12971         ,  p_sub_component_tbl   => x_sub_component_tbl
12972         ,  p_mesg_token_tbl      => l_mesg_token_tbl
12973         ,  p_rev_operation_tbl   => x_rev_operation_tbl    --L1
12974         ,  p_rev_op_resource_tbl => x_rev_op_resource_tbl  --L1
12975         ,  p_rev_sub_resource_tbl=> x_rev_sub_resource_tbl --L1
12976         ,  p_error_status        => Error_Handler.G_STATUS_FATAL
12977         ,  p_error_scope         => Error_Handler.G_SCOPE_ALL
12978         ,  p_other_message       => l_other_message
12979         ,  p_other_status        => Error_Handler.G_STATUS_FATAL
12980         ,  p_other_token_tbl     => l_other_token_tbl
12981         ,  p_error_level         => ECO_Error_Handler.G_CL_LEVEL
12982         ,  p_entity_index        => I
12983         ,  x_ECO_rec             => l_ECO_rec
12984         ,  x_eco_revision_tbl    => l_eco_revision_tbl
12985         ,  x_change_line_tbl     => x_change_line_tbl -- Eng Change
12986         ,  x_revised_item_tbl    => x_revised_item_tbl
12987         ,  x_rev_component_tbl   => x_rev_component_tbl
12988         ,  x_ref_designator_tbl  => x_ref_designator_tbl
12989         ,  x_sub_component_tbl   => x_sub_component_tbl
12990         ,  x_rev_operation_tbl   => x_rev_operation_tbl    --L1
12991         ,  x_rev_op_resource_tbl => x_rev_op_resource_tbl  --L1
12992         ,  x_rev_sub_resource_tbl=> x_rev_sub_resource_tbl --L1
12993         );
12994 
12995         l_return_status := 'Q';
12996 
12997         x_return_status                := l_return_status;
12998         x_Mesg_Token_Tbl               := l_Mesg_Token_Tbl;
12999 
13000         --x_change_line_tbl              := l_change_line_tbl ;      -- Eng Change
13001         --x_revised_item_tbl             := l_revised_item_tbl;
13002         --x_rev_component_tbl            := l_rev_component_tbl;
13003         --x_ref_designator_tbl           := l_ref_designator_tbl;
13004         --x_sub_component_tbl            := l_sub_component_tbl;
13005         --x_rev_operation_tbl            := l_rev_operation_tbl;     --L1
13006         --x_rev_op_resource_tbl          := l_rev_op_resource_tbl;   --L1
13007         --x_rev_sub_resource_tbl         := l_rev_sub_resource_tbl;  --L1
13008 
13009 
13010     WHEN EXC_UNEXP_SKIP_OBJECT THEN
13011 
13012         Eco_Error_Handler.Log_Error
13013         (  p_change_line_tbl     => x_change_line_tbl -- Eng Change
13014         ,  p_revised_item_tbl    => x_revised_item_tbl
13015         ,  p_rev_component_tbl   => x_rev_component_tbl
13016         ,  p_ref_designator_tbl  => x_ref_designator_tbl
13017         ,  p_sub_component_tbl   => x_sub_component_tbl
13018         ,  p_rev_operation_tbl   => x_rev_operation_tbl    --L1
13019         ,  p_rev_op_resource_tbl => x_rev_op_resource_tbl  --L1
13020         ,  p_rev_sub_resource_tbl=> x_rev_sub_resource_tbl --L1
13021         ,  p_mesg_token_tbl      => l_mesg_token_tbl
13022         ,  p_error_status        => Error_Handler.G_STATUS_UNEXPECTED
13023         ,  p_other_status        => Error_Handler.G_STATUS_NOT_PICKED
13024         ,  p_other_message       => l_other_message
13025         ,  p_other_token_tbl     => l_other_token_tbl
13026         ,  p_error_level         => ECO_Error_Handler.G_CL_LEVEL
13027         ,  x_ECO_rec             => l_ECO_rec
13028         ,  x_eco_revision_tbl    => l_eco_revision_tbl
13029         ,  x_change_line_tbl     => x_change_line_tbl -- Eng Change
13030         ,  x_revised_item_tbl    => x_revised_item_tbl
13031         ,  x_rev_component_tbl   => x_rev_component_tbl
13032         ,  x_ref_designator_tbl  => x_ref_designator_tbl
13033         ,  x_sub_component_tbl   => x_sub_component_tbl
13034         ,  x_rev_operation_tbl   => x_rev_operation_tbl    --L1
13035         ,  x_rev_op_resource_tbl => x_rev_op_resource_tbl  --L1
13036         ,  x_rev_sub_resource_tbl=> x_rev_sub_resource_tbl --L1
13037         );
13038 
13039         l_return_status := 'U';
13040 
13041         x_return_status                := l_return_status;
13042         x_Mesg_Token_Tbl               := l_Mesg_Token_Tbl;
13043 
13044         --x_change_line_tbl              := l_change_line_tbl ;      -- Eng Change
13045         --x_revised_item_tbl             := l_revised_item_tbl;
13046         --x_rev_component_tbl            := l_rev_component_tbl;
13047         --x_ref_designator_tbl           := l_ref_designator_tbl;
13048         --x_sub_component_tbl            := l_sub_component_tbl;
13049         --x_rev_operation_tbl            := l_rev_operation_tbl;     --L1
13050         --x_rev_op_resource_tbl          := l_rev_op_resource_tbl;   --L1
13051         --x_rev_sub_resource_tbl         := l_rev_sub_resource_tbl;  --L1
13052 
13053   END; -- END Change Line processing block
13054   END IF; -- End of processing records for which the return status is null
13055   END LOOP; -- END Change Line processing loop
13056 
13057   IF l_return_status in ('Q', 'U')
13058   THEN
13059         x_return_status := l_return_status;
13060         RETURN;
13061   END IF;
13062 
13063 
13064 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Change Line returning with ' || l_bo_return_status); END IF;
13065 
13066   IF NVL(l_bo_return_status, 'S') <> 'S'
13067   THEN
13068         x_return_status        := l_bo_return_status;
13069 
13070   END IF;
13071 
13072   --  Load OUT parameters
13073   --x_change_line_tbl          := l_change_line_tbl ;      -- Eng Change
13074   --x_revised_item_tbl         := l_revised_item_tbl;
13075   --x_rev_component_tbl        := l_rev_component_tbl;
13076   --x_ref_designator_tbl       := l_ref_designator_tbl;
13077   --x_sub_component_tbl        := l_sub_component_tbl;
13078   --x_Mesg_Token_Tbl           := l_Mesg_Token_Tbl;
13079   --x_rev_operation_tbl        := l_rev_operation_tbl;     --L1
13080   --x_rev_op_resource_tbl      := l_rev_op_resource_tbl;   --L1
13081   --x_rev_sub_resource_tbl     := l_rev_sub_resource_tbl;  --L1
13082 
13083 END Change_Line ;
13084 
13085 
13086 
13087 --  Eco_Rev
13088 PROCEDURE Eco_Rev
13089 (   p_validation_level            IN  NUMBER
13090 ,   p_change_notice               IN  VARCHAR2 := NULL
13091 ,   p_organization_id             IN  NUMBER := NULL
13092 ,   p_eco_revision_tbl            IN  ENG_Eco_PUB.Eco_Revision_Tbl_Type
13093 ,   p_change_line_tbl             IN  ENG_Eco_PUB.Change_Line_Tbl_Type    -- Eng Change
13094 ,   p_revised_item_tbl            IN  ENG_Eco_PUB.Revised_Item_Tbl_Type
13095 ,   p_rev_component_tbl           IN  BOM_BO_PUB.Rev_Component_Tbl_Type
13096 ,   p_ref_designator_tbl          IN  BOM_BO_PUB.Ref_Designator_Tbl_Type
13097 ,   p_sub_component_tbl           IN  BOM_BO_PUB.Sub_Component_Tbl_Type
13098 ,   p_rev_operation_tbl           IN  Bom_Rtg_Pub.Rev_Operation_Tbl_Type   --L1
13099 ,   p_rev_op_resource_tbl         IN  Bom_Rtg_Pub.Rev_Op_Resource_Tbl_Type --L1
13100 ,   p_rev_sub_resource_tbl        IN  Bom_Rtg_Pub.Rev_Sub_Resource_Tbl_Type--L1
13101 ,   x_eco_revision_tbl            IN OUT NOCOPY ENG_Eco_PUB.Eco_Revision_Tbl_Type
13102 ,   x_change_line_tbl             IN OUT NOCOPY ENG_Eco_PUB.Change_Line_Tbl_Type      -- Eng Change
13103 ,   x_revised_item_tbl            IN OUT NOCOPY ENG_Eco_PUB.Revised_Item_Tbl_Type
13104 ,   x_rev_component_tbl           IN OUT NOCOPY BOM_BO_PUB.Rev_Component_Tbl_Type
13105 ,   x_ref_designator_tbl          IN OUT NOCOPY BOM_BO_PUB.Ref_Designator_Tbl_Type
13106 ,   x_sub_component_tbl           IN OUT NOCOPY BOM_BO_PUB.Sub_Component_Tbl_Type
13107 ,   x_rev_operation_tbl           IN OUT NOCOPY Bom_Rtg_Pub.Rev_Operation_Tbl_Type   --L1
13108 ,   x_rev_op_resource_tbl         IN OUT NOCOPY Bom_Rtg_Pub.Rev_Op_Resource_Tbl_Type --L1
13109 ,   x_rev_sub_resource_tbl        IN OUT NOCOPY Bom_Rtg_Pub.Rev_Sub_Resource_Tbl_Type--L1
13110 ,   x_Mesg_Token_Tbl              OUT NOCOPY Error_Handler.Mesg_Token_Tbl_Type
13111 ,   x_return_status               OUT NOCOPY VARCHAR2
13112 )
13113 IS
13114 l_Mesg_Token_Tbl        Error_Handler.Mesg_Token_Tbl_Type;
13115 l_other_token_tbl       Error_Handler.Token_Tbl_Type;
13116 l_other_message         VARCHAR2(2000);
13117 l_err_text              VARCHAR2(2000);
13118 l_valid                 BOOLEAN := TRUE;
13119 l_Return_Status         VARCHAR2(1);
13120 l_bo_return_status      VARCHAR2(1);
13121 l_eco_parent_exists     BOOLEAN := FALSE;
13122 l_eco_rec               ENG_ECO_PUB.ECO_Rec_Type;
13123 l_old_eco_rec           ENG_Eco_PUB.Eco_Rec_Type;
13124 l_old_eco_unexp_rec     ENG_Eco_PUB.Eco_Unexposed_Rec_Type;
13125 l_eco_revision_rec      ENG_Eco_PUB.Eco_Revision_Rec_Type;
13126 --l_eco_revision_tbl      ENG_Eco_PUB.Eco_Revision_Tbl_Type := p_eco_revision_tbl;
13127 l_eco_rev_unexp_rec     ENG_Eco_PUB.Eco_Rev_Unexposed_Rec_Type;
13128 l_old_eco_rev_rec       ENG_Eco_PUB.Eco_Revision_Rec_Type := NULL;
13129 l_old_eco_rev_unexp_rec ENG_Eco_PUB.Eco_Rev_Unexposed_Rec_Type := NULL;
13130 --l_revised_item_tbl      ENG_Eco_PUB.Revised_Item_Tbl_Type := p_revised_item_tbl;
13131 --l_rev_component_tbl     BOM_BO_PUB.Rev_Component_Tbl_Type := p_rev_component_tbl;
13132 --l_ref_designator_tbl    BOM_BO_PUB.Ref_Designator_Tbl_Type := p_ref_designator_tbl;
13133 --l_sub_component_tbl     BOM_BO_PUB.Sub_Component_Tbl_Type := p_sub_component_tbl;
13134 --l_rev_operation_tbl     Bom_Rtg_Pub.Rev_Operation_Tbl_Type := p_rev_operation_tbl;  --L1
13135 --l_rev_op_resource_tbl   Bom_Rtg_Pub.Rev_Op_Resource_Tbl_Type :=p_rev_op_resource_tbl; --L1
13136 --l_rev_sub_resource_tbl  Bom_Rtg_Pub.Rev_Sub_Resource_Tbl_Type :=p_rev_sub_resource_tbl; --L1
13137 --l_change_line_tbl       Eng_Eco_Pub.Change_Line_Tbl_Type := p_change_line_tbl; -- Eng Change
13138 
13139 
13140 l_return_value          NUMBER;
13141 l_Token_Tbl             Error_Handler.Token_Tbl_Type;
13142 
13143 EXC_SEV_QUIT_RECORD     EXCEPTION;
13144 EXC_SEV_QUIT_OBJECT     EXCEPTION;
13145 EXC_FAT_QUIT_OBJECT     EXCEPTION;
13146 EXC_UNEXP_SKIP_OBJECT   EXCEPTION;
13147 
13148 	-- Bug 2918350 // kamohan
13149 	-- Start Changes
13150 
13151 	l_chk_co_sch eng_engineering_changes.status_type%TYPE;
13152 
13153 	-- Bug 2918350 // kamohan
13154 	-- End Changes
13155 
13156 BEGIN
13157 
13158 
13159     l_return_status := 'S';
13160     l_bo_return_status := 'S';
13161 
13162     --  Init local table variables.
13163 
13164     x_eco_revision_tbl                  := p_eco_revision_tbl;
13165     x_revised_item_tbl                  := p_revised_item_tbl;
13166     x_rev_component_tbl                 := p_rev_component_tbl;
13167     x_ref_designator_tbl                := p_ref_designator_tbl;
13168     x_sub_component_tbl                 := p_sub_component_tbl;
13169     x_rev_operation_tbl                 := p_rev_operation_tbl;
13170     x_rev_op_resource_tbl               := p_rev_op_resource_tbl;
13171     x_rev_sub_resource_tbl              := p_rev_sub_resource_tbl;
13172     x_change_line_tbl                   := p_change_line_tbl;
13173 
13174     l_eco_rev_unexp_rec.organization_id := ENG_GLOBALS.Get_org_id;
13175 
13176     FOR I IN 1..x_eco_revision_tbl.COUNT LOOP
13177     IF (x_eco_revision_tbl(I).return_status IS NULL OR
13178          x_eco_revision_tbl(I).return_status = FND_API.G_MISS_CHAR) THEN
13179 
13180     BEGIN
13181 
13182         --  Load local records.
13183 
13184         l_eco_revision_rec := x_eco_revision_tbl(I);
13185 
13186         l_eco_revision_rec.transaction_type :=
13187                 UPPER(l_eco_revision_rec.transaction_type);
13188 
13189         IF p_change_notice IS NOT NULL AND
13190            p_organization_id IS NOT NULL
13191         THEN
13192                 l_eco_parent_exists := TRUE;
13193         END IF;
13194 
13195         -- Process Flow Step 2: Check if record has not yet been processed and
13196         -- that it is the child of the parent that called this procedure
13197         --
13198 
13199         IF --(l_eco_revision_rec.return_status IS NULL OR
13200             --l_eco_revision_rec.return_status = FND_API.G_MISS_CHAR)
13201            --AND
13202            (NOT l_eco_parent_exists
13203             OR
13204             (l_eco_parent_exists AND
13205              (l_eco_revision_rec.ECO_Name = p_change_notice AND
13206               l_eco_rev_unexp_rec.organization_id = p_organization_id)))
13207         THEN
13208 
13209            l_return_status := FND_API.G_RET_STS_SUCCESS;
13210 
13211            l_eco_revision_rec.return_status := FND_API.G_RET_STS_SUCCESS;
13212 
13213            -- Check if transaction_type is valid
13214            --
13215 
13216            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Transaction Type validity'); END IF;
13217            ENG_GLOBALS.Transaction_Type_Validity
13218            (   p_transaction_type       => l_eco_revision_rec.transaction_type
13219            ,   p_entity                 => 'ECO_Rev'
13220            ,   p_entity_id              => l_eco_revision_rec.revision
13221            ,   x_valid                  => l_valid
13222            ,   x_Mesg_Token_Tbl         => l_Mesg_Token_Tbl
13223            );
13224 
13225            IF NOT l_valid
13226            THEN
13227                 l_return_status := Error_Handler.G_STATUS_ERROR;
13228                 RAISE EXC_SEV_QUIT_RECORD;
13229            END IF;
13230 
13231            -- Process Flow step 3: Value-to-ID conversions
13232            --
13233 
13234            ENG_Val_To_Id.ECO_Revision_UUI_To_UI
13235                (  p_eco_revision_rec   => l_eco_revision_rec
13236                 , p_eco_rev_unexp_rec  => l_eco_rev_unexp_rec
13237                 , x_eco_rev_unexp_rec  => l_eco_rev_unexp_rec
13238                 , x_Mesg_Token_Tbl     => l_Mesg_Token_Tbl
13239                 , x_Return_Status      => l_return_status
13240                );
13241 
13242            -- Process Flow step 4: Verify that Revision is not NULL or MISSING
13243           --
13244 
13245            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Check if Revision is missing or null'); END IF;
13246            ENG_Validate_Eco_Revision.Check_Required
13247                 (  x_return_status              => l_return_status
13248                 ,  p_eco_revision_rec           => l_eco_revision_rec
13249                 ,  x_mesg_token_tbl             => l_Mesg_Token_Tbl
13250                 );
13251 
13252            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
13253 
13254            IF l_return_status = Error_Handler.G_STATUS_ERROR
13255            THEN
13256                 RAISE EXC_SEV_QUIT_RECORD;
13257            ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
13258            THEN
13259                 l_other_message := 'ENG_REV_KEYCOL_UNEXP_SKIP';
13260                 l_other_token_tbl(1).token_name := 'REVISION';
13261                 l_other_token_tbl(1).token_value := l_eco_revision_rec.revision;
13262                 RAISE EXC_UNEXP_SKIP_OBJECT;
13263            END IF;
13264 
13265            -- Process Flow step 5: Verify ECO's existence in database, if
13266            -- the revised item is being created on an ECO and the business
13267            -- object does not carry the ECO header
13268 
13269            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Check parent existence'); END IF;
13270 
13271            IF l_eco_revision_rec.transaction_type = ENG_GLOBALS.G_OPR_CREATE
13272               AND
13273               NOT l_eco_parent_exists
13274            THEN
13275                 ENG_Validate_ECO.Check_Existence
13276                 ( p_change_notice       => l_eco_revision_rec.ECO_Name
13277                 , p_organization_id     => l_eco_rev_unexp_rec.organization_id
13278                 , p_organization_code   => l_eco_revision_rec.organization_code
13279                 , p_calling_entity      => 'CHILD'
13280                 , p_transaction_type    => 'XXX'
13281                 , x_eco_rec             => l_old_eco_rec
13282                 , x_eco_unexp_rec       => l_old_eco_unexp_rec
13283                 , x_Mesg_Token_Tbl      => l_Mesg_Token_Tbl
13284                 , x_return_status       => l_Return_Status
13285                 );
13286 
13287                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
13288 
13289                 IF l_return_status = Error_Handler.G_STATUS_ERROR
13290                 THEN
13291                    l_other_message := 'ENG_PARENTECO_NOT_EXIST';
13292                    l_other_token_tbl(1).token_name := 'ECO_NAME';
13293                    l_other_token_tbl(1).token_value := l_eco_revision_rec.ECO_Name;
13294                    l_other_token_tbl(2).token_name := 'ORGANIZATION_CODE';
13295                    l_other_token_tbl(2).token_value := l_eco_revision_rec.organization_code;
13296                    RAISE EXC_SEV_QUIT_OBJECT;
13297                 ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
13298                 THEN
13299                    l_other_message := 'ENG_REV_LIN_UNEXP_SKIP';
13300                    l_other_token_tbl(1).token_name := 'REVISION';
13301                    l_other_token_tbl(1).token_value := l_eco_revision_rec.revision;
13302                    RAISE EXC_UNEXP_SKIP_OBJECT;
13303                 END IF;
13304            END IF;
13305 
13306 	-- Bug 2918350
13307 	-- Start Changes
13308 	 IF l_eco_revision_rec.Transaction_Type IN
13309                 (ENG_GLOBALS.G_OPR_UPDATE, ENG_GLOBALS.G_OPR_DELETE)
13310            THEN
13311 
13312 	IF p_change_notice IS NOT NULL AND p_organization_id IS NOT NULL THEN
13313 		l_chk_co_sch := ret_co_status ( p_change_notice, p_organization_id);
13314 	ELSE
13315 		l_chk_co_sch := ret_co_status (l_eco_revision_rec.eco_name, l_eco_rev_unexp_rec.organization_id);
13316 	END IF;
13317 
13318 	IF l_chk_co_sch = 4 THEN
13319 		l_return_status := error_handler.g_status_error;
13320 		error_handler.add_error_token (p_message_name        => 'ENG_ECO_REV_NOT_UPD',
13321 			p_mesg_token_tbl      => l_mesg_token_tbl,
13322 			x_mesg_token_tbl      => l_mesg_token_tbl,
13323 			p_token_tbl           => l_token_tbl
13324 			);
13325 		RAISE exc_sev_quit_record;
13326 	END IF;
13327         end if;
13328 	-- End Changes
13329 
13330            -- Process Flow step 4: Verify Revision's existence
13331            --
13332 
13333            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Check Existence'); END IF;
13334            ENG_Validate_ECO_Revision.Check_Existence
13335                 (  p_eco_revision_rec           => l_eco_revision_rec
13336                 ,  p_eco_rev_unexp_rec          => l_eco_rev_unexp_rec
13337                 ,  x_old_eco_revision_rec       => l_old_eco_rev_rec
13338                 ,  x_old_eco_rev_unexp_rec      => l_old_eco_rev_unexp_rec
13339                 ,  x_Mesg_Token_Tbl             => l_Mesg_Token_Tbl
13340                 ,  x_return_status              => l_Return_Status
13341                 );
13342 
13343            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
13344 
13345            IF l_return_status = Error_Handler.G_STATUS_ERROR
13346            THEN
13347                 RAISE EXC_SEV_QUIT_RECORD;
13348            ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
13349            THEN
13350                 l_other_message := 'ENG_REV_EXS_UNEXP_SKIP';
13351                 l_other_token_tbl(1).token_name := 'REVISION';
13352                 l_other_token_tbl(1).token_value := l_eco_revision_rec.revision;
13353                 RAISE EXC_UNEXP_SKIP_OBJECT;
13354            END IF;
13355 
13356 
13357            -- Process Flow step 5: Is ECO Revision record an orphan ?
13358 
13359            IF NOT l_eco_parent_exists
13360            THEN
13361 
13362                 -- Process Flow step 6(a and b): Is ECO impl/cancl,
13363                 -- or in wkflw process ?
13364                 --
13365 
13366                 ENG_Validate_ECO.Check_Access
13367                 ( p_change_notice       => l_eco_revision_rec.ECO_Name
13368                 , p_organization_id     => l_eco_rev_unexp_rec.organization_id
13369                 , p_Mesg_Token_Tbl      => l_Mesg_Token_Tbl
13370                 , x_Mesg_Token_Tbl      => l_Mesg_Token_Tbl
13371                 , x_Return_Status       => l_return_status
13372                 );
13373 
13374                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
13375 
13376                 IF l_return_status = Error_Handler.G_STATUS_ERROR
13377                 THEN
13378                         l_other_message := 'ENG_REV_ACCESS_FAT_FATAL';
13379                         l_other_token_tbl(1).token_name := 'REVISION';
13380                         l_other_token_tbl(1).token_value := l_eco_revision_rec.revision;
13381                         l_return_status := 'F';
13382                         RAISE EXC_FAT_QUIT_OBJECT;
13383                 ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
13384                 THEN
13385                         l_other_message := 'ENG_REV_ACCESS_UNEXP_ERROR';
13386                         l_other_token_tbl(1).token_name := 'REVISION';
13387                         l_other_token_tbl(1).token_value := l_eco_revision_rec.revision;
13388                         RAISE EXC_UNEXP_SKIP_OBJECT;
13389                 END IF;
13390 
13391            END IF;
13392 
13393            IF l_eco_revision_rec.Transaction_Type IN
13394                 (ENG_GLOBALS.G_OPR_UPDATE, ENG_GLOBALS.G_OPR_DELETE)
13395            THEN
13396 
13397                 -- Process flow step 7 - Populate NULL columns for Update and
13398                 -- Delete.
13399 
13400                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Populating NULL Columns'); END IF;
13401                 Eng_Default_ECO_Revision.Populate_NULL_Columns
13402                 (   p_eco_revision_rec          => l_eco_revision_rec
13403                 ,   p_eco_rev_unexp_rec         => l_eco_rev_unexp_rec
13404                 ,   p_old_eco_revision_rec      => l_old_eco_rev_rec
13405                 ,   p_old_eco_rev_unexp_rec     => l_old_eco_rev_unexp_rec
13406                 ,   x_eco_revision_rec          => l_eco_revision_rec
13407                 ,   x_eco_rev_unexp_rec         => l_eco_rev_unexp_rec
13408                 ,   x_Mesg_Token_Tbl            => l_Mesg_Token_Tbl
13409                 );
13410 
13411            ELSIF l_eco_revision_rec.Transaction_Type = ENG_GLOBALS.G_OPR_CREATE THEN
13412 
13413                 -- Process Flow step 8: Default missing values for Operation CREATE
13414 
13415                  IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Attribute Defaulting'); END IF;
13416                  Eng_Default_ECO_revision.Attribute_Defaulting
13417                         (   p_eco_revision_rec          => l_eco_revision_rec
13418                         ,   p_eco_rev_unexp_rec         => l_eco_rev_unexp_rec
13419                         ,   x_eco_revision_rec          => l_eco_revision_rec
13420                         ,   x_eco_rev_unexp_rec         => l_eco_rev_unexp_Rec
13421                         ,   x_Mesg_Token_Tbl            => l_Mesg_Token_Tbl
13422                         ,   x_return_status             => l_Return_Status
13423                         );
13424 
13425                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
13426 
13427                 IF l_return_status = Error_Handler.G_STATUS_ERROR
13428                 THEN
13429                         RAISE EXC_SEV_QUIT_RECORD;
13430                 ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
13431                 THEN
13432                         l_other_message := 'ENG_REV_ATTDEF_UNEXP_SKIP';
13433                         l_other_token_tbl(1).token_name := 'REVISION';
13434                         l_other_token_tbl(1).token_value :=
13435                                                  l_eco_revision_rec.revision;
13436                         RAISE EXC_UNEXP_SKIP_OBJECT;
13437                 ELSIF l_return_status ='S' AND
13438                         l_Mesg_Token_Tbl.COUNT <>0
13439                 THEN
13440                         Eco_Error_Handler.Log_Error
13441                         (  p_eco_revision_tbl    => x_eco_revision_tbl
13442                         ,  p_change_line_tbl     => x_change_line_tbl -- Eng Change
13443                         ,  p_revised_item_tbl    => x_revised_item_tbl
13444                         ,  p_rev_component_tbl   => x_rev_component_tbl
13445                         ,  p_ref_designator_tbl  => x_ref_designator_tbl
13446                         ,  p_sub_component_tbl   => x_sub_component_tbl
13447                         ,  p_rev_operation_tbl   => x_rev_operation_tbl   --L1
13448                         ,  p_rev_op_resource_tbl => x_rev_op_resource_tbl --L1
13449                         ,  p_rev_sub_resource_tbl=> x_rev_sub_resource_tbl--L1
13450                         ,  p_mesg_token_tbl      => l_mesg_token_tbl
13451                         ,  p_error_status        => 'W'
13452                         ,  p_error_level         => 2
13453                         ,  p_entity_index        => I
13454                         ,  x_eco_rec             => l_eco_rec
13455                         ,  x_eco_revision_tbl    => x_eco_revision_tbl
13456                         ,  x_change_line_tbl     => x_change_line_tbl -- Eng Change
13457                         ,  x_revised_item_tbl    => x_revised_item_tbl
13458                         ,  x_rev_component_tbl   => x_rev_component_tbl
13459                         ,  x_ref_designator_tbl  => x_ref_designator_tbl
13460                         ,  x_sub_component_tbl   => x_sub_component_tbl
13461                         ,  x_rev_operation_tbl   => x_rev_operation_tbl    --L1
13462                         ,  x_rev_op_resource_tbl => x_rev_op_resource_tbl  --L1
13463                         ,  x_rev_sub_resource_tbl=> x_rev_sub_resource_tbl --L1
13464                         );
13465                 END IF;
13466            END IF;
13467 
13468            -- Process Flow step 10 - Entity Level Validation
13469 
13470            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Entity validation'); END IF;
13471            Eng_Validate_ECO_Revision.Check_Entity
13472                 (  x_return_status        => l_Return_Status
13473                 ,  x_Mesg_Token_Tbl       => l_Mesg_Token_Tbl
13474                 ,  p_eco_revision_rec     => l_eco_revision_rec
13475                 ,  p_eco_rev_unexp_rec    => l_eco_rev_unexp_rec
13476                 );
13477 
13478            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
13479 
13480            IF l_return_status = Error_Handler.G_STATUS_ERROR
13481            THEN
13482                 RAISE EXC_SEV_QUIT_RECORD;
13483            ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
13484            THEN
13485                 l_other_message := 'ENG_REV_ENTVAL_UNEXP_ERROR';
13486                 l_other_token_tbl(1).token_name := 'REVISION';
13487                 l_other_token_tbl(1).token_value := l_eco_revision_rec.revision;
13488                 RAISE EXC_UNEXP_SKIP_OBJECT;
13489            ELSIF l_return_status ='S' AND
13490                 l_Mesg_Token_Tbl.COUNT <>0
13491            THEN
13492                 Eco_Error_Handler.Log_Error
13493                 (  p_eco_revision_tbl       => x_eco_revision_tbl
13494                 ,  p_change_line_tbl        => x_change_line_tbl -- Eng Change
13495                 ,  p_revised_item_tbl       => x_revised_item_tbl
13496                 ,  p_rev_component_tbl      => x_rev_component_tbl
13497                 ,  p_ref_designator_tbl     => x_ref_designator_tbl
13498                 ,  p_sub_component_tbl      => x_sub_component_tbl
13499                 ,  p_rev_operation_tbl      => x_rev_operation_tbl    --L1
13500                 ,  p_rev_op_resource_tbl    => x_rev_op_resource_tbl  --L1
13501                 ,  p_rev_sub_resource_tbl   => x_rev_sub_resource_tbl --L1
13502                 ,  p_mesg_token_tbl         => l_mesg_token_tbl
13503                 ,  p_error_status           => 'W'
13504                 ,  p_error_level            => 2
13505                 ,  p_entity_index           => I
13506                 ,  x_eco_rec                => l_eco_rec
13507                 ,  x_eco_revision_tbl       => x_eco_revision_tbl
13508                 ,  x_change_line_tbl        => x_change_line_tbl -- Eng Change
13509                 ,  x_revised_item_tbl       => x_revised_item_tbl
13510                 ,  x_rev_component_tbl      => x_rev_component_tbl
13511                 ,  x_ref_designator_tbl     => x_ref_designator_tbl
13512                 ,  x_sub_component_tbl      => x_sub_component_tbl
13513                 ,  x_rev_operation_tbl      => x_rev_operation_tbl    --L1
13514                 ,  x_rev_op_resource_tbl    => x_rev_op_resource_tbl  --L1
13515                 ,  x_rev_sub_resource_tbl   => x_rev_sub_resource_tbl --L1
13516                 );
13517            END IF;
13518 
13519            -- Process Flow step 11 : Database Writes
13520 
13521            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Writing to the database'); END IF;
13522            ENG_ECO_Revision_Util.Perform_Writes
13523                 (   p_eco_revision_rec          => l_eco_revision_rec
13524                 ,   p_eco_rev_unexp_rec         => l_eco_rev_unexp_rec
13525                 ,   x_Mesg_Token_Tbl            => l_Mesg_Token_Tbl
13526                 ,   x_return_status             => l_return_status
13527                 );
13528 
13529            IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
13530 
13531            IF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
13532            THEN
13533                 l_other_message := 'ENG_REV_WRITES_UNEXP_ERROR';
13534                 l_other_token_tbl(1).token_name := 'REVISION';
13535                 l_other_token_tbl(1).token_value := l_eco_revision_rec.revision;
13536                 RAISE EXC_UNEXP_SKIP_OBJECT;
13537            ELSIF l_return_status ='S' AND
13538               l_Mesg_Token_Tbl.COUNT <>0
13539            THEN
13540                 Eco_Error_Handler.Log_Error
13541                 (  p_eco_revision_tbl      => x_eco_revision_tbl
13542                 ,  p_change_line_tbl       => x_change_line_tbl -- Eng Change
13543                 ,  p_revised_item_tbl      => x_revised_item_tbl
13544                 ,  p_rev_component_tbl     => x_rev_component_tbl
13545                 ,  p_ref_designator_tbl    => x_ref_designator_tbl
13546                 ,  p_sub_component_tbl     => x_sub_component_tbl
13547                 ,  p_rev_operation_tbl     => x_rev_operation_tbl    --L1
13548                 ,  p_rev_op_resource_tbl   => x_rev_op_resource_tbl  --L1
13549                 ,  p_rev_sub_resource_tbl  => x_rev_sub_resource_tbl --L1
13550                 ,  p_mesg_token_tbl        => l_mesg_token_tbl
13551                 ,  p_error_status          => 'W'
13552                 ,  p_error_level           => 2
13553                 ,  x_eco_rec               => l_eco_rec
13554                 ,  x_eco_revision_tbl      => x_eco_revision_tbl
13555                 ,  x_change_line_tbl       => x_change_line_tbl -- Eng Change
13556                 ,  x_revised_item_tbl      => x_revised_item_tbl
13557                 ,  x_rev_component_tbl     => x_rev_component_tbl
13558                 ,  x_ref_designator_tbl    => x_ref_designator_tbl
13559                 ,  x_sub_component_tbl     => x_sub_component_tbl
13560                 ,  x_rev_operation_tbl     => x_rev_operation_tbl    --L1
13561                 ,  x_rev_op_resource_tbl   => x_rev_op_resource_tbl  --L1
13562                 ,  x_rev_sub_resource_tbl  => x_rev_sub_resource_tbl --L1
13563                 );
13564            END IF;
13565 
13566         END IF; -- End IF that checks RETURN STATUS AND PARENT-CHILD RELATIONSHIP
13567 
13568         --  Load tables.
13569 
13570         x_eco_revision_tbl(I)          := l_eco_revision_rec;
13571 
13572         --  For loop exception handler.
13573 
13574 
13575      EXCEPTION
13576 
13577        WHEN EXC_SEV_QUIT_RECORD THEN
13578 
13579         Eco_Error_Handler.Log_Error
13580                 (  p_eco_revision_tbl       => x_eco_revision_tbl
13581                 ,  p_change_line_tbl        => x_change_line_tbl -- Eng Change
13582                 ,  p_revised_item_tbl       => x_revised_item_tbl
13583                 ,  p_rev_component_tbl      => x_rev_component_tbl
13584                 ,  p_ref_designator_tbl     => x_ref_designator_tbl
13585                 ,  p_sub_component_tbl      => x_sub_component_tbl
13586                 ,  p_rev_operation_tbl      => x_rev_operation_tbl    --L1
13587                 ,  p_rev_op_resource_tbl    => x_rev_op_resource_tbl  --L1
13588                 ,  p_rev_sub_resource_tbl   => x_rev_sub_resource_tbl --L1
13589                 ,  p_mesg_token_tbl         => l_mesg_token_tbl
13590                 ,  p_error_status           => FND_API.G_RET_STS_ERROR
13591                 ,  p_error_scope            => Error_Handler.G_SCOPE_RECORD
13592                 ,  p_error_level            => 2
13593                 ,  p_entity_index           => I
13594                 ,  x_eco_rec                => l_eco_rec
13595                 ,  x_eco_revision_tbl       => x_eco_revision_tbl
13596                 ,  x_change_line_tbl        => x_change_line_tbl -- Eng Change
13597                 ,  x_revised_item_tbl       => x_revised_item_tbl
13598                 ,  x_rev_component_tbl      => x_rev_component_tbl
13599                 ,  x_ref_designator_tbl     => x_ref_designator_tbl
13600                 ,  x_sub_component_tbl      => x_sub_component_tbl
13601                 ,  x_rev_operation_tbl      => x_rev_operation_tbl    --L1
13602                 ,  x_rev_op_resource_tbl    => x_rev_op_resource_tbl  --L1
13603                 ,  x_rev_sub_resource_tbl   => x_rev_sub_resource_tbl --L1
13604                 );
13605 
13606         IF l_bo_return_status = 'S'
13607         THEN
13608                 l_bo_return_status     := l_return_status;
13609         END IF;
13610 
13611         x_return_status                := l_bo_return_status;
13612         x_Mesg_Token_Tbl               := l_Mesg_Token_Tbl;
13613         --x_eco_revision_tbl             := l_eco_revision_tbl;
13614         --x_revised_item_tbl             := l_revised_item_tbl;
13615         --x_rev_component_tbl            := l_rev_component_tbl;
13616         --x_ref_designator_tbl           := l_ref_designator_tbl;
13617         --x_sub_component_tbl            := l_sub_component_tbl;
13618         --x_rev_operation_tbl            := l_rev_operation_tbl;     --L1
13619         --x_rev_op_resource_tbl          := l_rev_op_resource_tbl;   --L1
13620         --x_rev_sub_resource_tbl         := l_rev_sub_resource_tbl;  --L1
13621         --x_change_line_tbl              := l_change_line_tbl ;      -- Eng Change
13622 
13623         WHEN EXC_SEV_QUIT_OBJECT THEN
13624 
13625         Eco_Error_Handler.Log_Error
13626             (  p_eco_revision_tbl       => x_eco_revision_tbl
13627              , p_change_line_tbl        => x_change_line_tbl -- Eng Change
13628              , p_revised_item_tbl       => x_revised_item_tbl
13629              , p_rev_component_tbl      => x_rev_component_tbl
13630              , p_ref_designator_tbl     => x_ref_designator_tbl
13631              , p_sub_component_tbl      => x_sub_component_tbl
13632              , p_rev_operation_tbl      => x_rev_operation_tbl    --L1
13633              , p_rev_op_resource_tbl    => x_rev_op_resource_tbl  --L1
13634              , p_rev_sub_resource_tbl   => x_rev_sub_resource_tbl --L1
13635              , p_error_status           => Error_Handler.G_STATUS_ERROR
13636              , p_error_scope            => Error_Handler.G_SCOPE_ALL
13637              , p_error_level            => Error_Handler.G_BO_LEVEL
13638              , p_other_message          => l_other_message
13639              , p_other_status           => Error_Handler.G_STATUS_ERROR
13640              , p_other_token_tbl        => l_other_token_tbl
13641              , x_eco_rec                => l_eco_rec
13642              , x_eco_revision_tbl       => x_eco_revision_tbl
13643              , x_change_line_tbl        => x_change_line_tbl -- Eng Change
13644              , x_revised_item_tbl       => x_revised_item_tbl
13645              , x_rev_component_tbl      => x_rev_component_tbl
13646              , x_ref_designator_tbl     => x_ref_designator_tbl
13647              , x_sub_component_tbl      => x_sub_component_tbl
13648              , x_rev_operation_tbl      => x_rev_operation_tbl    --L1
13649              , x_rev_op_resource_tbl    => x_rev_op_resource_tbl  --L1
13650              , x_rev_sub_resource_tbl   => x_rev_sub_resource_tbl --L1
13651              );
13652 
13653         IF l_bo_return_status = 'S'
13654         THEN
13655                 l_bo_return_status     := l_return_status;
13656         END IF;
13657 
13658         x_return_status                := l_bo_return_status;
13659         x_Mesg_Token_Tbl               := l_Mesg_Token_Tbl;
13660         --x_eco_revision_tbl             := l_eco_revision_tbl;
13661         --x_revised_item_tbl             := l_revised_item_tbl;
13662         --x_rev_component_tbl            := l_rev_component_tbl;
13663         --x_ref_designator_tbl           := l_ref_designator_tbl;
13664         --x_sub_component_tbl            := l_sub_component_tbl;
13665         --x_rev_operation_tbl            := l_rev_operation_tbl;     --L1
13666         --x_rev_op_resource_tbl          := l_rev_op_resource_tbl;   --L1
13667         --x_rev_sub_resource_tbl         := l_rev_sub_resource_tbl;  --L1
13668         --x_change_line_tbl              := l_change_line_tbl ;      -- Eng Change
13669 
13670        WHEN EXC_FAT_QUIT_OBJECT THEN
13671 
13672         Eco_Error_Handler.Log_Error
13673                 (  p_eco_revision_tbl    => x_eco_revision_tbl
13674                 ,  p_change_line_tbl     => x_change_line_tbl -- Eng Change
13675                 ,  p_revised_item_tbl    => x_revised_item_tbl
13676                 ,  p_rev_component_tbl   => x_rev_component_tbl
13677                 ,  p_ref_designator_tbl  => x_ref_designator_tbl
13678                 ,  p_sub_component_tbl   => x_sub_component_tbl
13679                 ,  p_rev_operation_tbl   => x_rev_operation_tbl    --L1
13680                 ,  p_rev_op_resource_tbl => x_rev_op_resource_tbl  --L1
13681                 ,  p_rev_sub_resource_tbl=> x_rev_sub_resource_tbl --L1
13682                 ,  p_mesg_token_tbl      => l_mesg_token_tbl
13683                 ,  p_error_status        => Error_Handler.G_STATUS_FATAL
13684                 ,  p_error_scope         => Error_Handler.G_SCOPE_ALL
13685                 ,  p_other_status        => Error_Handler.G_STATUS_FATAL
13686                 ,  p_other_message       => l_other_message
13687                 ,  p_other_token_tbl     => l_other_token_tbl
13688                 ,  p_error_level         => 2
13689                 ,  p_entity_index        => I
13690                 ,  x_eco_rec             => l_eco_rec
13691                 ,  x_eco_revision_tbl    => x_eco_revision_tbl
13692                 ,  x_change_line_tbl     => x_change_line_tbl -- Eng Change
13693                 ,  x_revised_item_tbl    => x_revised_item_tbl
13694                 ,  x_rev_component_tbl   => x_rev_component_tbl
13695                 ,  x_ref_designator_tbl  => x_ref_designator_tbl
13696                 ,  x_sub_component_tbl   => x_sub_component_tbl
13697                 ,  x_rev_operation_tbl   => x_rev_operation_tbl    --L1
13698                 ,  x_rev_op_resource_tbl => x_rev_op_resource_tbl  --L1
13699                 ,  x_rev_sub_resource_tbl=> x_rev_sub_resource_tbl --L1
13700                 );
13701 
13702         x_Mesg_Token_Tbl               := l_Mesg_Token_Tbl;
13703         --x_eco_revision_tbl             := l_eco_revision_tbl;
13704         --x_revised_item_tbl             := l_revised_item_tbl;
13705         --x_rev_component_tbl            := l_rev_component_tbl;
13706         --x_ref_designator_tbl           := l_ref_designator_tbl;
13707         --x_sub_component_tbl            := l_sub_component_tbl;
13708         --x_rev_operation_tbl            := l_rev_operation_tbl;     --L1
13709         --x_rev_op_resource_tbl          := l_rev_op_resource_tbl;   --L1
13710         --x_rev_sub_resource_tbl         := l_rev_sub_resource_tbl;  --L1
13711         --x_change_line_tbl              := l_change_line_tbl ;      -- Eng Change
13712 
13713         l_return_status := 'Q';
13714 
13715        WHEN EXC_UNEXP_SKIP_OBJECT THEN
13716 
13717         Eco_Error_Handler.Log_Error
13718                 (  p_eco_revision_tbl    => x_eco_revision_tbl
13719                 ,  p_change_line_tbl     => x_change_line_tbl -- Eng Change
13720                 ,  p_revised_item_tbl    => x_revised_item_tbl
13721                 ,  p_rev_component_tbl   => x_rev_component_tbl
13722                 ,  p_ref_designator_tbl  => x_ref_designator_tbl
13723                 ,  p_sub_component_tbl   => x_sub_component_tbl
13724                 ,  p_rev_operation_tbl   => x_rev_operation_tbl    --L1
13725                 ,  p_rev_op_resource_tbl => x_rev_op_resource_tbl  --L1
13726                 ,  p_rev_sub_resource_tbl=> x_rev_sub_resource_tbl --L1
13727                 ,  p_mesg_token_tbl      => l_mesg_token_tbl
13728                 ,  p_error_status        => Error_Handler.G_STATUS_UNEXPECTED
13729                 ,  p_other_status        => Error_Handler.G_STATUS_NOT_PICKED
13730                 ,  p_other_message       => l_other_message
13731                 ,  p_other_token_tbl     => l_other_token_tbl
13732                 ,  p_error_level         => 2
13733                 ,  x_ECO_rec             => l_ECO_rec
13734                 ,  x_eco_revision_tbl    => x_eco_revision_tbl
13735                 ,  x_change_line_tbl     => x_change_line_tbl -- Eng Change
13736                 ,  x_revised_item_tbl    => x_revised_item_tbl
13737                 ,  x_rev_component_tbl   => x_rev_component_tbl
13738                 ,  x_ref_designator_tbl  => x_ref_designator_tbl
13739                 ,  x_sub_component_tbl   => x_sub_component_tbl
13740                 ,  x_rev_operation_tbl   => x_rev_operation_tbl    --L1
13741                 ,  x_rev_op_resource_tbl => x_rev_op_resource_tbl  --L1
13742                 ,  x_rev_sub_resource_tbl=> x_rev_sub_resource_tbl --L1
13743                 );
13744 
13745         IF l_bo_return_status = 'S'
13746         THEN
13747                 l_bo_return_status     := l_return_status;
13748         END IF;
13749 
13750         x_return_status                := l_bo_return_status;
13751         x_Mesg_Token_Tbl               := l_Mesg_Token_Tbl;
13752         --x_eco_revision_tbl             := l_eco_revision_tbl;
13753         --x_revised_item_tbl             := l_revised_item_tbl;
13754         --x_rev_component_tbl            := l_rev_component_tbl;
13755         --x_ref_designator_tbl           := l_ref_designator_tbl;
13756         --x_sub_component_tbl            := l_sub_component_tbl;
13757         --x_rev_operation_tbl            := l_rev_operation_tbl;     --L1
13758         --x_rev_op_resource_tbl          := l_rev_op_resource_tbl;   --L1
13759         --x_rev_sub_resource_tbl         := l_rev_sub_resource_tbl;  --L1
13760         --x_change_line_tbl              := l_change_line_tbl ;      -- Eng Change
13761 
13762         l_return_status := 'U';
13763 
13764         END; -- END block
13765      END IF; -- End of processing records for which the return status is null
13766      END LOOP; -- END Revisions processing loop
13767 
13768     IF l_return_status in ('Q', 'U')
13769     THEN
13770         x_return_status := l_return_status;
13771         RETURN;
13772     END IF;
13773 
13774      --  Load OUT parameters
13775 
13776      x_return_status            := l_bo_return_status;
13777      --x_eco_revision_tbl         := l_eco_revision_tbl;
13778      --x_revised_item_tbl         := l_revised_item_tbl;
13779      --x_rev_component_tbl        := l_rev_component_tbl;
13780      --x_ref_designator_tbl       := l_ref_designator_tbl;
13781      --x_sub_component_tbl        := l_sub_component_tbl;
13782      --x_rev_operation_tbl        := l_rev_operation_tbl;     --L1
13783      --x_rev_op_resource_tbl      := l_rev_op_resource_tbl;   --L1
13784      --x_rev_sub_resource_tbl     := l_rev_sub_resource_tbl;  --L1
13785      --x_change_line_tbl          := l_change_line_tbl ;      -- Eng Change
13786 
13787      x_Mesg_Token_Tbl           := l_Mesg_Token_Tbl;
13788 
13789 END Eco_Rev;
13790 
13791 PROCEDURE Create_Change_Lifecycle (
13792 	p_change_id	 IN	NUMBER,
13793 	p_change_type_id IN	NUMBER,
13794 	p_user_id        IN	NUMBER,
13795 	p_login_id       IN	NUMBER,
13796 	x_Mesg_Token_Tbl IN OUT NOCOPY Error_Handler.Mesg_Token_Tbl_Type,
13797 	x_return_status	 IN OUT NOCOPY VARCHAR2 )
13798 IS
13799 
13800   l_lifecycle_status_id NUMBER;
13801   l_return_status       VARCHAR2(1);
13802   l_err_text            VARCHAR2(2000) ;
13803   l_Mesg_Token_Tbl      Error_Handler.Mesg_Token_Tbl_Type ;
13804 
13805   /* Cursor to Fetch all the life cycle Statuses for corresponding Type. */
13806   CURSOR c_lifecycle_statuses IS
13807   SELECT *
13808   FROM eng_lifecycle_statuses
13809   WHERE entity_name = 'ENG_CHANGE_TYPE'
13810   AND entity_id1 = p_change_type_id;
13811 
13812 BEGIN
13813 	 FOR cls IN c_lifecycle_statuses
13814 	 LOOP
13815                   -- fetch the CHANGE_LIFECYCLE_STATUS_ID from sequence
13816 		SELECT ENG_LIFECYCLE_STATUSES_S.NEXTVAL
13817 		INTO l_lifecycle_status_id
13818 		FROM dual;
13819 
13820 		  -- Insert the Statuses data
13821 		INSERT INTO ENG_LIFECYCLE_STATUSES
13822 		(   CHANGE_LIFECYCLE_STATUS_ID
13823 		  , ENTITY_NAME
13824 		  , ENTITY_ID1
13825 		  , ENTITY_ID2
13826 		  , ENTITY_ID3
13827 		  , ENTITY_ID4
13828 		  , ENTITY_ID5
13829 		  , SEQUENCE_NUMBER
13830 		  , STATUS_CODE
13831 		  , START_DATE
13832 		  , COMPLETION_DATE
13833 		  , CHANGE_WF_ROUTE_ID
13834 		  , AUTO_PROMOTE_STATUS
13835 		  , AUTO_DEMOTE_STATUS
13836 		  , WORKFLOW_STATUS
13837 		  , CHANGE_EDITABLE_FLAG
13838 		  , CREATION_DATE
13839 		  , CREATED_BY
13840 		  , LAST_UPDATE_DATE
13841 		  , LAST_UPDATED_BY
13842 		  , LAST_UPDATE_LOGIN
13843 		  , ITERATION_NUMBER
13844 		  , ACTIVE_FLAG
13845 		  , CHANGE_WF_ROUTE_TEMPLATE_ID
13846 		)
13847 		VALUES
13848 		(   l_lifecycle_status_id
13849 		  , 'ENG_CHANGE'
13850 		  , p_change_id
13851 		  , NULL -- cls.ENTITY_ID2
13852 		  , NULL -- cls.ENTITY_ID3
13853 		  , NULL -- cls.ENTITY_ID4
13854 		  , NULL -- cls.ENTITY_ID5
13855 		  , cls.SEQUENCE_NUMBER
13856 		  , cls.STATUS_CODE
13857 		  , NULL -- cls.START_DATE
13858 		  , NULL -- cls.COMPLETION_DATE
13859 		  , NULL -- cls.CHANGE_WF_ROUTE_ID
13860 		  , cls.AUTO_PROMOTE_STATUS
13861 		  , cls.AUTO_DEMOTE_STATUS
13862 		  , NULL -- cls.WORKFLOW_STATUS
13863 		  , cls.CHANGE_EDITABLE_FLAG
13864 		  , SYSDATE
13865 		  , p_user_id
13866 		  , SYSDATE
13867 		  , p_user_id
13868 		  , p_login_id
13869 		  , 0 -- cls.ITERATION_NUMBER
13870 		  , 'Y' -- cls.ACTIVE_FLAG
13871 		  , cls.CHANGE_WF_ROUTE_ID -- cls.CHANGE_WF_ROUTE_TEMPLATE_ID
13872 		);
13873 
13874 		-- Inserting the status properties
13875 		INSERT INTO  eng_status_properties(
13876 		   CHANGE_LIFECYCLE_STATUS_ID
13877 		 , STATUS_CODE
13878 		 , PROMOTION_STATUS_FLAG
13879 		 , CREATION_DATE
13880 		 , CREATED_BY
13881 		 , LAST_UPDATE_DATE
13882 		 , LAST_UPDATED_BY
13883 		 , LAST_UPDATE_LOGIN
13884 		) SELECT l_lifecycle_status_id, status_code, PROMOTION_STATUS_FLAG,
13885 		         sysdate, p_user_id, sysdate, p_user_id, p_login_id
13886 		  FROM eng_status_properties
13887 		  WHERE CHANGE_LIFECYCLE_STATUS_ID = cls.CHANGE_LIFECYCLE_STATUS_ID;
13888 	 END LOOP; -- End loop c_lifecycle_statuses
13889 EXCEPTION
13890 WHEN OTHERS THEN
13891 
13892 	IF BOM_Globals.Get_Debug = 'Y'
13893 	THEN
13894 		Error_Handler.Write_Debug('Unexpected Error occured in Insert in Create_Change_Lifecycle . . .' || SQLERRM);
13895 	END IF;
13896 
13897 	IF FND_MSG_PUB.Check_Msg_Level(FND_MSG_PUB.G_MSG_LVL_UNEXP_ERROR)
13898 	THEN
13899 		l_err_text := G_PKG_NAME||' : Utility (Create_Change_Lifecycle Lifecycle Insert) '||SUBSTR(SQLERRM, 1, 200);
13900 
13901 		Error_Handler.Add_Error_Token
13902 		(  p_message_name   => NULL
13903 		 , p_message_text   => l_err_text
13904 		 , p_mesg_token_tbl => l_mesg_token_tbl
13905 		 , x_mesg_token_tbl => l_mesg_token_tbl
13906 		);
13907 	END IF ;
13908 
13909 	-- Return the status and message table.
13910 	x_return_status := Error_Handler.G_STATUS_UNEXPECTED;
13911 	x_mesg_token_tbl := l_mesg_token_tbl ;
13912 
13913 END Create_Change_Lifecycle;
13914 
13915 PROCEDURE Create_Tasks
13916 (   p_change_id                IN  NUMBER
13917 ,   p_change_type_id           IN  NUMBER
13918 ,   p_organization_id          IN  NUMBER
13919 ,   p_transaction_type         IN VARCHAR2
13920 ,   p_approval_status_type	IN NUMBER	-- Bug 3436684
13921 ,   x_Mesg_Token_Tbl           OUT NOCOPY Error_Handler.Mesg_Token_Tbl_Type
13922 ,   x_return_status            OUT NOCOPY VARCHAR2
13923 )
13924 IS
13925 
13926 
13927 CURSOR c_change_tasks (v_change_type_id    IN NUMBER,
13928                        v_organization_id   IN NUMBER)
13929 IS
13930   SELECT tsk.sequence_number,
13931          tsk.required_flag,
13932 	 tsk.default_assignee_id,
13933          tsk.default_assignee_type,
13934 	 tsk.task_name,
13935 	 tsk.description,
13936          typtsk.complete_before_status_code,
13937 	 typtsk.start_after_status_code,
13938          typtsk.change_type_id
13939    FROM eng_change_tasks_vl tsk,
13940         eng_change_type_org_tasks typtsk
13941    WHERE tsk.organization_id = typtsk.organization_id
13942    AND typtsk.organization_id = v_organization_id
13943    AND tsk.change_template_id = typtsk.change_template_or_task_id
13944    AND typtsk.template_or_task_flag ='E'
13945    AND typtsk.change_type_id = v_change_type_id;
13946 
13947 /*CURSOR c_grp_assignee ( v_default_assignee_id IN NUMBER)
13948 IS
13949   SELECT member_person_id
13950   FROM ego_group_members_v
13951   WHERE group_id = v_default_assignee_id;
13952 */-- Commented for Bug 3311072
13953 CURSOR c_role_assignee (v_assignee_id IN NUMBER,
13954 		        v_assignee_type IN VARCHAR)
13955 IS
13956   SELECT fg.grantee_orig_system_id
13957   FROM fnd_grants fg,
13958        fnd_menus_tl tl,
13959        fnd_menus m,
13960        (SELECT distinct f.object_id,
13961                e.menu_id
13962         FROM fnd_form_functions f,
13963 	     fnd_menu_entries e
13964 	WHERE e.function_id = f.function_id) r,
13965 	fnd_objects o
13966   WHERE fg.grantee_orig_system='HZ_PARTY'
13967   AND fg.grantee_type = 'USER'
13968   AND fg.menu_id = tl.menu_id
13969   AND fg.object_id = o.object_id
13970   AND tl.menu_id = r.menu_id
13971   AND m.menu_id = tl.menu_id
13972   AND tl.menu_id = v_assignee_id
13973   AND tl.LANGUAGE= USERENV('LANG')
13974   AND r.object_id = o.object_id
13975   AND o.obj_name = v_assignee_type;
13976 
13977     v_assignee_id               NUMBER;
13978     v_assignee_type		VARCHAR2(80);
13979     l_change_line_rec           Eng_Eco_Pub.Change_Line_Rec_Type;
13980     l_change_line_unexp_rec     Eng_Eco_Pub.Change_Line_Unexposed_Rec_Type;
13981     l_dest_change_id            NUMBER;
13982     l_msg_token_tbl        Error_Handler.Mesg_Token_Tbl_Type;
13983     l_Return_Status         VARCHAR2(1) := FND_API.G_RET_STS_SUCCESS;
13984     l_sql_stmt			VARCHAR2(1000);
13985 
13986 BEGIN
13987 
13988 
13989 
13990 
13991     IF p_transaction_type = 'CREATE'
13992     THEN
13993 
13994       BOM_globals.set_debug('N');
13995 
13996 
13997 
13998       FOR change_line IN c_change_tasks(p_change_type_id, p_organization_id)
13999       LOOP
14000 
14001         SELECT eng_change_lines_s.nextval INTO l_change_line_unexp_rec.change_line_id FROM SYS.DUAL;
14002         l_change_line_unexp_rec.change_id := p_change_id;
14003         l_change_line_unexp_rec.change_type_id := -1;
14004         l_change_line_rec.sequence_number := change_line.sequence_number;
14005         l_change_line_rec.name := change_line.task_name;
14006         l_change_line_rec.description := change_line.description;
14007         l_change_line_rec.complete_before_status_code := change_line.complete_before_status_code;
14008         l_change_line_rec.start_after_status_code := change_line.start_after_status_code;
14009         l_change_line_rec.required_flag := change_line.required_flag;
14010 	l_change_line_unexp_rec.Approval_Status_Type := p_approval_status_type; -- Bug 3436684
14011 	l_change_line_unexp_rec.status_code := 1; -- Bug 3436684
14012 
14013 	--setting the Assignee_Id
14014 	IF change_line.default_assignee_type = 'PERSON' or change_line.default_assignee_type = 'GROUP'
14015 	THEN
14016 	  l_change_line_unexp_rec.assignee_id := change_line.default_assignee_id;
14017 
14018 	/*ELSIF change_line.default_assignee_type = 'GROUP'
14019 	THEN
14020 		--
14021 		-- Changes Added for bug 3311072
14022 
14023 		l_sql_stmt := ' SELECT member_person_id '
14024 			|| ' FROM ego_group_members_v '
14025 			|| ' WHERE group_id = :1 ';
14026 		BEGIN
14027 			EXECUTE IMMEDIATE l_sql_stmt INTO v_assignee_id USING change_line.default_assignee_id;
14028 			l_change_line_unexp_rec.assignee_id := v_assignee_id;
14029 		EXCEPTION
14030 		WHEN NO_DATA_FOUND THEN
14031 			l_change_line_unexp_rec.assignee_id := NULL;
14032 		WHEN OTHERS THEN
14033 			IF BOM_Globals.Get_Debug = 'Y'
14034 			THEN
14035 				Error_Handler.Write_Debug('Unexpected Error occured in Insert . . .' || SQLERRM);
14036 			END IF;
14037 		END;*/
14038 	   /*OPEN c_grp_assignee(change_line.default_assignee_id);
14039 	   FETCH c_grp_assignee INTO v_assignee_id;
14040 	   IF (c_grp_assignee%FOUND)
14041 	   THEN
14042 	     l_change_line_unexp_rec.assignee_id := v_assignee_id;
14043 	   END IF;
14044 	   CLOSE c_grp_assignee;*/-- Commented for bug 3311072
14045 	   -- End changes for bug 3311072
14046 
14047 	ELSE
14048 	   OPEN c_role_assignee(change_line.default_assignee_id, change_line.default_assignee_type);
14049 	   FETCH c_role_assignee INTO v_assignee_id;
14050 	   IF (c_role_assignee%FOUND)
14051 	   THEN
14052 	     l_change_line_unexp_rec.assignee_id := v_assignee_id;
14053 	   END IF;
14054 	   CLOSE c_role_assignee;
14055 
14056 	END IF;
14057 	Eng_Change_Line_Util.Insert_Row
14058         (  p_change_line_rec => l_change_line_rec
14059          , p_change_line_unexp_rec => l_change_line_unexp_rec
14060          , x_Mesg_Token_Tbl => l_msg_token_tbl
14061          , x_return_status => l_return_status
14062         );
14063      x_return_status :=l_return_status ;
14064       END LOOP;
14065     END IF;
14066 
14067 
14068 END Create_Tasks;
14069 
14070 
14071 PROCEDURE Create_Relation(
14072     p_change_id                IN  NUMBER
14073 ,   p_organization_id          IN  NUMBER
14074 ,   x_Mesg_Token_Tbl           OUT NOCOPY Error_Handler.Mesg_Token_Tbl_Type
14075 ,   x_return_status            OUT NOCOPY VARCHAR2
14076 )
14077 is
14078 -- Error Handlig Variables
14079     l_return_status       VARCHAR2(1);
14080     l_err_text            VARCHAR2(2000) ;
14081     l_Mesg_Token_Tbl      Error_Handler.Mesg_Token_Tbl_Type ;
14082     l_new_prop_relation   NUMBER;
14083   begin
14084 
14085  select ENG_CHANGE_OBJ_RELATIONSHIPS_S.nextval
14086   into l_new_prop_relation
14087   from dual;
14088 
14089   insert into eng_change_obj_relationships (
14090   CHANGE_RELATIONSHIP_ID,
14091   CHANGE_ID,
14092   RELATIONSHIP_CODE,
14093   OBJECT_TO_NAME,
14094   OBJECT_TO_ID1,
14095   OBJECT_TO_ID2,
14096   OBJECT_TO_ID3,
14097   OBJECT_TO_ID4,
14098   OBJECT_TO_ID5,
14099   CREATION_DATE,
14100   CREATED_BY,
14101   LAST_UPDATE_DATE,
14102   LAST_UPDATED_BY,
14103   LAST_UPDATE_LOGIN )
14104   values(
14105    l_new_prop_relation,
14106    ENGECOBO.GLOBAL_CHANGE_ID,
14107    'PROPAGATED_TO',
14108    'ENG_CHANGE',
14109    p_change_id,
14110    ENGECOBO.GLOBAL_ORG_ID,
14111    p_organization_id,
14112    null,
14113    null,
14114    sysdate,
14115    Eng_Globals.Get_User_Id,
14116    sysdate,
14117    Eng_Globals.Get_User_Id,
14118    Eng_Globals.Get_Login_id
14119   );
14120 
14121 
14122 EXCEPTION
14123 
14124     WHEN OTHERS THEN
14125        IF BOM_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
14126          ('Unexpected Error occured in Insert . . .' || SQLERRM);
14127        END IF;
14128 
14129 
14130 
14131         IF FND_MSG_PUB.Check_Msg_Level(FND_MSG_PUB.G_MSG_LVL_UNEXP_ERROR)
14132        THEN
14133           l_err_text := G_PKG_NAME || ' : Utility (Relationship  Insert) ' ||
14134                                         SUBSTR(SQLERRM, 1, 200);
14135 
14136           Error_Handler.Add_Error_Token
14137           (  p_message_name   => NULL
14138            , p_message_text   => l_err_text
14139            , p_mesg_token_tbl => l_mesg_token_tbl
14140            , x_mesg_token_tbl => l_mesg_token_tbl
14141           ) ;
14142        END IF ;
14143 
14144        -- Return the status and message table.
14145        x_return_status := FND_API.G_RET_STS_UNEXP_ERROR ;
14146        x_mesg_token_tbl := l_mesg_token_tbl ;
14147 
14148 end Create_Relation;
14149 
14150 
14151 
14152 
14153 
14154 
14155 
14156 
14157 
14158 
14159 
14160 
14161 
14162 PROCEDURE Eco_Header
14163 (   p_validation_level            IN  NUMBER
14164 ,   p_ECO_rec                     IN  ENG_Eco_PUB.Eco_Rec_Type
14165 ,   p_eco_revision_tbl            IN  ENG_Eco_PUB.Eco_Revision_Tbl_Type
14166 ,   p_change_line_tbl             IN  ENG_Eco_PUB.Change_Line_Tbl_Type    -- Eng Change
14167 ,   p_revised_item_tbl            IN  ENG_Eco_PUB.Revised_Item_Tbl_Type
14168 ,   p_rev_component_tbl           IN  BOM_BO_PUB.Rev_Component_Tbl_Type
14169 ,   p_ref_designator_tbl          IN  BOM_BO_PUB.Ref_Designator_Tbl_Type
14170 ,   p_sub_component_tbl           IN  BOM_BO_PUB.Sub_Component_Tbl_Type
14171 ,   p_rev_operation_tbl           IN  Bom_Rtg_Pub.Rev_Operation_Tbl_Type   --L1
14172 ,   p_rev_op_resource_tbl         IN  Bom_Rtg_Pub.Rev_Op_Resource_Tbl_Type --L1
14173 ,   p_rev_sub_resource_tbl        IN  Bom_Rtg_Pub.Rev_Sub_Resource_Tbl_Type--L1
14174 ,   x_ECO_rec                     IN OUT NOCOPY ENG_Eco_PUB.Eco_Rec_Type
14175 ,   x_eco_revision_tbl            IN OUT NOCOPY ENG_Eco_PUB.Eco_Revision_Tbl_Type
14176 ,   x_change_line_tbl             IN OUT NOCOPY ENG_Eco_PUB.Change_Line_Tbl_Type      -- Eng Change
14177 ,   x_revised_item_tbl            IN OUT NOCOPY ENG_Eco_PUB.Revised_Item_Tbl_Type
14178 ,   x_rev_component_tbl           IN OUT NOCOPY BOM_BO_PUB.Rev_Component_Tbl_Type
14179 ,   x_ref_designator_tbl          IN OUT NOCOPY BOM_BO_PUB.Ref_Designator_Tbl_Type
14180 ,   x_sub_component_tbl           IN OUT NOCOPY BOM_BO_PUB.Sub_Component_Tbl_Type
14181 ,   x_rev_operation_tbl           IN OUT NOCOPY Bom_Rtg_Pub.Rev_Operation_Tbl_Type    --L1--
14182 ,   x_rev_op_resource_tbl         IN OUT NOCOPY Bom_Rtg_Pub.Rev_Op_Resource_Tbl_Type  --L1--
14183 ,   x_rev_sub_resource_tbl        IN OUT NOCOPY Bom_Rtg_Pub.Rev_Sub_Resource_Tbl_Type --L1--
14184 ,   x_Mesg_Token_Tbl              OUT NOCOPY Error_Handler.Mesg_Token_Tbl_Type
14185 ,   x_return_status               OUT NOCOPY VARCHAR2
14186 ,   x_disable_revision            OUT NOCOPY NUMBER --Bug no:3034642
14187 )
14188 IS
14189 
14190 l_Mesg_Token_Tbl        Error_Handler.Mesg_Token_Tbl_Type;
14191 l_other_token_tbl       Error_Handler.Token_Tbl_Type;
14192 l_other_message         VARCHAR2(50);
14193 l_err_text              VARCHAR2(2000);
14194 l_valid                 BOOLEAN := TRUE;
14195 l_Return_Status         VARCHAR2(1) := FND_API.G_RET_STS_SUCCESS;
14196 l_bo_return_status      VARCHAR2(1) := 'S';
14197 l_ECO_Rec               Eng_Eco_Pub.ECO_Rec_Type;
14198 l_ECO_Unexp_Rec         Eng_Eco_Pub.ECO_Unexposed_Rec_Type;
14199 l_Old_ECO_Rec           Eng_Eco_Pub.ECO_Rec_Type := NULL;
14200 l_Old_ECO_Unexp_Rec     Eng_Eco_Pub.ECO_Unexposed_Rec_Type := NULL;
14201 l_eco_revision_tbl      ENG_Eco_PUB.Eco_Revision_Tbl_Type := p_eco_revision_tbl;
14202 l_revised_item_tbl      ENG_Eco_PUB.Revised_Item_Tbl_Type := p_revised_item_tbl;
14203 l_rev_component_tbl     BOM_BO_PUB.Rev_Component_Tbl_Type := p_rev_component_tbl;
14204 l_ref_designator_tbl    BOM_BO_PUB.Ref_Designator_Tbl_Type := p_ref_designator_tbl;
14205 l_sub_component_tbl     BOM_BO_PUB.Sub_Component_Tbl_Type := p_sub_component_tbl;
14206 
14207 l_rev_operation_tbl     Bom_Rtg_Pub.Rev_Operation_Tbl_Type
14208                                                 := p_rev_operation_tbl;  --L1
14209 l_rev_op_resource_tbl   Bom_Rtg_Pub.Rev_Op_Resource_Tbl_Type
14210                                                 :=p_rev_op_resource_tbl; --L1
14211 l_rev_sub_resource_tbl  Bom_Rtg_Pub.Rev_Sub_Resource_Tbl_Type
14212                                                 :=p_rev_sub_resource_tbl;--L1
14213 
14214 l_change_line_tbl       Eng_Eco_Pub.Change_Line_Tbl_Type := p_change_line_tbl; -- Eng Change
14215 l_status_check_required BOOLEAN := TRUE; -- Added for enhancement 541
14216     -- Bug 2916558 // kamohan
14217     -- Start Changes
14218 
14219     CURSOR check_co_type ( p_change_notice VARCHAR2, p_organization_id NUMBER) IS
14220      SELECT ecot.type_name CHANGE_ORDER_TYPE, eec.assignee_id
14221        FROM eng_engineering_changes eec, eng_change_order_types_vl ecot
14222       WHERE eec.change_notice =p_change_notice
14223            AND eec.organization_id = p_organization_id
14224 	   AND eec.change_order_type_id = ecot.change_order_type_id;
14225 
14226     chk_co_type check_co_type%ROWTYPE;
14227 
14228     l_organization_id NUMBER;
14229 
14230     -- Bug 2916558 // kamohan
14231     -- End Changes
14232 
14233 l_return_value          NUMBER;
14234 l_Token_Tbl             Error_Handler.Token_Tbl_Type;
14235 
14236 EXC_SEV_QUIT_RECORD     EXCEPTION;
14237 EXC_SEV_QUIT_BRANCH     EXCEPTION;
14238 EXC_SEV_SKIP_BRANCH     EXCEPTION;
14239 EXC_FAT_QUIT_OBJECT     EXCEPTION;
14240 EXC_UNEXP_SKIP_OBJECT   EXCEPTION;
14241 l_user_id               NUMBER;
14242 l_login_id              NUMBER;
14243 l_prog_appid            NUMBER;
14244 l_prog_id               NUMBER;
14245 l_request_id            NUMBER;
14246 l_profile_exist     BOOLEAN;
14247 l_package_name   varchar2(100) :='EGO_CHANGETYPE_EXPLOSION.explodeTemplates';
14248 l_change_subject_unexp_rec  Eng_Eco_Pub.Change_Subject_Unexp_Rec_Type;
14249 
14250 -- Changes for bug 3426896
14251 l_pls_msg_count			NUMBER;
14252 l_pls_msg_data			VARCHAR2(3000);
14253 l_plsql_block			VARCHAR2(1000);
14254 -- End changes for bug 3426896
14255 
14256 BEGIN
14257 
14258     -- Begin block that processes header. This block holds the exception handlers
14259     -- for header errors.
14260 
14261     BEGIN
14262 
14263         --  Load entity and record-specific details into system_information record
14264 	l_ECO_Unexp_rec.organization_id := ENG_GLOBALS.Get_Org_Id;
14265 	l_ECO_rec := p_ECO_rec;
14266         l_ECO_rec.transaction_type := UPPER(l_eco_rec.transaction_type);
14267 
14268         -- Process Flow Step 2: Check if record has not yet been processed
14269         --
14270 
14271         IF l_ECO_rec.return_status IS NOT NULL AND
14272            l_ECO_rec.return_status <> FND_API.G_MISS_CHAR
14273         THEN
14274                 x_return_status                := l_return_status;
14275                 x_ECO_rec                      := l_ECO_rec;
14276                 x_eco_revision_tbl             := l_eco_revision_tbl;
14277                 x_revised_item_tbl             := l_revised_item_tbl;
14278                 x_rev_component_tbl            := l_rev_component_tbl;
14279                 x_ref_designator_tbl           := l_ref_designator_tbl;
14280                 x_sub_component_tbl            := l_sub_component_tbl;
14281                 x_rev_operation_tbl            := l_rev_operation_tbl;     --L1
14282                 x_rev_op_resource_tbl          := l_rev_op_resource_tbl;   --L1
14283                 x_rev_sub_resource_tbl         := l_rev_sub_resource_tbl;  --L1
14284                 x_change_line_tbl              := l_change_line_tbl ;      -- Eng Change
14285 
14286                 RETURN;
14287         END IF;
14288 
14289         l_return_status := FND_API.G_RET_STS_SUCCESS;
14290         l_eco_rec.return_status := FND_API.G_RET_STS_SUCCESS;
14291 
14292         -- Check if transaction_type is valid
14293         --
14294 
14295         ENG_GLOBALS.Transaction_Type_Validity
14296         (   p_transaction_type  => l_ECO_rec.transaction_type
14297         ,   p_entity            => 'ECO_Header'
14298         ,   p_entity_id         => l_ECO_rec.ECO_Name
14299         ,   x_valid             => l_valid
14300         ,   x_Mesg_Token_Tbl    => l_Mesg_Token_Tbl
14301         );
14302 	IF NOT l_valid
14303         THEN
14304                 l_return_status := Error_Handler.G_STATUS_ERROR;
14305                 RAISE EXC_SEV_QUIT_RECORD;
14306         END IF;
14307 
14308 
14309         -- Process Flow step 3: Verify ECO's existence
14310         --
14311         ENG_Validate_Eco.Check_Existence
14312                 ( p_change_notice       => l_eco_rec.ECO_Name
14313                 , p_organization_id     => l_eco_unexp_rec.organization_id
14314                 , p_organization_code   => l_eco_rec.organization_code
14315                 , p_calling_entity      => 'ECO'
14316                 , p_transaction_type    => l_eco_rec.transaction_type
14317                 , x_eco_rec             => l_old_eco_rec
14318                 , x_eco_unexp_rec       => l_old_eco_unexp_rec
14319                 , x_Mesg_Token_Tbl      => l_Mesg_Token_Tbl
14320                 , x_return_status       => l_Return_Status
14321                 );
14322 	IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
14323 
14324         IF l_return_status = Error_Handler.G_STATUS_ERROR
14325         THEN
14326                 l_other_message := 'ENG_ECO_EXS_SEV_ERROR';
14327                 l_other_token_tbl(1).token_name := 'ECO_NAME';
14328                 l_other_token_tbl(1).token_value := l_ECO_rec.ECO_Name;
14329                 RAISE EXC_SEV_QUIT_BRANCH;
14330         ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
14331         THEN
14332                 l_other_message := 'ENG_ECO_EXS_UNEXP_SKIP';
14333                 l_other_token_tbl(1).token_name := 'ECO_NAME';
14334                 l_other_token_tbl(1).token_value := l_ECO_rec.ECO_Name;
14335                 RAISE EXC_UNEXP_SKIP_OBJECT;
14336         END IF;
14337 
14338         -- Process Flow step : Convert User unique index to unique index
14339         -- Added for bug 3591992
14340 
14341         ENG_Val_To_Id.ECO_Header_UUI_To_UI
14342         (  p_eco_rec        => l_ECO_rec
14343          , p_eco_unexp_rec  => l_eco_unexp_rec
14344          , x_eco_unexp_rec  => l_eco_unexp_rec
14345          , x_Mesg_Token_Tbl => l_Mesg_Token_Tbl
14346          , x_Return_Status  => l_return_status
14347         );
14348 	-- Process Flow step 4: Change Order Value-Id conversion
14349         --
14350 	 ENG_Val_To_Id.Change_Order_VID
14351 	 (p_ECO_rec               => l_ECO_rec
14352 	 ,p_old_eco_unexp_rec     => l_old_eco_unexp_rec
14353          ,P_eco_unexp_rec         => l_eco_unexp_rec
14354 	 ,x_Mesg_Token_Tbl        => l_Mesg_Token_Tbl
14355          ,x_return_status         => l_return_status
14356 	 );
14357 	IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
14358 
14359         IF l_return_status = Error_Handler.G_STATUS_ERROR
14360         THEN
14361             IF l_ECO_rec.transaction_type = 'CREATE'
14362             THEN
14363                 l_other_message := 'ENG_ECO_CHGVID_CSEV_SKIP';
14364                 l_other_token_tbl(1).token_name := 'ECO_NAME';
14365                 l_other_token_tbl(1).token_value := l_ECO_rec.ECO_Name;
14366                 RAISE EXC_SEV_SKIP_BRANCH;
14367             ELSE
14368                 RAISE EXC_SEV_QUIT_RECORD;
14369             END IF;
14370         ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
14371         THEN
14372                 l_other_message := 'ENG_ECO_CHGVID_UNEXP_SKIP';
14373                 l_other_token_tbl(1).token_name := 'ECO_NAME';
14374                 l_other_token_tbl(1).token_value := l_ECO_rec.ECO_Name;
14375                 RAISE EXC_UNEXP_SKIP_OBJECT;
14376         END IF;
14377 
14378         -- Process Flow step 5(a): Is ECO implemented/canceled, or in wkflw process
14379         -- AND
14380         -- Process Flow step 5(b): Does user have access to change order type
14381         --
14382 
14383 	-- Added for enhancement 5414834
14384 	IF(l_eco_unexp_rec.Status_Type = 5)
14385 	THEN
14386 	   l_status_check_required := FALSE;
14387 	END IF;
14388 
14389         ENG_Validate_ECO.Check_Access
14390         ( p_change_notice       => l_ECO_rec.ECO_Name
14391         , p_organization_id     => l_eco_unexp_rec.organization_id
14392         , p_change_type_code    => l_eco_rec.change_type_code
14393         , p_change_order_type_id=> l_eco_unexp_rec.change_order_type_id
14394         , p_Mesg_Token_Tbl      => l_Mesg_Token_Tbl
14395         , x_Mesg_Token_Tbl      => l_Mesg_Token_Tbl
14396         , x_Return_Status       => l_return_status
14397 	, p_status_check_required => l_status_check_required
14398         );
14399 
14400        -- Bug 2916558 // kamohan
14401 	-- Start Changes
14402 
14403 	-- Check if the CO record is updated
14404 	IF l_eco_rec.transaction_type = eng_launch_eco_oi_pk.g_update THEN
14405 
14406 		-- Find the Organization ID corresponding to the Organization Code
14407 		l_organization_id := eng_val_to_id.organization
14408 					( l_eco_rec.organization_code, l_err_text);
14409 
14410 		-- Get the system change_order_type along with the assignee id
14411 		OPEN check_co_type(l_eco_rec.eco_name, l_organization_id);
14412 		FETCH check_co_type INTO chk_co_type;
14413 		CLOSE check_co_type;
14414 
14415 		-- If it is PLM CO and when the user tries to change the change order type
14416 		-- raise an error and stop processing the record
14417 		IF ( NVL(chk_co_type.change_order_type, '***') <> l_eco_rec.change_type_code AND chk_co_type.assignee_id IS NOT NULL) THEN
14418 			l_return_status := error_handler.g_status_error;
14419 			error_handler.add_error_token (p_message_name        => 'ENG_CHG_ORD_TYP_CNUPD',
14420 				p_mesg_token_tbl      => l_mesg_token_tbl,
14421 				x_mesg_token_tbl      => l_mesg_token_tbl,
14422 				p_token_tbl           => l_token_tbl
14423 				);
14424 			RAISE exc_sev_quit_record;
14425 		END IF;
14426 	END IF;
14427 	-- Bug 2916558 // kamohan
14428 	-- End Changes
14429 
14430         IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
14431 
14432         IF l_return_status = Error_Handler.G_STATUS_ERROR
14433         THEN
14434                 l_other_message := 'ENG_ECO_ACCESS_FAT_FATAL';
14435                 l_other_token_tbl(1).token_name := 'ECO_NAME';
14436                 l_other_token_tbl(1).token_value := l_ECO_rec.ECO_Name;
14437                 l_return_status := 'F';
14438                 RAISE EXC_FAT_QUIT_OBJECT;
14439         ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
14440         THEN
14441                 l_other_message := 'ENG_ECO_ACCESS_UNEXP_SKIP';
14442                 l_other_token_tbl(1).token_name := 'ECO_NAME';
14443                 l_other_token_tbl(1).token_value := l_ECO_rec.ECO_Name;
14444                 RAISE EXC_UNEXP_SKIP_OBJECT;
14445         END IF;
14446 
14447         -- Process Flow step 6: Value-to-ID conversions
14448         --
14449 
14450         IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Value-Id conversions'); END IF;
14451 
14452         ENG_Val_To_Id.ECO_Header_VID
14453         (  x_Return_Status   => l_return_status
14454         ,  x_Mesg_Token_Tbl  => l_Mesg_Token_Tbl
14455         ,  p_ECO_Rec         => l_ECO_Rec
14456         ,  p_ECO_Unexp_Rec   => l_ECO_Unexp_Rec
14457         ,  x_ECO_Unexp_Rec   => l_ECO_Unexp_Rec
14458         );
14459 	IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
14460 
14461         IF l_return_status = Error_Handler.G_STATUS_ERROR
14462         THEN
14463             IF l_ECO_rec.transaction_type = 'CREATE'
14464             THEN
14465                 l_other_message := 'ENG_ECO_VID_CSEV_SKIP';
14466                 l_other_token_tbl(1).token_name := 'ECO_NAME';
14467                 l_other_token_tbl(1).token_value := l_ECO_rec.ECO_Name;
14468                 RAISE EXC_SEV_SKIP_BRANCH;
14469             ELSE
14470                 RAISE EXC_SEV_QUIT_RECORD;
14471             END IF;
14472         ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
14473         THEN
14474                 l_other_message := 'ENG_ECO_VID_UNEXP_SKIP';
14475                 l_other_token_tbl(1).token_name := 'ECO_NAME';
14476                 l_other_token_tbl(1).token_value := l_ECO_rec.ECO_Name;
14477                 RAISE EXC_UNEXP_SKIP_OBJECT;
14478         ELSIF l_return_status ='S' AND
14479               l_Mesg_Token_Tbl.COUNT <>0
14480         THEN
14481                 Eco_Error_Handler.Log_Error
14482                 (  p_ECO_rec                => l_ECO_rec
14483                 ,  p_eco_revision_tbl       => l_eco_revision_tbl
14484                 ,  p_change_line_tbl        => l_change_line_tbl -- Eng Change
14485                 ,  p_revised_item_tbl       => l_revised_item_tbl
14486                 ,  p_rev_component_tbl      => l_rev_component_tbl
14487                 ,  p_ref_designator_tbl     => l_ref_designator_tbl
14488                 ,  p_sub_component_tbl      => l_sub_component_tbl
14489                 ,  p_rev_operation_tbl      => l_rev_operation_tbl    --L1
14490                 ,  p_rev_op_resource_tbl    => l_rev_op_resource_tbl  --L1
14491                 ,  p_rev_sub_resource_tbl   => l_rev_sub_resource_tbl --L1
14492                 ,  p_mesg_token_tbl         => l_mesg_token_tbl
14493                 ,  p_error_status           => 'W'
14494                 ,  p_error_level            => 1
14495                 ,  x_ECO_rec                => l_ECO_rec
14496                 ,  x_eco_revision_tbl       => l_eco_revision_tbl
14497                 ,  x_change_line_tbl        => l_change_line_tbl -- Eng Change
14498                 ,  x_revised_item_tbl       => l_revised_item_tbl
14499                 ,  x_rev_component_tbl      => l_rev_component_tbl
14500                 ,  x_ref_designator_tbl     => l_ref_designator_tbl
14501                 ,  x_sub_component_tbl      => l_sub_component_tbl
14502                 ,  x_rev_operation_tbl      => l_rev_operation_tbl    --L1
14503                 ,  x_rev_op_resource_tbl    => l_rev_op_resource_tbl  --L1
14504                 ,  x_rev_sub_resource_tbl   => l_rev_sub_resource_tbl --L1
14505                 );
14506         END IF;
14507 
14508         -- Process Flow step 7: Attribute Validation for Create and Update
14509         --
14510 
14511         IF l_ECO_rec.transaction_type IN
14512                 (ENG_GLOBALS.G_OPR_UPDATE, ENG_GLOBALS.G_OPR_CREATE)
14513         THEN
14514                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Attribute validation'); END IF;
14515 
14516                 ENG_Validate_ECO.Check_Attributes
14517                 (   x_return_status            => l_return_status
14518                 ,   x_err_text                 => l_err_text
14519                 ,   x_Mesg_Token_Tbl           => l_Mesg_Token_Tbl
14520                 ,   p_ECO_rec                  => l_ECO_rec
14521                 ,   p_Unexp_ECO_rec            => l_ECO_Unexp_Rec
14522                 ,   p_old_ECO_rec              => l_Old_ECO_Rec
14523                 ,   p_old_Unexp_ECO_rec        => l_Old_ECO_Unexp_Rec
14524 		,   p_change_line_tbl          => l_change_line_tbl --Bug no:2908248
14525 		,   p_revised_item_tbl         => l_revised_item_tbl --Bug 2908248
14526                 );
14527 		IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
14528 
14529                 IF l_return_status = Error_Handler.G_STATUS_ERROR
14530                 THEN
14531                         IF l_ECO_rec.transaction_type = 'CREATE'
14532                         THEN
14533                                 l_other_message := 'ENG_ECO_ATTVAL_CSEV_SKIP';
14534                                 l_other_token_tbl(1).token_name := 'ECO_NAME';
14535                                 l_other_token_tbl(1).token_value := l_ECO_rec.ECO_Name;
14536                                 RAISE EXC_SEV_SKIP_BRANCH;
14537                         ELSE
14538                                 RAISE EXC_SEV_QUIT_RECORD;
14539                         END IF;
14540                 ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
14541                 THEN
14542                         l_other_message := 'ENG_ECO_ATTVAL_UNEXP_SKIP';
14543                         l_other_token_tbl(1).token_name := 'ECO_NAME';
14544                         l_other_token_tbl(1).token_value := l_ECO_rec.ECO_Name;
14545 
14546                         RAISE EXC_UNEXP_SKIP_OBJECT;
14547                 ELSIF l_return_status ='S' AND
14548                         l_Mesg_Token_Tbl.COUNT <>0
14549                 THEN
14550                         Eco_Error_Handler.Log_Error
14551                         (  p_ECO_rec             => l_ECO_rec
14552                         ,  p_eco_revision_tbl    => l_eco_revision_tbl
14553                         ,  p_change_line_tbl     => l_change_line_tbl -- Eng Change
14554                         ,  p_revised_item_tbl    => l_revised_item_tbl
14555                         ,  p_rev_component_tbl   => l_rev_component_tbl
14556                         ,  p_ref_designator_tbl  => l_ref_designator_tbl
14557                         ,  p_sub_component_tbl   => l_sub_component_tbl
14558                         ,  p_rev_operation_tbl   => l_rev_operation_tbl    --L1
14559                         ,  p_rev_op_resource_tbl => l_rev_op_resource_tbl  --L1
14560                         ,  p_rev_sub_resource_tbl=> l_rev_sub_resource_tbl --L1
14561                         ,  p_mesg_token_tbl      => l_mesg_token_tbl
14562                         ,  p_error_status        => 'W'
14563                         ,  p_error_level         => 1
14564                         ,  x_ECO_rec             => l_ECO_rec
14565                         ,  x_eco_revision_tbl    => l_eco_revision_tbl
14566                         ,  x_change_line_tbl     => l_change_line_tbl -- Eng Change
14567                         ,  x_revised_item_tbl    => l_revised_item_tbl
14568                         ,  x_rev_component_tbl   => l_rev_component_tbl
14569                         ,  x_ref_designator_tbl  => l_ref_designator_tbl
14570                         ,  x_sub_component_tbl   => l_sub_component_tbl
14571                         ,  x_rev_operation_tbl   => l_rev_operation_tbl    --L1
14572                         ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl  --L1
14573                         ,  x_rev_sub_resource_tbl=> l_rev_sub_resource_tbl --L1
14574                         );
14575                 END IF;
14576         END IF;
14577 
14578         IF l_ECO_Rec.Transaction_Type IN
14579            (ENG_GLOBALS.G_OPR_UPDATE, ENG_GLOBALS.G_OPR_DELETE)
14580         THEN
14581 
14582          -- Process flow step 8 - Populate NULL columns for Update and
14583          -- Delete.
14584 
14585          IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Populating NULL Columns'); END IF;
14586          Eng_Default_ECO.Populate_NULL_Columns
14587                 (   p_ECO_rec           => l_ECO_Rec
14588                 ,   p_Unexp_ECO_rec     => l_ECO_Unexp_Rec
14589                 ,   p_Old_ECO_rec       => l_Old_ECO_Rec
14590                 ,   p_Old_Unexp_ECO_rec => l_Old_ECO_Unexp_Rec
14591                 ,   x_ECO_rec           => l_ECO_Rec
14592                 ,   x_Unexp_ECO_rec     => l_ECO_Unexp_Rec
14593                 );
14594 
14595      ELSIF l_ECO_Rec.Transaction_Type = ENG_GLOBALS.G_OPR_CREATE THEN
14596 
14597          -- Process Flow step 9: Default missing values for Operation CREATE
14598 
14599          IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Attribute Defaulting'); END IF;
14600          Eng_Default_ECO.Attribute_Defaulting
14601                 (   p_ECO_rec           => l_ECO_Rec
14602                 ,   p_Unexp_ECO_Rec     => l_ECO_Unexp_Rec
14603                 ,   x_ECO_rec           => l_ECO_Rec
14604                 ,   x_Unexp_ECO_Rec     => l_ECO_Unexp_Rec
14605                 ,   x_Mesg_Token_Tbl    => l_Mesg_Token_Tbl
14606                 ,   x_return_status     => l_Return_Status
14607                 );
14608 
14609          IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
14610 
14611         IF l_return_status = Error_Handler.G_STATUS_ERROR
14612         THEN
14613             IF l_ECO_rec.transaction_type = 'CREATE'
14614             THEN
14615                 l_other_message := 'ENG_ECO_ATTDEF_CSEV_SKIP';
14616                 l_other_token_tbl(1).token_name := 'ECO_NAME';
14617                 l_other_token_tbl(1).token_value := l_ECO_rec.ECO_Name;
14618                 RAISE EXC_SEV_SKIP_BRANCH;
14619             ELSE
14620                 RAISE EXC_SEV_QUIT_RECORD;
14621             END IF;
14622         ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
14623         THEN
14624                 l_other_message := 'ENG_ECO_ATTDEF_UNEXP_SKIP';
14625                 l_other_token_tbl(1).token_name := 'ECO_NAME';
14626                 l_other_token_tbl(1).token_value := l_ECO_rec.ECO_Name;
14627                 RAISE EXC_UNEXP_SKIP_OBJECT;
14628         ELSIF l_return_status ='S' AND
14629               l_Mesg_Token_Tbl.COUNT <>0
14630         THEN
14631                 Eco_Error_Handler.Log_Error
14632                 (  p_ECO_rec             => l_ECO_rec
14633                 ,  p_eco_revision_tbl    => l_eco_revision_tbl
14634                 ,  p_change_line_tbl     => l_change_line_tbl -- Eng Change
14635                 ,  p_revised_item_tbl    => l_revised_item_tbl
14636                 ,  p_rev_component_tbl   => l_rev_component_tbl
14637                 ,  p_ref_designator_tbl  => l_ref_designator_tbl
14638                 ,  p_sub_component_tbl   => l_sub_component_tbl
14639                 ,  p_rev_operation_tbl   => l_rev_operation_tbl    --L1
14640                 ,  p_rev_op_resource_tbl => l_rev_op_resource_tbl  --L1
14641                 ,  p_rev_sub_resource_tbl=> l_rev_sub_resource_tbl --L1
14642                 ,  p_mesg_token_tbl      => l_mesg_token_tbl
14643                 ,  p_error_status        => 'W'
14644                 ,  p_error_level         => 1
14645                 ,  x_ECO_rec             => l_ECO_rec
14646                 ,  x_eco_revision_tbl    => l_eco_revision_tbl
14647                 ,  x_change_line_tbl     => l_change_line_tbl -- Eng Change
14648                 ,  x_revised_item_tbl    => l_revised_item_tbl
14649                 ,  x_rev_component_tbl   => l_rev_component_tbl
14650                 ,  x_ref_designator_tbl  => l_ref_designator_tbl
14651                 ,  x_sub_component_tbl   => l_sub_component_tbl
14652                 ,  x_rev_operation_tbl   => l_rev_operation_tbl    --L1
14653                 ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl  --L1
14654                 ,  x_rev_sub_resource_tbl=> l_rev_sub_resource_tbl --L1
14655                 );
14656         END IF;
14657      END IF;
14658 
14659      -- Process Flow step 10 - Check Conditionally Required Fields
14660      IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Check conditionally required attributes'); END IF;
14661      ENG_Validate_ECO.Conditionally_Required
14662                 (   x_return_status     => l_return_status
14663                 ,   x_Mesg_Token_Tbl    => l_Mesg_Token_Tbl
14664                 ,   p_ECO_rec           => l_ECO_rec
14665                 ,   p_Unexp_ECO_rec     => l_ECO_Unexp_Rec
14666                 ,   p_old_ECO_rec       => l_old_ECO_rec
14667                 ,   p_old_Unexp_ECO_rec => l_old_ECO_unexp_rec
14668                 );
14669      IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
14670 
14671      IF l_return_status = Error_Handler.G_STATUS_ERROR
14672      THEN
14673         IF l_ECO_rec.transaction_type = 'CREATE'
14674         THEN
14675                 l_other_message := 'ENG_ECO_CONREQ_CSEV_SKIP';
14676                 l_other_token_tbl(1).token_name := 'ECO_NAME';
14677                 l_other_token_tbl(1).token_value := l_ECO_rec.ECO_Name;
14678                 RAISE EXC_SEV_SKIP_BRANCH;
14679         ELSE
14680                 RAISE EXC_SEV_QUIT_RECORD;
14681         END IF;
14682      ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
14683      THEN
14684         l_other_message := 'ENG_ECO_CONREQ_UNEXP_SKIP';
14685         l_other_token_tbl(1).token_name := 'ECO_NAME';
14686         l_other_token_tbl(1).token_value := l_ECO_rec.ECO_Name;
14687         RAISE EXC_UNEXP_SKIP_OBJECT;
14688      ELSIF l_return_status ='S' AND
14689            l_Mesg_Token_Tbl.COUNT <>0
14690      THEN
14691         Eco_Error_Handler.Log_Error
14692                 (  p_ECO_rec             => l_ECO_rec
14693                 ,  p_eco_revision_tbl    => l_eco_revision_tbl
14694                 ,  p_change_line_tbl     => l_change_line_tbl -- Eng Change
14695                 ,  p_revised_item_tbl    => l_revised_item_tbl
14696                 ,  p_rev_component_tbl   => l_rev_component_tbl
14697                 ,  p_ref_designator_tbl  => l_ref_designator_tbl
14698                 ,  p_sub_component_tbl   => l_sub_component_tbl
14699                 ,  p_rev_operation_tbl   => l_rev_operation_tbl    --L1
14700                 ,  p_rev_op_resource_tbl => l_rev_op_resource_tbl  --L1
14701                 ,  p_rev_sub_resource_tbl=> l_rev_sub_resource_tbl --L1
14702                 ,  p_mesg_token_tbl      => l_mesg_token_tbl
14703                 ,  p_error_status        => 'W'
14704                 ,  p_error_level         => 1
14705                 ,  x_ECO_rec             => l_ECO_rec
14706                 ,  x_eco_revision_tbl    => l_eco_revision_tbl
14707                 ,  x_change_line_tbl     => l_change_line_tbl -- Eng Change
14708                 ,  x_revised_item_tbl    => l_revised_item_tbl
14709                 ,  x_rev_component_tbl   => l_rev_component_tbl
14710                 ,  x_ref_designator_tbl  => l_ref_designator_tbl
14711                 ,  x_sub_component_tbl   => l_sub_component_tbl
14712                 ,  x_rev_operation_tbl   => l_rev_operation_tbl    --L1
14713                 ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl  --L1
14714                 ,  x_rev_sub_resource_tbl=> l_rev_sub_resource_tbl --L1
14715                 );
14716      END IF;
14717 
14718      -- Process Flow step 11 - Entity Level Defaulting
14719      IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Entity Defaulting'); END IF;
14720      ENG_Default_ECO.Entity_Defaulting
14721                 (   p_ECO_rec            => l_ECO_rec
14722                 ,   p_Unexp_ECO_rec      => l_ECO_unexp_rec
14723                 ,   p_Old_ECO_rec        => l_old_ECO_rec
14724                 ,   p_Old_Unexp_ECO_rec  => l_old_ECO_unexp_rec
14725                 ,   x_ECO_rec            => l_ECO_rec
14726                 ,   x_Unexp_ECO_rec      => l_ECO_unexp_rec
14727                 ,   x_return_status      => l_return_status
14728                 ,   x_Mesg_Token_Tbl     => l_Mesg_Token_Tbl
14729                 );
14730      IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
14731 
14732      IF l_return_status = Error_Handler.G_STATUS_ERROR
14733      THEN
14734         IF l_ECO_rec.transaction_type = 'CREATE'
14735         THEN
14736                 l_other_message := 'ENG_ECO_ENTDEF_CSEV_SKIP';
14737                 l_other_token_tbl(1).token_name := 'ECO_NAME';
14738                 l_other_token_tbl(1).token_value := l_ECO_rec.ECO_Name;
14739                 RAISE EXC_SEV_SKIP_BRANCH;
14740         ELSE
14741                 RAISE EXC_SEV_QUIT_RECORD;
14742         END IF;
14743      ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
14744      THEN
14745         l_other_message := 'ENG_ECO_ENTDEF_UNEXP_SKIP';
14746         l_other_token_tbl(1).token_name := 'ECO_NAME';
14747         l_other_token_tbl(1).token_value := l_ECO_rec.ECO_Name;
14748         RAISE EXC_UNEXP_SKIP_OBJECT;
14749      ELSIF l_return_status ='S' AND
14750            l_Mesg_Token_Tbl.COUNT <>0
14751      THEN
14752         Eco_Error_Handler.Log_Error
14753                 (  p_ECO_rec             => l_ECO_rec
14754                 ,  p_eco_revision_tbl    => l_eco_revision_tbl
14755                 ,  p_change_line_tbl     => l_change_line_tbl -- Eng Change
14756                 ,  p_revised_item_tbl    => l_revised_item_tbl
14757                 ,  p_rev_component_tbl   => l_rev_component_tbl
14758                 ,  p_ref_designator_tbl  => l_ref_designator_tbl
14759                 ,  p_sub_component_tbl   => l_sub_component_tbl
14760                 ,  p_rev_operation_tbl   => l_rev_operation_tbl    --L1
14761                 ,  p_rev_op_resource_tbl => l_rev_op_resource_tbl  --L1
14762                 ,  p_rev_sub_resource_tbl=> l_rev_sub_resource_tbl --L1
14763                 ,  p_mesg_token_tbl      => l_mesg_token_tbl
14764                 ,  p_error_status        => 'W'
14765                 ,  p_error_level         => 1
14766                 ,  x_ECO_rec             => l_ECO_rec
14767                 ,  x_eco_revision_tbl    => l_eco_revision_tbl
14768                 ,  x_change_line_tbl     => l_change_line_tbl -- Eng Change
14769                 ,  x_revised_item_tbl    => l_revised_item_tbl
14770                 ,  x_rev_component_tbl   => l_rev_component_tbl
14771                 ,  x_ref_designator_tbl  => l_ref_designator_tbl
14772                 ,  x_sub_component_tbl   => l_sub_component_tbl
14773                 ,  x_rev_operation_tbl   => l_rev_operation_tbl    --L1
14774                 ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl  --L1
14775                 ,  x_rev_sub_resource_tbl=> l_rev_sub_resource_tbl --L1
14776                 );
14777      END IF;
14778 
14779      -- Process Flow step 12 - Entity Level Validation
14780 
14781      IF l_eco_rec.transaction_type = 'DELETE'
14782      THEN
14783        IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Calling Check_Delete...'); END IF;
14784        ENG_Validate_ECO.Check_Delete
14785                ( p_eco_rec             => l_eco_rec
14786                , p_Unexp_ECO_rec       => l_ECO_Unexp_Rec
14787                , x_return_status       => l_return_status
14788                , x_Mesg_Token_Tbl      => l_Mesg_Token_Tbl
14789                );
14790      END IF;
14791 
14792 
14793      IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Entity validation'); END IF;
14794      Eng_Validate_ECO.Check_Entity
14795                 (  x_return_status        => l_Return_Status
14796                 ,  x_err_text             => l_err_text
14797                 ,  x_Mesg_Token_Tbl       => l_Mesg_Token_Tbl
14798                 ,  p_ECO_rec              => l_ECO_Rec
14799                 ,  p_Unexp_ECO_Rec        => l_ECO_Unexp_Rec
14800                 ,  p_old_ECO_rec          => l_old_ECO_rec
14801                 ,  p_old_unexp_ECO_rec    => l_old_ECO_unexp_rec
14802                 );
14803 
14804      IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
14805 
14806      IF l_return_status = Error_Handler.G_STATUS_ERROR
14807      THEN
14808         IF l_ECO_rec.transaction_type = 'CREATE'
14809         THEN
14810                 l_other_message := 'ENG_ECO_ENTVAL_CSEV_SKIP';
14811                 l_other_token_tbl(1).token_name := 'ECO_NAME';
14812                 l_other_token_tbl(1).token_value := l_ECO_rec.ECO_Name;
14813                 RAISE EXC_SEV_SKIP_BRANCH;
14814         ELSE
14815                 RAISE EXC_SEV_QUIT_RECORD;
14816         END IF;
14817      ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
14818      THEN
14819                 l_other_message := 'ENG_ECO_ENTVAL_UNEXP_SKIP';
14820                 l_other_token_tbl(1).token_name := 'ECO_NAME';
14821                 l_other_token_tbl(1).token_value := l_ECO_rec.ECO_Name;
14822         RAISE EXC_UNEXP_SKIP_OBJECT;
14823      ELSIF l_return_status ='S' AND
14824            l_Mesg_Token_Tbl.COUNT <>0
14825      THEN
14826         Eco_Error_Handler.Log_Error
14827                 (  p_ECO_rec             => l_ECO_rec
14828                 ,  p_eco_revision_tbl    => l_eco_revision_tbl
14829                 ,  p_change_line_tbl     => l_change_line_tbl -- Eng Change
14830                 ,  p_revised_item_tbl    => l_revised_item_tbl
14831                 ,  p_rev_component_tbl   => l_rev_component_tbl
14832                 ,  p_ref_designator_tbl  => l_ref_designator_tbl
14833                 ,  p_sub_component_tbl   => l_sub_component_tbl
14834                 ,  p_rev_operation_tbl   => l_rev_operation_tbl    --L1
14835                 ,  p_rev_op_resource_tbl => l_rev_op_resource_tbl  --L1
14836                 ,  p_rev_sub_resource_tbl=> l_rev_sub_resource_tbl --L1
14837                 ,  p_mesg_token_tbl      => l_mesg_token_tbl
14838                 ,  p_error_status        => 'W'
14839                 ,  p_error_level         => 1
14840                 ,  x_ECO_rec             => l_ECO_rec
14841                 ,  x_eco_revision_tbl    => l_eco_revision_tbl
14842                 ,  x_change_line_tbl     => l_change_line_tbl -- Eng Change
14843                 ,  x_revised_item_tbl    => l_revised_item_tbl
14844                 ,  x_rev_component_tbl   => l_rev_component_tbl
14845                 ,  x_ref_designator_tbl  => l_ref_designator_tbl
14846                 ,  x_sub_component_tbl   => l_sub_component_tbl
14847                 ,  x_rev_operation_tbl   => l_rev_operation_tbl    --L1
14848                 ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl  --L1
14849                 ,  x_rev_sub_resource_tbl=> l_rev_sub_resource_tbl --L1
14850                 );
14851      END IF;
14852 
14853      -- Process Flow step 13 : Database Writes
14854      SAVEPOINT EngEcoPvt_Eco_Header; -- bug 3572721
14855      IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Writing to the database'); END IF;
14856      ENG_ECO_Util.Perform_Writes
14857                 (   p_ECO_rec          => l_ECO_rec
14858                 ,   p_Unexp_ECO_rec    => l_ECO_unexp_rec
14859                 ,   p_old_ECO_rec      => l_old_ECO_rec
14860                 ,   x_Mesg_Token_Tbl   => l_Mesg_Token_Tbl
14861                 ,   x_return_status    => l_return_status
14862                 );
14863 
14864      IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('return_status: ' || l_return_status); END IF;
14865 
14866      IF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
14867      THEN
14868         l_other_message := 'ENG_ECO_WRITES_UNEXP_SKIP';
14869         l_other_token_tbl(1).token_name := 'ECO_NAME';
14870         l_other_token_tbl(1).token_value := l_ECO_rec.ECO_Name;
14871         RAISE EXC_UNEXP_SKIP_OBJECT;
14872      ELSIF l_return_status ='S' AND
14873            l_Mesg_Token_Tbl.COUNT <>0
14874      THEN
14875         Eco_Error_Handler.Log_Error
14876                 (  p_ECO_rec             => l_ECO_rec
14877                 ,  p_eco_revision_tbl    => l_eco_revision_tbl
14878                 ,  p_change_line_tbl     => l_change_line_tbl -- Eng Change
14879                 ,  p_revised_item_tbl    => l_revised_item_tbl
14880                 ,  p_rev_component_tbl   => l_rev_component_tbl
14881                 ,  p_ref_designator_tbl  => l_ref_designator_tbl
14882                 ,  p_sub_component_tbl   => l_sub_component_tbl
14883                 ,  p_rev_operation_tbl   => l_rev_operation_tbl    --L1
14884                 ,  p_rev_op_resource_tbl => l_rev_op_resource_tbl  --L1
14885                 ,  p_rev_sub_resource_tbl=> l_rev_sub_resource_tbl --L1
14886                 ,  p_mesg_token_tbl      => l_mesg_token_tbl
14887                 ,  p_error_status        => 'W'
14888                 ,  p_error_level         => 1
14889                 ,  x_ECO_rec             => l_ECO_rec
14890                 ,  x_eco_revision_tbl    => l_eco_revision_tbl
14891                 ,  x_change_line_tbl     => l_change_line_tbl -- Eng Change
14892                 ,  x_revised_item_tbl    => l_revised_item_tbl
14893                 ,  x_rev_component_tbl   => l_rev_component_tbl
14894                 ,  x_ref_designator_tbl  => l_ref_designator_tbl
14895                 ,  x_sub_component_tbl   => l_sub_component_tbl
14896                 ,  x_rev_operation_tbl   => l_rev_operation_tbl    --L1
14897                 ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl  --L1
14898                 ,  x_rev_sub_resource_tbl=> l_rev_sub_resource_tbl --L1
14899                 );
14900      END IF;
14901 
14902      --
14903      -- Subjects Handling
14904      --
14905      IF l_return_status = 'S' AND nvl(l_ECO_rec.plm_or_erp_change, 'PLM')='PLM'
14906      THEN
14907          ENG_Eco_Util.Change_Subjects
14908          ( p_eco_rec             =>       l_ECO_rec
14909          , p_ECO_Unexp_Rec       =>       l_ECO_unexp_rec
14910          , x_change_subject_unexp_rec  =>l_change_subject_unexp_rec
14911          , x_Mesg_Token_Tbl        => l_Mesg_Token_Tbl --bug 3572721
14912          , x_return_status  => l_return_status);
14913 
14914 	 -- Added subjects error Handling for bug 3572721
14915          IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Subjects created with status  ' || l_return_status);
14916          END IF;
14917          IF l_return_status = Error_Handler.G_STATUS_ERROR
14918          THEN
14919             Rollback TO EngEcoPvt_Eco_Header; -- bug 3572721
14920             RAISE EXC_SEV_SKIP_BRANCH;
14921          ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
14922          THEN
14923             l_other_message := 'ENG_ECO_WRITES_UNEXP_SKIP';
14924             l_other_token_tbl(1).token_name := 'ECO_NAME';
14925             l_other_token_tbl(1).token_value := l_ECO_rec.ECO_Name;
14926             RAISE EXC_UNEXP_SKIP_OBJECT;
14927          END IF;
14928      END IF;
14929 
14930    l_profile_exist := FND_PROFILE.DEFINED ( 'EGO_ITEM_RESTRICT_INV_ACTIONS' );
14931 
14932   if 	 l_return_status ='S'and  l_ECO_rec.plm_or_erp_change='PLM' and
14933          l_ECO_rec.transaction_type = Eng_Globals.G_OPR_CREATE  then
14934 
14935 --    if l_profile_exist = TRUE    then
14936          /*    The procedure first explodes and inserts the Statuses for
14937               the given Type, Routes for each Status, Steps for each Route,
14938           People for each Step, and Persons for each Group and Role. */
14939 
14940     l_user_id           := Eng_Globals.Get_User_Id;
14941     l_login_id          := Eng_Globals.Get_Login_Id;
14942     l_request_id        := ENG_GLOBALS.Get_request_id;
14943     l_prog_appid        := ENG_GLOBALS.Get_prog_appid;
14944     l_prog_id           := ENG_GLOBALS.Get_prog_id;
14945 
14946     /*
14947        --subjects handling
14948 
14949      ENG_Eco_Util.Change_Subjects
14950         ( p_eco_rec             =>       l_ECO_rec
14951         , p_ECO_Unexp_Rec       =>       l_ECO_unexp_rec
14952         , x_change_subject_unexp_rec  =>l_change_subject_unexp_rec
14953         , x_Mesg_Token_Tbl        => l_Mesg_Token_Tbl --bug 3572721
14954         , x_return_status  => l_return_status);
14955 
14956      -- Added subjects error Handling for bug 3572721
14957      IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Subjects created with status  ' || l_return_status);
14958      END IF;
14959      IF l_return_status = Error_Handler.G_STATUS_ERROR
14960      THEN
14961         Rollback TO EngEcoPvt_Eco_Header; -- bug 3572721
14962         RAISE EXC_SEV_SKIP_BRANCH;
14963      ELSIF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
14964      THEN
14965         l_other_message := 'ENG_ECO_WRITES_UNEXP_SKIP';
14966         l_other_token_tbl(1).token_name := 'ECO_NAME';
14967         l_other_token_tbl(1).token_value := l_ECO_rec.ECO_Name;
14968         RAISE EXC_UNEXP_SKIP_OBJECT;
14969      END IF;
14970      */
14971 
14972        --tasks craetion
14973        Create_Tasks
14974 		(   p_change_id           => l_eco_unexp_rec.change_id
14975 		,   p_change_type_id      => l_ECO_unexp_rec.change_order_type_id
14976 		,   p_organization_id     => l_eco_unexp_rec.organization_id
14977 		,   p_transaction_type    => l_ECO_rec.transaction_type
14978 		,   p_approval_status_type=> l_eco_unexp_rec.approval_status_type  -- Bug 3436684
14979 		,   x_Mesg_Token_Tbl      => l_mesg_token_tbl
14980 		,   x_return_status       => l_return_status
14981 		);
14982 
14983 	-- Changes for bug 3547737
14984       /*execute immediate 'begin ' || l_package_name || '(:1,:2, :3,:4,:5,:6,:7,:8); end;'
14985            using
14986 	    in l_ECO_unexp_rec.change_id ,
14987 	    in l_ECO_unexp_rec.change_order_type_id,
14988 	   in l_user_id ,
14989 	   in l_login_id,
14990 	   in l_prog_appid,
14991 	   in l_prog_id ,
14992 	   in l_request_id,
14993 	   in out l_err_text;*/ -- Commented.
14994 
14995 	-- Creating the lifecycle for the change object from its header level definition
14996 
14997 	Create_Change_Lifecycle(
14998 	   p_change_id		=> l_eco_unexp_rec.change_id
14999 	 , p_change_type_id	=> l_ECO_unexp_rec.change_order_type_id
15000 	 , p_user_id		=> l_user_id
15001 	 , p_login_id		=> l_login_id
15002 	 , x_Mesg_Token_Tbl	=> l_mesg_token_tbl
15003 	 , x_return_status	=> l_return_status);
15004 
15005 	IF (l_return_status = Error_Handler.G_STATUS_UNEXPECTED)
15006 	THEN
15007 		l_other_message := 'ENG_ECO_WRITES_UNEXP_SKIP';
15008 		l_other_token_tbl(1).token_name := 'ECO_NAME';
15009 		l_other_token_tbl(1).token_value := l_ECO_rec.ECO_Name;
15010 		RAISE EXC_UNEXP_SKIP_OBJECT;
15011 	END IF;
15012 	-- End Changes for bug 3547737
15013 
15014    IF l_ECO_Unexp_Rec.Status_Type <> 0 AND l_ECO_Unexp_Rec.Status_Code <> 0
15015       AND l_ECO_Unexp_Rec.Status_Code <> 7
15016       -- Bug# 12791511, creating ECO in released status, if uses Init_Lifecycle, if will reset the status_code to Open
15017       -- also since in API creation, we all need explode workflow manually, so Init_Lifecycle is not needed with release status.
15018    THEN
15019 	-- Changes for bug 3426896
15020 	-- Initializing the lifecycle
15021 	BEGIN
15022 		l_pls_msg_count := 0;
15023 		l_plsql_block := 'BEGIN '
15024 			|| 'ENG_CHANGE_LIFECYCLE_UTIL.Init_Lifecycle('
15025 			|| '  p_api_version		=> :1'
15026 			|| ', p_change_id		=> :2'
15027 			|| ', x_return_status	=> :3'
15028 			|| ', x_msg_count		=> :4'
15029 			|| ', x_msg_data		=> :5'
15030 			|| ', p_api_caller		=> :6'
15031 			|| '); END;';
15032 		EXECUTE IMMEDIATE l_plsql_block USING IN 1.0, IN l_eco_unexp_rec.change_id,
15033 		OUT l_return_status, OUT l_pls_msg_count, OUT l_pls_msg_data, IN 'CP';
15034 
15035 		IF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
15036 		THEN
15037 			l_other_message := 'ENG_ECO_WRITES_UNEXP_SKIP';
15038 			l_other_token_tbl(1).token_name := 'ECO_NAME';
15039 			l_other_token_tbl(1).token_value := l_ECO_rec.ECO_Name;
15040 			RAISE EXC_UNEXP_SKIP_OBJECT;
15041 		ELSIF l_return_status ='S' AND l_pls_msg_count <> 0
15042 		THEN
15043 
15044 			FOR I IN 1..l_pls_msg_count
15045             LOOP
15046 				Error_Handler.Add_Error_Token
15047                                 ( p_Message_Text => FND_MSG_PUB.get(I, 'F')
15048                                 , p_Mesg_Token_Tbl => l_Mesg_Token_Tbl
15049                                 , x_Mesg_Token_Tbl => l_Mesg_Token_Tbl
15050                                 );
15051 
15052             END LOOP;
15053 			Eco_Error_Handler.Log_Error
15054 				(  p_ECO_rec             => l_ECO_rec
15055 				,  p_eco_revision_tbl    => l_eco_revision_tbl
15056 				,  p_change_line_tbl     => l_change_line_tbl -- Eng Change
15057 				,  p_revised_item_tbl    => l_revised_item_tbl
15058 				,  p_rev_component_tbl   => l_rev_component_tbl
15059 				,  p_ref_designator_tbl  => l_ref_designator_tbl
15060 				,  p_sub_component_tbl   => l_sub_component_tbl
15061 				,  p_rev_operation_tbl   => l_rev_operation_tbl    --L1
15062 				,  p_rev_op_resource_tbl => l_rev_op_resource_tbl  --L1
15063 				,  p_rev_sub_resource_tbl=> l_rev_sub_resource_tbl --L1
15064 				,  p_mesg_token_tbl      => l_mesg_token_tbl
15065 				,  p_error_status        => 'W'
15066 				,  p_error_level         => 1
15067 				,  x_ECO_rec             => l_ECO_rec
15068 				,  x_eco_revision_tbl    => l_eco_revision_tbl
15069 				,  x_change_line_tbl     => l_change_line_tbl -- Eng Change
15070 				,  x_revised_item_tbl    => l_revised_item_tbl
15071 				,  x_rev_component_tbl   => l_rev_component_tbl
15072 				,  x_ref_designator_tbl  => l_ref_designator_tbl
15073 				,  x_sub_component_tbl   => l_sub_component_tbl
15074 				,  x_rev_operation_tbl   => l_rev_operation_tbl    --L1
15075 				,  x_rev_op_resource_tbl => l_rev_op_resource_tbl  --L1
15076 				,  x_rev_sub_resource_tbl=> l_rev_sub_resource_tbl --L1
15077 				);
15078 		END IF;
15079 	EXCEPTION
15080 	WHEN OTHERS THEN
15081 		IF Bom_Globals.Get_Debug = 'Y'
15082 		THEN
15083 			Error_Handler.Write_Debug('Lifecycle initialized with status ' || l_return_status);
15084 		END IF;
15085 		l_other_message := 'ENG_ECO_WRITES_UNEXP_SKIP';
15086 		l_other_token_tbl(1).token_name := 'ECO_NAME';
15087 		l_other_token_tbl(1).token_value := l_ECO_rec.ECO_Name;
15088 		RAISE EXC_UNEXP_SKIP_OBJECT;
15089 
15090 	END;
15091    END IF;
15092 	-- End changes for bug 3426896
15093 	IF (ENGECOBO.GLOBAL_CHANGE_ID <> -1)
15094 	THEN
15095       --relationship creation
15096         Create_Relation(
15097             p_change_id           =>  l_eco_unexp_rec.change_id
15098           , p_organization_id     => l_eco_unexp_rec.organization_id
15099           , x_Mesg_Token_Tbl      => l_mesg_token_tbl
15100           , x_return_status       => l_return_status);
15101         -- Fix for Bug 4517503
15102         -- Resetting the global value of ENGECOBO.GLOBAL_CHANGE_ID which is used to
15103         -- detaermine whether a relation is to be created or not.
15104         -- ECO BO is also being called by IOI in the same session when auto-enabling
15105         -- component items and since the value  was retained , ended up creating a
15106         -- relationship for NIR.
15107         -- So as to avaoid this it has to be reset once the relation has been created.
15108         ENGECOBO.GLOBAL_CHANGE_ID := -1;
15109         -- End of Fix for Bug 4517503
15110 
15111 	END IF;
15112 
15113 
15114   --  end if; --end of if
15115 
15116   end if;
15117 
15118 
15119 
15120      IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Tasks created with status  ' || l_return_status);
15121      END IF;
15122 
15123      IF l_return_status = Error_Handler.G_STATUS_UNEXPECTED
15124      THEN
15125         l_other_message := 'ENG_ECO_WRITES_UNEXP_SKIP';
15126         l_other_token_tbl(1).token_name := 'ECO_NAME';
15127         l_other_token_tbl(1).token_value := l_ECO_rec.ECO_Name;
15128         RAISE EXC_UNEXP_SKIP_OBJECT;
15129      ELSIF l_return_status ='S' AND
15130            l_Mesg_Token_Tbl.COUNT <>0
15131      THEN
15132      Eco_Error_Handler.Log_Error
15133                 (  p_ECO_rec             => l_ECO_rec
15134                 ,  p_eco_revision_tbl    => l_eco_revision_tbl
15135                 ,  p_change_line_tbl     => l_change_line_tbl -- Eng Change
15136                 ,  p_revised_item_tbl    => l_revised_item_tbl
15137                 ,  p_rev_component_tbl   => l_rev_component_tbl
15138                 ,  p_ref_designator_tbl  => l_ref_designator_tbl
15139                 ,  p_sub_component_tbl   => l_sub_component_tbl
15140                 ,  p_rev_operation_tbl   => l_rev_operation_tbl    --L1
15141                 ,  p_rev_op_resource_tbl => l_rev_op_resource_tbl  --L1
15142                 ,  p_rev_sub_resource_tbl=> l_rev_sub_resource_tbl --L1
15143                 ,  p_mesg_token_tbl      => l_mesg_token_tbl
15144                 ,  p_error_status        => 'W'
15145                 ,  p_error_level         => 1
15146                 ,  x_ECO_rec             => l_ECO_rec
15147                 ,  x_eco_revision_tbl    => l_eco_revision_tbl
15148                 ,  x_change_line_tbl     => l_change_line_tbl -- Eng Change
15149                 ,  x_revised_item_tbl    => l_revised_item_tbl
15150                 ,  x_rev_component_tbl   => l_rev_component_tbl
15151                 ,  x_ref_designator_tbl  => l_ref_designator_tbl
15152                 ,  x_sub_component_tbl   => l_sub_component_tbl
15153                 ,  x_rev_operation_tbl   => l_rev_operation_tbl    --L1
15154                 ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl  --L1
15155                 ,  x_rev_sub_resource_tbl=> l_rev_sub_resource_tbl --L1
15156                 );
15157        END IF;
15158 
15159   EXCEPTION
15160 
15161     WHEN EXC_SEV_QUIT_RECORD THEN
15162 
15163         Eco_Error_Handler.Log_Error
15164                 (  p_ECO_rec             => l_ECO_rec
15165                 ,  p_eco_revision_tbl    => l_eco_revision_tbl
15166                 ,  p_change_line_tbl     => l_change_line_tbl -- Eng Change
15167                 ,  p_revised_item_tbl    => l_revised_item_tbl
15168                 ,  p_rev_component_tbl   => l_rev_component_tbl
15169                 ,  p_ref_designator_tbl  => l_ref_designator_tbl
15170                 ,  p_sub_component_tbl   => l_sub_component_tbl
15171                 ,  p_rev_operation_tbl   => l_rev_operation_tbl    --L1
15172                 ,  p_rev_op_resource_tbl => l_rev_op_resource_tbl  --L1
15173                 ,  p_rev_sub_resource_tbl=> l_rev_sub_resource_tbl --L1
15174                 ,  p_mesg_token_tbl      => l_mesg_token_tbl
15175                 ,  p_error_status        => FND_API.G_RET_STS_ERROR
15176                 ,  p_error_scope         => Error_Handler.G_SCOPE_RECORD
15177                 ,  p_error_level         => 1
15178                 ,  x_ECO_rec             => l_ECO_rec
15179                 ,  x_eco_revision_tbl    => l_eco_revision_tbl
15180                 ,  x_change_line_tbl     => l_change_line_tbl -- Eng Change
15181                 ,  x_revised_item_tbl    => l_revised_item_tbl
15182                 ,  x_rev_component_tbl   => l_rev_component_tbl
15183                 ,  x_ref_designator_tbl  => l_ref_designator_tbl
15184                 ,  x_sub_component_tbl   => l_sub_component_tbl
15185                 ,  x_rev_operation_tbl   => l_rev_operation_tbl    --L1
15186                 ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl  --L1
15187                 ,  x_rev_sub_resource_tbl=> l_rev_sub_resource_tbl --L1
15188                 );
15189 
15190         x_return_status                := l_return_status;
15191         x_Mesg_Token_Tbl               := l_Mesg_Token_Tbl;
15192         x_ECO_rec                      := l_ECO_rec;
15193         x_eco_revision_tbl             := l_eco_revision_tbl;
15194         x_revised_item_tbl             := l_revised_item_tbl;
15195         x_rev_component_tbl            := l_rev_component_tbl;
15196         x_ref_designator_tbl           := l_ref_designator_tbl;
15197         x_sub_component_tbl            := l_sub_component_tbl;
15198         x_rev_operation_tbl            := l_rev_operation_tbl;     --L1
15199         x_rev_op_resource_tbl          := l_rev_op_resource_tbl;   --L1
15200         x_rev_sub_resource_tbl         := l_rev_sub_resource_tbl;  --L1
15201         x_change_line_tbl              := l_change_line_tbl ;      -- Eng Change
15202 
15203        WHEN EXC_SEV_QUIT_BRANCH THEN
15204 
15205         Eco_Error_Handler.Log_Error
15206                 (  p_ECO_rec             => l_ECO_rec
15207                 ,  p_eco_revision_tbl    => l_eco_revision_tbl
15208                 ,  p_change_line_tbl     => l_change_line_tbl -- Eng Change
15209                 ,  p_revised_item_tbl    => l_revised_item_tbl
15210                 ,  p_rev_component_tbl   => l_rev_component_tbl
15211                 ,  p_ref_designator_tbl  => l_ref_designator_tbl
15212                 ,  p_sub_component_tbl   => l_sub_component_tbl
15213                 ,  p_rev_operation_tbl   => l_rev_operation_tbl    --L1
15214                 ,  p_rev_op_resource_tbl => l_rev_op_resource_tbl  --L1
15215                 ,  p_rev_sub_resource_tbl=> l_rev_sub_resource_tbl --L1
15216                 ,  p_mesg_token_tbl      => l_mesg_token_tbl
15217                 ,  p_error_status        => Error_Handler.G_STATUS_ERROR
15218                 ,  p_error_scope         => Error_Handler.G_SCOPE_CHILDREN
15219                 ,  p_other_status        => Error_Handler.G_STATUS_ERROR
15220                 ,  p_other_message       => l_other_message
15221                 ,  p_other_token_tbl     => l_other_token_tbl
15222                 ,  p_error_level         => 1
15223                 ,  x_eco_rec             => l_eco_rec
15224                 ,  x_eco_revision_tbl    => l_eco_revision_tbl
15225                 ,  x_change_line_tbl     => l_change_line_tbl -- Eng Change
15226                 ,  x_revised_item_tbl    => l_revised_item_tbl
15227                 ,  x_rev_component_tbl   => l_rev_component_tbl
15228                 ,  x_ref_designator_tbl  => l_ref_designator_tbl
15229                 ,  x_sub_component_tbl   => l_sub_component_tbl
15230                 ,  x_rev_operation_tbl   => l_rev_operation_tbl    --L1
15231                 ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl  --L1
15232                 ,  x_rev_sub_resource_tbl=> l_rev_sub_resource_tbl --L1
15233                 );
15234 
15235         x_return_status                := l_return_status;
15236         x_Mesg_Token_Tbl               := l_Mesg_Token_Tbl;
15237         x_eco_rec                      := l_eco_rec;
15238         x_eco_revision_tbl             := l_eco_revision_tbl;
15239         x_revised_item_tbl             := l_revised_item_tbl;
15240         x_rev_component_tbl            := l_rev_component_tbl;
15241         x_ref_designator_tbl           := l_ref_designator_tbl;
15242         x_sub_component_tbl            := l_sub_component_tbl;
15243         x_rev_operation_tbl            := l_rev_operation_tbl;     --L1
15244         x_rev_op_resource_tbl          := l_rev_op_resource_tbl;   --L1
15245         x_rev_sub_resource_tbl         := l_rev_sub_resource_tbl;  --L1
15246         x_change_line_tbl              := l_change_line_tbl ;      -- Eng Change
15247 
15248         RETURN;
15249 
15250     WHEN EXC_SEV_SKIP_BRANCH THEN
15251 
15252         Eco_Error_Handler.Log_Error
15253                 (  p_ECO_rec             => l_ECO_rec
15254                 ,  p_eco_revision_tbl    => l_eco_revision_tbl
15255                 ,  p_change_line_tbl     => l_change_line_tbl -- Eng Change
15256                 ,  p_revised_item_tbl    => l_revised_item_tbl
15257                 ,  p_rev_component_tbl   => l_rev_component_tbl
15258                 ,  p_ref_designator_tbl  => l_ref_designator_tbl
15259                 ,  p_sub_component_tbl   => l_sub_component_tbl
15260                 ,  p_rev_operation_tbl   => l_rev_operation_tbl    --L1
15261                 ,  p_rev_op_resource_tbl => l_rev_op_resource_tbl  --L1
15262                 ,  p_rev_sub_resource_tbl=> l_rev_sub_resource_tbl --L1
15263                 ,  p_mesg_token_tbl      => l_mesg_token_tbl
15264                 ,  p_error_status        => Error_Handler.G_STATUS_ERROR
15265                 ,  p_error_scope         => Error_Handler.G_SCOPE_CHILDREN
15266                 ,  p_other_message       => l_other_message
15267                 ,  p_other_token_tbl     => l_other_token_tbl
15268                 ,  p_other_status        => Error_Handler.G_STATUS_NOT_PICKED
15269                 ,  p_error_level         => 1
15270                 ,  x_ECO_rec             => l_ECO_rec
15271                 ,  x_eco_revision_tbl    => l_eco_revision_tbl
15272                 ,  x_change_line_tbl     => l_change_line_tbl -- Eng Change
15273                 ,  x_revised_item_tbl    => l_revised_item_tbl
15274                 ,  x_rev_component_tbl   => l_rev_component_tbl
15275                 ,  x_ref_designator_tbl  => l_ref_designator_tbl
15276                 ,  x_sub_component_tbl   => l_sub_component_tbl
15277                 ,  x_rev_operation_tbl   => l_rev_operation_tbl    --L1
15278                 ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl  --L1
15279                 ,  x_rev_sub_resource_tbl=> l_rev_sub_resource_tbl --L1
15280                 );
15281 
15282         x_return_status                := l_return_status;
15283         x_Mesg_Token_Tbl               := l_Mesg_Token_Tbl;
15284         x_ECO_rec                      := l_ECO_rec;
15285         x_eco_revision_tbl             := l_eco_revision_tbl;
15286         x_revised_item_tbl             := l_revised_item_tbl;
15287         x_rev_component_tbl            := l_rev_component_tbl;
15288         x_ref_designator_tbl           := l_ref_designator_tbl;
15289         x_sub_component_tbl            := l_sub_component_tbl;
15290         x_rev_operation_tbl            := l_rev_operation_tbl;     --L1
15291         x_rev_op_resource_tbl          := l_rev_op_resource_tbl;   --L1
15292         x_rev_sub_resource_tbl         := l_rev_sub_resource_tbl;  --L1
15293         x_change_line_tbl              := l_change_line_tbl ;      -- Eng Change
15294 
15295         RETURN;
15296 
15297     WHEN EXC_FAT_QUIT_OBJECT THEN
15298 
15299         Eco_Error_Handler.Log_Error
15300                 (  p_ECO_rec             => l_ECO_rec
15301                 ,  p_eco_revision_tbl    => l_eco_revision_tbl
15302                 ,  p_change_line_tbl     => l_change_line_tbl -- Eng Change
15303                 ,  p_revised_item_tbl    => l_revised_item_tbl
15304                 ,  p_rev_component_tbl   => l_rev_component_tbl
15305                 ,  p_ref_designator_tbl  => l_ref_designator_tbl
15306                 ,  p_sub_component_tbl   => l_sub_component_tbl
15307                 ,  p_mesg_token_tbl      => l_mesg_token_tbl
15308                 ,  p_rev_operation_tbl   => l_rev_operation_tbl    --L1
15309                 ,  p_rev_op_resource_tbl => l_rev_op_resource_tbl  --L1
15310                 ,  p_rev_sub_resource_tbl=> l_rev_sub_resource_tbl --L1
15311                 ,  p_error_status        => Error_Handler.G_STATUS_FATAL
15312                 ,  p_error_scope         => Error_Handler.G_SCOPE_ALL
15313                 ,  p_other_message       => l_other_message
15314                 ,  p_other_status        => Error_Handler.G_STATUS_FATAL
15315                 ,  p_other_token_tbl     => l_other_token_tbl
15316                 ,  p_error_level         => 1
15317                 ,  x_ECO_rec             => l_ECO_rec
15318                 ,  x_eco_revision_tbl    => l_eco_revision_tbl
15319                 ,  x_change_line_tbl     => l_change_line_tbl -- Eng Change
15320                 ,  x_revised_item_tbl    => l_revised_item_tbl
15321                 ,  x_rev_component_tbl   => l_rev_component_tbl
15322                 ,  x_ref_designator_tbl  => l_ref_designator_tbl
15323                 ,  x_sub_component_tbl   => l_sub_component_tbl
15324                 ,  x_rev_operation_tbl   => l_rev_operation_tbl    --L1
15325                 ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl  --L1
15326                 ,  x_rev_sub_resource_tbl=> l_rev_sub_resource_tbl --L1
15327                 );
15328 
15329         x_Mesg_Token_Tbl               := l_Mesg_Token_Tbl;
15330         x_ECO_rec                      := l_ECO_rec;
15331         x_eco_revision_tbl             := l_eco_revision_tbl;
15332         x_revised_item_tbl             := l_revised_item_tbl;
15333         x_rev_component_tbl            := l_rev_component_tbl;
15334         x_ref_designator_tbl           := l_ref_designator_tbl;
15335         x_sub_component_tbl            := l_sub_component_tbl;
15336         x_rev_operation_tbl            := l_rev_operation_tbl;     --L1
15337         x_rev_op_resource_tbl          := l_rev_op_resource_tbl;   --L1
15338         x_rev_sub_resource_tbl         := l_rev_sub_resource_tbl;  --L1
15339         x_change_line_tbl              := l_change_line_tbl ;      -- Eng Change
15340         l_return_status := 'Q';
15341 
15342     WHEN EXC_UNEXP_SKIP_OBJECT THEN
15343 
15344         Eco_Error_Handler.Log_Error
15345                 (  p_ECO_rec             => l_ECO_rec
15346                 ,  p_eco_revision_tbl    => l_eco_revision_tbl
15347                 ,  p_change_line_tbl     => l_change_line_tbl -- Eng Change
15348                 ,  p_revised_item_tbl    => l_revised_item_tbl
15349                 ,  p_rev_component_tbl   => l_rev_component_tbl
15350                 ,  p_ref_designator_tbl  => l_ref_designator_tbl
15351                 ,  p_sub_component_tbl   => l_sub_component_tbl
15352                 ,  p_rev_operation_tbl   => l_rev_operation_tbl    --L1
15353                 ,  p_rev_op_resource_tbl => l_rev_op_resource_tbl  --L1
15354                 ,  p_rev_sub_resource_tbl=> l_rev_sub_resource_tbl --L1
15355                 ,  p_mesg_token_tbl      => l_mesg_token_tbl
15356                 ,  p_error_status        => Error_Handler.G_STATUS_UNEXPECTED
15357                 ,  p_other_status        => Error_Handler.G_STATUS_NOT_PICKED
15358                 ,  p_other_message       => l_other_message
15359                 ,  p_other_token_tbl     => l_other_token_tbl
15360                 ,  p_error_level         => 1
15361                 ,  x_ECO_rec             => l_ECO_rec
15362                 ,  x_eco_revision_tbl    => l_eco_revision_tbl
15363                 ,  x_change_line_tbl     => l_change_line_tbl -- Eng Change
15364                 ,  x_revised_item_tbl    => l_revised_item_tbl
15365                 ,  x_rev_component_tbl   => l_rev_component_tbl
15366                 ,  x_ref_designator_tbl  => l_ref_designator_tbl
15367                 ,  x_sub_component_tbl   => l_sub_component_tbl
15368                 ,  x_rev_operation_tbl   => l_rev_operation_tbl    --L1
15369                 ,  x_rev_op_resource_tbl => l_rev_op_resource_tbl  --L1
15370                 ,  x_rev_sub_resource_tbl=> l_rev_sub_resource_tbl --L1
15371                 );
15372 
15373         x_return_status                := l_return_status;
15374         x_Mesg_Token_Tbl               := l_Mesg_Token_Tbl;
15375         x_ECO_rec                      := l_ECO_rec;
15376         x_eco_revision_tbl             := l_eco_revision_tbl;
15377         x_revised_item_tbl             := l_revised_item_tbl;
15378         x_rev_component_tbl            := l_rev_component_tbl;
15379         x_ref_designator_tbl           := l_ref_designator_tbl;
15380         x_sub_component_tbl            := l_sub_component_tbl;
15381         x_rev_operation_tbl            := l_rev_operation_tbl;     --L1
15382         x_rev_op_resource_tbl          := l_rev_op_resource_tbl;   --L1
15383         x_rev_sub_resource_tbl         := l_rev_sub_resource_tbl;  --L1
15384         x_change_line_tbl              := l_change_line_tbl ;      -- Eng Change
15385         l_return_status := 'U';
15386 
15387   END; -- END Header processing block
15388 
15389     IF l_return_status in ('Q', 'U')
15390     THEN
15391         x_return_status := l_return_status;
15392         RETURN;
15393     END IF;
15394 
15395     l_bo_return_status := l_return_status;
15396 
15397     -- Process ECO Revisions that are chilren of this header
15398 
15399     Eco_Rev
15400         (   p_validation_level          => p_validation_level
15401         ,   p_change_notice             => l_eco_rec.ECO_Name
15402         ,   p_organization_id           => l_eco_unexp_rec.organization_id
15403         ,   p_eco_revision_tbl          => l_eco_revision_tbl
15404         ,   p_change_line_tbl           => l_change_line_tbl -- Eng Change
15405         ,   p_revised_item_tbl          => l_revised_item_tbl
15406         ,   p_rev_component_tbl         => l_rev_component_tbl
15407         ,   p_ref_designator_tbl        => l_ref_designator_tbl
15408         ,   p_sub_component_tbl         => l_sub_component_tbl
15409         ,   p_rev_operation_tbl         => l_rev_operation_tbl    --L1
15410         ,   p_rev_op_resource_tbl       => l_rev_op_resource_tbl  --L1
15411         ,   p_rev_sub_resource_tbl      => l_rev_sub_resource_tbl --L1
15412         ,   x_eco_revision_tbl          => l_eco_revision_tbl
15413         ,   x_change_line_tbl           => l_change_line_tbl -- Eng Change
15414         ,   x_revised_item_tbl          => l_revised_item_tbl
15415         ,   x_rev_component_tbl         => l_rev_component_tbl
15416         ,   x_ref_designator_tbl        => l_ref_designator_tbl
15417         ,   x_sub_component_tbl         => l_sub_component_tbl
15418         ,   x_rev_operation_tbl         => l_rev_operation_tbl    --L1
15419         ,   x_rev_op_resource_tbl       => l_rev_op_resource_tbl  --L1
15420         ,   x_rev_sub_resource_tbl      => l_rev_sub_resource_tbl --L1
15421         ,   x_Mesg_Token_Tbl            => l_Mesg_Token_Tbl
15422         ,   x_return_status             => l_return_status
15423         );
15424     IF l_return_status <> 'S'
15425     THEN
15426         l_bo_return_status := l_return_status;
15427     END IF;
15428 
15429    -- Process Change Line that are chilren of this header
15430    Change_Line
15431         (   p_validation_level          => p_validation_level
15432         ,   p_change_notice             => l_eco_rec.ECO_Name
15433         ,   p_organization_id           => l_eco_unexp_rec.organization_id
15434         ,   p_change_line_tbl           => l_change_line_tbl      -- Eng Change
15435         ,   p_revised_item_tbl          => l_revised_item_tbl
15436         ,   p_rev_component_tbl         => l_rev_component_tbl
15437         ,   p_ref_designator_tbl        => l_ref_designator_tbl
15438         ,   p_sub_component_tbl         => l_sub_component_tbl
15439         ,   p_rev_operation_tbl         => l_rev_operation_tbl    --L1
15440         ,   p_rev_op_resource_tbl       => l_rev_op_resource_tbl  --L1
15441         ,   p_rev_sub_resource_tbl      => l_rev_sub_resource_tbl --L1
15442         ,   x_change_line_tbl           => l_change_line_tbl      -- Eng Change
15443         ,   x_revised_item_tbl          => l_revised_item_tbl
15444         ,   x_rev_component_tbl         => l_rev_component_tbl
15445         ,   x_ref_designator_tbl        => l_ref_designator_tbl
15446         ,   x_sub_component_tbl         => l_sub_component_tbl
15447         ,   x_rev_operation_tbl         => l_rev_operation_tbl    --L1
15448         ,   x_rev_op_resource_tbl       => l_rev_op_resource_tbl  --L1
15449         ,   x_rev_sub_resource_tbl      => l_rev_sub_resource_tbl --L1
15450         ,   x_Mesg_Token_Tbl            => l_Mesg_Token_Tbl
15451         ,   x_return_status             => l_return_status
15452         );
15453 
15454     IF l_return_status <> 'S'
15455     THEN
15456         l_bo_return_status := l_return_status;
15457     END IF;
15458 
15459 
15460     -- Process Revised Items that are chilren of this header
15461 
15462     Rev_Items
15463         (   p_validation_level          => p_validation_level
15464         ,   p_change_notice             => l_eco_rec.ECO_Name
15465         ,   p_organization_id           => l_eco_unexp_rec.organization_id
15466         ,   p_revised_item_tbl          => l_revised_item_tbl
15467         ,   p_rev_component_tbl         => l_rev_component_tbl
15468         ,   p_ref_designator_tbl        => l_ref_designator_tbl
15469         ,   p_sub_component_tbl         => l_sub_component_tbl
15470         ,   p_rev_operation_tbl         => l_rev_operation_tbl    --L1
15471         ,   p_rev_op_resource_tbl       => l_rev_op_resource_tbl  --L1
15472         ,   p_rev_sub_resource_tbl      => l_rev_sub_resource_tbl --L1
15473         ,   x_revised_item_tbl          => l_revised_item_tbl
15474         ,   x_rev_component_tbl         => l_rev_component_tbl
15475         ,   x_ref_designator_tbl        => l_ref_designator_tbl
15476         ,   x_sub_component_tbl         => l_sub_component_tbl
15477         ,   x_rev_operation_tbl         => l_rev_operation_tbl    --L1
15478         ,   x_rev_op_resource_tbl       => l_rev_op_resource_tbl  --L1
15479         ,   x_rev_sub_resource_tbl      => l_rev_sub_resource_tbl --L1
15480         ,   x_Mesg_Token_Tbl            => l_Mesg_Token_Tbl
15481         ,   x_return_status             => l_return_status
15482 	,    x_disable_revision          => x_disable_revision        --Bug no:3034642
15483         );
15484 
15485     -- Bug 6657209. Reset the global variable after Rev_items are processed.
15486     Eng_Default_Revised_Item.G_OLD_SCHED_DATE := NULL;
15487 
15488     IF l_return_status <> 'S'
15489     THEN
15490         l_bo_return_status := l_return_status;
15491     END IF;
15492 
15493 
15494    -- L1: The following is for ECO enhancement
15495    -- Process operations that are orphans (without immediate revised
15496    -- item parents) but are indirect children of this header
15497     Rev_Operation_Sequences
15498        (    p_validation_level          => p_validation_level
15499         ,   p_change_notice             => l_eco_rec.ECO_Name
15500         ,   p_organization_id           => l_eco_unexp_rec.organization_id
15501         ,   p_rev_operation_tbl         => l_rev_operation_tbl
15502         ,   p_rev_op_resource_tbl       => l_rev_op_resource_tbl
15503         ,   p_rev_sub_resource_tbl      => l_rev_sub_resource_tbl
15504         ,   x_rev_operation_tbl         => l_rev_operation_tbl
15505         ,   x_rev_op_resource_tbl       => l_rev_op_resource_tbl
15506         ,   x_rev_sub_resource_tbl      => l_rev_sub_resource_tbl
15507         ,   x_Mesg_Token_Tbl            => l_Mesg_Token_Tbl
15508         ,   x_return_status             => l_return_status
15509      );
15510     IF l_return_status <> 'S'
15511     THEN
15512         l_bo_return_status := l_return_status;
15513     END IF;
15514 
15515    -- Process operation resources that are orphans (without immediate revised
15516    -- operation parents) but are indirect children of this header
15517        Rev_Operation_Resources
15518         (   p_validation_level          => p_validation_level
15519         ,   p_change_notice             => l_eco_rec.ECO_Name
15520         ,   p_organization_id           => l_eco_unexp_rec.organization_id
15521         ,   p_rev_op_resource_tbl       => l_rev_op_resource_tbl
15522         ,   p_rev_sub_resource_tbl      => l_rev_sub_resource_tbl
15523         ,   x_rev_op_resource_tbl       => l_rev_op_resource_tbl
15524         ,   x_rev_sub_resource_tbl      => l_rev_sub_resource_tbl
15525         ,   x_Mesg_Token_Tbl            => l_Mesg_Token_Tbl
15526         ,   x_return_status             => l_return_status
15527         );
15528     IF l_return_status <> 'S'
15529     THEN
15530         l_bo_return_status := l_return_status;
15531     END IF;
15532 
15533     -- Process substitute resources that are orphans (without immediate revised
15534     -- operaion parents) but are indirect children of this header
15535       Rev_Sub_Operation_Resources
15536         (   p_validation_level          => p_validation_level
15537         ,   p_change_notice             => l_eco_rec.ECO_Name
15538         ,   p_organization_id           => l_eco_unexp_rec.organization_id
15539         ,   p_rev_sub_resource_tbl      => l_rev_sub_resource_tbl
15540         ,   x_rev_sub_resource_tbl      => l_rev_sub_resource_tbl
15541         ,   x_Mesg_Token_Tbl            => l_Mesg_Token_Tbl
15542         ,   x_return_status             => l_return_status
15543         );
15544     IF l_return_status <> 'S'
15545     THEN
15546         l_bo_return_status := l_return_status;
15547     END IF;
15548 
15549 
15550     -- Process Revised Components that are orphans (without immediate revised
15551     -- item parents) but are indirect children of this header
15552 
15553     Rev_Comps
15554         (   p_validation_level          => p_validation_level
15555         ,   p_change_notice             => l_eco_rec.ECO_Name
15556         ,   p_organization_id           => l_eco_unexp_rec.organization_id
15557         ,   p_rev_component_tbl         => l_rev_component_tbl
15558         ,   p_ref_designator_tbl        => l_ref_designator_tbl
15559         ,   p_sub_component_tbl         => l_sub_component_tbl
15560         ,   x_rev_component_tbl         => l_rev_component_tbl
15561         ,   x_ref_designator_tbl        => l_ref_designator_tbl
15562         ,   x_sub_component_tbl         => l_sub_component_tbl
15563         ,   x_Mesg_Token_Tbl            => l_Mesg_Token_Tbl
15564         ,   x_return_status             => l_return_status
15565         );
15566 
15567     IF l_return_status <> 'S'
15568     THEN
15569         l_bo_return_status := l_return_status;
15570     END IF;
15571 
15572     -- Process Reference Designators that are orphans (without immediate revised
15573     -- component parents) but are indirect children of this header
15574 
15575     Ref_Desgs
15576         (   p_validation_level          => p_validation_level
15577         ,   p_change_notice             => l_eco_rec.ECO_Name
15578         ,   p_organization_id           => l_eco_unexp_rec.organization_id
15579         ,   p_ref_designator_tbl        => l_ref_designator_tbl
15580         ,   p_sub_component_tbl         => l_sub_component_tbl
15581         ,   x_ref_designator_tbl        => l_ref_designator_tbl
15582         ,   x_sub_component_tbl         => l_sub_component_tbl
15583         ,   x_Mesg_Token_Tbl            => l_Mesg_Token_Tbl
15584         ,   x_return_status             => l_return_status
15585         );
15586 
15587     IF l_return_status <> 'S'
15588     THEN
15589         l_bo_return_status := l_return_status;
15590     END IF;
15591 
15592    -- Process Substitute Components that are orphans (without immediate revised
15593    -- component parents) but are indirect children of this header
15594 
15595     Sub_Comps
15596         (   p_validation_level          => p_validation_level
15597         ,   p_change_notice             => l_eco_rec.ECO_Name
15598         ,   p_organization_id           => l_eco_unexp_rec.organization_id
15599         ,   p_sub_component_tbl         => l_sub_component_tbl
15600         ,   x_sub_component_tbl         => l_sub_component_tbl
15601         ,   x_Mesg_Token_Tbl            => l_Mesg_Token_Tbl
15602         ,   x_return_status             => l_return_status
15603         );
15604 
15605     IF l_return_status <> 'S'
15606     THEN
15607         l_bo_return_status := l_return_status;
15608     END IF;
15609 
15610 
15611   -- The above is for ECO enhancement
15612   --  Load OUT parameters
15613 
15614      x_return_status            := l_bo_return_status;
15615      x_ECO_rec                  := l_ECO_rec;
15616      x_eco_revision_tbl         := l_eco_revision_tbl;
15617      x_revised_item_tbl         := l_revised_item_tbl;
15618      x_rev_component_tbl        := l_rev_component_tbl;
15619      x_ref_designator_tbl       := l_ref_designator_tbl;
15620      x_sub_component_tbl        := l_sub_component_tbl;
15621      x_Mesg_Token_Tbl           := l_Mesg_Token_Tbl;
15622      x_rev_operation_tbl        := l_rev_operation_tbl;     --L1
15623      x_rev_op_resource_tbl      := l_rev_op_resource_tbl;   --L1
15624      x_rev_sub_resource_tbl     := l_rev_sub_resource_tbl;  --L1
15625      x_change_line_tbl          := l_change_line_tbl ;      -- Eng Change
15626 
15627 END Eco_Header;
15628 
15629 
15630 --  Start of Comments
15631 --  API name    Process_Eco
15632 --  Type        Private
15633 --  Function
15634 --
15635 --  Pre-reqs
15636 --
15637 --  Parameters
15638 --
15639 --  Version     Current version = 1.0
15640 --              Initial version = 1.0
15641 --
15642 --  Notes
15643 --
15644 --  End of Comments
15645 
15646 PROCEDURE Process_Eco
15647 (   p_api_version_number        IN  NUMBER
15648 ,   p_validation_level          IN  NUMBER := FND_API.G_VALID_LEVEL_FULL
15649 ,   p_control_rec               IN  ENG_GLOBALS.Control_Rec_Type :=
15650                                     ENG_GLOBALS.G_MISS_CONTROL_REC
15651 ,   x_return_status             OUT NOCOPY VARCHAR2
15652 ,   x_msg_count                 OUT NOCOPY NUMBER
15653 ,   p_ECO_rec                   IN  ENG_Eco_PUB.Eco_Rec_Type :=
15654                                     ENG_Eco_PUB.G_MISS_ECO_REC
15655 ,   p_eco_revision_tbl          IN  ENG_Eco_PUB.Eco_Revision_Tbl_Type :=
15656                                     ENG_Eco_PUB.G_MISS_ECO_REVISION_TBL
15657 ,   p_change_line_tbl           IN  ENG_Eco_PUB.Change_Line_Tbl_Type :=   -- Eng Change
15658                                     ENG_Eco_PUB.G_MISS_CHANGE_LINE_TBL
15659 ,   p_revised_item_tbl          IN  ENG_Eco_PUB.Revised_Item_Tbl_Type :=
15660                                     ENG_Eco_PUB.G_MISS_REVISED_ITEM_TBL
15661 ,   p_rev_component_tbl         IN  BOM_BO_PUB.Rev_Component_Tbl_Type :=
15662                                     BOM_BO_PUB.G_MISS_REV_COMPONENT_TBL
15663 ,   p_ref_designator_tbl        IN  BOM_BO_PUB.Ref_Designator_Tbl_Type :=
15664                                     BOM_BO_PUB.G_MISS_REF_DESIGNATOR_TBL
15665 ,   p_sub_component_tbl         IN  BOM_BO_PUB.Sub_Component_Tbl_Type :=
15666                                     BOM_BO_PUB.G_MISS_SUB_COMPONENT_TBL
15667 ,   p_rev_operation_tbl         IN  Bom_Rtg_Pub.Rev_Operation_Tbl_Type:=    --L1
15668                                     Bom_Rtg_Pub.G_MISS_REV_OPERATION_TBL
15669 ,   p_rev_op_resource_tbl       IN  Bom_Rtg_Pub.Rev_Op_Resource_Tbl_Type := --L1
15670                                     Bom_Rtg_Pub.G_MISS_REV_OP_RESOURCE_TBL --L1
15671 ,   p_rev_sub_resource_tbl      IN  Bom_Rtg_Pub.Rev_Sub_Resource_Tbl_Type:= --L1
15672                                     Bom_Rtg_Pub.G_MISS_REV_SUB_RESOURCE_TBL --L1
15673 ,   x_ECO_rec                   IN OUT NOCOPY ENG_Eco_PUB.Eco_Rec_Type
15674 ,   x_eco_revision_tbl          IN OUT NOCOPY ENG_Eco_PUB.Eco_Revision_Tbl_Type
15675 ,   x_change_line_tbl           IN OUT NOCOPY ENG_Eco_PUB.Change_Line_Tbl_Type      -- Eng Change
15676 ,   x_revised_item_tbl          IN OUT NOCOPY ENG_Eco_PUB.Revised_Item_Tbl_Type
15677 ,   x_rev_component_tbl         IN OUT NOCOPY BOM_BO_PUB.Rev_Component_Tbl_Type
15678 ,   x_ref_designator_tbl        IN OUT NOCOPY BOM_BO_PUB.Ref_Designator_Tbl_Type
15679 ,   x_sub_component_tbl         IN OUT NOCOPY BOM_BO_PUB.Sub_Component_Tbl_Type
15680 ,   x_rev_operation_tbl         IN OUT NOCOPY Bom_Rtg_Pub.Rev_Operation_Tbl_Type    --L1--
15681 ,   x_rev_op_resource_tbl       IN OUT NOCOPY Bom_Rtg_Pub.Rev_Op_Resource_Tbl_Type  --L1--
15682 ,   x_rev_sub_resource_tbl      IN OUT NOCOPY Bom_Rtg_Pub.Rev_Sub_Resource_Tbl_Type --L1--
15683  , x_disable_revision              OUT NOCOPY NUMBER --Bug no:3034642
15684 )
15685 IS
15686 l_api_version_number          CONSTANT NUMBER := 1.0;
15687 l_api_name                    CONSTANT VARCHAR2(30):= 'Process_Eco';
15688 l_err_text                    VARCHAR2(240);
15689 l_return_status               VARCHAR2(1);
15690 /* Added variable to hold business object status
15691    Added by AS on 03/17/99 to fix bug 852322
15692 */
15693 l_bo_return_status            VARCHAR2(1);
15694 
15695 l_organization_id       NUMBER;
15696 
15697 l_control_rec                 ENG_GLOBALS.Control_Rec_Type;
15698 
15699 l_ECO_rec                     ENG_Eco_PUB.Eco_Rec_Type := p_ECO_rec;
15700 l_eco_revision_rec            ENG_Eco_PUB.Eco_Revision_Rec_Type;
15701 l_eco_revision_tbl            ENG_Eco_PUB.Eco_Revision_Tbl_Type;
15702 l_revised_item_rec            ENG_Eco_PUB.Revised_Item_Rec_Type;
15703 l_revised_item_tbl            ENG_Eco_PUB.Revised_Item_Tbl_Type;
15704 l_rev_component_rec           BOM_BO_PUB.Rev_Component_Rec_Type;
15705 l_rev_component_tbl           BOM_BO_PUB.Rev_Component_Tbl_Type;
15706 l_ref_designator_rec          BOM_BO_PUB.Ref_Designator_Rec_Type;
15707 l_ref_designator_tbl          BOM_BO_PUB.Ref_Designator_Tbl_Type;
15708 l_sub_component_rec           BOM_BO_PUB.Sub_Component_Rec_Type;
15709 l_sub_component_tbl           BOM_BO_PUB.Sub_Component_Tbl_Type;
15710 l_rev_operation_tbl           Bom_Rtg_Pub.Rev_Operation_Tbl_Type;     -- L1--
15711 l_rev_op_resource_tbl         Bom_Rtg_Pub.Rev_Op_Resource_Tbl_Type;   -- L1--
15712 l_rev_sub_resource_tbl        Bom_Rtg_Pub.Rev_Sub_Resource_Tbl_Type;  -- L1--
15713 l_rev_operation_rec           Bom_Rtg_Pub.Rev_Operation_Rec_Type;     -- L1--
15714 l_rev_op_resource_rec         Bom_Rtg_Pub.Rev_Op_Resource_Rec_Type;   -- L1--
15715 l_rev_sub_resource_rec        Bom_Rtg_Pub.Rev_Sub_Resource_Rec_Type;  -- L1--
15716 l_change_line_rec             ENG_Eco_PUB.Change_Line_Rec_Type ;      -- Eng Change
15717 l_change_line_tbl             ENG_Eco_PUB.Change_Line_Tbl_Type ;      -- Eng Change
15718 
15719 l_mesg_token_tbl              Error_Handler.Mesg_Token_Tbl_Type;
15720 l_other_message               VARCHAR2(2000);
15721 l_other_token_tbl             Error_Handler.Token_Tbl_Type;
15722 
15723 EXC_ERR_PVT_API_MAIN          EXCEPTION;
15724 
15725 BEGIN
15726 
15727     --dbms_output.enable(1000000);
15728 
15729 
15730     --  Standard call to check for call compatibility
15731 
15732     IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('The following objects will be processed as part of the same business object'); END IF;
15733     IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('| ECO           : ' || l_ECO_rec.eco_name); END IF;
15734     IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('| ECO REVISIONS : ' || to_char(p_eco_revision_tbl.COUNT)); END IF;
15735     IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('| CHANGE LINES  : ' || to_char(p_change_line_tbl.COUNT)); END IF;
15736     IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('| REVISED ITEMS : ' || to_char(p_revised_item_tbl.COUNT)); END IF;
15737     IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('| REVISED COMPS : ' || to_char(p_rev_component_tbl.COUNT)); END IF;
15738     IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('| SUBS. COMPS   : ' || to_Char(p_sub_component_tbl.COUNT)); END IF;
15739     IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('| REFD. DESGS   : ' || to_char(p_ref_designator_tbl.COUNT)); END IF;
15740 
15741 --L1--
15742     IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('| OPERATION     : ' || to_char(p_rev_operation_tbl.COUNT)); END IF;
15743     IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('| RESOURCE      : ' || to_char(p_rev_op_resource_tbl.COUNT)); END IF;
15744     IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('| SUB RESOURCE  : ' || to_char(p_rev_sub_resource_tbl.COUNT)); END IF;
15745 --L1--
15746 
15747 
15748     IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('|----------------------------------------------------');  END IF;
15749 
15750 /*------------------------------------
15751 -- Not used
15752 
15753     IF NOT FND_API.Compatible_API_Call
15754            (   l_api_version_number
15755            ,   p_api_version_number
15756            ,   l_api_name
15757            ,   G_PKG_NAME
15758            )
15759     THEN
15760         RAISE EXC_ERR_PVT_API_MAIN;
15761     END IF;
15762 ------------------------------------*/
15763 
15764 
15765     --  Init local variables
15766 
15767     l_ECO_rec                      := p_ECO_rec;
15768 
15769     --  Init local table variables.
15770 
15771     l_eco_revision_tbl             := p_eco_revision_tbl;
15772     l_revised_item_tbl             := p_revised_item_tbl;
15773     l_rev_component_tbl            := p_rev_component_tbl;
15774     l_ref_designator_tbl           := p_ref_designator_tbl;
15775     l_sub_component_tbl            := p_sub_component_tbl;
15776     l_rev_operation_tbl            := p_rev_operation_tbl;     --L1
15777     l_rev_op_resource_tbl          := p_rev_op_resource_tbl;   --L1
15778     l_rev_sub_resource_tbl         := p_rev_sub_resource_tbl;  --L1
15779     l_change_line_tbl              := p_change_line_tbl ;      -- Eng Change
15780 
15781 
15782 --  Added by AS on 03/17/99 to fix bug 852322
15783     l_bo_return_status := 'S';
15784 
15785     -- Load environment information into the SYSTEM_INFORMATION record
15786     -- (USER_ID, LOGIN_ID, PROG_APPID, PROG_ID)
15787 
15788 
15789     ENG_GLOBALS.Init_System_Info_Rec
15790                         (  x_mesg_token_tbl => l_mesg_token_tbl
15791                         ,  x_return_status  => l_return_status
15792                         );
15793 
15794     -- Initialize System_Information Unit_Effectivity flag
15795     -- Modified on Sep 27,2001 by bzhang
15796    /* IF FND_PROFILE.DEFINED('PJM:PJM_UNITEFF_NO_EFFECT') AND
15797        FND_PROFILE.VALUE('PJM:PJM_UNITEFF_NO_EFFECT') = 'Y'
15798    */
15799     IF PJM_UNIT_EFF.Enabled = 'Y'
15800     THEN
15801         BOM_Globals.Set_Unit_Effectivity (TRUE);
15802         ENG_Globals.Set_Unit_Effectivity (TRUE);
15803     ELSE
15804         BOM_Globals.Set_Unit_Effectivity (FALSE);
15805         ENG_Globals.Set_Unit_Effectivity (FALSE);
15806     END IF;
15807 
15808     IF l_return_status <> FND_API.G_RET_STS_SUCCESS
15809     THEN
15810         RAISE EXC_ERR_PVT_API_MAIN;
15811     END IF;
15812     --  Eco
15813     IF  (l_ECO_rec.ECO_Name <> FND_API.G_MISS_CHAR
15814          AND l_ECO_rec.ECO_Name IS NOT NULL)
15815     THEN
15816         IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug(' '); END IF;
15817         IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('PVT API: Calling ECO_Header'); END IF;
15818 
15819         Eco_Header
15820         (   p_validation_level          => p_validation_level
15821         ,   p_ECO_rec                   => l_ECO_rec
15822         ,   p_eco_revision_tbl          => l_eco_revision_tbl
15823         ,   p_change_line_tbl           => l_change_line_tbl      -- Eng Change
15824         ,   p_revised_item_tbl          => l_revised_item_tbl
15825         ,   p_rev_component_tbl         => l_rev_component_tbl
15826         ,   p_ref_designator_tbl        => l_ref_designator_tbl
15827         ,   p_sub_component_tbl         => l_sub_component_tbl
15828         ,   p_rev_operation_tbl         => l_rev_operation_tbl    --L1
15829         ,   p_rev_op_resource_tbl       => l_rev_op_resource_tbl  --L1
15830         ,   p_rev_sub_resource_tbl      => l_rev_sub_resource_tbl --L1
15831         ,   x_ECO_rec                   => l_ECO_rec
15832         ,   x_eco_revision_tbl          => l_eco_revision_tbl
15833         ,   x_change_line_tbl           => l_change_line_tbl      -- Eng Change
15834         ,   x_revised_item_tbl          => l_revised_item_tbl
15835         ,   x_rev_component_tbl         => l_rev_component_tbl
15836         ,   x_ref_designator_tbl        => l_ref_designator_tbl
15837         ,   x_sub_component_tbl         => l_sub_component_tbl
15838         ,   x_rev_operation_tbl         => l_rev_operation_tbl    --L1
15839         ,   x_rev_op_resource_tbl       => l_rev_op_resource_tbl  --L1
15840         ,   x_rev_sub_resource_tbl      => l_rev_sub_resource_tbl --L1
15841         ,   x_Mesg_Token_Tbl            => l_Mesg_Token_Tbl
15842         ,   x_return_status             => l_return_status
15843 	 ,   x_disable_revision          =>x_disable_revision --Bug no:3034642
15844         );
15845 	IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('eco hdr return status: ' || l_eco_rec.return_status); END IF;
15846 
15847         -- Added by AS on 03/22/99 to fix bug 853529
15848 
15849         IF NVL(l_return_status, 'S') = 'Q'
15850         THEN
15851                 l_return_status := 'F';
15852                 RAISE G_EXC_QUIT_IMPORT;
15853         ELSIF NVL(l_return_status, 'S') = 'U'
15854         THEN
15855                 RAISE G_EXC_QUIT_IMPORT;
15856 
15857         --  Added by AS on 03/17/99 to fix bug 852322
15858         ELSIF NVL(l_return_status, 'S') <> 'S'
15859         THEN
15860                 l_bo_return_status := l_return_status;
15861         END IF;
15862 
15863    END IF;
15864 
15865    IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('BO error status: ' || l_bo_return_status); END IF;
15866 
15867    --  Eco Revisions
15868    IF l_eco_revision_tbl.Count <> 0
15869    THEN
15870         IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug(' '); END IF;
15871         IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('PVT API: Calling ECO_Rev'); END IF;
15872 
15873         Eco_Rev
15874         (   p_validation_level          => p_validation_level
15875         ,   p_eco_revision_tbl          => l_eco_revision_tbl
15876         ,   p_change_line_tbl           => l_change_line_tbl      -- Eng Change
15877         ,   p_revised_item_tbl          => l_revised_item_tbl
15878         ,   p_rev_component_tbl         => l_rev_component_tbl
15879         ,   p_ref_designator_tbl        => l_ref_designator_tbl
15880         ,   p_sub_component_tbl         => l_sub_component_tbl
15881         ,   p_rev_operation_tbl         => l_rev_operation_tbl    --L1
15882         ,   p_rev_op_resource_tbl       => l_rev_op_resource_tbl  --L1
15883         ,   p_rev_sub_resource_tbl      => l_rev_sub_resource_tbl --L1
15884         ,   x_eco_revision_tbl          => l_eco_revision_tbl
15885         ,   x_change_line_tbl           => l_change_line_tbl      -- Eng Change
15886         ,   x_revised_item_tbl          => l_revised_item_tbl
15887         ,   x_rev_component_tbl         => l_rev_component_tbl
15888         ,   x_ref_designator_tbl        => l_ref_designator_tbl
15889         ,   x_sub_component_tbl         => l_sub_component_tbl
15890         ,   x_rev_operation_tbl         => l_rev_operation_tbl    --L1
15891         ,   x_rev_op_resource_tbl       => l_rev_op_resource_tbl  --L1
15892         ,   x_rev_sub_resource_tbl      => l_rev_sub_resource_tbl --L1
15893         ,   x_Mesg_Token_Tbl            => l_Mesg_Token_Tbl
15894         ,   x_return_status             => l_return_status
15895         );
15896 	-- Added by AS on 03/22/99 to fix bug 853529
15897 
15898         IF NVL(l_return_status, 'S') = 'Q'
15899         THEN
15900                 l_return_status := 'F';
15901                 RAISE G_EXC_QUIT_IMPORT;
15902         ELSIF NVL(l_return_status, 'S') = 'U'
15903         THEN
15904                 RAISE G_EXC_QUIT_IMPORT;
15905 
15906         --  Added by AS on 03/17/99 to fix bug 852322
15907         ELSIF NVL(l_return_status, 'S') <> 'S'
15908         THEN
15909                 l_bo_return_status := l_return_status;
15910         END IF;
15911 
15912     END IF;
15913 
15914    IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('BO error status: ' || l_bo_return_status); END IF;
15915 
15916 
15917    --  Change Lines
15918    IF l_change_line_tbl.Count <> 0
15919    THEN
15920         IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug(' '); END IF;
15921         IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('PVT API: Calling Change_Line'); END IF;
15922 
15923         Change_Line
15924         (   p_validation_level          => p_validation_level
15925         ,   p_change_line_tbl           => l_change_line_tbl      -- Eng Change
15926         ,   p_revised_item_tbl          => l_revised_item_tbl
15927         ,   p_rev_component_tbl         => l_rev_component_tbl
15928         ,   p_ref_designator_tbl        => l_ref_designator_tbl
15929         ,   p_sub_component_tbl         => l_sub_component_tbl
15930         ,   p_rev_operation_tbl         => l_rev_operation_tbl    --L1
15931         ,   p_rev_op_resource_tbl       => l_rev_op_resource_tbl  --L1
15932         ,   p_rev_sub_resource_tbl      => l_rev_sub_resource_tbl --L1
15933         ,   x_change_line_tbl           => l_change_line_tbl      -- Eng Change
15934         ,   x_revised_item_tbl          => l_revised_item_tbl
15935         ,   x_rev_component_tbl         => l_rev_component_tbl
15936         ,   x_ref_designator_tbl        => l_ref_designator_tbl
15937         ,   x_sub_component_tbl         => l_sub_component_tbl
15938         ,   x_rev_operation_tbl         => l_rev_operation_tbl    --L1
15939         ,   x_rev_op_resource_tbl       => l_rev_op_resource_tbl  --L1
15940         ,   x_rev_sub_resource_tbl      => l_rev_sub_resource_tbl --L1
15941         ,   x_Mesg_Token_Tbl            => l_Mesg_Token_Tbl
15942         ,   x_return_status             => l_return_status
15943         );
15944 
15945         IF NVL(l_return_status, 'S') = 'Q'
15946         THEN
15947                 l_return_status := 'F';
15948                 RAISE G_EXC_QUIT_IMPORT;
15949         ELSIF NVL(l_return_status, 'S') = 'U'
15950         THEN
15951                 RAISE G_EXC_QUIT_IMPORT;
15952 
15953         ELSIF NVL(l_return_status, 'S') <> 'S'
15954         THEN
15955                 l_bo_return_status := l_return_status;
15956         END IF;
15957 
15958     END IF;
15959 
15960     IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('BO error status: ' || l_bo_return_status); END IF;
15961 
15962     --  Revised Items
15963 
15964     IF p_revised_item_tbl.COUNT <> 0
15965     THEN
15966         IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug(' '); END IF;
15967         IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('PVT API: Calling Rev_Items'); END IF;
15968 
15969         Rev_Items
15970         (   p_validation_level          => p_validation_level
15971         ,   p_revised_item_tbl          => l_revised_item_tbl
15972         ,   p_rev_component_tbl         => l_rev_component_tbl
15973         ,   p_ref_designator_tbl        => l_ref_designator_tbl
15974         ,   p_sub_component_tbl         => l_sub_component_tbl
15975         ,   p_rev_operation_tbl         => l_rev_operation_tbl    --L1
15976         ,   p_rev_op_resource_tbl       => l_rev_op_resource_tbl  --L1
15977         ,   p_rev_sub_resource_tbl      => l_rev_sub_resource_tbl --L1
15978         ,   x_revised_item_tbl          => l_revised_item_tbl
15979         ,   x_rev_component_tbl         => l_rev_component_tbl
15980         ,   x_ref_designator_tbl        => l_ref_designator_tbl
15981         ,   x_sub_component_tbl         => l_sub_component_tbl
15982         ,   x_rev_operation_tbl         => l_rev_operation_tbl    --L1
15983         ,   x_rev_op_resource_tbl       => l_rev_op_resource_tbl  --L1
15984         ,   x_rev_sub_resource_tbl      => l_rev_sub_resource_tbl --L1
15985         ,   x_Mesg_Token_Tbl            => l_Mesg_Token_Tbl
15986         ,   x_return_status             => l_return_status
15987 	,    x_disable_revision          => x_disable_revision        --Bug no:3034642
15988         );
15989 
15990        -- Bug 6657209. Reset the global variable after Rev_items are processed.
15991        Eng_Default_Revised_Item.G_OLD_SCHED_DATE := NULL;
15992 
15993 	-- Added by AS on 03/22/99 to fix bug 853529
15994 
15995         IF NVL(l_return_status, 'S') = 'Q'
15996         THEN
15997                 l_return_status := 'F';
15998                 RAISE G_EXC_QUIT_IMPORT;
15999         ELSIF NVL(l_return_status, 'S') = 'U'
16000         THEN
16001                 RAISE G_EXC_QUIT_IMPORT;
16002 
16003         --  Added by AS on 03/17/99 to fix bug 852322
16004         ELSIF NVL(l_return_status, 'S') <> 'S'
16005         THEN
16006                 l_bo_return_status := l_return_status;
16007         END IF;
16008 
16009     END IF;
16010 
16011    IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('BO error status: ' || l_bo_return_status); END IF;
16012 
16013     --  Revised Components
16014 
16015     IF l_rev_component_tbl.Count <> 0
16016     THEN
16017         IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug(' '); END IF;
16018         IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('PVT API: Calling Rev_Comps'); END IF;
16019 
16020         Rev_Comps
16021         (   p_validation_level          => p_validation_level
16022         ,   p_rev_component_tbl         => l_rev_component_tbl
16023         ,   p_ref_designator_tbl        => l_ref_designator_tbl
16024         ,   p_sub_component_tbl         => l_sub_component_tbl
16025         ,   x_rev_component_tbl         => l_rev_component_tbl
16026         ,   x_ref_designator_tbl        => l_ref_designator_tbl
16027         ,   x_sub_component_tbl         => l_sub_component_tbl
16028         ,   x_Mesg_Token_Tbl            => l_Mesg_Token_Tbl
16029         ,   x_return_status             => l_return_status
16030         );
16031 	-- Added by AS on 03/22/99 to fix bug 853529
16032 
16033         IF NVL(l_return_status, 'S') = 'Q'
16034         THEN
16035                 l_return_status := 'F';
16036                 RAISE G_EXC_QUIT_IMPORT;
16037         ELSIF NVL(l_return_status, 'S') = 'U'
16038         THEN
16039                 RAISE G_EXC_QUIT_IMPORT;
16040 
16041         --  Added by AS on 03/17/99 to fix bug 852322
16042         ELSIF NVL(l_return_status, 'S') <> 'S'
16043         THEN
16044                 l_bo_return_status := l_return_status;
16045         END IF;
16046 
16047     END IF;
16048 
16049    IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('BO error status: ' || l_bo_return_status); END IF;
16050 
16051     --  Reference Designators
16052 
16053     IF l_ref_designator_tbl.Count <> 0
16054     THEN
16055         IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug(' '); END IF;
16056         IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('PVT API: Calling Ref_Desgs'); END IF;
16057 
16058         Ref_Desgs
16059         (   p_validation_level          => p_validation_level
16060         ,   p_ref_designator_tbl        => l_ref_designator_tbl
16061         ,   p_sub_component_tbl         => l_sub_component_tbl
16062         ,   x_ref_designator_tbl        => l_ref_designator_tbl
16063         ,   x_sub_component_tbl         => l_sub_component_tbl
16064         ,   x_Mesg_Token_Tbl            => l_Mesg_Token_Tbl
16065         ,   x_return_status             => l_return_status
16066         );
16067 	-- Added by AS on 03/22/99 to fix bug 853529
16068 
16069         IF NVL(l_return_status, 'S') = 'Q'
16070         THEN
16071                 l_return_status := 'F';
16072                 RAISE G_EXC_QUIT_IMPORT;
16073         ELSIF NVL(l_return_status, 'S') = 'U'
16074         THEN
16075                 RAISE G_EXC_QUIT_IMPORT;
16076 
16077         --  Added by AS on 03/17/99 to fix bug 852322
16078         ELSIF NVL(l_return_status, 'S') <> 'S'
16079         THEN
16080                 l_bo_return_status := l_return_status;
16081         END IF;
16082 
16083     END IF;
16084 
16085    IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('BO error status: ' || l_bo_return_status); END IF;
16086 
16087     --  Substitute Components
16088 
16089     IF l_Sub_Component_Tbl.Count <> 0
16090     THEN
16091         IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug(' '); END IF;
16092         IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('PVT API: Calling Sub_Comps'); END IF;
16093 
16094         Sub_Comps
16095         (   p_validation_level          => p_validation_level
16096         ,   p_sub_component_tbl         => l_sub_component_tbl
16097         ,   x_sub_component_tbl         => l_sub_component_tbl
16098         ,   x_Mesg_Token_Tbl            => l_Mesg_Token_Tbl
16099         ,   x_return_status             => l_return_status
16100         );
16101 	-- Added by AS on 03/22/99 to fix bug 853529
16102 
16103         IF NVL(l_return_status, 'S') = 'Q'
16104         THEN
16105                 l_return_status := 'F';
16106                 RAISE G_EXC_QUIT_IMPORT;
16107         ELSIF NVL(l_return_status, 'S') = 'U'
16108         THEN
16109                 RAISE G_EXC_QUIT_IMPORT;
16110 
16111         --  Added by AS on 03/17/99 to fix bug 852322
16112         ELSIF NVL(l_return_status, 'S') <> 'S'
16113         THEN
16114                 l_bo_return_status := l_return_status;
16115         END IF;
16116 
16117     END IF;
16118 
16119    IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('BO error status: ' || l_bo_return_status); END IF;
16120 
16121 
16122   --  L1:  Operation
16123 
16124     IF l_rev_operation_tbl.Count <> 0
16125     THEN
16126         IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug(' '); END IF;
16127         IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('PVT API: Calling ECO operation'); END IF;
16128 
16129        Rev_Operation_Sequences
16130         (   p_validation_level          => p_validation_level
16131         ,   p_rev_operation_tbl         => l_rev_operation_tbl
16132         ,   p_rev_op_resource_tbl       => l_rev_op_resource_tbl
16133         ,   p_rev_sub_resource_tbl      => l_rev_sub_resource_tbl
16134         ,   x_rev_operation_tbl         => l_rev_operation_tbl
16135         ,   x_rev_op_resource_tbl       => l_rev_op_resource_tbl
16136         ,   x_rev_sub_resource_tbl      => l_rev_sub_resource_tbl
16137         ,   x_Mesg_Token_Tbl            => l_Mesg_Token_Tbl
16138         ,   x_return_status             => l_return_status
16139         );
16140 	IF NVL(l_return_status, 'S') = 'Q'
16141         THEN
16142                 l_return_status := 'F';
16143                 RAISE G_EXC_QUIT_IMPORT;
16144         ELSIF NVL(l_return_status, 'S') = 'U'
16145         THEN
16146                 RAISE G_EXC_QUIT_IMPORT;
16147 
16148         ELSIF NVL(l_return_status, 'S') <> 'S'
16149         THEN
16150                 l_bo_return_status := l_return_status;
16151         END IF;
16152 
16153     END IF;
16154 
16155    IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('BO error status: ' || l_bo_return_status); END IF;
16156 
16157 --  L1:  Operation Resource
16158 
16159     IF l_rev_op_resource_tbl.Count <> 0
16160     THEN
16161         IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug(' '); END IF;
16162         IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('PVT API: Calling ECO resource'); END IF;
16163 
16164         Rev_Operation_Resources
16165         (   p_validation_level          => p_validation_level
16166         ,   p_rev_op_resource_tbl       => l_rev_op_resource_tbl
16167         ,   p_rev_sub_resource_tbl      => l_rev_sub_resource_tbl
16168         ,   x_rev_op_resource_tbl       => l_rev_op_resource_tbl
16169         ,   x_rev_sub_resource_tbl      => l_rev_sub_resource_tbl
16170         ,   x_Mesg_Token_Tbl            => l_Mesg_Token_Tbl
16171         ,   x_return_status             => l_return_status
16172         );
16173 	IF NVL(l_return_status, 'S') = 'Q'
16174         THEN
16175                 l_return_status := 'F';
16176                 RAISE G_EXC_QUIT_IMPORT;
16177         ELSIF NVL(l_return_status, 'S') = 'U'
16178         THEN
16179                 RAISE G_EXC_QUIT_IMPORT;
16180 
16181         ELSIF NVL(l_return_status, 'S') <> 'S'
16182         THEN
16183                 l_bo_return_status := l_return_status;
16184         END IF;
16185 
16186     END IF;
16187 
16188    IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('BO error status: ' || l_bo_return_status); END IF;
16189 
16190 --  L1: Substitute resource
16191 
16192     IF l_rev_sub_resource_tbl.Count <> 0
16193     THEN
16194         IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug(' '); END IF;
16195         IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('PVT API: Calling ECO substitute resource'); END IF;
16196 
16197       Rev_Sub_Operation_Resources
16198         (   p_validation_level          => p_validation_level
16199         ,   p_rev_sub_resource_tbl      => l_rev_sub_resource_tbl
16200         ,   x_rev_sub_resource_tbl      => l_rev_sub_resource_tbl
16201         ,   x_Mesg_Token_Tbl            => l_Mesg_Token_Tbl
16202         ,   x_return_status             => l_return_status
16203         );
16204 	IF NVL(l_return_status, 'S') = 'Q'
16205         THEN
16206                 l_return_status := 'F';
16207                 RAISE G_EXC_QUIT_IMPORT;
16208         ELSIF NVL(l_return_status, 'S') = 'U'
16209         THEN
16210                 RAISE G_EXC_QUIT_IMPORT;
16211 
16212         ELSIF NVL(l_return_status, 'S') <> 'S'
16213         THEN
16214                 l_bo_return_status := l_return_status;
16215         END IF;
16216 
16217     END IF;
16218 
16219    IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('BO error status: ' || l_bo_return_status); END IF;
16220 
16221     --  Done processing, load OUT parameters.
16222 
16223     --  Added by AS on 03/17/99 to fix bug 852322
16224     x_return_status                := l_bo_return_status;
16225 
16226     x_ECO_rec                      := l_ECO_rec;
16227     x_eco_revision_tbl             := l_eco_revision_tbl;
16228     x_revised_item_tbl             := l_revised_item_tbl;
16229     x_rev_component_tbl            := l_rev_component_tbl;
16230     x_ref_designator_tbl           := l_ref_designator_tbl;
16231     x_sub_component_tbl            := l_sub_component_tbl;
16232     x_rev_operation_tbl            := l_rev_operation_tbl;     --L1
16233     x_rev_op_resource_tbl          := l_rev_op_resource_tbl;   --L1
16234     x_rev_sub_resource_tbl         := l_rev_sub_resource_tbl;  --L1
16235     x_change_line_tbl              := l_change_line_tbl ;      -- Eng Change
16236 
16237 
16238 
16239     -- Initialize System_Information Unit_Effectivity flag
16240 
16241 
16242     --  Clear API cache.
16243 
16244     IF p_control_rec.clear_api_cache THEN
16245 
16246         NULL;
16247 
16248     END IF;
16249 
16250     --  Clear API request tbl.
16251 
16252     IF p_control_rec.clear_api_requests THEN
16253 
16254         NULL;
16255 
16256     END IF;
16257 
16258     -- Reset system_information business object flags
16259 
16260     ENG_GLOBALS.Set_ECO_Impl( p_eco_impl        => NULL);
16261     ENG_GLOBALS.Set_ECO_Cancl( p_eco_cancl      => NULL);
16262     ENG_GLOBALS.Set_Wkfl_Process( p_wkfl_process=> NULL);
16263     ENG_GLOBALS.Set_ECO_Access( p_eco_access    => NULL);
16264     ENG_GLOBALS.Set_STD_Item_Access( p_std_item_access => NULL);
16265     ENG_GLOBALS.Set_MDL_Item_Access( p_mdl_item_access => NULL);
16266     ENG_GLOBALS.Set_PLN_Item_Access( p_pln_item_access => NULL);
16267     ENG_GLOBALS.Set_OC_Item_Access( p_oc_item_access   => NULL);
16268 
16269     -- Find the Organization ID corresponding to the Organization Code
16270     l_organization_id := eng_val_to_id.organization
16271         ( l_eco_rec.organization_code, l_err_text);
16272 
16273     -- Ehn 10647772: Change Order Workflow Auto Explosion and Submission
16274     Explode_WF_Routing(p_change_notice => l_ECO_rec.eco_name,
16275             p_org_id => l_organization_id,
16276             x_return_status => l_return_status,
16277             x_Mesg_Token_Tbl => l_Mesg_Token_Tbl);
16278 
16279     --Bug No: 3737881
16280     --Commenting out the following code as no 'Commit' should
16281     --be done in this API.
16282     --IF ENG_GLOBALS.G_ENG_LAUNCH_IMPORT = 1 THEN
16283     --       Error_Handler.Write_To_ConcurrentLog;
16284     --       Error_Handler.WRITE_TO_INTERFACETABLE;
16285     --       COMMIT;
16286     --END IF;
16287 
16288 EXCEPTION
16289 
16290     WHEN EXC_ERR_PVT_API_MAIN THEN
16291 
16292         Eco_Error_Handler.Log_Error
16293                 (  p_ECO_rec            => l_ECO_rec
16294                 ,  p_eco_revision_tbl   => l_eco_revision_tbl
16295                 ,  p_change_line_tbl    => l_change_line_tbl -- Eng Change
16296                 ,  p_revised_item_tbl   => l_revised_item_tbl
16297                 ,  p_rev_component_tbl  => l_rev_component_tbl
16298                 ,  p_ref_designator_tbl => l_ref_designator_tbl
16299                 ,  p_sub_component_tbl  => l_sub_component_tbl
16300                 ,  p_rev_operation_tbl    => l_rev_operation_tbl    --L1
16301                 ,  p_rev_op_resource_tbl  => l_rev_op_resource_tbl  --L1
16302                 ,  p_rev_sub_resource_tbl => l_rev_sub_resource_tbl --L1
16303                 ,  p_mesg_token_tbl     => l_mesg_token_tbl
16304                 ,  p_error_status       => FND_API.G_RET_STS_UNEXP_ERROR
16305                 ,  p_other_status       => Error_Handler.G_STATUS_NOT_PICKED
16306                 ,  p_other_message      => l_other_message
16307                 ,  p_other_token_tbl    => l_other_token_tbl
16308                 ,  p_error_level        => 0
16309                 ,  x_ECO_rec            => l_ECO_rec
16310                 ,  x_eco_revision_tbl   => l_eco_revision_tbl
16311                 ,  x_change_line_tbl    => l_change_line_tbl -- Eng Change
16312                 ,  x_revised_item_tbl   => l_revised_item_tbl
16313                 ,  x_rev_component_tbl  => l_rev_component_tbl
16314                 ,  x_ref_designator_tbl => l_ref_designator_tbl
16315                 ,  x_sub_component_tbl  => l_sub_component_tbl
16316                 ,  x_rev_operation_tbl    => l_rev_operation_tbl    --L1
16317                 ,  x_rev_op_resource_tbl  => l_rev_op_resource_tbl  --L1
16318                 ,  x_rev_sub_resource_tbl => l_rev_sub_resource_tbl --L1
16319                 );
16320 
16321         x_return_status                := l_return_status;
16322         x_ECO_rec                      := l_ECO_rec;
16323         x_eco_revision_tbl             := l_eco_revision_tbl;
16324         x_revised_item_tbl             := l_revised_item_tbl;
16325         x_rev_component_tbl            := l_rev_component_tbl;
16326         x_ref_designator_tbl           := l_ref_designator_tbl;
16327         x_sub_component_tbl            := l_sub_component_tbl;
16328         x_change_line_tbl              := l_change_line_tbl ;      -- Eng Change
16329 
16330         -- Reset system_information business object flags
16331 
16332     ENG_GLOBALS.Set_ECO_Impl( p_eco_impl        => NULL);
16333     ENG_GLOBALS.Set_ECO_Cancl( p_eco_cancl      => NULL);
16334     ENG_GLOBALS.Set_Wkfl_Process( p_wkfl_process=> NULL);
16335     ENG_GLOBALS.Set_ECO_Access( p_eco_access    => NULL);
16336     ENG_GLOBALS.Set_STD_Item_Access( p_std_item_access => NULL);
16337     ENG_GLOBALS.Set_MDL_Item_Access( p_mdl_item_access => NULL);
16338     ENG_GLOBALS.Set_PLN_Item_Access( p_pln_item_access => NULL);
16339     ENG_GLOBALS.Set_OC_Item_Access( p_oc_item_access   => NULL);
16340 
16341     WHEN G_EXC_QUIT_IMPORT THEN
16342 
16343         x_return_status                := l_return_status;
16344         x_ECO_rec                      := l_ECO_rec;
16345         x_eco_revision_tbl             := l_eco_revision_tbl;
16346         x_revised_item_tbl             := l_revised_item_tbl;
16347         x_rev_component_tbl            := l_rev_component_tbl;
16348         x_ref_designator_tbl           := l_ref_designator_tbl;
16349         x_sub_component_tbl            := l_sub_component_tbl;
16350         x_rev_operation_tbl            := l_rev_operation_tbl;     --L1
16351         x_rev_op_resource_tbl          := l_rev_op_resource_tbl;   --L1
16352         x_rev_sub_resource_tbl         := l_rev_sub_resource_tbl;  --L1
16353         x_change_line_tbl              := l_change_line_tbl ;      -- Eng Change
16354 
16355         -- Reset system_information business object flags
16356 
16357     ENG_GLOBALS.Set_ECO_Impl( p_eco_impl        => NULL);
16358     ENG_GLOBALS.Set_ECO_Cancl( p_eco_cancl      => NULL);
16359     ENG_GLOBALS.Set_Wkfl_Process( p_wkfl_process=> NULL);
16360     ENG_GLOBALS.Set_ECO_Access( p_eco_access    => NULL);
16361     ENG_GLOBALS.Set_STD_Item_Access( p_std_item_access => NULL);
16362     ENG_GLOBALS.Set_MDL_Item_Access( p_mdl_item_access => NULL);
16363     ENG_GLOBALS.Set_PLN_Item_Access( p_pln_item_access => NULL);
16364     ENG_GLOBALS.Set_OC_Item_Access( p_oc_item_access   => NULL);
16365 
16366     WHEN OTHERS THEN
16367 
16368         IF FND_MSG_PUB.Check_Msg_Level(FND_MSG_PUB.G_MSG_LVL_UNEXP_ERROR)
16369         THEN
16370                 l_err_text := G_PKG_NAME || ' : Process ECO '
16371                         || substrb(SQLERRM,1,200);
16372                 Error_Handler.Add_Error_Token
16373                         ( p_Message_Text => l_err_text
16374                         , p_Mesg_Token_Tbl => l_Mesg_Token_Tbl
16375                         , x_Mesg_Token_Tbl => l_Mesg_Token_Tbl
16376                         );
16377         END IF;
16378 
16379         Eco_Error_Handler.Log_Error
16380                 (  p_ECO_rec            => l_ECO_rec
16381                 ,  p_eco_revision_tbl   => l_eco_revision_tbl
16382                 ,  p_change_line_tbl    => l_change_line_tbl -- Eng Change
16383                 ,  p_revised_item_tbl   => l_revised_item_tbl
16384                 ,  p_rev_component_tbl  => l_rev_component_tbl
16385                 ,  p_ref_designator_tbl => l_ref_designator_tbl
16386                 ,  p_sub_component_tbl  => l_sub_component_tbl
16387                 ,  p_rev_operation_tbl    => l_rev_operation_tbl    --L1
16388                 ,  p_rev_op_resource_tbl  => l_rev_op_resource_tbl  --L1
16389                 ,  p_rev_sub_resource_tbl => l_rev_sub_resource_tbl --L1
16390                 ,  p_mesg_token_tbl     => l_mesg_token_tbl
16391                 ,  p_error_status       => FND_API.G_RET_STS_UNEXP_ERROR
16392                 ,  p_other_status       => Error_Handler.G_STATUS_NOT_PICKED
16393                 ,  p_other_message      => l_other_message
16394                 ,  p_other_token_tbl    => l_other_token_tbl
16395                 ,  p_error_level        => 0
16396                 ,  x_ECO_rec            => l_ECO_rec
16397                 ,  x_eco_revision_tbl   => l_eco_revision_tbl
16398                 ,  x_change_line_tbl    => l_change_line_tbl -- Eng Change
16399                 ,  x_revised_item_tbl   => l_revised_item_tbl
16400                 ,  x_rev_component_tbl  => l_rev_component_tbl
16401                 ,  x_ref_designator_tbl => l_ref_designator_tbl
16402                 ,  x_sub_component_tbl  => l_sub_component_tbl
16403                 ,  x_rev_operation_tbl    => l_rev_operation_tbl    --L1
16404                 ,  x_rev_op_resource_tbl  => l_rev_op_resource_tbl  --L1
16405                 ,  x_rev_sub_resource_tbl => l_rev_sub_resource_tbl --L1
16406                 );
16407 
16408         x_return_status                := l_return_status;
16409         x_ECO_rec                      := l_ECO_rec;
16410         x_eco_revision_tbl             := l_eco_revision_tbl;
16411         x_revised_item_tbl             := l_revised_item_tbl;
16412         x_rev_component_tbl            := l_rev_component_tbl;
16413         x_ref_designator_tbl           := l_ref_designator_tbl;
16414         x_sub_component_tbl            := l_sub_component_tbl;
16415         x_rev_operation_tbl            := l_rev_operation_tbl;     --L1
16416         x_rev_op_resource_tbl          := l_rev_op_resource_tbl;   --L1
16417         x_rev_sub_resource_tbl         := l_rev_sub_resource_tbl;  --L1
16418         x_change_line_tbl              := l_change_line_tbl ;      -- Eng Change
16419 
16420         -- Reset system_information business object flags
16421 
16422     ENG_GLOBALS.Set_ECO_Impl( p_eco_impl        => NULL);
16423     ENG_GLOBALS.Set_ECO_Cancl( p_eco_cancl      => NULL);
16424     ENG_GLOBALS.Set_Wkfl_Process( p_wkfl_process=> NULL);
16425     ENG_GLOBALS.Set_ECO_Access( p_eco_access    => NULL);
16426     ENG_GLOBALS.Set_STD_Item_Access( p_std_item_access => NULL);
16427     ENG_GLOBALS.Set_MDL_Item_Access( p_mdl_item_access => NULL);
16428     ENG_GLOBALS.Set_PLN_Item_Access( p_pln_item_access => NULL);
16429     ENG_GLOBALS.Set_OC_Item_Access( p_oc_item_access   => NULL);
16430 
16431 END Process_Eco;
16432 
16433 --  Start of Comments
16434 --  API name    Lock_Eco
16435 --  Type        Private
16436 --  Function
16437 --
16438 --  Pre-reqs
16439 --
16440 --  Parameters
16441 --
16442 --  Version     Current version = 1.0
16443 --              Initial version = 1.0
16444 --
16445 --  Notes
16446 --
16447 --  End of Comments
16448 
16449 PROCEDURE Lock_Eco
16450 (   p_api_version_number            IN  NUMBER
16451 ,   p_init_msg_list                 IN  VARCHAR2 := FND_API.G_FALSE
16452 ,   x_return_status                 OUT NOCOPY VARCHAR2
16453 ,   x_msg_count                     OUT NOCOPY NUMBER
16454 ,   x_msg_data                      OUT NOCOPY VARCHAR2
16455 ,   p_ECO_rec                       IN  ENG_Eco_PUB.Eco_Rec_Type :=
16456                                         ENG_Eco_PUB.G_MISS_ECO_REC
16457 ,   p_eco_revision_tbl              IN  ENG_Eco_PUB.Eco_Revision_Tbl_Type :=
16458                                         ENG_Eco_PUB.G_MISS_ECO_REVISION_TBL
16459 ,   p_revised_item_tbl              IN  ENG_Eco_PUB.Revised_Item_Tbl_Type :=
16460                                         ENG_Eco_PUB.G_MISS_REVISED_ITEM_TBL
16461 ,   p_rev_component_tbl             IN  BOM_BO_PUB.Rev_Component_Tbl_Type :=
16462                                         BOM_BO_PUB.G_MISS_REV_COMPONENT_TBL
16463 ,   p_ref_designator_tbl            IN  BOM_BO_PUB.Ref_Designator_Tbl_Type :=
16464                                         BOM_BO_PUB.G_MISS_REF_DESIGNATOR_TBL
16465 ,   p_sub_component_tbl             IN  BOM_BO_PUB.Sub_Component_Tbl_Type :=
16466                                         BOM_BO_PUB.G_MISS_SUB_COMPONENT_TBL
16467 ,   x_ECO_rec                       IN OUT NOCOPY ENG_Eco_PUB.Eco_Rec_Type
16468 ,   x_eco_revision_tbl              IN OUT NOCOPY ENG_Eco_PUB.Eco_Revision_Tbl_Type
16469 ,   x_revised_item_tbl              IN OUT NOCOPY ENG_Eco_PUB.Revised_Item_Tbl_Type
16470 ,   x_rev_component_tbl             IN OUT NOCOPY BOM_BO_PUB.Rev_Component_Tbl_Type
16471 ,   x_ref_designator_tbl            IN OUT NOCOPY BOM_BO_PUB.Ref_Designator_Tbl_Type
16472 ,   x_sub_component_tbl             IN OUT NOCOPY BOM_BO_PUB.Sub_Component_Tbl_Type
16473 ,   x_err_text                      OUT NOCOPY VARCHAR2
16474 )
16475 IS
16476 l_api_version_number          CONSTANT NUMBER := 1.0;
16477 l_api_name                    CONSTANT VARCHAR2(30):= 'Lock_Eco';
16478 l_return_status               VARCHAR2(1) := FND_API.G_RET_STS_SUCCESS;
16479 l_eco_revision_rec            ENG_Eco_PUB.Eco_Revision_Rec_Type;
16480 l_revised_item_rec            ENG_Eco_PUB.Revised_Item_Rec_Type;
16481 l_rev_component_rec           BOM_BO_PUB.Rev_Component_Rec_Type;
16482 l_ref_designator_rec          BOM_BO_PUB.Ref_Designator_Rec_Type;
16483 l_sub_component_rec           BOM_BO_PUB.Sub_Component_Rec_Type;
16484 BEGIN
16485 
16486     --  Standard call to check for call compatibility
16487 
16488 NULL;
16489 
16490 /*********************** Temporarily commented *****************************
16491 
16492     IF NOT FND_API.Compatible_API_Call
16493            (   l_api_version_number
16494            ,   p_api_version_number
16495            ,   l_api_name
16496            ,   G_PKG_NAME
16497            )
16498     THEN
16499         RAISE FND_API.G_EXC_UNEXPECTED_ERROR;
16500     END IF;
16501 
16502     --  Initialize message list.
16503 
16504     IF FND_API.to_Boolean(p_init_msg_list) THEN
16505         FND_MSG_PUB.initialize;
16506     END IF;
16507 
16508     --  Set Savepoint
16509 
16510     SAVEPOINT Lock_Eco_PVT;
16511 
16512     --  Lock ECO
16513 
16514     IF p_ECO_rec.operation = ENG_GLOBALS.G_OPR_LOCK THEN
16515 
16516         ENG_Eco_Util.Lock_Row
16517         (   p_ECO_rec                     => p_ECO_rec
16518         ,   x_ECO_rec                     => x_ECO_rec
16519         ,   x_return_status               => l_return_status
16520         ,   x_err_text                    => x_err_text
16521         );
16522 
16523         IF l_return_status = FND_API.G_RET_STS_UNEXP_ERROR THEN
16524             RAISE FND_API.G_EXC_UNEXPECTED_ERROR;
16525         ELSIF l_return_status = FND_API.G_RET_STS_ERROR THEN
16526             RAISE FND_API.G_EXC_ERROR;
16527         END IF;
16528 
16529 
16530     END IF;
16531 
16532     --  Lock eco_revision
16533 
16534     FOR I IN 1..p_eco_revision_tbl.COUNT LOOP
16535 
16536         IF p_eco_revision_tbl(I).operation = ENG_GLOBALS.G_OPR_LOCK THEN
16537 
16538             ENG_Eco_Revision_Util.Lock_Row
16539             (   p_eco_revision_rec            => p_eco_revision_tbl(I)
16540             ,   x_eco_revision_rec            => l_eco_revision_rec
16541             ,   x_return_status               => l_return_status
16542             ,   x_err_text                          => x_err_text
16543             );
16544 
16545             IF l_return_status = FND_API.G_RET_STS_UNEXP_ERROR THEN
16546                 RAISE FND_API.G_EXC_UNEXPECTED_ERROR;
16547             ELSIF l_return_status = FND_API.G_RET_STS_ERROR THEN
16548                 RAISE FND_API.G_EXC_ERROR;
16549             END IF;
16550 
16551             x_eco_revision_tbl(I)          := l_eco_revision_rec;
16552 
16553         END IF;
16554 
16555     END LOOP;
16556 
16557     --  Lock revised_item
16558 
16559     FOR I IN 1..p_revised_item_tbl.COUNT LOOP
16560 
16561         IF p_revised_item_tbl(I).operation = ENG_GLOBALS.G_OPR_LOCK THEN
16562 
16563             ENG_Revised_Item_Util.Lock_Row
16564             (   p_revised_item_rec            => p_revised_item_tbl(I)
16565             ,   x_revised_item_rec            => l_revised_item_rec
16566             ,   x_return_status               => l_return_status
16567             ,   x_err_text                    => x_err_text
16568             );
16569 
16570             IF l_return_status = FND_API.G_RET_STS_UNEXP_ERROR THEN
16571                 RAISE FND_API.G_EXC_UNEXPECTED_ERROR;
16572             ELSIF l_return_status = FND_API.G_RET_STS_ERROR THEN
16573                 RAISE FND_API.G_EXC_ERROR;
16574             END IF;
16575 
16576             x_revised_item_tbl(I)          := l_revised_item_rec;
16577 
16578         END IF;
16579 
16580     END LOOP;
16581 
16582     --  Lock rev_component
16583 
16584     FOR I IN 1..p_rev_component_tbl.COUNT LOOP
16585 
16586         IF p_rev_component_tbl(I).operation = ENG_GLOBALS.G_OPR_LOCK THEN
16587 
16588             Bom_Bom_Component_Util.Lock_Row
16589             (   p_rev_component_rec           => p_rev_component_tbl(I)
16590             ,   x_rev_component_rec           => l_rev_component_rec
16591             ,   x_return_status               => l_return_status
16592                 ,   x_err_text                      => x_err_text
16593             );
16594 
16595             IF l_return_status = FND_API.G_RET_STS_UNEXP_ERROR THEN
16596                 RAISE FND_API.G_EXC_UNEXPECTED_ERROR;
16597             ELSIF l_return_status = FND_API.G_RET_STS_ERROR THEN
16598                 RAISE FND_API.G_EXC_ERROR;
16599             END IF;
16600 
16601             x_rev_component_tbl(I)         := l_rev_component_rec;
16602 
16603         END IF;
16604 
16605     END LOOP;
16606 
16607     --  Lock ref_designator
16608 
16609     FOR I IN 1..p_ref_designator_tbl.COUNT LOOP
16610 
16611         IF p_ref_designator_tbl(I).operation = ENG_GLOBALS.G_OPR_LOCK THEN
16612 
16613             Bom_Ref_Designator_Util.Lock_Row
16614             (   p_ref_designator_rec          => p_ref_designator_tbl(I)
16615             ,   x_ref_designator_rec          => l_ref_designator_rec
16616             ,   x_return_status               => l_return_status
16617             ,   x_err_text                    => x_err_text
16618             );
16619 
16620             IF l_return_status = FND_API.G_RET_STS_UNEXP_ERROR THEN
16621                 RAISE FND_API.G_EXC_UNEXPECTED_ERROR;
16622             ELSIF l_return_status = FND_API.G_RET_STS_ERROR THEN
16623                 RAISE FND_API.G_EXC_ERROR;
16624             END IF;
16625 
16626             x_ref_designator_tbl(I)        := l_ref_designator_rec;
16627 
16628         END IF;
16629 
16630     END LOOP;
16631 
16632     --  Lock sub_component
16633 
16634     FOR I IN 1..p_sub_component_tbl.COUNT LOOP
16635 
16636         IF p_sub_component_tbl(I).operation = ENG_GLOBALS.G_OPR_LOCK THEN
16637 
16638             ENG_Sub_Component_Util.Lock_Row
16639             (   p_sub_component_rec           => p_sub_component_tbl(I)
16640             ,   x_sub_component_rec           => l_sub_component_rec
16641             ,   x_return_status               => l_return_status
16642             ,   x_err_text                    => x_err_text
16643             );
16644 
16645             IF l_return_status = FND_API.G_RET_STS_UNEXP_ERROR THEN
16646                 RAISE FND_API.G_EXC_UNEXPECTED_ERROR;
16647             ELSIF l_return_status = FND_API.G_RET_STS_ERROR THEN
16648                 RAISE FND_API.G_EXC_ERROR;
16649             END IF;
16650 
16651             x_sub_component_tbl(I)         := l_sub_component_rec;
16652 
16653         END IF;
16654 
16655     END LOOP;
16656 
16657     --  Set return status
16658 
16659     x_return_status := FND_API.G_RET_STS_SUCCESS;
16660 
16661     --  Get message count and data
16662 
16663     FND_MSG_PUB.Count_And_Get
16664     (   p_count                       => x_msg_count
16665     ,   p_data                        => x_msg_data
16666     );
16667 
16668 
16669 EXCEPTION
16670 
16671     WHEN FND_API.G_EXC_ERROR THEN
16672 
16673         x_return_status := FND_API.G_RET_STS_ERROR;
16674 
16675         --  Get message count and data
16676 
16677         FND_MSG_PUB.Count_And_Get
16678         (   p_count                       => x_msg_count
16679         ,   p_data                        => x_msg_data
16680         );
16681 
16682         --  Rollback
16683 
16684         ROLLBACK TO Lock_Eco_PVT;
16685 
16686     WHEN FND_API.G_EXC_UNEXPECTED_ERROR THEN
16687 
16688         x_return_status := FND_API.G_RET_STS_UNEXP_ERROR ;
16689 
16690         --  Get message count and data
16691 
16692         FND_MSG_PUB.Count_And_Get
16693         (   p_count                       => x_msg_count
16694         ,   p_data                        => x_msg_data
16695         );
16696 
16697         --  Rollback
16698 
16699         ROLLBACK TO Lock_Eco_PVT;
16700 
16701     WHEN OTHERS THEN
16702 
16703         x_return_status := FND_API.G_RET_STS_UNEXP_ERROR ;
16704 
16705         IF FND_MSG_PUB.Check_Msg_Level(FND_MSG_PUB.G_MSG_LVL_UNEXP_ERROR)
16706         THEN
16707             FND_MSG_PUB.Add_Exc_Msg
16708             (   G_PKG_NAME
16709             ,   'Lock_Eco'
16710             );
16711         END IF;
16712 
16713         --  Get message count and data
16714 
16715         FND_MSG_PUB.Count_And_Get
16716         (   p_count                       => x_msg_count
16717         ,   p_data                        => x_msg_data
16718         );
16719 
16720         --  Rollback
16721 
16722         ROLLBACK TO Lock_Eco_PVT;
16723 
16724 ****************************************************************************/
16725 
16726 END Lock_Eco;
16727 
16728  -- Ehn 10647772: Change Order Workflow Auto Explosion and Submission
16729 PROCEDURE Explode_WF_Routing(p_change_notice IN VARCHAR2,
16730                     p_org_id        IN NUMBER,
16731                     x_return_status IN  OUT NOCOPY   VARCHAR2,
16732                     x_Mesg_Token_Tbl  IN OUT NOCOPY  Error_Handler.Mesg_Token_Tbl_Type ) IS
16733 
16734     TYPE Items_Org_Role_Rec_Type IS RECORD(
16735       Grantee_Type VARCHAR2(1) := EGO_ITEM_PUB.G_MISS_CHAR,
16736       Role_Id      NUMBER := EGO_ITEM_PUB.G_MISS_NUM,
16737       Party_Id     NUMBER := EGO_ITEM_PUB.G_MISS_NUM);
16738 
16739     TYPE Items_Org_Role_Tbl_Type IS TABLE OF Items_Org_Role_Rec_Type INDEX BY BINARY_INTEGER;
16740 
16741     l_return_status               VARCHAR2(1);
16742     l_to_route_id NUMBER;
16743     l_people_id   NUMBER;
16744 
16745     l_instance_set_id      number := EGO_ITEM_PUB.G_MISS_NUM;
16746     l_item_role_type_id    number := EGO_ITEM_PUB.G_MISS_NUM;
16747     l_items_org_role_table Items_Org_Role_Tbl_Type;
16748     c_index                number := 1;
16749     t_index                number := 1;
16750 
16751     l_people_existed_flag number := 0;
16752     l_row_inserted_flag number := 0;  -- bug 13860012
16753     l_submit_flag varchar(1) := 1;      -- 1: Yes; 2: No
16754     l_change_mgmt_type_code VARCHAR2(50) := EGO_ITEM_PUB.G_MISS_CHAR;
16755 
16756     l_change_id number;
16757 
16758      -- bug 13921167 start
16759     l_menu_name    VARCHAR2(30) default null;
16760     l_menu_id      number;
16761     l_assignee_id  number;
16762     l_requestor_id NUMBER;
16763 
16764     l_row_count NUMBER default 0;
16765    -- bug 13921167 end
16766 
16767     CURSOR c_get_items_org_roles(cp_instance_set_id IN NUMBER) IS
16768       SELECT 'A' grantee_type,
16769              'A1' name_link,
16770              grants.grant_guid grant_guid,
16771              grants.start_date start_date,
16772              grants.end_date end_date,
16773              grants.instance_type object_key_type,
16774              grants.instance_pk1_value object_key,
16775              ltrim(grantee_global.party_name, '* ') party_name,
16776              NULL company_name,
16777              -1 company_id,
16778              grantee_global.party_id party_id,
16779              granted_menu.menu_name role_name,
16780              granted_menu.menu_name role_description,
16781              obj.obj_name object_name,
16782              granted_menu.menu_id menu_id,
16783              'egorolegranttableviewrolename' switcherCol,
16784              menutl.user_menu_name roleNameLink,
16785              grants.instance_pk1_value pk1_value,
16786              grants.instance_pk2_value pk2_value,
16787              grants.instance_pk3_value pk3_value,
16788              grants.instance_pk4_value pk4_value,
16789              grants.instance_pk5_value pk5_value,
16790              grants.instance_set_id instance_set_id,
16791              grants.ROWID as row_id,
16792              LTRIM(grantee_global.party_name, '* ') as decoded_party_name
16793         FROM fnd_grants   grants,
16794              hz_parties   grantee_global,
16795              fnd_menus    granted_menu,
16796              fnd_objects  obj,
16797              fnd_menus_tl menutl
16798        WHERE obj.obj_name = 'EGO_ITEM'
16799          AND grants.object_id = obj.object_id
16800          AND grants.grantee_type = 'GLOBAL'
16801          AND NVL(grants.end_date, SYSDATE + 1) >= TRUNC(SYSDATE)
16802          AND grants.menu_id = granted_menu.menu_id
16803          AND grants.menu_id = menutl.menu_id
16804          AND menutl.language = USERENV('LANG')
16805          AND grantee_global.party_id = -1000
16806          AND grants.instance_type = 'INSTANCE'
16807          AND grants.instance_pk1_value = '*NULL*'
16808          AND grants.instance_pk2_value = '*NULL*'
16809          AND grants.instance_pk3_value = '*NULL*'
16810          AND grants.instance_pk4_value = '*NULL*'
16811          AND grants.instance_pk5_value = '*NULL*'
16812       union all
16813       SELECT 'A' grantee_type,
16814              'A1' name_link,
16815              grants.grant_guid grant_guid,
16816              grants.start_date start_date,
16817              grants.end_date end_date,
16818              grants.instance_type object_key_type,
16819              grants.instance_pk1_value object_key,
16820              ltrim(grantee_global.party_name, '* ') party_name,
16821              NULL company_name,
16822              -1 company_id,
16823              grantee_global.party_id party_id,
16824              granted_menu.menu_name role_name,
16825              granted_menu.menu_name role_description,
16826              obj.obj_name object_name,
16827              granted_menu.menu_id menu_id,
16828              'egorolegranttableviewrolename' switcherCol,
16829              menutl.user_menu_name roleNameLink,
16830              grants.instance_pk1_value pk1_value,
16831              grants.instance_pk2_value pk2_value,
16832              grants.instance_pk3_value pk3_value,
16833              grants.instance_pk4_value pk4_value,
16834              grants.instance_pk5_value pk5_value,
16835              grants.instance_set_id instance_set_id,
16836              grants.ROWID as row_id,
16837              LTRIM(grantee_global.party_name, '* ') as decoded_party_name
16838         FROM fnd_grants   grants,
16839              hz_parties   grantee_global,
16840              fnd_menus    granted_menu,
16841              fnd_objects  obj,
16842              fnd_menus_tl menutl
16843        WHERE obj.obj_name = 'EGO_ITEM'
16844          AND grants.object_id = obj.object_id
16845          AND grants.grantee_type = 'GLOBAL'
16846          AND NVL(grants.end_date, SYSDATE + 1) >= TRUNC(SYSDATE)
16847          AND grants.menu_id = granted_menu.menu_id
16848          AND grants.menu_id = menutl.menu_id
16849          AND menutl.language = USERENV('LANG')
16850          AND grantee_global.party_id = -1000
16851          AND grants.instance_type = 'SET'
16852          AND grants.instance_set_id = cp_instance_set_id
16853       union all
16854       SELECT 'G' grantee_type,
16855              'G1' name_link,
16856              grants.grant_guid grant_guid,
16857              grants.start_date start_date,
16858              grants.end_date end_date,
16859              grants.instance_type object_key_type,
16860              grants.instance_pk1_value object_key,
16861              grantee_group.group_name party_name,
16862              NULL company_name,
16863              -1 company_id,
16864              grantee_group.group_id party_id,
16865              granted_menu.menu_name role_name,
16866              granted_menu.menu_name role_description,
16867              obj.obj_name object_name,
16868              granted_menu.menu_id menu_id,
16869              'egorolegranttableviewrolename' switcherCol,
16870              menutl.user_menu_name roleNameLink,
16871              grants.instance_pk1_value pk1_value,
16872              grants.instance_pk2_value pk2_value,
16873              grants.instance_pk3_value pk3_value,
16874              grants.instance_pk4_value pk4_value,
16875              grants.instance_pk5_value pk5_value,
16876              grants.instance_set_id instance_set_id,
16877              grants.ROWID as row_id,
16878              grantee_group.group_name as decoded_party_name
16879         FROM fnd_grants   grants,
16880              ego_groups_v grantee_group,
16881              fnd_menus    granted_menu,
16882              fnd_objects  obj,
16883              fnd_menus_tl menutl
16884        WHERE obj.obj_name = 'EGO_ITEM'
16885          AND grants.object_id = obj.object_id
16886          AND grants.grantee_type = 'GROUP'
16887          AND TO_NUMBER(REPLACE(grants.grantee_key, 'HZ_GROUP:', '')) =
16888              grantee_group.group_id
16889          AND grantee_key like 'HZ_GROUP%'
16890          AND NVL(grants.end_date, SYSDATE + 1) >= TRUNC(SYSDATE)
16891          AND grants.menu_id = granted_menu.menu_id
16892          AND grants.menu_id = menutl.menu_id
16893          AND menutl.language = USERENV('LANG')
16894          AND grants.instance_type = 'INSTANCE'
16895          AND grants.instance_pk1_value = '*NULL*'
16896          AND grants.instance_pk2_value = '*NULL*'
16897          AND grants.instance_pk3_value = '*NULL*'
16898          AND grants.instance_pk4_value = '*NULL*'
16899          AND grants.instance_pk5_value = '*NULL*'
16900       union all
16901       SELECT 'G' grantee_type,
16902              'G1' name_link,
16903              grants.grant_guid grant_guid,
16904              grants.start_date start_date,
16905              grants.end_date end_date,
16906              grants.instance_type object_key_type,
16907              grants.instance_pk1_value object_key,
16908              grantee_group.group_name party_name,
16909              NULL company_name,
16910              -1 company_id,
16911              grantee_group.group_id party_id,
16912              granted_menu.menu_name role_name,
16913              granted_menu.menu_name role_description,
16914              obj.obj_name object_name,
16915              granted_menu.menu_id menu_id,
16916              'egorolegranttableviewrolename' switcherCol,
16917              menutl.user_menu_name roleNameLink,
16918              grants.instance_pk1_value pk1_value,
16919              grants.instance_pk2_value pk2_value,
16920              grants.instance_pk3_value pk3_value,
16921              grants.instance_pk4_value pk4_value,
16922              grants.instance_pk5_value pk5_value,
16923              grants.instance_set_id instance_set_id,
16924              grants.ROWID as row_id,
16925              grantee_group.group_name decoded_party_name
16926         FROM fnd_grants   grants,
16927              ego_groups_v grantee_group,
16928              fnd_menus    granted_menu,
16929              fnd_objects  obj,
16930              fnd_menus_tl menutl
16931        WHERE obj.obj_name = 'EGO_ITEM'
16932          AND grants.object_id = obj.object_id
16933          AND grants.grantee_type = 'GROUP'
16934          AND TO_NUMBER(REPLACE(grants.grantee_key, 'HZ_GROUP:', '')) =
16935              grantee_group.group_id
16936          AND grantee_key like 'HZ_GROUP%'
16937          AND NVL(grants.end_date, SYSDATE + 1) >= TRUNC(SYSDATE)
16938          AND grants.menu_id = granted_menu.menu_id
16939          AND grants.menu_id = menutl.menu_id
16940          AND menutl.language = USERENV('LANG')
16941          AND grants.instance_type = 'SET'
16942          AND grants.instance_set_id = cp_instance_set_id
16943       union all
16944       SELECT 'P' grantee_type,
16945              'P1' name_link,
16946              grants.grant_guid grant_guid,
16947              grants.start_date start_date,
16948              grants.end_date end_date,
16949              grants.instance_type object_key_type,
16950              grants.instance_pk1_value object_key,
16951              ltrim(grantee_person.person_name, '* ') party_name,
16952              grantee_person.company_name company_name,
16953              grantee_person.company_id company_id,
16954              grantee_person.person_id party_id,
16955              granted_menu.menu_name role_name,
16956              granted_menu.menu_name role_description,
16957              obj.obj_name object_name,
16958              granted_menu.menu_id menu_id,
16959              'egorolegranttableviewrolename' switcherCol,
16960              menutl.user_menu_name roleNameLink,
16961              grants.instance_pk1_value pk1_value,
16962              grants.instance_pk2_value pk2_value,
16963              grants.instance_pk3_value pk3_value,
16964              grants.instance_pk4_value pk4_value,
16965              grants.instance_pk5_value pk5_value,
16966              grants.instance_set_id instance_set_id,
16967              grants.ROWID as row_id,
16968              LTRIM(grantee_person.person_name, '* ') as decoded_party_name
16969         FROM fnd_grants           grants,
16970              ego_person_company_v grantee_person,
16971              fnd_menus            granted_menu,
16972              fnd_objects          obj,
16973              fnd_menus_tl         menutl
16974        WHERE obj.obj_name = 'EGO_ITEM'
16975          AND grants.object_id = obj.object_id
16976          AND grants.grantee_type = 'USER'
16977          AND TO_NUMBER(REPLACE(grants.grantee_key, 'HZ_PARTY:', '')) =
16978              grantee_person.person_id
16979          AND grantee_key like 'HZ_PARTY%'
16980          AND NVL(grants.end_date, SYSDATE + 1) >= TRUNC(SYSDATE)
16981          AND grants.menu_id = granted_menu.menu_id
16982          AND grants.menu_id = menutl.menu_id
16983          AND menutl.language = USERENV('LANG')
16984          AND grants.instance_type = 'INSTANCE'
16985          AND grants.instance_pk1_value = '*NULL*'
16986          AND grants.instance_pk2_value = '*NULL*'
16987          AND grants.instance_pk3_value = '*NULL*'
16988          AND grants.instance_pk4_value = '*NULL*'
16989          AND grants.instance_pk5_value = '*NULL*'
16990       union all
16991       SELECT 'P' grantee_type,
16992              'P1' name_link,
16993              grants.grant_guid grant_guid,
16994              grants.start_date start_date,
16995              grants.end_date end_date,
16996              grants.instance_type object_key_type,
16997              grants.instance_pk1_value object_key,
16998              ltrim(grantee_person.person_name, '* ') party_name,
16999              grantee_person.company_name company_name,
17000              grantee_person.company_id company_id,
17001              grantee_person.person_id party_id,
17002              granted_menu.menu_name role_name,
17003              granted_menu.menu_name role_description,
17004              obj.obj_name object_name,
17005              granted_menu.menu_id menu_id,
17006              'egorolegranttableviewrolename' switcherCol,
17007              menutl.user_menu_name roleNameLink,
17008              grants.instance_pk1_value pk1_value,
17009              grants.instance_pk2_value pk2_value,
17010              grants.instance_pk3_value pk3_value,
17011              grants.instance_pk4_value pk4_value,
17012              grants.instance_pk5_value pk5_value,
17013              grants.instance_set_id instance_set_id,
17014              grants.ROWID as row_id,
17015              LTRIM(grantee_person.person_name, '* ') as decoded_party_name
17016         FROM fnd_grants           grants,
17017              ego_person_company_v grantee_person,
17018              fnd_menus            granted_menu,
17019              fnd_objects          obj,
17020              fnd_menus_tl         menutl
17021        WHERE obj.obj_name = 'EGO_ITEM'
17022          AND grants.object_id = obj.object_id
17023          AND grants.grantee_type = 'USER'
17024          AND TO_NUMBER(REPLACE(grants.grantee_key, 'HZ_PARTY:', '')) =
17025              grantee_person.person_id
17026          AND grantee_key like 'HZ_PARTY%'
17027          AND NVL(grants.end_date, SYSDATE + 1) >= TRUNC(SYSDATE)
17028          AND grants.menu_id = granted_menu.menu_id
17029          AND grants.menu_id = menutl.menu_id
17030          AND menutl.language = USERENV('LANG')
17031          AND grants.instance_type = 'SET'
17032          AND grants.instance_set_id = cp_instance_set_id
17033       union all
17034       SELECT 'C' grantee_type,
17035              'C1' name_link,
17036              grants.grant_guid grant_id,
17037              grants.start_date start_date,
17038              grants.end_date end_date,
17039              grants.instance_type object_key_type,
17040              grants.instance_pk1_value object_key,
17041              grantee_company.company_name party_name,
17042              grantee_company.company_name company_name,
17043              grantee_company.company_id company_id,
17044              grantee_company.company_id party_id,
17045              granted_menu.menu_name role_name,
17046              granted_menu.menu_name role_description,
17047              obj.obj_name object_name,
17048              granted_menu.menu_id menu_id,
17049              'egorolegranttableviewrolename' switcherCol,
17050              menutl.user_menu_name roleNameLink,
17051              grants.instance_pk1_value pk1_value,
17052              grants.instance_pk2_value pk2_value,
17053              grants.instance_pk3_value pk3_value,
17054              grants.instance_pk4_value pk4_value,
17055              grants.instance_pk5_value pk5_value,
17056              grants.instance_set_id instance_set_id,
17057              grants.ROWID as row_id,
17058              grantee_company.company_name decoded_party_name
17059         FROM fnd_grants      grants,
17060              ego_companies_v grantee_company,
17061              fnd_menus       granted_menu,
17062              fnd_objects     obj,
17063              fnd_menus_tl    menutl
17064        WHERE obj.obj_name = 'EGO_ITEM'
17065          AND grants.object_id = obj.object_id
17066          AND grants.grantee_type = 'COMPANY'
17067          AND NVL(grants.end_date, SYSDATE + 1) >= TRUNC(SYSDATE)
17068          AND grants.menu_id = granted_menu.menu_id
17069          AND grants.menu_id = menutl.menu_id
17070          AND TO_NUMBER(REPLACE(grants.grantee_key, 'HZ_COMPANY:', '')) =
17071              grantee_company.company_id
17072          AND grantee_key like 'HZ_COMPANY%'
17073          AND menutl.language = USERENV('LANG')
17074          AND grants.instance_type = 'INSTANCE'
17075          AND grants.instance_pk1_value = '*NULL*'
17076          AND grants.instance_pk2_value = '*NULL*'
17077          AND grants.instance_pk3_value = '*NULL*'
17078          AND grants.instance_pk4_value = '*NULL*'
17079          AND grants.instance_pk5_value = '*NULL*'
17080       union all
17081       SELECT 'C' grantee_type,
17082              'C1' name_link,
17083              grants.grant_guid grant_id,
17084              grants.start_date start_date,
17085              grants.end_date end_date,
17086              grants.instance_type object_key_type,
17087              grants.instance_pk1_value object_key,
17088              grantee_company.company_name party_name,
17089              grantee_company.company_name company_name,
17090              grantee_company.company_id company_id,
17091              grantee_company.company_id party_id,
17092              granted_menu.menu_name role_name,
17093              granted_menu.menu_name role_description,
17094              obj.obj_name object_name,
17095              granted_menu.menu_id menu_id,
17096              'egorolegranttableviewrolename' switcherCol,
17097              menutl.user_menu_name roleNameLink,
17098              grants.instance_pk1_value pk1_value,
17099              grants.instance_pk2_value pk2_value,
17100              grants.instance_pk3_value pk3_value,
17101              grants.instance_pk4_value pk4_value,
17102              grants.instance_pk5_value pk5_value,
17103              grants.instance_set_id instance_set_id,
17104              grants.ROWID as row_id,
17105              grantee_company.company_name decoded_party_name
17106         FROM fnd_grants      grants,
17107              ego_companies_v grantee_company,
17108              fnd_menus       granted_menu,
17109              fnd_objects     obj,
17110              fnd_menus_tl    menutl
17111        WHERE obj.obj_name = 'EGO_ITEM'
17112          AND grants.object_id = obj.object_id
17113          AND grants.grantee_type = 'COMPANY'
17114          AND NVL(grants.end_date, SYSDATE + 1) >= TRUNC(SYSDATE)
17115          AND grants.menu_id = granted_menu.menu_id
17116          AND grants.menu_id = menutl.menu_id
17117          AND TO_NUMBER(REPLACE(grants.grantee_key, 'HZ_COMPANY:', '')) =
17118              grantee_company.company_id
17119          AND grantee_key like 'HZ_COMPANY%'
17120          AND menutl.language = USERENV('LANG')
17121          AND grants.instance_type = 'SET'
17122          AND grants.instance_set_id = cp_instance_set_id;
17123 
17124     CURSOR C_GET_PARENT_ROLES(cp_role_id IN NUMBER, cp_change_mgmt_type_code IN VARCHAR2) IS
17125       SELECT DISTINCT map.PARENT_OBJECT_ID,
17126                       map.PARENT_ROLE_ID,
17127                       map.CHILD_OBJECT_ID,
17128                       map.CHILD_OBJECT_TYPE,
17129                       map.CHILD_ROLE_ID,
17130                       menus.MENU_NAME CHILD_ROLE,
17131                       decode(e.created_by,
17132                              1,
17133                              menus.description,
17134                              menus.user_menu_name) CHILD_ROLE_NAME,
17135                       lookup.change_mgmt_type_code CHANGE_MGMT_TYPE,
17136                       lookup.name CHANGE_MGMT_TYPE_NAME,
17137                       'ENG_CHANGE'
17138         FROM EGO_OBJ_ROLE_MAPPINGS    map,
17139              fnd_menus_vl             menus,
17140              eng_change_mgmt_types_vl lookup,
17141              fnd_menu_entries         e,
17142              fnd_objects              fo
17143        WHERE menus.menu_id(+) = map.child_role_id
17144          AND e.menu_id(+) = menus.menu_id
17145          AND map.CHILD_OBJECT_TYPE(+) = lookup.change_mgmt_type_code
17146          AND lookup.disable_flag = 'N'
17147          AND lookup.base_change_mgmt_type_code <> 'DOM_DOCUMENT_LIFECYCLE'
17148          AND lookup.change_mgmt_type_code = cp_change_mgmt_type_code
17149          AND fo.obj_name = 'EGO_ITEM'
17150          AND map.PARENT_OBJECT_ID = fo.object_id
17151          AND map.CHILD_ROLE_ID(+) = cp_role_id;
17152 
17153     CURSOR C_CHANGES IS
17154       SELECT CHANGE_LIFECYCLE_STATUS_ID,
17155              ENTITY_NAME,
17156              ENTITY_ID1,
17157              SEQUENCE_NUMBER,
17158              STATUS_CODE,
17159              START_DATE,
17160              COMPLETION_DATE,
17161              CHANGE_WF_ROUTE_ID,
17162              CHANGE_WF_ROUTE_TEMPLATE_ID,
17163              AUTO_PROMOTE_STATUS,
17164              WORKFLOW_STATUS,
17165              CREATION_DATE,
17166              CREATED_BY,
17167              LAST_UPDATE_DATE,
17168              LAST_UPDATED_BY
17169         FROM ENG_LIFECYCLE_STATUSES
17170        WHERE ENTITY_ID1 IN
17171              (SELECT CHANGE_ID
17172                 FROM ENG_ENGINEERING_CHANGES
17173                WHERE CHANGE_NOTICE = p_change_notice
17174                  AND ORGANIZATION_ID = p_org_id)
17175          and change_wf_route_id is null
17176          and change_wf_route_template_id is not null --needed for part with workflow
17177        ORDER BY ENTITY_ID1, SEQUENCE_NUMBER;
17178 
17179     l_msg_count           number;
17180     l_msg_data            varchar2(1000);
17181     l_classification_code VARCHAR2(150);
17182 
17183     -- Get the copied role id or group id of Role/Group type as Route assignee
17184     -- When Eng_Change_Route_Util.COPY_ROUTE, it only copied role_id or group_id, but not doing the people assginment.
17185     -- Hence, we need to find out these id to do people assignment
17186     CURSOR C_GET_ROUTE_STEP_ASSIGNEE(cp_route_id IN NUMBER) IS
17187       SELECT *
17188         FROM ENG_CHANGE_ROUTE_PEOPLE
17189        WHERE STEP_ID IN (SELECT STEP_ID
17190                            FROM ENG_CHANGE_ROUTE_STEPS
17191                           WHERE ROUTE_ID IN (cp_route_id))
17192          AND ORIGINAL_ASSIGNEE_TYPE_CODE IS NULL
17193          AND ORIGINAL_ASSIGNEE_ID IS NULL
17194          AND ASSIGNEE_TYPE_CODE <> 'PERSON'
17195        ORDER BY STEP_ID;
17196 
17197     CURSOR C_GET_GROUP_MEMBER(cp_group_id IN NUMBER) IS
17198       SELECT MEMBER_PERSON_ID
17199         FROM ENG_SECURITY_GROUP_MEMBERS_V
17200        WHERE GROUP_ID = cp_group_id
17201        ORDER BY MEMBER_PERSON_ID;
17202 
17203     CURSOR c_propagated_change_order(cp_change_notice eng_engineering_changes.change_notice%type, cp_local_organization_id eng_change_obj_relationships.object_to_id3%type)
17204     IS
17205       SELECT eec.change_id
17206       FROM eng_engineering_changes eec ,
17207         eng_change_obj_relationships ecor
17208       WHERE eec.change_id         = ecor.object_to_id1
17209       AND ecor.relationship_code IN ( 'PROPAGATED_TO', 'TRANSFERRED_TO' )
17210       AND ecor.object_to_name     ='ENG_CHANGE'
17211       AND ecor.object_to_id3      = cp_local_organization_id
17212       AND eec.change_notice       = cp_change_notice;
17213 
17214   BEGIN
17215 
17216     SELECT CHANGE_MGMT_TYPE_CODE
17217       INTO l_change_mgmt_type_code
17218       FROM ENG_ENGINEERING_CHANGES
17219      WHERE CHANGE_NOTICE = p_change_notice
17220        AND ORGANIZATION_ID = p_org_id;
17221 
17222     FOR C_CHANGES_REC IN C_CHANGES LOOP
17223 
17224        -- Get new ROute Id
17225       SELECT ENG_CHANGE_ROUTES_S.NEXTVAL into l_to_route_id FROM DUAL;
17226 
17227       IF Bom_Globals.Get_Debug = 'Y' THEN
17228          Error_Handler.Write_Debug('Inside Loop Template_id: ' ||
17229                    C_CHANGES_REC.CHANGE_WF_ROUTE_TEMPLATE_ID);
17230       END IF;
17231 
17232       --This is a Oracle API which will copy the Routes needed
17233       Eng_Change_Route_Util.COPY_ROUTE(X_TO_ROUTE_ID   => l_to_route_id,
17234                                        P_FROM_ROUTE_ID => C_CHANGES_REC.CHANGE_WF_ROUTE_TEMPLATE_ID,
17235                                        P_USER_ID       => FND_GLOBAL.USER_ID,
17236                                        P_API_CALLER    => NULL);
17237 
17238       IF Bom_Globals.Get_Debug = 'Y' THEN
17239          Error_Handler.Write_Debug('New Route Id Created is ' || l_to_route_id);
17240       END IF;
17241 
17242       --Will need to update the various related tables  along with the ENG_LIFECYCLE_STATUSES
17243       UPDATE ENG_LIFECYCLE_STATUSES
17244          SET CHANGE_WF_ROUTE_ID = l_to_route_id,
17245              WORKFLOW_STATUS    = 'NOT_STARTED'
17246        WHERE ENTITY_ID1 = C_CHANGES_REC.ENTITY_ID1
17247          AND CHANGE_LIFECYCLE_STATUS_ID =
17248              C_CHANGES_REC.CHANGE_LIFECYCLE_STATUS_ID;
17249 
17250       SELECT to_char(status_code)
17251         INTO l_classification_code
17252         FROM eng_lifecycle_statuses
17253        WHERE change_wf_route_id = l_to_route_id;
17254 
17255       UPDATE ENG_CHANGE_ROUTES
17256          SET OBJECT_ID1          = C_CHANGES_REC.ENTITY_ID1,
17257              CLASSIFICATION_CODE = l_classification_code,
17258              OWNER_ID            = FND_GLOBAL.USER_ID,
17259              APPLIED_TEMPLATE_ID = C_CHANGES_REC.CHANGE_WF_ROUTE_TEMPLATE_ID
17260        WHERE ROUTE_ID = l_to_route_id;
17261 
17262       UPDATE ENG_CHANGE_ROUTE_PEOPLE -- bug 13860012
17263          SET ORIGINAL_ASSIGNEE_TYPE_CODE = 'PERSON'
17264          WHERE ASSIGNEE_TYPE_CODE = 'PERSON'
17265          AND STEP_ID IN ( SELECT STEP_ID FROM ENG_CHANGE_ROUTE_STEPS_VL WHERE ROUTE_ID = l_to_route_id );
17266       /** === Part: Populate Route People  ===  **/
17267 
17268       -- pre-populate the item role in this organization
17269       l_instance_set_id := EGO_SECURITY_PUB.CREATE_INSTANCE_SET(p_instance_set_name => 'EGO_ORG_ITEM_' ||
17270                                                                                        p_org_id,
17271                                                                 p_object_name       => 'EGO_ITEM',
17272                                                                 p_predicate         => 'ORGANIZATION_ID = ' ||
17273                                                                                        p_org_id,
17274                                                                 P_display_name      => 'EGO_ORG_ITEM_' ||
17275                                                                                        p_org_id,
17276                                                                 p_description       => 'EGO_ORG_ITEM_' ||
17277                                                                                        p_org_id);
17278 
17279       FOR cr IN c_get_items_org_roles(cp_instance_set_id => l_instance_set_id) LOOP
17280         l_items_org_role_table(c_index).Grantee_Type := cr.grantee_type;
17281         l_items_org_role_table(c_index).Role_Id := cr.menu_id;
17282         l_items_org_role_table(c_index).Party_Id := cr.party_id;
17283 
17284         c_index := c_index + 1;
17285       END LOOP;
17286 
17287       FOR cr IN C_GET_ROUTE_STEP_ASSIGNEE(cp_route_id => l_to_route_id) LOOP
17288 
17289           ---bug 13921167 start
17290         l_menu_id := cr.assignee_id;
17291         select count(1)
17292           into l_row_count
17293           from fnd_menus
17294          where menu_id = l_menu_id;
17295 
17296         if (l_row_count > 0) then
17297           select menu_name
17298             into l_menu_name
17299             from fnd_menus
17300            where menu_id = l_menu_id;
17301         else
17302           l_menu_name := null;
17303         end if;
17304 
17305         --When workflow is assigned to change role 'Assignee'
17306         IF (l_menu_name is not null and 'ENG_CHANGE_ASSIGNEE' = l_menu_name) THEN
17307 
17308           SELECT ASSIGNEE_ID
17309             into l_assignee_id
17310             FROM ENG_ENGINEERING_CHANGES
17311            WHERE CHANGE_NOTICE = p_change_notice
17312              AND ORGANIZATION_ID = p_org_id;
17313           IF (l_assignee_id is not null) THEN
17314             -- check if the person is created in current step, if l_people_existed_flag = 0, then create
17315             SELECT COUNT(1)
17316               INTO l_people_existed_flag
17317               FROM ENG_CHANGE_ROUTE_PEOPLE
17318              WHERE step_id = cr.step_id
17319                AND assignee_id = l_assignee_id;
17320 
17321             IF (l_people_existed_flag = 0) THEN
17322               -- generate new people id
17323               SELECT ENG_CHANGE_ROUTE_PEOPLE_S.NEXTVAL
17324                 into l_people_id
17325                 FROM DUAL;
17326 
17327               INSERT INTO ENG_CHANGE_ROUTE_PEOPLE
17328                 (route_people_id,
17329                  step_id,
17330                  assignee_id,
17331                  assignee_type_code,
17332                  adhoc_people_flag,
17333                  wf_notification_id,
17334                  response_code,
17335                  response_date,
17336                  creation_date,
17337                  created_by,
17338                  last_update_date,
17339                  last_updated_by,
17340                  last_update_login,
17341                  request_id,
17342                  program_id,
17343                  program_application_id,
17344                  program_update_date,
17345                  original_system_reference,
17346                  original_assignee_id,
17347                  original_assignee_type_code,
17348                  response_condition_code,
17349                  parent_route_people_id)
17350               VALUES
17351                 (l_people_id,
17352                  cr.step_id,
17353                  l_assignee_id,
17354                  'PERSON',
17355                  cr.adhoc_people_flag,
17356                  cr.wf_notification_id,
17357                  cr.response_code,
17358                  cr.response_date,
17359                  cr.creation_date,
17360                  cr.created_by,
17361                  cr.last_update_date,
17362                  cr.last_updated_by,
17363                  cr.last_update_login,
17364                  cr.request_id,
17365                  cr.program_id,
17366                  cr.program_application_id,
17367                  cr.program_update_date,
17368                  cr.original_system_reference,
17369                  cr.assignee_id,
17370                  cr.assignee_type_code,
17371                  cr.response_condition_code,
17372                  cr.route_people_id);
17373 
17374               insert into ENG_CHANGE_ROUTE_PEOPLE_TL
17375                 (ROUTE_PEOPLE_ID,
17376                  CREATION_DATE,
17377                  CREATED_BY,
17378                  LAST_UPDATE_DATE,
17379                  LAST_UPDATED_BY,
17380                  LAST_UPDATE_LOGIN,
17381                  RESPONSE_DESCRIPTION,
17382                  LANGUAGE,
17383                  SOURCE_LANG)
17384                 select l_people_id,
17385                        cr.creation_date,
17386                        cr.created_by,
17387                        cr.last_update_date,
17388                        cr.last_updated_by,
17389                        cr.last_update_login,
17390                        NULL,
17391                        L.LANGUAGE_CODE,
17392                        userenv('LANG')
17393                   from FND_LANGUAGES L
17394                  where L.INSTALLED_FLAG in ('I', 'B')
17395                    and not exists
17396                  (select NULL
17397                           from ENG_CHANGE_ROUTE_PEOPLE_TL T
17398                          where T.ROUTE_PEOPLE_ID = l_people_id
17399                            and T.LANGUAGE = L.LANGUAGE_CODE);
17400 
17401             END IF;
17402 
17403           ELSE
17404             -- generate new people id
17405             SELECT ENG_CHANGE_ROUTE_PEOPLE_S.NEXTVAL
17406               into l_people_id
17407               FROM DUAL;
17408 
17409             --insert an 'Unassigned' assignee record
17410             INSERT INTO ENG_CHANGE_ROUTE_PEOPLE
17411               (route_people_id,
17412                step_id,
17413                assignee_id,
17414                assignee_type_code,
17415                adhoc_people_flag,
17416                wf_notification_id,
17417                response_code,
17418                response_date,
17419                creation_date,
17420                created_by,
17421                last_update_date,
17422                last_updated_by,
17423                last_update_login,
17424                request_id,
17425                program_id,
17426                program_application_id,
17427                program_update_date,
17428                original_system_reference,
17429                original_assignee_id,
17430                original_assignee_type_code,
17431                response_condition_code,
17432                parent_route_people_id)
17433             VALUES
17434               (l_people_id,
17435                cr.step_id,
17436                -1,
17437                'PERSON',
17438                cr.adhoc_people_flag,
17439                cr.wf_notification_id,
17440                cr.response_code,
17441                cr.response_date,
17442                cr.creation_date,
17443                cr.created_by,
17444                cr.last_update_date,
17445                cr.last_updated_by,
17446                cr.last_update_login,
17447                cr.request_id,
17448                cr.program_id,
17449                cr.program_application_id,
17450                cr.program_update_date,
17451                cr.original_system_reference,
17452                cr.assignee_id,
17453                cr.assignee_type_code,
17454                cr.response_condition_code,
17455                cr.route_people_id);
17456 
17457             insert into ENG_CHANGE_ROUTE_PEOPLE_TL
17458               (ROUTE_PEOPLE_ID,
17459                CREATION_DATE,
17460                CREATED_BY,
17461                LAST_UPDATE_DATE,
17462                LAST_UPDATED_BY,
17463                LAST_UPDATE_LOGIN,
17464                RESPONSE_DESCRIPTION,
17465                LANGUAGE,
17466                SOURCE_LANG)
17467               select l_people_id,
17468                      cr.creation_date,
17469                      cr.created_by,
17470                      cr.last_update_date,
17471                      cr.last_updated_by,
17472                      cr.last_update_login,
17473                      NULL,
17474                      L.LANGUAGE_CODE,
17475                      userenv('LANG')
17476                 from FND_LANGUAGES L
17477                where L.INSTALLED_FLAG in ('I', 'B')
17478                  and not exists
17479                (select NULL
17480                         from ENG_CHANGE_ROUTE_PEOPLE_TL T
17481                        where T.ROUTE_PEOPLE_ID = l_people_id
17482                          and T.LANGUAGE = L.LANGUAGE_CODE);
17483 
17484           END IF;
17485 
17486           --when workflow is assigned to change role 'Requestor'
17487         ELSIF (l_menu_name is not null and
17488               'ENG_CHANGE_REQUESTOR' = l_menu_name) THEN
17489 
17490           SELECT REQUESTOR_ID
17491             into l_requestor_id
17492             FROM ENG_ENGINEERING_CHANGES
17493            WHERE CHANGE_NOTICE = p_change_notice
17494              AND ORGANIZATION_ID = p_org_id;
17495           IF (l_requestor_id is not null) THEN
17496             -- check if the person is created in current step, if l_people_existed_flag = 0, then create
17497             SELECT COUNT(1)
17498               INTO l_people_existed_flag
17499               FROM ENG_CHANGE_ROUTE_PEOPLE
17500              WHERE step_id = cr.step_id
17501                AND assignee_id = l_requestor_id;
17502 
17503             IF (l_people_existed_flag = 0) THEN
17504               -- generate new people id
17505               SELECT ENG_CHANGE_ROUTE_PEOPLE_S.NEXTVAL
17506                 into l_people_id
17507                 FROM DUAL;
17508 
17509               INSERT INTO ENG_CHANGE_ROUTE_PEOPLE
17510                 (route_people_id,
17511                  step_id,
17512                  assignee_id,
17513                  assignee_type_code,
17514                  adhoc_people_flag,
17515                  wf_notification_id,
17516                  response_code,
17517                  response_date,
17518                  creation_date,
17519                  created_by,
17520                  last_update_date,
17521                  last_updated_by,
17522                  last_update_login,
17523                  request_id,
17524                  program_id,
17525                  program_application_id,
17526                  program_update_date,
17527                  original_system_reference,
17528                  original_assignee_id,
17529                  original_assignee_type_code,
17530                  response_condition_code,
17531                  parent_route_people_id)
17532               VALUES
17533                 (l_people_id,
17534                  cr.step_id,
17535                  l_requestor_id,
17536                  'PERSON',
17537                  cr.adhoc_people_flag,
17538                  cr.wf_notification_id,
17539                  cr.response_code,
17540                  cr.response_date,
17541                  cr.creation_date,
17542                  cr.created_by,
17543                  cr.last_update_date,
17544                  cr.last_updated_by,
17545                  cr.last_update_login,
17546                  cr.request_id,
17547                  cr.program_id,
17548                  cr.program_application_id,
17549                  cr.program_update_date,
17550                  cr.original_system_reference,
17551                  cr.assignee_id,
17552                  cr.assignee_type_code,
17553                  cr.response_condition_code,
17554                  cr.route_people_id);
17555 
17556               insert into ENG_CHANGE_ROUTE_PEOPLE_TL
17557                 (ROUTE_PEOPLE_ID,
17558                  CREATION_DATE,
17559                  CREATED_BY,
17560                  LAST_UPDATE_DATE,
17561                  LAST_UPDATED_BY,
17562                  LAST_UPDATE_LOGIN,
17563                  RESPONSE_DESCRIPTION,
17564                  LANGUAGE,
17565                  SOURCE_LANG)
17566                 select l_people_id,
17567                        cr.creation_date,
17568                        cr.created_by,
17569                        cr.last_update_date,
17570                        cr.last_updated_by,
17571                        cr.last_update_login,
17572                        NULL,
17573                        L.LANGUAGE_CODE,
17574                        userenv('LANG')
17575                   from FND_LANGUAGES L
17576                  where L.INSTALLED_FLAG in ('I', 'B')
17577                    and not exists
17578                  (select NULL
17579                           from ENG_CHANGE_ROUTE_PEOPLE_TL T
17580                          where T.ROUTE_PEOPLE_ID = l_people_id
17581                            and T.LANGUAGE = L.LANGUAGE_CODE);
17582 
17583             END IF;
17584 
17585           ELSE
17586             -- generate new people id
17587             SELECT ENG_CHANGE_ROUTE_PEOPLE_S.NEXTVAL
17588               into l_people_id
17589               FROM DUAL;
17590 
17591             --insert an 'Unassigned' assignee record
17592             INSERT INTO ENG_CHANGE_ROUTE_PEOPLE
17593               (route_people_id,
17594                step_id,
17595                assignee_id,
17596                assignee_type_code,
17597                adhoc_people_flag,
17598                wf_notification_id,
17599                response_code,
17600                response_date,
17601                creation_date,
17602                created_by,
17603                last_update_date,
17604                last_updated_by,
17605                last_update_login,
17606                request_id,
17607                program_id,
17608                program_application_id,
17609                program_update_date,
17610                original_system_reference,
17611                original_assignee_id,
17612                original_assignee_type_code,
17613                response_condition_code,
17614                parent_route_people_id)
17615             VALUES
17616               (l_people_id,
17617                cr.step_id,
17618                -1,
17619                'PERSON',
17620                cr.adhoc_people_flag,
17621                cr.wf_notification_id,
17622                cr.response_code,
17623                cr.response_date,
17624                cr.creation_date,
17625                cr.created_by,
17626                cr.last_update_date,
17627                cr.last_updated_by,
17628                cr.last_update_login,
17629                cr.request_id,
17630                cr.program_id,
17631                cr.program_application_id,
17632                cr.program_update_date,
17633                cr.original_system_reference,
17634                cr.assignee_id,
17635                cr.assignee_type_code,
17636                cr.response_condition_code,
17637                cr.route_people_id);
17638 
17639             insert into ENG_CHANGE_ROUTE_PEOPLE_TL
17640               (ROUTE_PEOPLE_ID,
17641                CREATION_DATE,
17642                CREATED_BY,
17643                LAST_UPDATE_DATE,
17644                LAST_UPDATED_BY,
17645                LAST_UPDATE_LOGIN,
17646                RESPONSE_DESCRIPTION,
17647                LANGUAGE,
17648                SOURCE_LANG)
17649               select l_people_id,
17650                      cr.creation_date,
17651                      cr.created_by,
17652                      cr.last_update_date,
17653                      cr.last_updated_by,
17654                      cr.last_update_login,
17655                      NULL,
17656                      L.LANGUAGE_CODE,
17657                      userenv('LANG')
17658                 from FND_LANGUAGES L
17659                where L.INSTALLED_FLAG in ('I', 'B')
17660                  and not exists
17661                (select NULL
17662                         from ENG_CHANGE_ROUTE_PEOPLE_TL T
17663                        where T.ROUTE_PEOPLE_ID = l_people_id
17664                          and T.LANGUAGE = L.LANGUAGE_CODE);
17665 
17666           END IF;
17667         ELSE
17668 
17669           ---bug 13921167 end
17670 
17671 
17672 
17673 
17674         IF (cr.ASSIGNEE_TYPE_CODE = 'GROUP') THEN
17675           FOR cr2 IN C_GET_GROUP_MEMBER(cp_group_id => cr.assignee_id) LOOP
17676 
17677             -- check if the person is created in current step, if l_people_existed_flag = 0, then create
17678             SELECT COUNT(1)
17679               INTO l_people_existed_flag
17680               FROM ENG_CHANGE_ROUTE_PEOPLE
17681              WHERE step_id = cr.step_id
17682             AND assignee_id = cr2.member_person_id;
17683 
17684             IF (l_people_existed_flag = 0) THEN
17685               -- generate new people id
17686               SELECT ENG_CHANGE_ROUTE_PEOPLE_S.NEXTVAL
17687                 into l_people_id
17688                 FROM DUAL;
17689 
17690               INSERT INTO ENG_CHANGE_ROUTE_PEOPLE
17691                 (route_people_id,
17692                  step_id,
17693                  assignee_id,
17694                  assignee_type_code,
17695                  adhoc_people_flag,
17696                  wf_notification_id,
17697                  response_code,
17698                  response_date,
17699                  creation_date,
17700                  created_by,
17701                  last_update_date,
17702                  last_updated_by,
17703                  last_update_login,
17704                  request_id,
17705                  program_id,
17706                  program_application_id,
17707                  program_update_date,
17708                  original_system_reference,
17709                  original_assignee_id,
17710                  original_assignee_type_code,
17711                  response_condition_code,
17712                  parent_route_people_id)
17713               VALUES
17714                 (l_people_id,
17715                  cr.step_id,
17716                  cr2.member_person_id,
17717                  'PERSON',
17718                  cr.adhoc_people_flag,
17719                  cr.wf_notification_id,
17720                  cr.response_code,
17721                  cr.response_date,
17722                  cr.creation_date,
17723                  cr.created_by,
17724                  cr.last_update_date,
17725                  cr.last_updated_by,
17726                  cr.last_update_login,
17727                  cr.request_id,
17728                  cr.program_id,
17729                  cr.program_application_id,
17730                  cr.program_update_date,
17731                  cr.original_system_reference,
17732                  cr.assignee_id,
17733                  cr.assignee_type_code,
17734                  cr.response_condition_code,
17735                  --cr.route_people_id
17736                  null);
17737 
17738               insert into ENG_CHANGE_ROUTE_PEOPLE_TL (
17739                 ROUTE_PEOPLE_ID,
17740                 CREATION_DATE,
17741                 CREATED_BY,
17742                 LAST_UPDATE_DATE,
17743                 LAST_UPDATED_BY,
17744                 LAST_UPDATE_LOGIN,
17745                 RESPONSE_DESCRIPTION,
17746                 LANGUAGE,
17747                 SOURCE_LANG
17748               ) select
17749                 l_people_id,
17750                 cr.creation_date,
17751                 cr.created_by,
17752                 cr.last_update_date,
17753                 cr.last_updated_by,
17754                 cr.last_update_login,
17755                 NULL,
17756                 L.LANGUAGE_CODE,
17757                 userenv('LANG')
17758               from FND_LANGUAGES L
17759               where L.INSTALLED_FLAG in ('I', 'B')
17760               and not exists
17761                 (select NULL
17762                 from ENG_CHANGE_ROUTE_PEOPLE_TL T
17763                 where T.ROUTE_PEOPLE_ID = l_people_id
17764                 and T.LANGUAGE = L.LANGUAGE_CODE);
17765 
17766             END IF;
17767           END LOOP; -- end cr2 in cursor C_GET_GROUP_MEMBER
17768         ELSIF (cr.ASSIGNEE_TYPE_CODE = 'ROLE') THEN
17769 
17770           l_row_inserted_flag := 0;  -- bug 13860012
17771           FOR t_index in 1 .. l_items_org_role_table.last LOOP
17772             IF (l_items_org_role_table(t_index).role_id = cr.assignee_id) THEN
17773 
17774               -- if the role_id is in organization role ,
17775               IF (l_items_org_role_table(t_index).Grantee_Type = 'P') THEN
17776 
17777                 -- if the role's type = 'PERSON', then start to create the people
17778 
17779                 -- check if the person is created in current step, if l_people_existed_flag = 0, then create
17780                 SELECT COUNT(1)
17781                   INTO l_people_existed_flag
17782                   FROM ENG_CHANGE_ROUTE_PEOPLE
17783                  WHERE step_id = cr.step_id
17784                 AND assignee_id = l_items_org_role_table(t_index).party_id;
17785 
17786                 IF (l_people_existed_flag = 0) THEN
17787                   -- generate new people id
17788                   SELECT ENG_CHANGE_ROUTE_PEOPLE_S.NEXTVAL
17789                     into l_people_id
17790                     FROM DUAL;
17791 
17792                   INSERT INTO ENG_CHANGE_ROUTE_PEOPLE
17793                     (route_people_id,
17794                      step_id,
17795                      assignee_id,
17796                      assignee_type_code,
17797                      adhoc_people_flag,
17798                      wf_notification_id,
17799                      response_code,
17800                      response_date,
17801                      creation_date,
17802                      created_by,
17803                      last_update_date,
17804                      last_updated_by,
17805                      last_update_login,
17806                      request_id,
17807                      program_id,
17808                      program_application_id,
17809                      program_update_date,
17810                      original_system_reference,
17811                      original_assignee_id,
17812                      original_assignee_type_code,
17813                      response_condition_code,
17814                      parent_route_people_id)
17815                   VALUES
17816                     (l_people_id,
17817                      cr.step_id,
17818                      l_items_org_role_table(t_index).party_id,
17819                      'PERSON',
17820                      cr.adhoc_people_flag,
17821                      cr.wf_notification_id,
17822                      cr.response_code,
17823                      cr.response_date,
17824                      cr.creation_date,
17825                      cr.created_by,
17826                      cr.last_update_date,
17827                      cr.last_updated_by,
17828                      cr.last_update_login,
17829                      cr.request_id,
17830                      cr.program_id,
17831                      cr.program_application_id,
17832                      cr.program_update_date,
17833                      cr.original_system_reference,
17834                      cr.assignee_id,
17835                      cr.assignee_type_code,
17836                      cr.response_condition_code,
17837                      cr.route_people_id);
17838 
17839                   insert into ENG_CHANGE_ROUTE_PEOPLE_TL (
17840                     ROUTE_PEOPLE_ID,
17841                     CREATION_DATE,
17842                     CREATED_BY,
17843                     LAST_UPDATE_DATE,
17844                     LAST_UPDATED_BY,
17845                     LAST_UPDATE_LOGIN,
17846                     RESPONSE_DESCRIPTION,
17847                     LANGUAGE,
17848                     SOURCE_LANG
17849                   ) select
17850                     l_people_id,
17851                     cr.creation_date,
17852                     cr.created_by,
17853                     cr.last_update_date,
17854                     cr.last_updated_by,
17855                     cr.last_update_login,
17856                     NULL,
17857                     L.LANGUAGE_CODE,
17858                     userenv('LANG')
17859                   from FND_LANGUAGES L
17860                   where L.INSTALLED_FLAG in ('I', 'B')
17861                   and not exists
17862                     (select NULL
17863                     from ENG_CHANGE_ROUTE_PEOPLE_TL T
17864                     where T.ROUTE_PEOPLE_ID = l_people_id
17865                     and T.LANGUAGE = L.LANGUAGE_CODE);
17866 
17867                 l_row_inserted_flag := 1;  -- bug 13860012
17868                 END IF; -- End if l_people_existed_flag = 0
17869               ELSIF (l_items_org_role_table(t_index).Grantee_Type = 'G') THEN
17870                 -- when role_type = 'GROUP'
17871                 FOR cr2 IN C_GET_GROUP_MEMBER(cp_group_id => l_items_org_role_table(t_index).party_id) LOOP
17872                   -- check if the person is created in current step, if l_people_existed_flag = 0, then create
17873                   SELECT COUNT(1)
17874                     INTO l_people_existed_flag
17875                     FROM ENG_CHANGE_ROUTE_PEOPLE
17876                    WHERE step_id = cr.step_id
17877                   AND assignee_id = cr2.member_person_id;
17878 
17879                   IF (l_people_existed_flag = 0) THEN
17880                     -- generate new people id
17881                     SELECT ENG_CHANGE_ROUTE_PEOPLE_S.NEXTVAL
17882                       into l_people_id
17883                       FROM DUAL;
17884 
17885                     INSERT INTO ENG_CHANGE_ROUTE_PEOPLE
17886                       (route_people_id,
17887                        step_id,
17888                        assignee_id,
17889                        assignee_type_code,
17890                        adhoc_people_flag,
17891                        wf_notification_id,
17892                        response_code,
17893                        response_date,
17894                        creation_date,
17895                        created_by,
17896                        last_update_date,
17897                        last_updated_by,
17898                        last_update_login,
17899                        request_id,
17900                        program_id,
17901                        program_application_id,
17902                        program_update_date,
17903                        original_system_reference,
17904                        original_assignee_id,
17905                        original_assignee_type_code,
17906                        response_condition_code,
17907                        parent_route_people_id)
17908                     VALUES
17909                       (l_people_id,
17910                        cr.step_id,
17911                        cr2.member_person_id,
17912                        'PERSON',
17913                        cr.adhoc_people_flag,
17914                        cr.wf_notification_id,
17915                        cr.response_code,
17916                        cr.response_date,
17917                        cr.creation_date,
17918                        cr.created_by,
17919                        cr.last_update_date,
17920                        cr.last_updated_by,
17921                        cr.last_update_login,
17922                        cr.request_id,
17923                        cr.program_id,
17924                        cr.program_application_id,
17925                        cr.program_update_date,
17926                        cr.original_system_reference,
17927                        cr.assignee_id,
17928                        cr.assignee_type_code,
17929                        cr.response_condition_code,
17930                        cr.route_people_id);
17931 
17932                     insert into ENG_CHANGE_ROUTE_PEOPLE_TL (
17933                       ROUTE_PEOPLE_ID,
17934                       CREATION_DATE,
17935                       CREATED_BY,
17936                       LAST_UPDATE_DATE,
17937                       LAST_UPDATED_BY,
17938                       LAST_UPDATE_LOGIN,
17939                       RESPONSE_DESCRIPTION,
17940                       LANGUAGE,
17941                       SOURCE_LANG
17942                     ) select
17943                       l_people_id,
17944                       cr.creation_date,
17945                       cr.created_by,
17946                       cr.last_update_date,
17947                       cr.last_updated_by,
17948                       cr.last_update_login,
17949                       NULL,
17950                       L.LANGUAGE_CODE,
17951                       userenv('LANG')
17952                     from FND_LANGUAGES L
17953                     where L.INSTALLED_FLAG in ('I', 'B')
17954                     and not exists
17955                       (select NULL
17956                       from ENG_CHANGE_ROUTE_PEOPLE_TL T
17957                       where T.ROUTE_PEOPLE_ID = l_people_id
17958                       and T.LANGUAGE = L.LANGUAGE_CODE);
17959 
17960                   l_row_inserted_flag := 1;  -- bug 13860012
17961                   END IF;
17962                 END LOOP; -- end loop for cr2
17963 
17964               END IF; -- end IF l_items_org_role_table(t_index).Grantee_Type
17965 
17966             ELSE
17967               -- if the role id is as child role object of organization role, such as Change/Document object
17968               FOR cr2 IN C_GET_PARENT_ROLES(cp_role_id              => cr.assignee_id,
17969                                             cp_change_mgmt_type_code => l_change_mgmt_type_code) LOOP
17970                 FOR t_index in 1 .. l_items_org_role_table.last LOOP
17971                   IF (l_items_org_role_table(t_index).role_id = cr2.parent_role_id) THEN
17972                     -- if the parent_role_id is in organization role ,
17973                     IF (l_items_org_role_table(t_index).Grantee_Type = 'P') THEN
17974                       -- if the role's type = 'PERSON', then start to create the people
17975                       -- check if the person is created in current step, if l_people_existed_flag = 0, then create
17976                       SELECT COUNT(1)
17977                         INTO l_people_existed_flag
17978                         FROM ENG_CHANGE_ROUTE_PEOPLE
17979                        WHERE step_id = cr.step_id
17980                       AND assignee_id = l_items_org_role_table(t_index).party_id;
17981 
17982                       IF (l_people_existed_flag = 0) THEN
17983                         -- generate new people id
17984                         SELECT ENG_CHANGE_ROUTE_PEOPLE_S.NEXTVAL
17985                           into l_people_id
17986                           FROM DUAL;
17987 
17988                         INSERT INTO ENG_CHANGE_ROUTE_PEOPLE
17989                           (route_people_id,
17990                            step_id,
17991                            assignee_id,
17992                            assignee_type_code,
17993                            adhoc_people_flag,
17994                            wf_notification_id,
17995                            response_code,
17996                            response_date,
17997                            creation_date,
17998                            created_by,
17999                            last_update_date,
18000                            last_updated_by,
18001                            last_update_login,
18002                            request_id,
18003                            program_id,
18004                            program_application_id,
18005                            program_update_date,
18006                            original_system_reference,
18007                            original_assignee_id,
18008                            original_assignee_type_code,
18009                            response_condition_code,
18010                            parent_route_people_id)
18011                         VALUES
18012                           (l_people_id,
18013                            cr.step_id,
18014                            l_items_org_role_table(t_index).party_id,
18015                            'PERSON',
18016                            cr.adhoc_people_flag,
18017                            cr.wf_notification_id,
18018                            cr.response_code,
18019                            cr.response_date,
18020                            cr.creation_date,
18021                            cr.created_by,
18022                            cr.last_update_date,
18023                            cr.last_updated_by,
18024                            cr.last_update_login,
18025                            cr.request_id,
18026                            cr.program_id,
18027                            cr.program_application_id,
18028                            cr.program_update_date,
18029                            cr.original_system_reference,
18030                            cr.assignee_id,
18031                            cr.assignee_type_code,
18032                            cr.response_condition_code,
18033                            cr.route_people_id);
18034 
18035                         insert into ENG_CHANGE_ROUTE_PEOPLE_TL (
18036                           ROUTE_PEOPLE_ID,
18037                           CREATION_DATE,
18038                           CREATED_BY,
18039                           LAST_UPDATE_DATE,
18040                           LAST_UPDATED_BY,
18041                           LAST_UPDATE_LOGIN,
18042                           RESPONSE_DESCRIPTION,
18043                           LANGUAGE,
18044                           SOURCE_LANG
18045                         ) select
18046                           l_people_id,
18047                           cr.creation_date,
18048                           cr.created_by,
18049                           cr.last_update_date,
18050                           cr.last_updated_by,
18051                           cr.last_update_login,
18052                           NULL,
18053                           L.LANGUAGE_CODE,
18054                           userenv('LANG')
18055                         from FND_LANGUAGES L
18056                         where L.INSTALLED_FLAG in ('I', 'B')
18057                         and not exists
18058                           (select NULL
18059                           from ENG_CHANGE_ROUTE_PEOPLE_TL T
18060                           where T.ROUTE_PEOPLE_ID = l_people_id
18061                           and T.LANGUAGE = L.LANGUAGE_CODE);
18062 
18063                       l_row_inserted_flag := 1;  -- bug 13860012
18064                       END IF; -- End IF l_people_existed_flag = 0
18065                     ELSIF (l_items_org_role_table(t_index).Grantee_Type = 'G') THEN
18066                       -- when role_type = 'GROUP'
18067                       FOR cr2 IN C_GET_GROUP_MEMBER(cp_group_id => l_items_org_role_table(t_index).party_id) LOOP
18068                         -- check if the person is created in current step, if l_people_existed_flag = 0, then create
18069                         SELECT COUNT(1)
18070                           INTO l_people_existed_flag
18071                           FROM ENG_CHANGE_ROUTE_PEOPLE
18072                          WHERE step_id = cr.step_id
18073                         AND assignee_id = cr2.member_person_id;
18074 
18075                         IF (l_people_existed_flag = 0) THEN
18076                           -- generate new people id
18077                           SELECT ENG_CHANGE_ROUTE_PEOPLE_S.NEXTVAL
18078                             into l_people_id
18079                             FROM DUAL;
18080 
18081                           INSERT INTO ENG_CHANGE_ROUTE_PEOPLE
18082                             (route_people_id,
18083                              step_id,
18084                              assignee_id,
18085                              assignee_type_code,
18086                              adhoc_people_flag,
18087                              wf_notification_id,
18088                              response_code,
18089                              response_date,
18090                              creation_date,
18091                              created_by,
18092                              last_update_date,
18093                              last_updated_by,
18094                              last_update_login,
18095                              request_id,
18096                              program_id,
18097                              program_application_id,
18098                              program_update_date,
18099                              original_system_reference,
18100                              original_assignee_id,
18101                              original_assignee_type_code,
18102                              response_condition_code,
18103                              parent_route_people_id)
18104                           VALUES
18105                             (l_people_id,
18106                              cr.step_id,
18107                              cr2.member_person_id,
18108                              'PERSON',
18109                              cr.adhoc_people_flag,
18110                              cr.wf_notification_id,
18111                              cr.response_code,
18112                              cr.response_date,
18113                              cr.creation_date,
18114                              cr.created_by,
18115                              cr.last_update_date,
18116                              cr.last_updated_by,
18117                              cr.last_update_login,
18118                              cr.request_id,
18119                              cr.program_id,
18120                              cr.program_application_id,
18121                              cr.program_update_date,
18122                              cr.original_system_reference,
18123                              cr.assignee_id,
18124                              cr.assignee_type_code,
18125                              cr.response_condition_code,
18126                              cr.route_people_id);
18127 
18128                           insert into ENG_CHANGE_ROUTE_PEOPLE_TL (
18129                             ROUTE_PEOPLE_ID,
18130                             CREATION_DATE,
18131                             CREATED_BY,
18132                             LAST_UPDATE_DATE,
18133                             LAST_UPDATED_BY,
18134                             LAST_UPDATE_LOGIN,
18135                             RESPONSE_DESCRIPTION,
18136                             LANGUAGE,
18137                             SOURCE_LANG
18138                           ) select
18139                             l_people_id,
18140                             cr.creation_date,
18141                             cr.created_by,
18142                             cr.last_update_date,
18143                             cr.last_updated_by,
18144                             cr.last_update_login,
18145                             NULL,
18146                             L.LANGUAGE_CODE,
18147                             userenv('LANG')
18148                           from FND_LANGUAGES L
18149                           where L.INSTALLED_FLAG in ('I', 'B')
18150                           and not exists
18151                             (select NULL
18152                             from ENG_CHANGE_ROUTE_PEOPLE_TL T
18153                             where T.ROUTE_PEOPLE_ID = l_people_id
18154                             and T.LANGUAGE = L.LANGUAGE_CODE);
18155 
18156                         l_row_inserted_flag := 1;  -- bug 13860012
18157                         END IF;
18158                       END LOOP; -- end loop for cr2
18159                     END IF; -- End IF (l_items_org_role_table(t_index).Grantee_Type = 'P')
18160                   END IF; -- End IF l_items_org_role_table(t_index).role_id = cr2.parent_role_id
18161 
18162                 END LOOP; -- FOR t_index in 1..l_items_org_role_table.last
18163               END LOOP; -- FOR cr2 IN C_GET_PARENT_ROLES
18164 
18165             END IF;
18166           END LOOP; -- FOR t_index in 1..l_items_org_role_table.last
18167           IF(l_row_inserted_flag = 0) THEN -- bug 13860012
18168             -- generate new people id
18169             SELECT ENG_CHANGE_ROUTE_PEOPLE_S.NEXTVAL
18170               into l_people_id
18171               FROM DUAL;
18172 
18173             --insert an 'Unassigned' assignee record
18174             INSERT INTO ENG_CHANGE_ROUTE_PEOPLE
18175                             (route_people_id,
18176                              step_id,
18177                              assignee_id,
18178                              assignee_type_code,
18179                              adhoc_people_flag,
18180                              wf_notification_id,
18181                              response_code,
18182                              response_date,
18183                              creation_date,
18184                              created_by,
18185                              last_update_date,
18186                              last_updated_by,
18187                              last_update_login,
18188                              request_id,
18189                              program_id,
18190                              program_application_id,
18191                              program_update_date,
18192                              original_system_reference,
18193                              original_assignee_id,
18194                              original_assignee_type_code,
18195                              response_condition_code,
18196                              parent_route_people_id)
18197                           VALUES
18198                             (l_people_id,
18199                              cr.step_id,
18200                              -1,
18201                              'PERSON',
18202                              cr.adhoc_people_flag,
18203                              cr.wf_notification_id,
18204                              cr.response_code,
18205                              cr.response_date,
18206                              cr.creation_date,
18207                              cr.created_by,
18208                              cr.last_update_date,
18209                              cr.last_updated_by,
18210                              cr.last_update_login,
18211                              cr.request_id,
18212                              cr.program_id,
18213                              cr.program_application_id,
18214                              cr.program_update_date,
18215                              cr.original_system_reference,
18216                              cr.assignee_id,
18217                              cr.assignee_type_code,
18218                              cr.response_condition_code,
18219                              cr.route_people_id);
18220 
18221                           insert into ENG_CHANGE_ROUTE_PEOPLE_TL (
18222                             ROUTE_PEOPLE_ID,
18223                             CREATION_DATE,
18224                             CREATED_BY,
18225                             LAST_UPDATE_DATE,
18226                             LAST_UPDATED_BY,
18227                             LAST_UPDATE_LOGIN,
18228                             RESPONSE_DESCRIPTION,
18229                             LANGUAGE,
18230                             SOURCE_LANG
18231                           ) select
18232                             l_people_id,
18233                             cr.creation_date,
18234                             cr.created_by,
18235                             cr.last_update_date,
18236                             cr.last_updated_by,
18237                             cr.last_update_login,
18238                             NULL,
18239                             L.LANGUAGE_CODE,
18240                             userenv('LANG')
18241                           from FND_LANGUAGES L
18242                           where L.INSTALLED_FLAG in ('I', 'B')
18243                           and not exists
18244                             (select NULL
18245                             from ENG_CHANGE_ROUTE_PEOPLE_TL T
18246                             where T.ROUTE_PEOPLE_ID = l_people_id
18247                             and T.LANGUAGE = L.LANGUAGE_CODE);
18248           END IF;
18249         END IF; -- IF GROUP/ROLE
18250 	END IF; --IF Assignee:  bug 13921167
18251 
18252         -- Remove the original copied assignee object (Group/Role)
18253         DELETE FROM ENG_CHANGE_ROUTE_PEOPLE
18254         WHERE route_people_id = cr.route_people_id;
18255 
18256         DELETE FROM ENG_CHANGE_ROUTE_PEOPLE_TL
18257         WHERE route_people_id = cr.route_people_id;
18258 
18259       END LOOP; -- end cursor C_GET_ROUTE_STEP_ASSIGNEE
18260 
18261     END LOOP;
18262 
18263     IF Bom_Globals.Get_Debug = 'Y' THEN
18264        Error_Handler.Write_Debug('ENG_ECO_PVT API: Calling ENG_CHANGE_LIFECYCLE_UTIL.Init_Lifecycle');
18265     END IF;
18266 
18267     -- Get the profile: ENG: Allow Auto-Submit Workflow, 1: Yes; 2: No
18268 
18269     FND_PROFILE.Get('ENG_AUTO_SUBMIT_WF', l_submit_flag);
18270 
18271     -- fix bug 13956277, if the ECO is propagate ECO, skip auto submission as propagate ECO will submit accordingly
18272     OPEN c_propagated_change_order (cp_change_notice => p_change_notice, cp_local_organization_id => p_org_id);
18273     FETCH c_propagated_change_order INTO l_change_id;
18274     CLOSE c_propagated_change_order;
18275     IF (l_submit_flag = 1 AND l_change_id is null) THEN
18276     --After the explosion is done then the workflow needs to be started
18277         SELECT change_id
18278          INTO l_change_id
18279         FROM eng_engineering_changes WHERE change_notice = p_change_notice
18280          AND organization_id = p_org_id;
18281 
18282         ENG_CHANGE_LIFECYCLE_UTIL.Init_Lifecycle(
18283             p_api_version          =>    1.0,
18284             p_init_msg_list        =>    FND_API.G_TRUE,
18285             p_commit               =>    FND_API.G_FALSE,
18286             p_validation_level     =>    FND_API.G_VALID_LEVEL_FULL,
18287             p_debug                =>    FND_API.G_FALSE,
18288             p_output_dir           =>    null,
18289             p_debug_filename       =>    null,
18290             x_return_status        =>    l_return_status,
18291             x_msg_count            =>    l_msg_count,
18292             x_msg_data             =>    l_msg_data,
18293             p_change_id            =>    l_change_id,
18294             p_api_caller           =>    'UI'
18295           );
18296 
18297         IF Bom_Globals.Get_Debug = 'Y' THEN
18298            Error_Handler.Write_Debug('ENG_CHANGE_LIFECYCLE_UTIL.Init_Lifecycle: Return Status: ' || l_return_status ||
18299                                       '; Message data: ' || l_msg_data);
18300         END IF;
18301      END IF; -- IF (l_submit_flag = 1)
18302   EXCEPTION
18303     WHEN OTHERS THEN
18304         Error_Handler.Add_Error_Token
18305           (  p_Message_Name  => NULL
18306             ,p_Message_Text  => 'Error in ENG_ECO_PVT.Explode_WF_Routing: '|| SUBSTR(SQLERRM, 1, 30) || ' ' ||to_char(SQLCODE)
18307             ,x_Mesg_Token_Tbl  => x_Mesg_Token_Tbl
18308            , p_Mesg_Token_Tbl  => x_Mesg_Token_Tbl
18309            );
18310         x_return_status := FND_API.G_RET_STS_UNEXP_ERROR;
18311 
18312   END Explode_WF_Routing;
18313 
18314 END ENG_Eco_PVT;