DBA Data[Home] [Help]

PACKAGE BODY: APPS.ECO_ERROR_HANDLER

Source


1 PACKAGE BODY Eco_Error_Handler AS
2 /* $Header: ENGBOEHB.pls 120.1 2006/06/05 06:49:31 prgopala noship $ */
3         g_eco_rec               ENG_Eco_Pub.Eco_Rec_Type;
4         g_eco_revision_tbl      Eng_Eco_Pub.Eco_Revision_tbl_Type;
5         g_revised_item_tbl      Eng_Eco_Pub.Revised_Item_Tbl_Type;
6         g_rev_component_tbl     Bom_Bo_Pub.Rev_Component_Tbl_Type;
7         g_ref_designator_tbl    Bom_Bo_Pub.Ref_Designator_Tbl_Type;
8         g_sub_component_tbl     Bom_Bo_Pub.Sub_Component_Tbl_Type;
9 
10         /*******************************************************
11         -- Followings are for ECO Routing
12         ********************************************************/
13         g_rev_operation_tbl          Bom_Rtg_Pub.Rev_Operation_Tbl_Type ;
14         g_rev_op_resource_tbl        Bom_Rtg_Pub.Rev_Op_Resource_Tbl_Type ;
15         g_rev_sub_resource_tbl       Bom_Rtg_Pub.Rev_Sub_Resource_Tbl_Type ;
16         -- Added by MK on 08/23/2000
17 
18 
19 
20         /*******************************************************
21         -- Followings are for Eng Change
22         ********************************************************/
23         g_change_line_tbl            Eng_Eco_Pub.Change_Line_Tbl_Type ;
24         -- Added by MK on 08/13/2002
25 
26 
27         G_ERROR_TABLE           Error_Handler.Error_Tbl_Type;
28         G_Msg_Index             NUMBER := 0;
29         G_Msg_Count             NUMBER := 0;
30 
31         /******************************************************************
32         * Procedure     : setSubComponents (Unexposed)
33         * Parameters    : Other Message
34         *                 Other Status
35         *                 Error Scope
36         *                 Revised Item Index
37         *                 Revised Component Index
38         *                 Reference Designator Index
39         * Purpose       : This procedure will set the reference designator
40         *                 record status to other status by looking at the
41         *                 revised item key or the revised component key or
42         *                 else setting all the record status to other status
43         ********************************************************************/
44         PROCEDURE setSubComponents
45         (  p_error_scope        IN  VARCHAR2
46          , p_other_mesg_text    IN  VARCHAR2
47          , p_other_status       IN  VARCHAR2
48          , p_ri_idx             IN  NUMBER := 0
49          , p_rc_idx             IN  NUMBER := 0
50          , p_rd_idx             IN  NUMBER := 0
51          , p_entity_index       IN  NUMBER := 0
52 	 , p_other_mesg_name    IN  VARCHAR2 := NULL -- bug 5174203
53         )
54         IS
55                 l_idx   NUMBER;
56         BEGIN
57 
58 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Setting substitute component records to ' ||
59                        p_other_status);
60 END IF;
61 
62              IF p_error_scope = G_SCOPE_ALL
63              THEN
64                 FOR l_idx IN 1..g_sub_component_tbl.COUNT
65                 LOOP
66                         g_sub_component_tbl(l_idx).return_status :=
67                                         p_other_status;
68                         /* Put in fix in response to bug 851387
69                         -- Added IF condition
70                         -- Fix made by AS on 03/17/99
71                         */
72                         IF p_other_mesg_text IS NOT NULL
73                         THEN
74                                 Error_Handler.Add_Message
75                                 (  p_mesg_text  => p_other_mesg_text
76                                 , p_entity_id   => G_SC_LEVEL
77                                 , p_entity_index=> l_idx
78                                 , p_message_type=> 'E'
79 				, p_mesg_name   => p_other_mesg_name);--bug 5174203
80                         END IF;
81                 END LOOP;
82 
83              ELSIF p_error_scope = G_SCOPE_CHILDREN AND
84                    p_ri_idx <> 0
85              THEN
86                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Scope=Children in Substitute Component'); END IF;
87                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Revised Item index <> 0'); END IF;
88 
89                 FOR l_idx IN 1..g_sub_component_tbl.COUNT
90                 LOOP
91                    IF NVL(g_sub_component_tbl(l_idx).revised_item_name, ' ') =
92                       NVL(g_revised_item_tbl(p_ri_idx).revised_item_name, ' ')
93                       AND
94                       NVL(g_sub_component_tbl(l_idx).organization_code,' ') =
95                       NVL(g_revised_item_tbl(p_ri_idx).organization_code,' ') AND
96                       NVL(g_sub_component_tbl(l_idx).eco_name,' ') =
97                       NVL(g_revised_item_tbl(p_ri_idx).eco_name,' ') AND
98                       NVL(g_sub_component_tbl(l_idx).start_effective_date, SYSDATE) =
99                       NVL(g_revised_item_tbl(p_ri_idx).start_effective_date, SYSDATE) AND
100                       NVL(g_sub_component_tbl(l_idx).new_revised_item_revision, 'X') =
101                       NVL(g_revised_item_tbl(p_ri_idx).new_revised_item_revision, 'X')
102                     THEN
103                         g_sub_component_tbl(l_idx).return_status :=
104                                         p_other_status;
105 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Substitute Component at ' || to_char(l_idx) || ' set to status ' ||
106                 p_other_status);
107 END IF;
108 
109                         Error_Handler.Add_Message
110                         (  p_mesg_text     => p_other_mesg_text
111                          , p_entity_id     => G_SC_LEVEL
112                          , p_entity_index  => l_idx
113                          , p_message_type  => 'E'
114             		 , p_mesg_name     => p_other_mesg_name);--bug 5174203
115                      END IF;
116                 END LOOP;
117              ELSIF p_error_scope = G_SCOPE_CHILDREN AND
118                    p_rc_idx <> 0
119              THEN
120 
121                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Scope=Children in Substitute Component'); END IF;
122                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Revised Component index <> 0'); END IF;
123 
124                 FOR l_idx IN 1..g_sub_component_tbl.COUNT
125                 LOOP
126                     IF NVL(g_sub_component_tbl(l_idx).component_item_name, ' ')=
127                        NVL(g_rev_component_tbl(p_rc_idx).component_item_name,' '
128                           ) AND
129                        NVL(g_sub_component_tbl(l_idx).start_effective_date,
130                            SYSDATE ) =
131                        NVL(g_rev_component_tbl(p_rc_idx).start_effective_date,
132                            SYSDATE )
133                        AND
134                        NVL(g_sub_component_tbl(l_idx).operation_sequence_number, 0) =
135                        NVL(g_rev_component_tbl(p_rc_idx).operation_sequence_number, 0)
136                        AND
137                        NVL(g_sub_component_tbl(l_idx).revised_item_name, ' ') =
138                        NVL(g_rev_component_tbl(p_rc_idx).revised_item_name, ' ')
139                        AND
140                        NVL(g_sub_component_tbl(l_idx).new_revised_item_revision, 'X') =
141                        NVL(g_rev_component_tbl(p_rc_idx).new_revised_item_revision, 'X')
142                        AND
143                        NVL(g_sub_component_tbl(l_idx).eco_name, ' ') =
144                        NVL(g_rev_component_tbl(p_rc_idx).eco_name, ' ') AND
145                        NVL(g_sub_component_tbl(l_idx).organization_code, ' ') =
146                        NVL(g_rev_component_tbl(p_rc_idx).organization_code, ' ')
147                     THEN
148                         --
149                         -- Since bill sequence id is not available
150                         -- match the revised item information also.
151                         --
152                         IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
153                        ('Substitute Comp. at ' || to_char(l_idx) || ' set to '
154                                 || p_other_status);
155                         END IF;
156 
157                         g_sub_component_tbl(l_idx).return_status :=
158                                                 p_other_status;
159                         Error_Handler.Add_Message
160                         (  p_mesg_text          => p_other_mesg_text
161                          , p_entity_id          => G_SC_LEVEL
162                          , p_entity_index       => l_idx
163                          , p_message_type       => 'E'
164 			 , p_mesg_name          => p_other_mesg_name);--bug 5174203
165                     END IF;
166                 END LOOP;  -- Ref. Desg Children of Rev Comps Ends.
167 
168              ELSIF p_error_scope = G_SCOPE_SIBLINGS AND
169                    p_rd_idx <> 0
170              THEN
171 
172                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Scope = Siblings in Sub. Components'); END IF;
173                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Reference Desg Index <> 0'); END IF;
174 
175                 FOR l_idx IN 1..g_sub_component_tbl.COUNT
176                 LOOP
177                     IF NVL(g_sub_component_tbl(l_idx).component_item_name,' ') =
178                        NVL(g_ref_designator_tbl(p_rd_idx).component_item_name, ' ') AND
179                        NVL(g_sub_component_tbl(l_idx).start_effective_date, SYSDATE) =
180                        NVL(g_ref_designator_tbl(p_rd_idx).start_effective_date, SYSDATE)
181                        AND
182                        NVL(g_sub_component_tbl(l_idx).operation_sequence_number, 0) =
183                        NVL(g_ref_designator_tbl(p_rd_idx).operation_sequence_number, 0)
184                        AND
185                        NVL(g_sub_component_tbl(l_idx).revised_item_name, ' ') =
186                        NVL(g_ref_designator_tbl(p_rd_idx).revised_item_name, ' ')
187                        AND
188                        NVL(g_sub_component_tbl(l_idx).new_revised_item_revision, 'X') =
189                        NVL(g_ref_designator_tbl(p_rd_idx).new_revised_item_revision, 'X')
190                        AND
191                        NVL(g_sub_component_tbl(l_idx).eco_name, ' ') =
192                        NVL(g_ref_designator_tbl(p_rd_idx).eco_name, ' ') AND
193                        NVL(g_sub_component_tbl(l_idx).organization_code, ' ') =
194                        NVL(g_ref_designator_tbl(p_rd_idx).organization_code, ' ')
195                     THEN
196                         --
197                         -- Since bill sequence id is not available
198                         -- match the revised item information also.
199                         --
200                         g_sub_component_tbl(l_idx).return_status :=
201                                                 p_other_status;
202 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Substitute Component at ' || to_char(l_idx) || ' set to status ' ||
203                        p_other_status);
204 END IF;
205                         Error_Handler.Add_Message
206                         (  p_mesg_text          => p_other_mesg_text
207                          , p_entity_id          => G_SC_LEVEL
208                          , p_entity_index       => l_idx
209                          , p_message_type       => 'E'
210 			 , p_mesg_name          => p_other_mesg_name);--bug 5174203
211                     END IF;
212 
213                 END LOOP; -- Scope = Siblings with rd_idx <> 0 Ends
214 
215              ELSIF p_error_scope = G_SCOPE_SIBLINGS AND
216                    p_ri_idx = 0 AND
217                    p_rc_idx = 0 AND
218                    p_rd_idx = 0
219              THEN
220                 --
221                 -- This situation will arise when rev. item and rev comp and
222                 -- reference designator are not part of the business object
223                 -- input data.
224                 -- Match the component key information at the entity index
225                 -- location with rest of the records, all those that are found
226                 -- will be siblings and should get an error.
227                 --
228                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Scope=Siblings in Substitute Component'); END IF;
229                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('All entity indexes = 0'); END IF;
230 
231 
232                 FOR l_idx IN (p_entity_index+1)..g_sub_component_tbl.COUNT
233                 LOOP
234                     IF NVL(g_sub_component_tbl(l_idx).component_item_name, ' ') =
235                        NVL(g_sub_component_tbl(p_entity_index).component_item_name, ' ')
236                        AND
237                        NVL(g_sub_component_tbl(l_idx).start_effective_date, SYSDATE) =
238                        NVL(g_sub_component_tbl(p_entity_index).start_effective_date, SYSDATE)
239                        AND
240                        NVL(g_sub_component_tbl(l_idx).operation_sequence_number, 0) =
241                        NVL(g_sub_component_tbl(p_entity_index).operation_sequence_number, 0)
242                        AND
243                        NVL(g_sub_component_tbl(l_idx).revised_item_name, ' ') =
244                        NVL(g_sub_component_tbl(p_entity_index).revised_item_name, ' ')
245                        AND
246                        NVL(g_sub_component_tbl(l_idx).new_revised_item_revision, 'X') =
247                        NVL(g_sub_component_tbl(p_entity_index).new_revised_item_revision, 'X')
248                        AND
249                        NVL(g_sub_component_tbl(l_idx).eco_name, ' ') =
250                        NVL(g_sub_component_tbl(p_entity_index).eco_name, ' ') AND
251                        NVL(g_sub_component_tbl(l_idx).organization_code, ' ') =
252                        NVL(g_sub_component_tbl(p_entity_index).organization_code, ' ')
253                     THEN
254                         --
255                         -- Since bill sequence id is not available
256                         -- match the revised item information also.
257                         --
258                         g_sub_component_tbl(l_idx).return_status :=
259                                                 p_other_status;
260                         Error_Handler.Add_Message
261                         (  p_mesg_text          => p_other_mesg_text
262                          , p_entity_id          => G_SC_LEVEL
263                          , p_entity_index       => l_idx
264                          , p_message_type       => 'E'
265 			 , p_mesg_name          => p_other_mesg_name);--bug 5174203
266                     END IF;
267                 END LOOP;
268              END IF; -- If Scope = Ends.
269 
270         END setSubComponents;
271 
272         /******************************************************************
273         * Procedure     : setRefDesignators (Unexposed)
274         * Parameters    : Other Message
275         *                 Other Status
276         *                 Error Scope
277         *                 Revised Item Index
278         *                 Revised Component Index
279         * Purpose       : This procedure will set the reference designator
280         *                 record status to other status by looking at the
281         *                 revised item key or the revised component key or
282         *                 else setting all the record status to other status
283         ********************************************************************/
284         PROCEDURE setRefDesignators
285         (  p_error_scope        IN  VARCHAR2
286          , p_other_mesg_text    IN  VARCHAR2
287          , p_other_status       IN  VARCHAR2
288          , p_ri_idx             IN  NUMBER := 0
289          , p_rc_idx             IN  NUMBER := 0
290          , p_entity_index       IN  NUMBER := 0
291 	 , p_other_mesg_name    IN  VARCHAR2 := NULL -- bug 5174203
292         )
293         IS
294                 l_idx   NUMBER;
295         BEGIN
296 
297                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Setting reference designator records to '
298                      ||  p_other_status);
299 END IF;
300 
301              IF p_error_scope = G_SCOPE_ALL
302              THEN
303                 FOR l_idx IN (p_entity_index+1)..g_ref_designator_tbl.COUNT
304                 LOOP
308                         -- Added IF condition
305                         g_ref_designator_tbl(l_idx).return_status :=
306                                         p_other_status;
307                         /* Put in fix in response to bug 851387
309                         -- Fix made by AS on 03/17/99
310                         */
311                         IF p_other_mesg_text IS NOT NULL
312                         THEN
313                                 Error_Handler.Add_Message
314                                 (  p_mesg_text  => p_other_mesg_text
315                                 , p_entity_id   => G_RD_LEVEL
316                                 , p_entity_index=> l_idx
317                                 , p_message_type=> 'E'
318 				, p_mesg_name   => p_other_mesg_name);--bug 5174203
319                         END IF;
320                 END LOOP;
321                 --
322                 -- Set the Substitute Components Record Status too
323                 --
324                 setSubComponents
325                 (  p_other_status       => p_other_status
326                  , p_other_mesg_text    => p_other_mesg_text
327                  , p_error_scope        => p_error_scope
328 		 , p_other_mesg_name    => p_other_mesg_name --bug 5174203
329                  );
330              ELSIF p_error_scope = G_SCOPE_CHILDREN AND
331                    p_ri_idx <> 0
332              THEN
333 
334                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Scope=Children in Reference Designator'); END IF;
335                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Revised Item index <> 0'); END IF;
336 
337 
338                 FOR l_idx IN 1..g_ref_designator_tbl.COUNT
339                 LOOP
340                    IF NVL(g_ref_designator_tbl(l_idx).revised_item_name, ' ') =
341                       NVL(g_revised_item_tbl(p_ri_idx).revised_item_name, ' ') AND
342                       NVL(g_Ref_Designator_tbl(l_idx).organization_code, ' ') =
343                       NVL(g_revised_item_tbl(p_ri_idx).organization_code, ' ') AND
344                       NVL(g_Ref_Designator_tbl(l_idx).eco_name, ' ') =
345                       NVL(g_revised_item_tbl(p_ri_idx).eco_name, ' ') AND
346                       NVL(g_Ref_Designator_tbl(l_idx).start_effective_date, SYSDATE) =
347                       NVL(g_revised_item_tbl(p_ri_idx).start_effective_date, SYSDATE) AND
348                       NVL(g_Ref_Designator_tbl(l_idx).new_revised_item_revision, 'X') =
349                       NVL(g_revised_item_tbl(p_ri_idx).new_revised_item_revision, 'X')
350                     THEN
351                         g_ref_designator_tbl(l_idx).return_status :=
352                                         p_other_status;
353 
354 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Ref. Designator at ' || to_char(l_idx) || ' set to status ' ||
355                       p_other_status);
356 END IF;
357 
358                         Error_Handler.Add_Message
359                         (  p_mesg_text     => p_other_mesg_text
360                          , p_entity_id     => G_RD_LEVEL
361                          , p_entity_index  => l_idx
362                          , p_message_type  => 'E'
363 			 , p_mesg_name     => p_other_mesg_name);--bug 5174203
364                      END IF;
365                 END LOOP;
366 
367              ELSIF p_error_scope = G_SCOPE_CHILDREN AND
368                    p_rc_idx <> 0
369              THEN
370 
371                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Scope=Children in Reference Designator'); END IF;
372                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Revised Component index <> 0'); END IF;
373 
374                 FOR l_idx IN 1..g_ref_designator_tbl.COUNT
375                 LOOP
376                     IF NVL(g_ref_designator_tbl(l_idx).component_item_name, ' ') =
377                        NVL(g_rev_component_tbl(p_rc_idx).component_item_name, ' ') AND
378                        NVL(g_ref_designator_tbl(l_idx).start_effective_date, SYSDATE) =
379                        NVL(g_rev_component_tbl(p_rc_idx).start_effective_date, SYSDATE) AND
380                        NVL(g_ref_designator_tbl(l_idx).operation_sequence_number, 0) =
381                        NVL(g_rev_component_tbl(p_rc_idx).operation_sequence_number, 0)
382                        AND
383                        NVL(g_ref_designator_tbl(l_idx).revised_item_name, ' ') =
384                        NVL(g_rev_component_tbl(p_rc_idx).revised_item_name, ' ') AND
385                        NVL(g_ref_designator_tbl(l_idx).new_revised_item_revision , 'X') =
386                        NVL(g_rev_component_tbl(p_rc_idx).new_revised_item_revision, 'X')
387                        AND
388                        NVL(g_ref_designator_tbl(l_idx).eco_name, ' ') =
389                        NVL(g_rev_component_tbl(p_rc_idx).eco_name, ' ') AND
390                        NVL(g_ref_designator_tbl(l_idx).organization_code, ' ')=
391                        NVL(g_rev_component_tbl(p_rc_idx).organization_code, ' ')
392                     THEN
393                         --
394                         -- Since bill sequence id is not available
395                         -- match the revised item information also.
396                         --
397                         IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
398                         ('Refernce Desg. at ' || to_char(l_idx) || ' set to '
399                                 || p_other_status);
400                         END IF;
401 
405                         (  p_mesg_text          => p_other_mesg_text
402                         g_ref_designator_tbl(l_idx).return_status :=
403                                                 p_other_status;
404                         Error_Handler.Add_Message
406                          , p_entity_id          => G_RD_LEVEL
407                          , p_entity_index       => l_idx
408                          , p_message_type       => 'E'
409 			 , p_mesg_name          => p_other_mesg_name);--bug 5174203
410                     END IF;
411                 END LOOP;  -- Ref. Desg Children of Rev Comps Ends.
412 
413              ELSIF p_error_scope = G_SCOPE_SIBLINGS AND
414                    p_ri_idx = 0 AND
415                    p_rc_idx = 0
416              THEN
417                 --
418                 -- This situation will arise when rev. item and rev comp are
419                 -- not part of the business object input data.
420                 -- Match the component key information at the entity index
421                 -- location with rest of the records, all those that are found
422                 -- will be siblings and should get an error.
423                 --
424 
425                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Scope=Siblings in Reference Designator'); END IF;
426                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('All Indexes = 0'); END IF;
427 
428                 FOR l_idx IN (p_entity_index+1)..g_ref_designator_tbl.COUNT
429                 LOOP
430                     IF NVL(g_ref_designator_tbl(l_idx).component_item_name, ' ') =
431                        NVL(g_ref_designator_tbl(p_entity_index).component_item_name, ' ')
432                        AND
433                        NVL(g_ref_designator_tbl(l_idx).start_effective_date, SYSDATE) =
434                        NVL(g_ref_designator_tbl(p_entity_index).start_effective_date, SYSDATE)
435                        AND
436                        NVL(g_ref_designator_tbl(l_idx).operation_sequence_number, 0) =
437                        NVL(g_ref_designator_tbl(p_entity_index).operation_sequence_number, 0)
438                        AND
439                        NVL(g_ref_designator_tbl(l_idx).revised_item_name, ' ') =
440                        NVL(g_ref_designator_tbl(p_entity_index).revised_item_name, ' ')
441                        AND
442                        NVL(g_ref_designator_tbl(l_idx).new_revised_item_revision, 'X') =
443                        NVL(g_ref_designator_tbl(p_entity_index).new_revised_item_revision, 'X')
444                        AND
445                        NVL(g_ref_designator_tbl(l_idx).eco_name, ' ') =
446                        NVL(g_ref_designator_tbl(p_entity_index).eco_name, ' ') AND
447                        NVL(g_ref_designator_tbl(l_idx).organization_code, ' ') =
448                        NVL(g_ref_designator_tbl(p_entity_index).organization_code, ' ')
449                     THEN
450                         --
451                         -- Since bill sequence id is not available
452                         -- match the revised item information also.
453                         --
454                         g_ref_designator_tbl(l_idx).return_status :=
455                                                 p_other_status;
456 
457 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Ref. Designator at ' || to_char(l_idx) || ' set to status ' ||
458                        p_other_status);
459 END IF;
460 
461                         Error_Handler.Add_Message
462                         (  p_mesg_text          => p_other_mesg_text
463                          , p_entity_id          => G_RD_LEVEL
464                          , p_entity_index       => l_idx
465                          , p_message_type       => 'E'
466 		   	 , p_mesg_name          => p_other_mesg_name);--bug 5174203
467                     END IF;
468                 END LOOP;
469 
470                 --
471                 -- Substitute Components will also be considered as siblings
472                 -- of reference designators, they should get an error when
473                 -- error level is reference designator with scope of Siblings
474                 --
475                 setSubComponents
476                 (  p_other_status       => p_other_status
477                  , p_other_mesg_text    => p_other_mesg_text
478                  , p_error_scope        => p_error_scope
479                  , p_rd_idx             => p_entity_index
480 		 , p_other_mesg_name    => p_other_mesg_name --bug 5174203
481                  );
482              END IF; -- If error scope Ends
483 
484         END setRefDesignators;
485 
486         /*****************************************************************
487         * Procedure     : setRevisedComponents (unexposed)
488         * Parameters IN : Other Message Text
489         *                 Other status
490         *                 Entity Index
491         *                 Error Scope
492         *                 Error Status
493         *                 Revised Item Index
494         * Parameters OUT: None
495         * Purpose       : This procedure will set the revised components record
496         *                 status to other status and for each errored record
497         *                 it will log the other message indicating what caused
498         *                 the other records to fail.
499         ******************************************************************/
500         PROCEDURE setRevisedComponents
501         (  p_error_scope        IN  VARCHAR2
505          , p_ri_idx             IN  NUMBER := 0
502          , p_other_mesg_text    IN  VARCHAR2
503          , p_other_status       IN  VARCHAR2
504          , p_entity_index       IN  NUMBER := 0
506 	 , p_other_mesg_name    IN  VARCHAR2 := NULL -- bug 5174203
507          )
508         IS
509                 l_Idx           NUMBER;
510         BEGIN
511 
512                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Setting Revised component records to '
513                                 || p_other_status);
514                 END IF;
515 
516                 IF p_error_scope = G_SCOPE_CHILDREN AND
517                    p_ri_idx <> 0
518                 THEN
519 
520                     IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Scope=Children in Revised Component'); END IF;
521                     IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Revised Item index <> 0'); END IF;
522 
523                     FOR l_idx IN 1..g_rev_component_tbl.COUNT
524                     LOOP
525                         IF NVL(g_rev_component_tbl(l_Idx).eco_name, ' ') =
526                            NVL(g_revised_item_tbl(p_ri_idx).eco_name, ' ') AND
527                            NVL(g_rev_component_tbl(l_Idx).revised_item_name, ' ') =
528                            NVL(g_revised_item_tbl(p_ri_idx).revised_item_name, ' ') AND
529                            NVL(g_rev_component_tbl(l_Idx).organization_code, ' ') =
530                            NVL(g_revised_item_tbl(p_ri_idx).organization_code, ' ') AND
531                            NVL(g_rev_component_tbl(l_Idx).new_revised_item_revision, 'X') =
532                            NVL(g_revised_item_tbl(p_ri_idx).new_revised_item_revision, 'X')
533                            AND
534                            NVL(g_rev_component_tbl(l_Idx).start_effective_date, SYSDATE) =
535                            NVL(g_revised_item_tbl(p_ri_idx).start_effective_date, SYSDATE)
536                         THEN
537 
538                                 --
539                                 -- If the revised item key of the component
540                                 -- matches that of the revised item then
541                                 -- error that revised component too.
542                                 --
543 
544                                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
545                                 ('Comp. errored at index: '||to_char(l_idx));
546                                 END IF;
547 
548                                 g_rev_component_tbl(l_Idx).return_status :=
549                                         p_other_status;
550 
551                                Error_Handler.Add_Message
552                                (  p_mesg_text  => p_other_mesg_text
553                                , p_entity_id   => G_RC_LEVEL
554                                , p_entity_index=> l_Idx
555                                , p_message_type=> 'E'
556 			       , p_mesg_name   => p_other_mesg_name);--bug 5174203
557                         END IF;
558 
559                 END LOOP;
560                                 --
561                                 -- For each of the component child
562                                 -- set the reference designator and
563                                 -- substitute component childrens
564                                 --
565                                 SetRefDesignators
566                                 (  p_error_scope        => p_error_scope
567                                  , p_other_mesg_text    => p_other_mesg_text
568                                  , p_other_status       => p_other_status
569                                  , p_ri_idx             => p_ri_idx
570 				 , p_other_mesg_name    => p_other_mesg_name --bug 5174203
571                                  );
572 
573                                 SetSubComponents
574                                 (  p_error_scope        => p_error_scope
575                                  , p_other_mesg_text    => p_other_mesg_text
576                                  , p_other_status       => p_other_status
577                                  , p_ri_idx             => p_ri_idx
578 				 , p_other_mesg_name    => p_other_mesg_name --bug 5174203
579                                  );
580                 ELSIF p_error_scope = G_SCOPE_SIBLINGS THEN
581 
582                    IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Scope=Siblings in Revised Component'); END IF;
583                    IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Entity Index: ' ||
584                                 to_char(p_entity_index));
585                    END IF;
586 
587                       FOR l_idx IN 1..g_rev_component_tbl.COUNT
588                       LOOP
589                                 --
590                                 -- If there are any other components that
591                                 -- belong to the same revised item then error
592                                 -- those records too.
593                                 --
594                               IF NVL(g_rev_component_tbl(l_Idx).eco_name, ' ') =
595                                  NVL(g_rev_component_tbl(p_entity_index).eco_name, ' ')
596                                  AND
597                                  NVL(g_rev_component_tbl(l_Idx).revised_item_name, ' ') =
598                                  NVL(g_rev_component_tbl(p_entity_index).revised_item_name,
599                                  ' ')
600                                  AND
604                                  NVL(g_rev_component_tbl(p_entity_index).new_revised_item_revision, 'X')
601                                  NVL(g_rev_component_tbl(l_Idx).organization_code, ' ')=
602                                  NVL(g_rev_component_tbl(p_entity_index).organization_code, ' ') AND
603                                  NVL(g_rev_component_tbl(l_Idx).new_revised_item_revision, 'X') =
605                                  AND
606                                  NVL(g_rev_component_tbl(l_Idx).start_effective_date, SYSDATE)
607                                  =
608                                  NVL(g_rev_component_tbl(p_entity_index).start_effective_date,
609                                  SYSDATE)
610                               THEN
611                                         --
612                                         -- Set the Component error status
613                                         --
614                                  g_rev_component_tbl(l_idx).return_status :=
615                                                 p_other_status;
616 
617 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Revised Component at ' || to_char(l_idx) || ' set to status ' ||
618                       p_other_status);
619 END IF;
620 
621                                  Error_Handler.Add_Message
622                                  (  p_mesg_text    => p_other_mesg_text
623                                   , p_entity_id    => G_RC_LEVEL
624                                   , p_entity_index => l_idx
625                                   , p_message_type => 'E'
626  				  , p_mesg_name    => p_other_mesg_name);--bug 5174203
627 
628                                  --
629                                  -- Set an child records of the revised
630                                  -- component to other status too.
631                                  --
632                                  setRefDesignators
633                                  (  p_other_status    => p_other_status
634                                   , p_error_scope     => G_SCOPE_CHILDREN
635                                   , p_rc_idx          => l_idx
636                                   , p_other_mesg_text => p_other_mesg_text
637 				  , p_other_mesg_name => p_other_mesg_name --bug 5174203
638                                   );
639 
640                                  setSubComponents
641                                  (  p_other_status    => p_other_status
642                                   , p_error_scope     => G_SCOPE_CHILDREN
643                                   , p_rc_idx          => l_idx
644                                   , p_other_mesg_text => p_other_mesg_text
645 				  , p_other_mesg_name => p_other_mesg_name --bug 5174203
646                                   );
647 
648                               END IF; -- Component Siblings Found Ends
649                         END LOOP;
650                 ELSIF p_error_scope = G_SCOPE_ALL
651                 THEN
652 
653                     IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Scope=All in Revised Component'); END IF;
654 
655                     FOR l_idx IN 1..g_rev_component_tbl.COUNT
656                     LOOP
657                         g_rev_component_tbl(l_idx).return_status :=
658                                                 p_other_status;
659                         /* Put in fix in response to bug 851387
660                         -- Added IF condition
661                         -- Fix made by AS on 03/17/99
662                         */
663                         IF p_other_mesg_text IS NOT NULL
664                         THEN
665                                 Error_Handler.Add_Message
666                                 (  p_mesg_text  => p_other_mesg_text
667                                 , p_entity_id   => G_RC_LEVEL
668                                 , p_entity_index=> l_Idx
669                                 , p_message_type=> 'E'
670 				, p_mesg_name   => p_other_mesg_name);--bug 5174203
671                         END IF;
672 
673                     END LOOP;
674 
675                         --
676                         -- Set the reference designator and substitute
677                         -- component record status too.
678                         --
679                     setRefDesignators
680                     (  p_other_status    => p_other_status
681                      , p_error_scope     => p_error_scope
682                      , p_other_mesg_text => p_other_mesg_text
683 		     , p_other_mesg_name => p_other_mesg_name --bug 5174203
684                      );
685 
686                      /*** Substitute Component called from Reference designator
687                      setSubComponents
688                      (  p_other_status    => p_other_status
689                       , p_error_scope     => p_error_scope
690                       , p_other_mesg_text => p_other_mesg_text
691 		      , p_other_mesg_name       => p_other_mesg_name --bug 5174203
692                       );
693                      ***/
694 
695                 END IF; -- Error Scope Ends
696 
697         END setRevisedComponents;
698 
699 
700 
701         /*****************************************************************
702         * Procedure     : setChangeLines(unexposed)
703         * Parameters IN : Other Message Text
704         *                 Other status
705         *                 Entity Index
706         * Parameters OUT: None
707         * Purpose       : This procedure will set the Eng Change Line record
711         ******************************************************************/
708         *                 status to other status and for each errored record
709         *                 it will log the other message indicating what caused
710         *                 the other records to fail.
712         PROCEDURE setChangeLines
713         (  p_other_mesg_text    IN  VARCHAR2
714          , p_other_status       IN  VARCHAR2
715 	 , p_other_mesg_name    IN  VARCHAR2 := NULL -- bug 5174203
716         )
717         IS
718                 l_CurrentIndex  NUMBER;
719         BEGIN
720 
721 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Setting Change Line records to ' || p_other_status); END IF;
722 
723                 FOR l_CurrentIndex IN  1..g_change_line_tbl.COUNT
724                 LOOP
725                         g_change_line_tbl(l_CurrentIndex).return_status := p_other_status;
726 
727                         IF p_other_mesg_text IS NOT NULL
728                         THEN
729                                 Error_Handler.Add_Message
730                                 (  p_mesg_text          => p_other_mesg_text
731                                  , p_entity_id          => G_CL_LEVEL
732                                  , p_entity_index       => l_CurrentIndex
733                                  , p_message_type       => 'E'
734 				 , p_mesg_name          => p_other_mesg_name);--bug 5174203
735                         END IF;
736                 END LOOP;
737 
738         END setChangeLines ;
739 
740         /*****************************************************************
741         * Procedure     : setRevisions (unexposed)
742         * Parameters IN : Other Message Text
743         *                 Other status
744         *                 Entity Index
745         * Parameters OUT: None
746         * Purpose       : This procedure will set the ECO Revisions record
747         *                 status to other status and for each errored record
748         *                 it will log the other message indicating what caused
749         *                 the other records to fail.
750         ******************************************************************/
751         PROCEDURE setRevisions
752         (  p_other_mesg_text    IN  VARCHAR2
753          , p_other_status       IN  VARCHAR2
754 	 , p_other_mesg_name    IN  VARCHAR2 := NULL -- bug 5174203
755         )
756         IS
757                 l_CurrentIndex  NUMBER;
758         BEGIN
759 
760                 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Setting ECO Revision records to ' || p_other_status); END IF;
761 
762                 FOR l_CurrentIndex IN  1..g_eco_revision_tbl.COUNT
763                 LOOP
764                         g_eco_revision_tbl(l_CurrentIndex).return_status :=
765                                                 p_other_status;
766                         /* Put in fix in response to bug 851387
767                         -- Added IF condition
768                         -- Fix made by AS on 03/17/99
769                         */
770                         IF p_other_mesg_text IS NOT NULL
771                         THEN
772                                 Error_Handler.Add_Message
773                                 (  p_mesg_text          => p_other_mesg_text
774                                  , p_entity_id          => G_REV_LEVEL
775                                  , p_entity_index       => l_CurrentIndex
776                                  , p_message_type       => 'E'
777   				 , p_mesg_name          => p_other_mesg_name);--bug 5174203
778                         END IF;
779                 END LOOP;
780 
781         END setRevisions;
782 
783 
784     /*****************************************************************
785     *
786     *     Followings are enhacements for ECO Routing
787     *
788     ******************************************************************/
789 
790     /******************************************************************
791     * Enhancement for ECO Routing
792     * Added by Masanori Kimizka on 08/23/00
793     *
794     * Procedure     : setRevSubResources (Unexposed)
795     * Parameters    : Other Message
796     *                 Other Status
797     *                 Error Scope
798     *                 Entity Index
799     *                 Operation Index
800     *                 Operation Resource Index
801     * Purpose       : This procedure will set the reference designator
802     *                 record status to other status by looking at the
803     *                 revised item key or the revised component key or
804     *                 else setting all the record status to other status
805     ********************************************************************/
806     PROCEDURE setRevSubResources
807     (  p_error_scope        IN  VARCHAR2
808      , p_other_mesg_text    IN  VARCHAR2
809      , p_other_status       IN  VARCHAR2
810      , p_ri_idx             IN  NUMBER := 0
811      , p_op_idx             IN  NUMBER := 0
812      , p_res_idx            IN  NUMBER := 0
813      , p_entity_index       IN  NUMBER := 0
814      , p_other_mesg_name    IN  VARCHAR2 := NULL -- bug 5174203
815     )
816     IS
817         l_idx   NUMBER;
818     BEGIN
819 
820 IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Setting sub operation resources records to ' || p_other_status); END IF ;
821 
822         IF p_error_scope = G_SCOPE_ALL
823         THEN
827 
824             FOR l_idx IN 1..g_rev_sub_resource_tbl.COUNT
825             LOOP
826                 g_rev_sub_resource_tbl(l_idx).return_status := p_other_status;
828                 IF p_other_mesg_text IS NOT NULL
829                 THEN
830                        Error_Handler.Add_Message
831                        (  p_mesg_text  => p_other_mesg_text
832                         , p_entity_id   => G_SR_LEVEL
833                         , p_entity_index=> l_idx
834                         , p_message_type=> 'E'
835 			, p_mesg_name   => p_other_mesg_name);--bug 5174203
836                 END IF;
837             END LOOP;
838 
839         ELSIF p_error_scope = G_SCOPE_CHILDREN AND
840               p_ri_idx <> 0
841         THEN
842 
843 IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Scope=Children in Sub Op Resource'); END IF;
844 IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Revised Item index <> 0'); END IF;
845 
846             FOR l_idx IN 1..g_rev_sub_resource_tbl.COUNT
847             LOOP
848                    IF NVL(g_rev_sub_resource_tbl(l_idx).revised_item_name, ' ') =
849                       NVL(g_revised_item_tbl(p_ri_idx).revised_item_name, ' ')
850                       AND
851                       NVL(g_rev_sub_resource_tbl(l_idx).organization_code,' ') =
852                       NVL(g_revised_item_tbl(p_ri_idx).organization_code,' ')
853                       AND
854                       NVL(g_rev_sub_resource_tbl(l_idx).eco_name,' ') =
855                       NVL(g_revised_item_tbl(p_ri_idx).eco_name,' ')
856                       AND
857                       NVL(g_rev_sub_resource_tbl(l_idx).op_start_effective_date, SYSDATE) =
858                       NVL(g_revised_item_tbl(p_ri_idx).start_effective_date, SYSDATE)
859                       AND
860                       NVL(g_rev_sub_resource_tbl(l_idx).new_revised_item_revision, 'X') =
861                       NVL(g_revised_item_tbl(p_ri_idx).new_revised_item_revision, 'X')
862                     THEN
863                         g_rev_sub_resource_tbl(l_idx).return_status := p_other_status;
864 
865 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Sub Op Resource at ' || to_char(l_idx) || ' set to status ' ||  p_other_status);
866 END IF;
867 
868                         Error_Handler.Add_Message
869                         (  p_mesg_text     => p_other_mesg_text
870                          , p_entity_id     => G_SR_LEVEL
871                          , p_entity_index  => l_idx
872                          , p_message_type  => 'E'
873 			 , p_mesg_name     => p_other_mesg_name);--bug 5174203
874                     END IF;
875               END LOOP;
876 
877          ELSIF p_error_scope = G_SCOPE_CHILDREN AND
878                p_op_idx <> 0
879          THEN
880 
881              IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Scope=Children in Sub Op Resources'); END IF;
882              IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Operation Sequence index <> 0'); END IF;
883 
884              FOR l_idx IN 1..g_rev_sub_resource_tbl.COUNT
885              LOOP
886                    IF NVL(g_rev_sub_resource_tbl(l_idx).operation_sequence_number, 0 ) =
887                       NVL(g_rev_operation_tbl(p_op_idx).operation_sequence_number, 0 )
888                    AND
889                       NVL(g_rev_sub_resource_tbl(l_idx).op_start_effective_date, SYSDATE) =
890                       NVL(g_rev_operation_tbl(p_op_idx).start_effective_date, SYSDATE)
891                    AND
892                       NVL(g_rev_sub_resource_tbl(l_idx).operation_type, 0) =
893                       NVL(g_rev_operation_tbl(p_op_idx).operation_type, 0)
894                    AND
895                       NVL(g_rev_sub_resource_tbl(l_idx).revised_item_name, ' ') =
896                       NVL(g_rev_operation_tbl(p_op_idx).revised_item_name, ' ')
897                    AND
898                       NVL(g_rev_sub_resource_tbl(l_idx).new_revised_item_revision , 'X') =
899                       NVL(g_rev_operation_tbl(p_op_idx).new_revised_item_revision, 'X')
900                    AND
901                       NVL(g_rev_sub_resource_tbl(l_idx).eco_name, ' ') =
902                       NVL(g_rev_operation_tbl(p_op_idx).eco_name, ' ')
903                    THEN
904                         g_rev_sub_resource_tbl(l_idx).return_status := p_other_status ;
905                         Error_Handler.Add_Message
906                         (  p_mesg_text          => p_other_mesg_text
907                          , p_entity_id          => G_SR_LEVEL
908                          , p_entity_index       => l_idx
909                          , p_message_type       => 'E'
910 			 , p_mesg_name          => p_other_mesg_name);--bug 5174203
911                     END IF;
912                 END LOOP;  -- Sub Res Children of Op Seq Ends.
913 
914          ELSIF p_error_scope = G_SCOPE_SIBLINGS AND p_res_idx <> 0
915          THEN
916 
917 IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Scope = Siblings in Sub Op Resources'); END IF;
918 IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Operation Resource Index <> 0'); END IF ;
919 
920                 FOR l_idx IN 1..g_rev_sub_resource_tbl.COUNT
921                 LOOP
922                    IF NVL(g_rev_sub_resource_tbl(l_idx).operation_sequence_number, 0) =
923                       NVL(g_rev_op_resource_tbl(p_res_idx).operation_sequence_number, 0)
924                    AND
925                       NVL(g_rev_sub_resource_tbl(l_idx).op_start_effective_date, SYSDATE) =
929                       NVL(g_rev_op_resource_tbl(p_res_idx).operation_type, 0)
926                       NVL(g_rev_op_resource_tbl(p_res_idx).op_start_effective_date,SYSDATE)
927                    AND
928                       NVL(g_rev_sub_resource_tbl(l_idx).operation_type, 0) =
930                    AND
931                       NVL(g_rev_sub_resource_tbl(l_idx).revised_item_name, ' ') =
932                       NVL(g_rev_op_resource_tbl(p_res_idx).revised_item_name, ' ')
933                    AND
934                       NVL(g_rev_sub_resource_tbl(l_idx).new_revised_item_revision, 'X') =
935                       NVL(g_rev_op_resource_tbl(p_res_idx).new_revised_item_revision, 'X')
936                    AND
937                       NVL(g_rev_sub_resource_tbl(l_idx).eco_name, ' ') =
938                       NVL(g_rev_op_resource_tbl(p_res_idx).eco_name, ' ')
939                    THEN
940                         --
941                         -- Since routing sequence id is not available
942                         -- match the revised item information also.
943                         --
944                         g_rev_sub_resource_tbl(l_idx).return_status :=
945                                                 p_other_status;
946 
947                         Error_Handler.Add_Message
948                         (  p_mesg_text          => p_other_mesg_text
949                          , p_entity_id          => G_SR_LEVEL
950                          , p_entity_index       => l_idx
951                          , p_message_type       => 'E'
952 			 , p_mesg_name          => p_other_mesg_name);--bug 5174203
953                     END IF;
954 
955                 END LOOP; -- Scope = Siblings with res_idx <> 0 Ends
956 
957              ELSIF p_error_scope = G_SCOPE_SIBLINGS AND
958                    p_ri_idx = 0 AND
959                    p_op_idx = 0 AND
960                    p_res_idx = 0
961              THEN
962                 --
963                 -- This situation will arise when operation sequence and
964                 -- operation resource are not part of the business object
965                 -- input data.
966                 -- Match the operation key information at the entity index
967                 -- location with rest of the records, all those that are found
968                 -- will be siblings and should get an error.
969                 --
970 IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Scope=Siblings in Sub Op Resources'); END IF;
971 IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('All entity indexes = 0'); END IF;
972 
973                 FOR l_idx IN (p_entity_index+1)..g_rev_sub_resource_tbl.COUNT
974                 LOOP
975                     IF NVL(g_rev_sub_resource_tbl(l_idx).operation_sequence_number, 0) =
976                        NVL(g_rev_sub_resource_tbl(p_entity_index).operation_sequence_number, 0)
977                        AND
978                        NVL(g_rev_sub_resource_tbl(l_idx).op_start_effective_date, SYSDATE) =
979                        NVL(g_rev_sub_resource_tbl(p_entity_index).op_start_effective_date, SYSDATE)
980                        AND
981                        NVL(g_rev_sub_resource_tbl(l_idx).operation_type, 0) =
982                        NVL(g_rev_sub_resource_tbl(p_entity_index).operation_type, 0)
983                        AND
984                        NVL(g_rev_sub_resource_tbl(l_idx).revised_item_name, ' ') =
985                        NVL(g_rev_sub_resource_tbl(p_entity_index).revised_item_name, ' ')
986                        AND
987                        NVL(g_rev_sub_resource_tbl(l_idx).new_revised_item_revision, 'X') =
988                        NVL(g_rev_sub_resource_tbl(p_entity_index).new_revised_item_revision, 'X')
989                        AND
990                        NVL(g_rev_sub_resource_tbl(l_idx).eco_name, ' ') =
991                        NVL(g_rev_sub_resource_tbl(p_entity_index).eco_name, ' ')
992                    THEN
993                         g_rev_sub_resource_tbl(l_idx).return_status := p_other_status;
994                         Error_Handler.Add_Message
995                         (  p_mesg_text          => p_other_mesg_text
996                          , p_entity_id          => G_SR_LEVEL
997                          , p_entity_index       => l_idx
998                          , p_message_type       => 'E'
999 			 , p_mesg_name          => p_other_mesg_name);--bug 5174203
1000                     END IF;
1001                 END LOOP;
1002          END IF; -- If Scope = Ends.
1003 
1004     END setRevSubResources;
1005     -- Added by MK on 08/23/00
1006 
1007 
1008     /******************************************************************
1009     * Enhancement for ECO Routing
1010     * Added by Masanori Kimizka on 08/23/00
1011     *
1012     * Procedure : setRevOperationResources (Unexposed)
1013     * Parameters    : Other Message
1014     *                 Other Status
1015     *                 Error Scope
1016     *                 Entity Index
1017     *                 Operation Index
1018     * Purpose   : This procedure will set the operation resource
1019     *             record status to other status by looking at the
1020     *             operation sequence key or else setting all the record
1021     *             status to other status
1022     ********************************************************************/
1023 
1024     PROCEDURE setRevOperationResources
1025     (  p_error_scope        IN  VARCHAR2
1026      , p_other_mesg_text    IN  VARCHAR2
1030      , p_entity_index       IN  NUMBER := 0
1027      , p_other_status       IN  VARCHAR2
1028      , p_ri_idx             IN  NUMBER := 0
1029      , p_op_idx             IN  NUMBER := 0
1031      , p_other_mesg_name    IN  VARCHAR2 := NULL -- bug 5174203
1032     )
1033     IS
1034         l_idx   NUMBER;
1035     BEGIN
1036 
1037 IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Setting Opration Rsource records to ' ||  p_other_status);
1038 END IF;
1039 
1040 
1041         IF p_error_scope = G_SCOPE_ALL
1042         THEN
1043 
1044 
1045 
1046            FOR l_idx IN (p_entity_index+1)..g_rev_op_resource_tbl.COUNT
1047            LOOP
1048            g_rev_op_resource_tbl(l_idx).return_status := p_other_status;
1049 
1050                IF p_other_mesg_text IS NOT NULL
1051                THEN
1052                   Error_Handler.Add_Message
1053                   ( p_mesg_text     => p_other_mesg_text
1054                   , p_entity_id     => G_RES_LEVEL
1055                   , p_entity_index  => l_idx
1056                   , p_message_type  => 'E'
1057 		  , p_mesg_name     => p_other_mesg_name);--bug 5174203
1058                END IF;
1059            END LOOP;
1060 
1061             --
1062             -- Set the Substitute Operation Resources Record Status too
1063             --
1064             setRevSubResources
1065             (  p_other_status       => p_other_status
1066              , p_other_mesg_text    => p_other_mesg_text
1067              , p_error_scope        => p_error_scope
1068              );
1069 
1070          ELSIF p_error_scope = G_SCOPE_CHILDREN AND
1071                p_ri_idx <> 0
1072          THEN
1073 
1074 IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Scope=Children in Operation Resource'); END IF;
1075 IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Revised Item index <> 0'); END IF;
1076 
1077 
1078                 FOR l_idx IN 1..g_rev_op_resource_tbl.COUNT
1079                 LOOP
1080                    IF NVL(g_rev_op_resource_tbl(l_idx).revised_item_name, ' ') =
1081                       NVL(g_revised_item_tbl(p_ri_idx).revised_item_name, ' ')
1082                       AND
1083                       NVL(g_rev_op_resource_tbl(l_idx).organization_code, ' ') =
1084                       NVL(g_revised_item_tbl(p_ri_idx).organization_code, ' ')
1085                       AND
1086                       NVL(g_rev_op_resource_tbl(l_idx).eco_name, ' ') =
1087                       NVL(g_revised_item_tbl(p_ri_idx).eco_name, ' ')
1088                       AND
1089                       NVL(g_rev_op_resource_tbl(l_idx).op_start_effective_date, SYSDATE) =
1090                       NVL(g_revised_item_tbl(p_ri_idx).start_effective_date, SYSDATE)
1091                       AND
1092                       NVL(g_rev_op_resource_tbl(l_idx).new_revised_item_revision, 'X') =
1093                       NVL(g_revised_item_tbl(p_ri_idx).new_revised_item_revision, 'X')
1094                     THEN
1095                         g_rev_op_resource_tbl(l_idx).return_status := p_other_status;
1096 
1097 IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Op Resource at ' || to_char(l_idx) || ' set to status ' || p_other_status);
1098 END IF;
1099 
1100                         Error_Handler.Add_Message
1101                         (  p_mesg_text     => p_other_mesg_text
1102                          , p_entity_id     => G_RES_LEVEL
1103                          , p_entity_index  => l_idx
1104                          , p_message_type  => 'E'
1105 			 , p_mesg_name     => p_other_mesg_name);--bug 5174203
1106                      END IF;
1107                 END LOOP;
1108 
1109         ELSIF p_error_scope = G_SCOPE_CHILDREN AND
1110               p_op_idx <> 0
1111         THEN
1112 
1113 IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Scope=Children in Operation Resource'); END IF;
1114 IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Operation Sequence index <> 0'); END IF;
1115 
1116             FOR l_idx IN 1..g_rev_op_resource_tbl.COUNT
1117             LOOP
1118                 IF NVL(g_rev_op_resource_tbl(l_idx).operation_sequence_number, 0)=
1119                    NVL(g_rev_operation_tbl(p_op_idx).operation_sequence_number, 0)
1120                    AND
1121                    NVL(g_rev_op_resource_tbl(l_idx).op_start_effective_date, SYSDATE) =
1122                    NVL(g_rev_operation_tbl(p_op_idx).start_effective_date, SYSDATE)
1123                    AND
1124                    NVL(g_rev_op_resource_tbl(l_idx).operation_type, 0) =
1125                    NVL(g_rev_operation_tbl(p_op_idx).operation_type, 0)
1126                    AND
1127                    NVL(g_rev_op_resource_tbl(l_idx).revised_item_name, ' ') =
1128                    NVL(g_rev_operation_tbl(p_op_idx).revised_item_name, ' ')
1129                    AND
1130                    NVL(g_rev_op_resource_tbl(l_idx).new_revised_item_revision , 'X') =
1131                    NVL(g_rev_operation_tbl(p_op_idx).new_revised_item_revision, 'X')
1132                    AND
1133                    NVL(g_rev_op_resource_tbl(l_idx).eco_name, ' ') =
1134                    NVL(g_rev_operation_tbl(p_op_idx).eco_name, ' ')
1135                 THEN
1136 
1137                     g_rev_op_resource_tbl(l_idx).return_status := p_other_status;
1138                     Error_Handler.Add_Message
1139                     (  p_mesg_text      => p_other_mesg_text
1140                      , p_entity_id      => G_RES_LEVEL
1144                 END IF;
1141                      , p_entity_index   => l_idx
1142                      , p_message_type   => 'E'
1143 		     , p_mesg_name      => p_other_mesg_name);--bug 5174203
1145             END LOOP;  -- Op Resource Children of Op Seq Ends.
1146 
1147         ELSIF p_error_scope = G_SCOPE_SIBLINGS AND
1148               p_ri_idx = 0 AND p_op_idx = 0
1149         THEN
1150         --
1151         -- This situation will arise when Rev Item and Op Seq is
1152         -- not part of the business object input data.
1153         -- Match the operation key information at the entity index
1154         -- location with rest of the records, all those that are found
1155         -- will be siblings and should get an error.
1156         --
1157 
1158 IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Scope=Siblings in Operation Resource'); END IF;
1159 IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('All Indexes = 0'); END IF;
1160 
1161             FOR  l_idx IN (p_entity_index+1)..g_rev_op_resource_tbl.COUNT
1162             LOOP
1163                 IF NVL(g_rev_op_resource_tbl(l_idx).operation_sequence_number, 0) =
1164                    NVL(g_rev_op_resource_tbl(p_entity_index).operation_sequence_number,0)
1165                    AND
1166                    NVL(g_rev_op_resource_tbl(l_idx).op_start_effective_date, SYSDATE) =
1167                    NVL(g_rev_op_resource_tbl(p_entity_index).op_start_effective_date, SYSDATE)
1168                    AND
1169                    NVL(g_rev_op_resource_tbl(l_idx).operation_type, 0) =
1170                    NVL(g_rev_op_resource_tbl(p_entity_index).operation_type, 0)
1171                    AND
1172                    NVL(g_rev_op_resource_tbl(l_idx).revised_item_name, ' ') =
1173                    NVL(g_rev_op_resource_tbl(p_entity_index).revised_item_name, ' ')
1174                    AND
1175                    NVL(g_rev_op_resource_tbl(l_idx).new_revised_item_revision , 'X') =
1176                    NVL(g_rev_op_resource_tbl(p_entity_index).new_revised_item_revision, 'X')
1177                    AND
1178                    NVL(g_rev_op_resource_tbl(l_idx).eco_name, ' ') =
1179                    NVL(g_rev_op_resource_tbl(p_entity_index).eco_name, ' ')
1180                 THEN
1181 
1182                 g_rev_op_resource_tbl(l_idx).return_status := p_other_status;
1183                 Error_Handler.Add_Message
1184                 (  p_mesg_text      => p_other_mesg_text
1185                  , p_entity_id      => G_RES_LEVEL
1186                  , p_entity_index   => l_idx
1187                  , p_message_type   => 'E'
1188 		 , p_mesg_name      => p_other_mesg_name);--bug 5174203
1189                 END IF;
1190             END LOOP;
1191 
1192         --
1193         -- Substitute Operation Resources will also be considered as siblings
1194         -- of operation resource, they should get an error when
1195         -- error level is operation resource with scope of Siblings
1196                 --
1197             setRevSubResources
1198             (  p_other_status       => p_other_status
1199              , p_other_mesg_text    => p_other_mesg_text
1200              , p_error_scope        => p_error_scope
1201              , p_res_idx            => p_entity_index
1202             );
1203        END IF; -- If error scope Ends
1204 
1205     END setRevOperationResources ;
1206 
1207 
1208     /*****************************************************************
1209     * Enhancement for ECO Routing
1210     * Added by Masanori Kimizka on 08/23/00
1211     *
1212     * Procedure     : setRevOperationSequences (Unexposed)
1213     * Parameters IN : Other Message Text
1214     *                 Other status
1215     *                 Entity Index
1216     *                 Error Scope
1217     *                 Error Status
1218     *                 Revised Item Index
1219     * Parameters OUT: None
1220     * Purpose       : This procedure will set the revised components record
1221     *                 status to other status and for each errored record
1222     *                 it will log the other message indicating what caused
1223     *                 the other records to fail.
1224     ******************************************************************/
1225     PROCEDURE setRevOperationSequences
1226     (  p_error_scope        IN  VARCHAR2
1227      , p_other_mesg_text    IN  VARCHAR2
1228      , p_other_status       IN  VARCHAR2
1229      , p_entity_index       IN  NUMBER := 0
1230      , p_ri_idx             IN  NUMBER := 0
1231      , p_other_mesg_name    IN  VARCHAR2 := NULL -- bug 5174203
1232      )
1233     IS
1234         l_Idx       NUMBER;
1235     BEGIN
1236 
1237        IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Setting Revised operation records to '
1238        || p_other_status);
1239        END IF;
1240 
1241        IF p_error_scope = G_SCOPE_CHILDREN AND
1242           p_ri_idx <> 0
1243        THEN
1244 
1245 IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Scope=Children in Revised Operation'); END IF;
1246 IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Revised Item index <> 0'); END IF;
1247 
1248            FOR l_idx IN 1..g_rev_operation_tbl.COUNT
1249            LOOP
1250                IF NVL(g_rev_operation_tbl(l_Idx).eco_name, ' ') =
1251                   NVL(g_revised_item_tbl(p_ri_idx).eco_name, ' ')
1252                   AND
1253                   NVL(g_rev_operation_tbl(l_Idx).revised_item_name, ' ') =
1254                   NVL(g_revised_item_tbl(p_ri_idx).revised_item_name, ' ')
1258                   AND
1255                   AND
1256                   NVL(g_rev_operation_tbl(l_Idx).organization_code, ' ') =
1257                   NVL(g_revised_item_tbl(p_ri_idx).organization_code, ' ')
1259                   NVL(g_rev_operation_tbl(l_Idx).new_revised_item_revision, 'X') =
1260                   NVL(g_revised_item_tbl(p_ri_idx).new_revised_item_revision, 'X')
1261                   AND
1262                   NVL(g_rev_operation_tbl(l_Idx).start_effective_date, SYSDATE) =
1263                   NVL(g_revised_item_tbl(p_ri_idx).start_effective_date, SYSDATE)
1264                THEN
1265 
1266                     --
1267                     -- If the revised item key of the operation
1268                     -- matches that of the revised item then
1269                     -- error that revised operation too.
1270                     --
1271 
1272                     IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug
1273                     ('Comp. errored at index: '||to_char(l_idx));
1274                     END IF;
1275 
1276                         g_rev_operation_tbl(l_Idx).return_status := p_other_status;
1277 
1278                         Error_Handler.Add_Message
1279                         (  p_mesg_text  => p_other_mesg_text
1280                         , p_entity_id   => G_OP_LEVEL
1281                         , p_entity_index=> l_Idx
1282                         , p_message_type=> 'E'
1283 			, p_mesg_name   => p_other_mesg_name);--bug 5174203
1284                END IF;
1285 
1286            END LOOP;
1287 
1288            --
1289            -- For each of the operation child
1290            -- set the operation resources and
1291            -- substitute op resources childrens
1292            --
1293            --
1294 
1295            setRevOperationResources
1296            (  p_error_scope       => p_error_scope
1297             , p_other_mesg_text    => p_other_mesg_text
1298             , p_other_status       => p_other_status
1299             , p_ri_idx             => p_ri_idx
1300             );
1301 
1302            setRevSubResources
1303            (  p_error_scope        => p_error_scope
1304             , p_other_mesg_text    => p_other_mesg_text
1305             , p_other_status       => p_other_status
1306             , p_ri_idx             => p_ri_idx
1307             );
1308 
1309         ELSIF p_error_scope = G_SCOPE_SIBLINGS THEN
1310 
1311         IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Scope=Siblings in Revised Operation'); END IF;
1312         IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Entity Index: ' ||
1313         to_char(p_entity_index));
1314         END IF;
1315 
1316             FOR l_idx IN 1..g_rev_component_tbl.COUNT
1317             LOOP
1318                 --
1319                 -- If there are any other components that
1320                 -- belong to the same revised item then error
1321                 -- those records too.
1322                 --
1323                 IF NVL(g_rev_operation_tbl(l_Idx).eco_name, ' ') =
1324                 NVL(g_rev_operation_tbl(p_entity_index).eco_name, ' ')
1325                 AND
1326                 NVL(g_rev_operation_tbl(l_Idx).revised_item_name, ' ') =
1327                 NVL(g_rev_operation_tbl(p_entity_index).revised_item_name, ' ')
1328                 AND
1329                 NVL(g_rev_operation_tbl(l_Idx).organization_code, ' ')=
1330                 NVL(g_rev_operation_tbl(p_entity_index).organization_code, ' ')
1331                 AND
1332                 NVL(g_rev_operation_tbl(l_Idx).new_revised_item_revision, 'X') =
1333                 NVL(g_rev_operation_tbl(p_entity_index).new_revised_item_revision, 'X')
1334                 AND
1335                 NVL(g_rev_operation_tbl(l_Idx).start_effective_date, SYSDATE)=
1336                 NVL(g_rev_operation_tbl(p_entity_index).start_effective_date,SYSDATE)
1337                 THEN
1338                     --
1339                     -- Set the operation error status
1340                     --
1341                     g_rev_operation_tbl(l_idx).return_status :=  p_other_status;
1342 
1343 IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Revised Operation at ' || to_char(l_idx) || ' set to status ' ||p_other_status);
1344 END IF;
1345                     Error_Handler.Add_Message
1346                     (  p_mesg_text    => p_other_mesg_text
1347                      , p_entity_id    => G_RC_LEVEL
1348                      , p_entity_index => l_idx
1349                      , p_message_type => 'E'
1350  		     , p_mesg_name    => p_other_mesg_name);--bug 5174203
1351 
1352                      --
1353                      -- Set an child records of the revised
1354                      -- operation to other status too.
1355                      --
1356                      setRevOperationResources
1357                      (  p_other_status    => p_other_status
1358                       , p_error_scope     => G_SCOPE_CHILDREN
1359                       , p_op_idx          => l_idx
1360                       , p_other_mesg_text => p_other_mesg_text
1361                       );
1362 
1363                       setRevSubResources
1364                       (  p_other_status    => p_other_status
1365                        , p_error_scope     => G_SCOPE_CHILDREN
1366                        , p_op_idx          => l_idx
1367                        , p_other_mesg_text => p_other_mesg_text
1368                       );
1369 
1370                 END IF; -- Operation Siblings Found Ends
1374         THEN
1371             END LOOP;
1372 
1373         ELSIF p_error_scope = G_SCOPE_ALL
1375 
1376             IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Scope=All in Operation Sequences'); END IF;
1377 
1378             FOR l_idx IN 1..g_rev_operation_tbl.COUNT
1379             LOOP
1380                g_rev_operation_tbl(l_idx).return_status := p_other_status;
1381 
1382                IF p_other_mesg_text IS NOT NULL
1383                THEN
1384                   Error_Handler.Add_Message
1385                   ( p_mesg_text    => p_other_mesg_text
1386                   , p_entity_id    => G_OP_LEVEL
1387                   , p_entity_index => l_Idx
1388                   , p_message_type => 'E'
1389 		  , p_mesg_name    => p_other_mesg_name);--bug 5174203
1390                END IF;
1391 
1392             END LOOP;
1393 
1394             --
1395             -- Set the operation resource and substitute
1396             -- operation resource record status too.
1397             --
1398             setRevOperationResources
1399                     (  p_other_status    => p_other_status
1400                      , p_error_scope     => p_error_scope
1401                      , p_other_mesg_text => p_other_mesg_text
1402                      );
1403 
1404         END IF; -- Error Scope Ends
1405 
1406     END setRevOperationSequences ;
1407     -- Added by MK 08/23/2000
1408 
1409 
1410 
1411         /*****************************************************************
1412         * Procedure     : setRevisedItems (unexposed)
1413         * Parameters IN : Other Message Text
1414         *                 Other status
1415         *                 Entity Index
1416         *                 Error Scope
1417         *                 Error Status
1418         * Parameters OUT: None
1419         * Purpose       : This procedure will set the Revised Items record
1420         *                 status to other status and for each errored record
1421         *                 it will log the other message indicating what caused
1422         *                 the other records to fail.
1423         ******************************************************************/
1424         PROCEDURE setRevisedItems
1425         (  p_error_status       IN  VARCHAR2 := NULL
1426          , p_error_scope        IN  VARCHAR2
1427          , p_other_mesg_text    IN  VARCHAR2
1428          , p_other_status       IN  VARCHAR2
1429          , p_entity_index       IN  NUMBER := 0
1430 	 , p_other_mesg_name    IN  VARCHAR2 := NULL -- bug 5174203
1431         )
1432         IS
1433                 l_CurrentIndex  NUMBER;
1434         BEGIN
1435 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Setting Revised Item  records to ' || p_other_status); END IF;
1436 
1437                 FOR l_CurrentIndex IN 1..g_revised_item_tbl.COUNT
1438                 LOOP
1439                         g_revised_item_tbl(l_CurrentIndex).return_status :=
1440                                 p_other_status;
1441 
1442                 /* Put in fix in response to bug 851387
1443                 -- Added IF condition
1444                 -- Fix made by AS on 03/17/99
1445                 */
1446                 IF p_other_mesg_text IS NOT NULL
1447                         THEN
1448                                 Error_Handler.Add_Message
1449                                 (  p_mesg_text          => p_other_mesg_text
1450                                  , p_entity_id          => G_RI_LEVEL
1451                                  , p_entity_index       => l_CurrentIndex
1452                                  , p_message_type       => 'E'
1453 				 , p_mesg_name          => p_other_mesg_name);--bug 5174203
1454                         END IF;
1455                 END LOOP;
1456 
1457         END setRevisedItems;
1458 
1459         /******************************************************************
1460         * Procedure     : Log_Error
1461         * Parameters IN : ECO Header record and rest of the Entity Tables
1462         *                 Message Token Table
1463         *                 Other Message Table
1464         *                 Other Status
1465         *                 Entity Index
1466         *                 Error Level
1467         *                 Error Scope
1468         *                 Error Status
1469         * Parameters OUT: ECO Header record and rest of the Entity Tables
1470         * Purpose       : Log Error will take the Message Token Table and
1471         *                 seperate the message and their tokens, get the
1472         *                 token substitute messages from the message dictionary
1473         *                 and put in the error stack.
1474         *                 Log Error will also make sure that the error
1475         *                 propogates to the right level's of the business object
1476         *                 and that the rest of the entities get the appropriate
1477         *                 status and message.
1478         ******************************************************************/
1479 
1480 
1481         /* Comment out by MK on 08/23/2000 ***********************************
1482         PROCEDURE Log_Error
1483         (  p_eco_rec            IN  ENG_Eco_Pub.Eco_Rec_Type :=
1484                                                Eng_Eco_Pub.G_MISS_ECO_REC
1485          , p_eco_revision_tbl   IN  Eng_Eco_Pub.Eco_Revision_tbl_Type
1486                                     := Eng_Eco_Pub.G_MISS_ECO_REVISION_TBL
1487          , p_revised_item_tbl   IN  Eng_Eco_Pub.Revised_Item_Tbl_Type
1491          , p_ref_designator_tbl IN  Bom_Bo_Pub.Ref_Designator_Tbl_Type
1488                                           := Eng_Eco_Pub.G_MISS_REVISED_ITEM_TBL
1489          , p_rev_component_tbl  IN  Bom_Bo_Pub.Rev_Component_Tbl_Type
1490                                        := Bom_Bo_Pub.G_MISS_REV_COMPONENT_TBL
1492                                       := Bom_Bo_Pub.G_MISS_REF_DESIGNATOR_TBL
1493          , p_sub_component_tbl  IN  Bom_Bo_Pub.Sub_Component_Tbl_Type
1494                                        := Bom_Bo_Pub.G_MISS_SUB_COMPONENT_TBL
1495          , p_Mesg_Token_tbl     IN  Error_Handler.Mesg_Token_Tbl_Type
1496                                           := Error_Handler.G_MISS_MESG_TOKEN_TBL
1497          , p_error_status       IN  VARCHAR2
1498          , p_error_scope        IN  VARCHAR2 := NULL
1499          , p_other_message      IN  VARCHAR2 := NULL
1500          , p_other_status       IN  VARCHAR2 := NULL
1501          , p_other_token_tbl    IN  Error_Handler.Token_Tbl_Type
1502                                           := Error_Handler.G_MISS_TOKEN_TBL
1503          , p_error_level        IN  NUMBER
1504          , p_entity_index       IN  NUMBER := NULL
1505          , x_eco_rec            OUT ENG_Eco_Pub.Eco_Rec_Type
1506          , x_eco_revision_tbl   OUT Eng_Eco_Pub.Eco_Revision_tbl_Type
1507          , x_revised_item_tbl   OUT Eng_Eco_Pub.Revised_Item_Tbl_Type
1508          , x_rev_component_tbl  OUT Bom_Bo_Pub.Rev_Component_Tbl_Type
1509          , x_ref_designator_tbl OUT Bom_Bo_Pub.Ref_Designator_Tbl_Type
1510          , x_sub_component_tbl  OUT Bom_Bo_Pub.Sub_Component_Tbl_Type
1511          )
1512         ***********************************************************************/
1513 
1514 
1515 
1516         /*******************************************************
1517         -- Log_Error prodedure used for ECO Routing enhancement
1518         --
1519         -- Added rev op, rev op res and rev sub res error handling
1520         -- to existed Log_Error procedure
1521         --
1522         -- Modified by MK on 08/23/2000
1523         ********************************************************/
1524         PROCEDURE Log_Error
1525         (  p_eco_rec            IN  ENG_Eco_Pub.Eco_Rec_Type :=
1526                                                Eng_Eco_Pub.G_MISS_ECO_REC
1527          , p_eco_revision_tbl   IN  Eng_Eco_Pub.Eco_Revision_tbl_Type
1528                                     := Eng_Eco_Pub.G_MISS_ECO_REVISION_TBL
1529          , p_revised_item_tbl   IN  Eng_Eco_Pub.Revised_Item_Tbl_Type
1530                                     := Eng_Eco_Pub.G_MISS_REVISED_ITEM_TBL
1531 
1532          -- Followings are for Routing BO
1533          , p_rev_operation_tbl    IN  Bom_Rtg_Pub.Rev_Operation_Tbl_Type
1534                                       := Bom_Rtg_Pub.G_MISS_REV_OPERATION_TBL
1535          , p_rev_op_resource_tbl  IN  Bom_Rtg_Pub.Rev_Op_Resource_Tbl_Type
1536                                       := Bom_Rtg_Pub.G_MISS_REV_OP_RESOURCE_TBL
1537          , p_rev_sub_resource_tbl IN  Bom_Rtg_Pub.Rev_Sub_Resource_Tbl_Type
1538                                       := Bom_Rtg_Pub.G_MISS_REV_SUB_RESOURCE_TBL
1539          -- Added by MK on 08/23/2000
1540 
1541          , p_rev_component_tbl  IN  Bom_Bo_Pub.Rev_Component_Tbl_Type
1542                                        := Eng_Eco_Pub.G_MISS_REV_COMPONENT_TBL
1543          , p_ref_designator_tbl IN  Bom_Bo_Pub.Ref_Designator_Tbl_Type
1544                                       := Eng_Eco_Pub.G_MISS_REF_DESIGNATOR_TBL
1545          , p_sub_component_tbl  IN  Bom_Bo_Pub.Sub_Component_Tbl_Type
1546                                        := Eng_Eco_Pub.G_MISS_SUB_COMPONENT_TBL
1547          , p_Mesg_Token_tbl     IN  Error_Handler.Mesg_Token_Tbl_Type
1548                                     := Error_Handler.G_MISS_MESG_TOKEN_TBL
1549          , p_error_status       IN  VARCHAR2
1550          , p_error_scope        IN  VARCHAR2 := NULL
1551          , p_other_message      IN  VARCHAR2 := NULL
1552          , p_other_status       IN  VARCHAR2 := NULL
1553          , p_other_token_tbl    IN  Error_Handler.Token_Tbl_Type
1554                                           := Error_Handler.G_MISS_TOKEN_TBL
1555          , p_error_level        IN  NUMBER
1556          , p_entity_index       IN  NUMBER := 1 -- := NULL
1557          , x_eco_rec            IN OUT NOCOPY ENG_Eco_Pub.Eco_Rec_Type
1558          , x_eco_revision_tbl   IN OUT NOCOPY Eng_Eco_Pub.Eco_Revision_tbl_Type
1559          , x_revised_item_tbl   IN OUT NOCOPY Eng_Eco_Pub.Revised_Item_Tbl_Type
1560          , x_rev_component_tbl  IN OUT NOCOPY Bom_Bo_Pub.Rev_Component_Tbl_Type
1561          , x_ref_designator_tbl IN OUT NOCOPY Bom_Bo_Pub.Ref_Designator_Tbl_Type
1562          , x_sub_component_tbl  IN OUT NOCOPY Bom_Bo_Pub.Sub_Component_Tbl_Type
1563 
1564          -- Followings are for Routing BO
1565          , x_rev_operation_tbl    IN OUT NOCOPY Bom_Rtg_Pub.Rev_Operation_Tbl_Type
1566          , x_rev_op_resource_tbl  IN OUT NOCOPY Bom_Rtg_Pub.Rev_Op_Resource_Tbl_Type
1567          , x_rev_sub_resource_tbl IN OUT NOCOPY Bom_Rtg_Pub.Rev_Sub_Resource_Tbl_Type
1568          -- Added by MK on 08/23/2000
1569 
1570         )
1571         IS
1572 
1573             l_change_line_tbl       Eng_Eco_Pub.Change_Line_Tbl_Type;
1574 
1575         BEGIN
1576 
1577              -- Overloading Log_Error for Eng Change Mgmt Enhancement
1578              Log_Error
1579              (  p_eco_rec                   => p_eco_rec
1580               , p_eco_revision_tbl          => p_eco_revision_tbl
1581               , p_change_line_tbl           => l_change_line_tbl -- Eng Change
1582               , p_revised_item_tbl          => p_revised_item_tbl
1586               , p_rev_component_tbl         => p_rev_component_tbl
1583               , p_rev_operation_tbl         => p_rev_operation_tbl
1584               , p_rev_op_resource_tbl       => p_rev_op_resource_tbl
1585               , p_rev_sub_resource_tbl      => p_rev_sub_resource_tbl
1587               , p_ref_designator_tbl        => p_ref_designator_tbl
1588               , p_sub_component_tbl         => p_sub_component_tbl
1589               , p_Mesg_Token_tbl            => p_Mesg_Token_tbl
1590               , p_error_status              => p_error_status
1591               , p_error_scope               => p_error_scope
1592               , p_other_message             => p_other_message
1593               , p_other_status              => p_other_status
1594               , p_other_token_tbl           => p_other_token_tbl
1595               , p_error_level               => p_error_level
1596               , p_entity_index              => p_entity_index
1597               , x_eco_rec                   => x_eco_rec
1598               , x_eco_revision_tbl          => x_eco_revision_tbl
1599               , x_change_line_tbl           => l_change_line_tbl  -- Eng Change
1600               , x_revised_item_tbl          => x_revised_item_tbl
1601               , x_rev_component_tbl         => x_rev_component_tbl
1602               , x_ref_designator_tbl        => x_ref_designator_tbl
1603               , x_sub_component_tbl         => x_sub_component_tbl
1604               , x_rev_operation_tbl         => x_rev_operation_tbl
1605               , x_rev_op_resource_tbl       => x_rev_op_resource_tbl
1606               , x_rev_sub_resource_tbl      => x_rev_sub_resource_tbl
1607               );
1608 
1609 
1610          END Log_Error ;
1611 
1612 
1613 
1614         /*******************************************************
1615         -- Log_Error prodedure used for Eng Change Managmet
1616         -- enhancement
1617         --
1618         -- Added people and change Line error handling
1619         -- to existed Log_Error procedure
1620         --
1621         -- Added by MK on 08/13/2002
1622         ********************************************************/
1623         PROCEDURE Log_Error
1624         (  p_eco_rec              IN  Eng_Eco_Pub.Eco_Rec_Type
1625                                       := Eng_Eco_Pub.G_MISS_ECO_REC
1626          , p_eco_revision_tbl     IN  Eng_Eco_Pub.Eco_Revision_tbl_Type
1627                                       := Eng_Eco_Pub.G_MISS_ECO_REVISION_TBL
1628          , p_change_line_tbl      IN  Eng_Eco_Pub.Change_Line_Tbl_Type -- Eng Change
1629                                       := Eng_Eco_Pub.G_MISS_CHANGE_LINE_TBL
1630          , p_revised_item_tbl     IN  Eng_Eco_Pub.Revised_Item_Tbl_Type
1631                                       := Eng_Eco_Pub.G_MISS_REVISED_ITEM_TBL
1632          , p_rev_operation_tbl    IN  Bom_Rtg_Pub.Rev_Operation_Tbl_Type
1633                                       := Bom_Rtg_Pub.G_MISS_REV_OPERATION_TBL
1634          , p_rev_op_resource_tbl  IN  Bom_Rtg_Pub.Rev_Op_Resource_Tbl_Type
1635                                       := Bom_Rtg_Pub.G_MISS_REV_OP_RESOURCE_TBL
1636          , p_rev_sub_resource_tbl IN  Bom_Rtg_Pub.Rev_Sub_Resource_Tbl_Type
1637                                       := Bom_Rtg_Pub.G_MISS_REV_SUB_RESOURCE_TBL
1638          , p_rev_component_tbl    IN  Bom_Bo_Pub.Rev_Component_Tbl_Type
1639                                        := Eng_Eco_Pub.G_MISS_REV_COMPONENT_TBL
1640          , p_ref_designator_tbl   IN  Bom_Bo_Pub.Ref_Designator_Tbl_Type
1641                                       := Eng_Eco_Pub.G_MISS_REF_DESIGNATOR_TBL
1642          , p_sub_component_tbl    IN  Bom_Bo_Pub.Sub_Component_Tbl_Type
1643                                       := Eng_Eco_Pub.G_MISS_SUB_COMPONENT_TBL
1644          , p_Mesg_Token_tbl       IN  Error_Handler.Mesg_Token_Tbl_Type
1645                                       := Error_Handler.G_MISS_MESG_TOKEN_TBL
1646          , p_error_status         IN  VARCHAR2
1647          , p_error_scope          IN  VARCHAR2 := NULL
1648          , p_other_message        IN  VARCHAR2 := NULL
1649          , p_other_status         IN  VARCHAR2 := NULL
1650          , p_other_token_tbl      IN  Error_Handler.Token_Tbl_Type
1651                                       := Error_Handler.G_MISS_TOKEN_TBL
1652          , p_error_level          IN  NUMBER
1653          , p_entity_index         IN  NUMBER := 1 -- := NULL
1654          , x_eco_rec              IN OUT NOCOPY Eng_Eco_Pub.Eco_Rec_Type
1655          , x_eco_revision_tbl     IN OUT NOCOPY Eng_Eco_Pub.Eco_Revision_tbl_Type
1656          , x_change_line_tbl      IN OUT NOCOPY Eng_Eco_Pub.Change_Line_Tbl_Type      -- Eng Change
1657          , x_revised_item_tbl     IN OUT NOCOPY Eng_Eco_Pub.Revised_Item_Tbl_Type
1658          , x_rev_component_tbl    IN OUT NOCOPY Bom_Bo_Pub.Rev_Component_Tbl_Type
1659          , x_ref_designator_tbl   IN OUT NOCOPY Bom_Bo_Pub.Ref_Designator_Tbl_Type
1660          , x_sub_component_tbl    IN OUT NOCOPY Bom_Bo_Pub.Sub_Component_Tbl_Type
1661          , x_rev_operation_tbl    IN OUT NOCOPY Bom_Rtg_Pub.Rev_Operation_Tbl_Type
1662          , x_rev_op_resource_tbl  IN OUT NOCOPY Bom_Rtg_Pub.Rev_Op_Resource_Tbl_Type
1663          , x_rev_sub_resource_tbl IN OUT NOCOPY Bom_Rtg_Pub.Rev_Sub_Resource_Tbl_Type
1664          )
1665         IS
1666                 l_message_name          VARCHAR2(30);
1667                 l_other_message         VARCHAR2(2000);
1668                 l_message_text          VARCHAR2(2000);
1669                 l_LoopIndex             NUMBER;
1670                 l_Error_Level           NUMBER      := p_Error_Level;
1671                 l_error_scope           VARCHAR2(1) := p_error_scope;
1675                 g_eco_rec               := p_eco_rec;
1672                 l_error_status          VARCHAR2(1) := p_error_status;
1673         BEGIN
1674 
1676                 g_eco_revision_tbl      := p_eco_revision_tbl;
1677                 g_revised_item_tbl      := p_revised_item_tbl;
1678                 g_rev_component_tbl     := p_rev_component_tbl;
1679                 g_ref_designator_tbl    := p_ref_designator_tbl;
1680                 g_sub_component_tbl     := p_sub_component_tbl;
1681 
1682                 /*******************************************************
1683                 -- Followings are for ECO Routing
1684                 ********************************************************/
1685                 g_rev_operation_tbl     := p_rev_operation_tbl ;
1686                 g_rev_op_resource_tbl   := p_rev_op_resource_tbl ;
1687                 g_rev_sub_resource_tbl  := p_rev_sub_resource_tbl ;
1688                 -- Added by MK on 08/23/2000
1689 
1690                 /*******************************************************
1691                 -- Followings are for Eng Change
1692                 ********************************************************/
1693                 g_change_line_tbl       := p_change_line_tbl ;
1694                 -- Added by MK on 08/13/2002
1695 
1696 
1697 
1698                 /*************************************************
1699                 --
1700                 -- Seperate message and their tokens, get the
1701                 -- token substituted messages and put it in the
1702                 -- Error Table.
1703                 --
1704                 **************************************************/
1705 
1706 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Within the Log Error Procedure . . .'); END IF;
1707 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Scope: ' || l_error_scope); END IF;
1708 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Entity Index: ' || to_char(p_entity_index)); END IF;
1709 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Error Level: ' || to_char(p_error_level)); END IF;
1710 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Error Status: ' || l_error_status); END IF;
1711 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Other Status: ' || p_other_status); END IF;
1712 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Other Message: ' || p_other_message); END IF;
1713 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Business Object: ' || Bom_Globals.Get_Bo_Identifier); END IF;
1714 
1715 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Translating and Inserting Messages . . . '); END IF;
1716 
1717                 Error_Handler.Translate_And_Insert_Messages
1718                 (  p_Mesg_Token_Tbl     => p_Mesg_Token_Tbl
1719                  , p_error_level        => p_error_level
1720                  , p_entity_index       => p_entity_index
1721                 );
1722 
1723                 /**********************************************************
1724                 --
1725                 -- Get the other message text and token and retrieve the
1726                 -- token substituted message.
1727                 --
1728                 ***********************************************************/
1729 
1730                 IF p_other_token_tbl.COUNT <> 0
1731                 THEN
1732                         fnd_message.set_name
1733                         (  application  => SUBSTR(p_other_message, 1, 3)
1734                          , name         => p_other_message
1735                          );
1736 
1737                         FOR l_LoopIndex IN 1 .. p_other_token_tbl.COUNT
1738                         LOOP
1739                                 IF p_other_token_tbl(l_LoopIndex).token_name IS
1740                                    NOT NULL
1741                                 THEN
1742                                    fnd_message.set_token
1743                                    ( token  =>
1744                                       p_other_token_tbl(l_LoopIndex).token_name
1745                                     , value =>
1746                                       p_other_token_tbl(l_LoopIndex).token_value
1747                                     , translate   =>
1748                                       p_other_token_tbl(l_LoopIndex).translate
1749                                     );
1750                                 END IF;
1751                         END LOOP;
1752 
1753                         l_other_message := fnd_message.get;
1754 
1755                 ELSE
1756                         fnd_message.set_name
1757                         (  application  =>  SUBSTR(p_other_message, 1, 3)
1758                          , name         => p_other_message
1759                          );
1760 
1761                         l_other_message := fnd_message.get;
1762 
1763                 END IF; -- Other Token Tbl Count <> 0 Ends
1764 
1765 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Finished extracting other message . . . '); END IF;
1766 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Other Message generated: ' || l_other_message); END IF;
1767 
1768 
1769                 /**********************************************************
1770                 --
1771                 -- If the Error Level is Business Object
1772                 -- then set the Error Level = ECO
1773                 --
1774                 ************************************************************/
1775                 IF l_error_level = G_BO_LEVEL
1776                 THEN
1777                         l_error_level := G_ECO_LEVEL;
1778 
1782                 /**********************************************************
1779 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Error Level is Business Object . . . '); END IF;
1780 
1781                 END IF;
1783                 --
1784                 -- If the error_status is UNEXPECTED then set the error scope
1785                 -- to ALL, if WARNING then set the scope to RECORD.
1786                 --
1787                 ************************************************************/
1788                 IF l_error_status = G_STATUS_UNEXPECTED
1789                 THEN
1790 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Status unexpected and scope is All . . .'); END IF;
1791                         l_error_scope := G_SCOPE_ALL;
1792                 ELSIF l_error_status = G_STATUS_WARNING
1793                 THEN
1794                         l_error_scope := G_SCOPE_RECORD;
1795                         l_error_status := FND_API.G_RET_STS_SUCCESS;
1796 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Status is warning . . .'); END IF;
1797 
1798                 END IF;
1799 
1800                 --
1801                 -- If the Error Level is ECO, then the scope can be
1802                 -- ALL/CHILDREN OR RECORD.
1803                 --
1804                 /*************************************************************
1805                 --
1806                 -- If the Error Level is ECO.
1807                 --
1808                 *************************************************************/
1809                 IF l_error_level = G_ECO_LEVEL
1810                 THEN
1811 
1812 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Error Level is ECO . . .'); END IF;
1813                         --
1814                         -- Set the ECO Header record status to p_error_status
1815                         -- This will also take care of the scope RECORD.
1816                         --
1817                         g_eco_rec.return_status := l_error_status;
1818 
1819                         IF p_other_message IS NOT NULL AND
1820                            p_error_level = G_BO_LEVEL
1821                         THEN
1822                                 /* Changed l_error_level to p_error_level
1823                                 -- so that BO is the entity that the message
1824                                 -- is logged for, and not ECO.
1825                                 -- Changed by AS on 03/17/99 for bug 851387
1826                                 */
1827                                 Error_Handler.Add_Message
1828                                 (  p_mesg_text          => l_other_message
1829                                  , p_entity_id          => p_error_level
1830                                  , p_entity_index       => p_entity_index
1831                                  , p_message_type       => 'E'
1832 				 , p_mesg_name          => p_other_message);--bug 5174203
1833                                 l_other_message := NULL;
1834                         END IF;
1835 
1836 
1837                         IF l_error_scope = G_SCOPE_ALL OR
1838                            l_error_scope = G_SCOPE_CHILDREN
1839                         THEN
1840                                 IF g_eco_revision_tbl.COUNT <> 0
1841                                 THEN
1842                                         --
1843                                         -- Set all the revision record status
1844                                         --
1845                                         setRevisions
1846                                         (  p_other_mesg_text => l_other_message
1847                                          , p_other_status    => p_other_status
1848 				 	 , p_other_mesg_name => p_other_message --bug 5174203
1849                                          );
1850                                 END IF;
1851 
1852 
1853                                 /***************************************
1854                                 -- Added by MK on 08/13/2002
1855                                 -- Following is for Eng Change Mgmt
1856                                 -- Set all the change line's status.
1857                                 ****************************************/
1858                                 IF g_change_line_tbl.COUNT <> 0
1859                                 THEN
1860                                         --
1861                                         -- Set all the change line record status
1862                                         --
1863                                         setChangeLines
1864                                         (  p_other_mesg_text => l_other_message
1865                                          , p_other_status    => p_other_status
1866 				 	 , p_other_mesg_name => p_other_message --bug 5174203
1867                                          );
1868                                 END IF;
1869 
1870                                 IF g_revised_item_tbl.COUNT <> 0
1871                                 THEN
1872                                         --
1873                                         -- Set all the revised item's status
1874                                         --
1875                                         setRevisedItems
1876                                         (  p_other_mesg_text => l_other_message
1877                                          , p_other_status    => p_other_status
1878                                          , p_error_scope     => G_SCOPE_ALL
1879 				 	 , p_other_mesg_name => p_other_message --bug 5174203
1880                                          );
1881                                 END IF;
1882 
1886                                 -- status of the reference designators
1883                                 --
1884                                 -- Set all the revised component's
1885                                 -- status, this will then set the
1887                                 -- and substitute components
1888                                 --
1889 
1890                                 setRevisedComponents
1891                                 (  p_other_mesg_text => l_other_message
1892                                  , p_other_status    => p_other_status
1893                                  , p_error_scope     => G_SCOPE_ALL
1894 				 , p_other_mesg_name => p_other_message --bug 5174203
1895                                  );
1896 
1897 
1898                                 /***************************************
1899                                 -- Followings are for ECO Routing
1900                                 -- Added by MK on 08/23/2000
1901                                 -- Set all the revised operation's
1902                                 -- status, this will then set the status
1903                                 -- of the operation resources and
1904                                 -- substitute op resources.
1905                                 ****************************************/
1906                                 setRevOperationSequences
1907                                 (  p_other_mesg_text => l_other_message
1908                                  , p_other_status    => p_other_status
1909                                  , p_error_scope     => G_SCOPE_ALL
1910 				 , p_other_mesg_name => p_other_message --bug 5174203
1911                                 ) ;
1912                                 -- Added by MK on 08/23/2000
1913 
1914 
1915 
1916                         END IF; -- ECO Scope = ALL or Children Ends
1917 
1918                 /******************************************
1919                 --
1920                 -- If the Error Level is ECO REVISIONS.
1921                 --
1922                 *******************************************/
1923                 ELSIF l_error_level = G_REV_LEVEL
1924                 THEN
1925                         --
1926                         -- Set the Revision record at the current entity_index
1927                         -- This will take care of scope = RECORD
1928                         --
1929                         g_eco_revision_tbl(p_entity_index).return_status :=
1930                                                         l_error_status;
1931 
1932                         IF l_error_scope = G_SCOPE_ALL
1933                         THEN
1934                                 IF g_eco_revision_tbl.COUNT <> 0
1935                                 THEN
1936                                         --
1937                                         -- Set all the revision record status
1938                                         --
1939                                         setRevisions
1940                                         (  p_other_mesg_text => l_other_message
1941                                          , p_other_status    => p_other_status
1942 				 	 , p_other_mesg_name => p_other_message --bug 5174203
1943                                          );
1944                                 END IF;
1945 
1946 
1947                                 /***************************************
1948                                 -- Added by MK on 08/13/2002
1949                                 -- Following is for Eng Change Mgmt
1950                                 -- Set all the change line's status.
1951                                 ****************************************/
1952                                 IF g_change_line_tbl.COUNT <> 0
1953                                 THEN
1954                                         --
1955                                         -- Set all the change line record status
1956                                         --
1957                                         setChangeLines
1958                                         (  p_other_mesg_text => l_other_message
1959                                          , p_other_status    => p_other_status
1960 				 	 , p_other_mesg_name => p_other_message --bug 5174203
1961                                          );
1962                                 END IF;
1963 
1964 
1965                                 IF g_revised_item_tbl.COUNT <> 0
1966                                 THEN
1967                                         --
1968                                         -- Set all the revised item's status
1969                                         --
1970                                         setRevisedItems
1971                                         (  p_other_mesg_text => l_other_message
1972                                          , p_other_status    => p_other_status
1973                                          , p_error_scope     => l_error_scope
1974 				 	 , p_other_mesg_name => p_other_message --bug 5174203
1975                                          );
1976                                 END IF;
1977 
1978 
1979                                 /***************************************
1980                                 -- Followings are for ECO Routing
1981                                 -- Added by MK on 08/23/2000
1982                                 -- Set all the revised operation's
1983                                 -- status, this will then set the status
1984                                 -- of the operation resources and
1985                                 -- substitute op resources.
1986                                 ****************************************/
1990                                  , p_error_scope     => l_error_scope
1987                                 setRevOperationSequences
1988                                 (  p_other_mesg_text => l_other_message
1989                                  , p_other_status    => p_other_status
1991 				 , p_other_mesg_name => p_other_message --bug 5174203
1992                                 ) ;
1993                                 -- Added by MK on 08/23/2000
1994 
1995                                 --
1996                                 -- Set all the revised component's
1997                                 -- status, this will then set the
1998                                 -- status of the reference designators
1999                                 -- and substitute components
2000                                 --
2001                                 setRevisedComponents
2002                                 (  p_other_mesg_text => l_other_message
2003                                  , p_other_status    => p_other_status
2004                                  , p_error_scope     => l_error_scope
2005 				 , p_other_mesg_name => p_other_message --bug 5174203
2006                                  );
2007 
2008                         END IF;
2009 
2010                 /******************************************
2011                 --
2012                 -- If the Error Level is Change Lines.
2013                 --
2014                 *******************************************/
2015                 ELSIF l_error_level = G_CL_LEVEL
2016                 THEN
2017                         --
2018                         -- Set the Change Line record at the current entity_index
2019                         -- This will take care of scope = RECORD
2020                         --
2021                         g_change_line_tbl(p_entity_index).return_status :=
2022                                                         l_error_status;
2023 
2024                         IF l_error_scope = G_SCOPE_ALL
2025                         THEN
2026                                 IF g_eco_revision_tbl.COUNT <> 0
2027                                 THEN
2028                                         --
2029                                         -- Set all the revision record status
2030                                         --
2031                                         setRevisions
2032                                         (  p_other_mesg_text => l_other_message
2033                                          , p_other_status    => p_other_status
2034 				 	 , p_other_mesg_name => p_other_message --bug 5174203
2035                                          );
2036                                 END IF;
2037 
2038 
2039                                 /***************************************
2040                                 -- Added by MK on 08/13/2002
2041                                 -- Following is for Eng Change Mgmt
2042                                 -- Set all the change line's status.
2043                                 ****************************************/
2044                                 IF g_change_line_tbl.COUNT <> 0
2045                                 THEN
2046                                         --
2047                                         -- Set all the change line record status
2048                                         --
2049                                         setChangeLines
2050                                         (  p_other_mesg_text => l_other_message
2051                                          , p_other_status    => p_other_status
2052 				 	 , p_other_mesg_name => p_other_message --bug 5174203
2053                                          );
2054                                 END IF;
2055 
2056 
2057                                 IF g_revised_item_tbl.COUNT <> 0
2058                                 THEN
2059                                         --
2060                                         -- Set all the revised item's status
2061                                         --
2062                                         setRevisedItems
2063                                         (  p_other_mesg_text => l_other_message
2064                                          , p_other_status    => p_other_status
2065                                          , p_error_scope     => l_error_scope
2066 				 	 , p_other_mesg_name => p_other_message --bug 5174203
2067                                          );
2068                                 END IF;
2069 
2070 
2071                                 /***************************************
2072                                 -- Followings are for ECO Routing
2073                                 -- Added by MK on 08/23/2000
2074                                 -- Set all the revised operation's
2075                                 -- status, this will then set the status
2076                                 -- of the operation resources and
2077                                 -- substitute op resources.
2078                                 ****************************************/
2079                                 setRevOperationSequences
2080                                 (  p_other_mesg_text => l_other_message
2081                                  , p_other_status    => p_other_status
2082                                  , p_error_scope     => l_error_scope
2083 				 , p_other_mesg_name => p_other_message --bug 5174203
2084                                 ) ;
2085                                 -- Added by MK on 08/23/2000
2086 
2087                                 --
2088                                 -- Set all the revised component's
2089                                 -- status, this will then set the
2093                                 setRevisedComponents
2090                                 -- status of the reference designators
2091                                 -- and substitute components
2092                                 --
2094                                 (  p_other_mesg_text => l_other_message
2095                                  , p_other_status    => p_other_status
2096                                  , p_error_scope     => l_error_scope
2097 				 , p_other_mesg_name => p_other_message --bug 5174203
2098                                  );
2099 
2100                         END IF;
2101 
2102 
2103                 /******************************************
2104                 --
2105                 -- If the Error Level is REVISED ITEM.
2106                 --
2107                 *******************************************/
2108                 ELSIF l_error_level = G_RI_LEVEL
2109                 THEN
2110                         --
2111                         -- Set the revised item status at the entity_index
2112                         -- This will take care of scope RECORD
2113                         --
2114 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Error Level = Revised Items . . .'); END IF;
2115 
2116                         g_revised_item_tbl(p_entity_index).return_status :=
2117                                                 l_error_status;
2118 
2119                         IF l_error_scope = G_SCOPE_CHILDREN OR
2120                            l_error_scope = G_SCOPE_ALL
2121                         THEN
2122 
2123 
2124                                 /***************************************
2125                                 -- Followings are for ECO Routing
2126                                 -- Added by MK on 08/23/2000
2127                                 --
2128                                 -- Call revised operation procedure without
2129                                 -- checking for count since it is possible to
2130                                 -- have op resourcces and sub. op resources
2131                                 -- without having the revised operation as part
2132                                 -- of the business object
2133                                 --
2134                                 ****************************************/
2135                                 setRevOperationSequences
2136                                 (  p_other_mesg_text => l_other_message
2137                                  , p_other_status    => p_other_status
2138                                  , p_error_scope     => l_error_scope
2139                                  , p_ri_idx          => p_entity_index
2140 				 , p_other_mesg_name => p_other_message --bug 5174203
2141                                 ) ;
2142                                 -- Added by MK on 08/23/2000
2143 
2144                                 --
2145                                 -- Call revised component procedure without
2146                                 -- Checking for count since it is possible to
2147                                 -- have ref. designators and sub. components
2148                                 -- without having the revised component as part
2149                                 -- of the business object
2150                                 --
2151                                 setRevisedComponents
2152                                 (  p_other_mesg_text => l_other_message
2153                                  , p_other_status    => p_other_status
2154                                  , p_error_scope     => l_error_scope
2155                                  , p_ri_idx          => p_entity_index
2156 				 , p_other_mesg_name => p_other_message --bug 5174203
2157                                 );
2158 
2159                                 IF l_error_scope = G_SCOPE_ALL
2160                                 THEN
2161                                         setRevisedItems
2162                                         (  p_other_mesg_text => l_other_message
2163                                          , p_other_status    => p_other_status
2164                                          , p_entity_index    => p_entity_index
2165                                          , p_error_scope     => l_error_scope
2166 				 	 , p_other_mesg_name => p_other_message --bug 5174203
2167                                         );
2168                                 END IF;
2169 
2170                         END IF;  -- SCOPE = Children or ALL Ends
2171                 /********************************************
2172                 --
2173                 -- If the Error Level is REVISED COMPONENTS
2174                 --
2175                 *********************************************/
2176                 ELSIF l_error_level = G_RC_LEVEL
2177                 THEN
2178                         --
2179                         -- Set revised component record at the entity_index
2180                         -- to error_status
2181                         -- This will take care of Scope = RECORD.
2182                         --
2183                         g_rev_component_tbl(p_entity_index).return_status :=
2184                                                 l_error_status;
2185 
2186 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Error Level = Revised components . . .'); END IF;
2187 
2188                         IF l_error_scope = G_SCOPE_SIBLINGS OR
2189                            l_error_scope = G_SCOPE_ALL
2190                         THEN
2191                                  setRevisedComponents
2192                                 (  p_other_mesg_text => l_other_message
2193                                  , p_other_status    => p_other_status
2197                                 );
2194                                  , p_error_scope     => l_error_scope
2195                                  , p_entity_index    => p_entity_index
2196 				 , p_other_mesg_name => p_other_message --bug 5174203
2198                         ELSIF l_error_scope = G_SCOPE_CHILDREN
2199                         THEN
2200                                 IF g_ref_designator_tbl.COUNT <> 0
2201                                 THEN
2202                                         setRefDesignators
2203                                         (  p_error_scope     => l_error_scope
2204                                          , p_other_status    => p_other_status
2205                                          , p_other_mesg_text => l_other_message
2206                                          , p_rc_idx          => p_entity_index
2207 				 	 , p_other_mesg_name => p_other_message --bug 5174203
2208                                          );
2209                                 END IF;
2210 
2211                                 IF g_sub_component_tbl.COUNT <> 0
2212                                 THEN
2213                                         setSubComponents
2214                                         (  p_error_scope     => l_error_scope
2215                                          , p_other_status    => p_other_status
2216                                          , p_other_mesg_text => l_other_message
2217                                          , p_rc_idx          => p_entity_index
2218  					 , p_other_mesg_name => p_other_message --bug 5174203
2219                                          );
2220                                 END IF;
2221                         END IF; -- scope = Siblings or All Ends
2222 
2223                 /***********************************************
2224                 --
2225                 -- If the Error Level is REFERENCE DESIGNATOR.
2226                 --
2227                 ************************************************/
2228                 ELSIF l_error_level = G_RD_LEVEL
2229                 THEN
2230                         --
2231                         -- Set reference designator record status at entity_idx
2232                         -- This will take care of Scope = RECORD.
2233                         --
2234 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Error Level = Reference Designators . . .'); END IF;
2235 
2236                         g_ref_designator_tbl(p_entity_index).return_status :=
2237                                                 l_error_status;
2238                         IF l_error_scope <> G_SCOPE_RECORD
2239                         THEN
2240                                 setRefDesignators
2241                                 (  p_error_scope     => l_error_scope
2242                                  , p_other_status    => p_other_status
2243                                  , p_other_mesg_text => l_other_message
2244                                  , p_entity_index    => p_entity_index
2245 				 , p_other_mesg_name => p_other_message --bug 5174203
2246                                  );
2247                         END IF;
2248 
2249                 /***********************************************
2250                 --
2251                 -- If the Error Level is SUBSTITUTE COMPONENTS.
2252                 --
2253                 ************************************************/
2254                 ELSIF l_error_level = G_SC_LEVEL
2255                 THEN
2256                         -- Set substitute component record status at entity_idx
2257                         -- This will take care of Scope = RECORD.
2258                         --
2259 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Error Level = Substitute Components . . .'); END IF;
2260 
2261                         g_sub_component_tbl(p_entity_index).return_status :=
2262                                                 l_error_status;
2263                         IF l_error_scope <> G_SCOPE_RECORD
2264                         THEN
2265                                 setSubComponents
2266                                 (  p_error_scope     => l_error_scope
2267                                  , p_other_status    => p_other_status
2268                                  , p_other_mesg_text => l_other_message
2269                                  , p_entity_index    => p_entity_index
2270 				 , p_other_mesg_name => p_other_message --bug 5174203
2271                                  );
2272                         END IF;
2273 
2274 
2275 
2276                 /********************************************
2277                 -- Enhancement for ECO Routing
2278                 -- Added by MK on 08/23/00
2279                 --
2280                 -- If the Error Level is REVISED OPERATIONS
2281                 --
2282                 *********************************************/
2283                 ELSIF l_error_level = G_OP_LEVEL
2284                 THEN
2285                         --
2286                         -- Set revised operation record at the entity_index
2287                         -- to error_status
2288                         -- This will take care of Scope = RECORD.
2289                         --
2290                         g_rev_operation_tbl(p_entity_index).return_status :=
2291                                                 l_error_status;
2292 
2293 IF Bom_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Error Level = Revised operations . . .'); END IF;
2294 
2295                         IF l_error_scope = G_SCOPE_SIBLINGS OR
2296                            l_error_scope = G_SCOPE_ALL
2297                         THEN
2301                                  , p_error_scope     => l_error_scope
2298                                  setRevOperationSequences
2299                                 (  p_other_mesg_text => l_other_message
2300                                  , p_other_status    => p_other_status
2302                                  , p_entity_index    => p_entity_index
2303 				 , p_other_mesg_name => p_other_message --bug 5174203
2304                                 );
2305                         ELSIF l_error_scope = G_SCOPE_CHILDREN
2306                         THEN
2307                              IF g_rev_op_resource_tbl.COUNT <> 0
2308                              THEN
2309                                  setRevOperationResources
2310                                (  p_error_scope     => l_error_scope
2311                                 , p_other_status    => p_other_status
2312                                 , p_other_mesg_text => l_other_message
2316                              END IF;
2313                                 , p_op_idx          => p_entity_index
2314 				, p_other_mesg_name => p_other_message --bug 5174203
2315                                 );
2317 
2318                              IF g_rev_sub_resource_tbl.COUNT <> 0
2319                              THEN
2320                                  setRevSubResources
2321                                  (  p_error_scope     => l_error_scope
2322                                   , p_other_status    => p_other_status
2323                                   , p_other_mesg_text => l_other_message
2324                                   , p_op_idx          => p_entity_index
2325 				  , p_other_mesg_name => p_other_message --bug 5174203
2326                                  );
2327                              END IF;
2328 
2329                         END IF; -- scope = Siblings or All Ends
2330 
2331 
2332 
2333                 /***********************************************
2334                 -- Enhancement for ECO Routing
2335                 -- Added by MK on 08/23/00
2336                 --
2337                 -- If the Error Level is REV OPERATION RESOURCES
2338                 --
2339                 ************************************************/
2340                 ELSIF l_error_level = G_RES_LEVEL
2341                 THEN
2342 
2343                         --
2344                         -- Set operation resource record status at entity_idx
2345                         -- This will take care of Scope = RECORD.
2346                         --
2347 IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Error Level = Ope ration Resource . . .'); END IF;
2348 
2349                         g_rev_op_resource_tbl(p_entity_index).return_status := l_error_status;
2350                         IF l_error_scope <> G_SCOPE_RECORD
2351                         THEN
2352                             setRevOperationResources
2353                             (  p_error_scope     => l_error_scope
2354                              , p_other_status    => p_other_status
2355                              , p_other_mesg_text => l_other_message
2356                              , p_entity_index    => p_entity_index
2357 			     , p_other_mesg_name => p_other_message --bug 5174203
2358                             ) ;
2359                         END IF;
2360 
2361                 /***********************************************
2362                 -- Enhancement for ECO Routing
2363                 -- Added by MK on 08/23/00
2364                 --
2365                 -- If the Error Level is REV SUB OP RESOURCES
2366                 --
2370                         -- Set substitute resource record status at entity_idx
2367                 ************************************************/
2368                 ELSIF l_error_level = G_SR_LEVEL
2369                 THEN
2371                         -- This will take care of Scope = RECORD.
2372                         --
2373 IF Bom_Rtg_Globals.Get_Debug = 'Y' THEN Error_Handler.Write_Debug('Error Level = Sub
2374 stitute Op Resources . . .'); END IF;
2375 
2376                         g_rev_sub_resource_tbl(p_entity_index).return_status := l_error_status;
2377 
2378 
2379                         IF l_error_scope <> G_SCOPE_RECORD
2380                         THEN
2381                            setRevSubResources
2382                            (  p_error_scope     => l_error_scope
2383                             , p_other_status    => p_other_status
2384                             , p_other_mesg_text => l_other_message
2385                             , p_entity_index    => p_entity_index
2386 			    , p_other_mesg_name => p_other_message --bug 5174203
2387                            ) ;
2388                         END IF ;
2389 
2390                 END IF; -- Error Level  If Ends.
2391 
2392                 --
2393                 -- Copy the changed record/Tables to the out parameters for
2394                 -- returing to the calling program.
2395                 --
2396                 x_eco_rec               := g_eco_rec;
2397                 x_eco_revision_tbl      := g_eco_revision_tbl;
2398                 x_revised_item_tbl      := g_revised_item_tbl;
2399                 x_rev_component_tbl     := g_rev_component_tbl;
2400                 x_ref_designator_tbl    := g_ref_designator_tbl;
2401                 x_sub_component_tbl     := g_sub_component_tbl;
2402 
2403 
2404                 /*******************************************************
2405                 -- Followings are for ECO Routing
2406                 ********************************************************/
2407                 x_rev_operation_tbl     := g_rev_operation_tbl ;
2408                 x_rev_op_resource_tbl   := g_rev_op_resource_tbl ;
2409                 x_rev_sub_resource_tbl  := g_rev_sub_resource_tbl ;
2410                 -- Added by MK on 08/23/2000
2411 
2412                 /*******************************************************
2413                 -- Followings are for Eng Change
2414                 ********************************************************/
2415                 x_change_line_tbl       := g_change_line_tbl ;
2416                 -- Added by MK on 08/13/2002
2417 
2418 
2419         END Log_Error;
2420 
2421 
2422 
2423 END Eco_Error_Handler;