DBA Data[Home] [Help]

PACKAGE BODY: APPS.EAM_OPERATIONS_JSP

Source


1 package body EAM_OPERATIONS_JSP AS
2 /* $Header: EAMOPSJB.pls 120.9 2006/08/22 16:22:33 sdandapa noship $
3    $Author: sdandapa $ */
4 
5 G_PKG_NAME              CONSTANT VARCHAR2(30) := 'eam_operations_jsp';
6 g_debug_sqlerrm VARCHAR2(250);
7 g_shutdown_type VARCHAR2(30) := EAM_CONSTANTS.G_SHUTDOWN_TYPE;
8 g_supply_type VARCHAR2(30) := EAM_CONSTANTS.G_SUPPLY_TYPE;
9 
10 
11 -------------------------------------------------------------------------
12 -- Procedure to check whether the handover operation is being
13 -- conducted properly or not
14 -- Bug fix # 2113203 - baroy
15 -- Bug 3133704 - removed l_completed_yn and merged the 2 sql's
16 -------------------------------------------------------------------------
17   procedure handover_validate
18   ( p_wip_entity_id               IN NUMBER,
19     p_operation_sequence_number   IN NUMBER,
20     p_organization_id             IN NUMBER,
21     x_return_stat                  OUT NOCOPY NUMBER
22   ) IS
23 
24     l_op_complete_count NUMBER;
25 
26     BEGIN
27       x_return_stat := 1;
28   -- Bug  3133704
29    SELECT count(operation_completed) into l_op_complete_count
30    FROM wip_operation_networks won, wip_operations wo
31    WHERE won.wip_entity_id = p_wip_entity_id
32    AND won.next_operation =  p_operation_sequence_number
33    AND won.organization_id =  p_organization_id
34    AND wo.wip_entity_id =  p_wip_entity_id
35    AND wo.operation_seq_num = won.prior_operation
36    AND wo.organization_id = p_organization_id
37    AND nvl(wo.operation_completed,'N')='N' ;
38 
39    IF l_op_complete_count > 0 THEN
40       x_return_stat := 0;
41    END IF;
42 
43 
44   END handover_validate;
45 
46 -- removed procedure charge_resource_validate
47 
48 -------------------------------------------------------------------------
49 -- Procedure to check whether the assign employee operation is being
50 -- conducted on a completed or uncompleted operation
51 -- Bug fix # 2113203 - baroy
52 -------------------------------------------------------------------------
53   procedure assign_employee_validate
54   ( p_wip_entity_id               IN NUMBER,
55     p_operation_sequence_number   IN NUMBER,
56     p_organization_id             IN NUMBER,
57     x_return_stat                 OUT NOCOPY NUMBER
58   ) IS
59 
60     l_complete_yn    VARCHAR2(1);
61 
62     BEGIN
63     select operation_completed
64       into l_complete_yn
65       from wip_operations where
66       wip_entity_id = p_wip_entity_id and
67       operation_seq_num = p_operation_sequence_number and
68       organization_id = p_organization_id;
69 
70     IF nvl(upper(l_complete_yn),'N') = 'Y' THEN
71       x_return_stat := 0;  -- operation should not be allowed to charge resource/employee
72                          -- as it is already completed
73     ELSE
74       x_return_stat := 1;  -- operation can be allowed to charge resource/employee
75     END IF;
76   END assign_employee_validate;
77 
78 
79 -------------------------------------------------------------------------
80 -- Procedure to check whether the operation uncompletion/completion
81 -- is being conducted properly or not
82 -- Bug fix # 2113203 - baroy
83 -------------------------------------------------------------------------
84   procedure complete_uncomplete_validate
85   ( p_wip_entity_id               IN NUMBER,
86     p_operation_sequence_number   IN NUMBER,
87     p_organization_id             IN NUMBER,
88     x_return_stat                  OUT NOCOPY NUMBER
89   ) IS
90 
91     l_completed_yn VARCHAR2(1);
92     l_cur_completed_yn VARCHAR2(1);
93 
94 
95     BEGIN
96       x_return_stat := 1;
97 
98       select operation_completed
99         into l_cur_completed_yn
100         from wip_operations where
101         wip_entity_id = p_wip_entity_id and
102         operation_seq_num = p_operation_sequence_number and
103         organization_id = p_organization_id;
104 
105       IF( nvl(upper(l_cur_completed_yn),'N') = 'Y') THEN
106         -- operation being contemplated by user is a uncomplete op. Hence check whether
107         -- all next ops are uncomplet or not
108         FOR cur_operation_record IN (select next_operation from wip_operation_networks where
109                                        wip_entity_id = p_wip_entity_id and
110                                        prior_operation = p_operation_sequence_number and
111                                        organization_id = p_organization_id) LOOP
112 
113           SELECT operation_completed INTO
114             l_completed_yn from wip_operations where
115             wip_entity_id = p_wip_entity_id and
116             operation_seq_num = cur_operation_record.next_operation and
117             organization_id = p_organization_id;
118 
119           IF nvl(upper(l_completed_yn),'N') = 'Y' THEN
120             x_return_stat := 2; -- some next ops are complete
121                                 -- error msg : uncomplete them first.
122           END IF;
123         END LOOP;
124       ELSIF( nvl(upper(l_cur_completed_yn),'N') = 'N') THEN
125         -- operation being contemplated by user is a complete op. Hence check whether
126         -- all previous ops have been completed or not
127         FOR cur_operation_record IN (select prior_operation from wip_operation_networks where
128                                        wip_entity_id = p_wip_entity_id and
129                                        next_operation = p_operation_sequence_number and
130                                        organization_id = p_organization_id) LOOP
131 
132           SELECT operation_completed INTO
133             l_completed_yn from wip_operations where
134             wip_entity_id = p_wip_entity_id and
135             operation_seq_num = cur_operation_record.prior_operation and
136             organization_id = p_organization_id;
137 
138           IF nvl(upper(l_completed_yn),'N') = 'N' THEN
139             x_return_stat := 3; -- some previous ops are still uncomplete
140                                 -- error msg : complete them first.
141           END IF;
142         END LOOP;
143 
144       ELSE
145         -- Proceed to operation completion/uncompletion page
146         x_return_stat := 1;
147       END IF;
148 
149   END complete_uncomplete_validate;
150 
151 
152 --------------------------------------------------------------------------
153 -- A wrapper to the operation completion logic, cache the return status
154 -- and convert it the the message that can be accepted by JSP pages
155 --------------------------------------------------------------------------
156   procedure complete_operation
157   (  p_api_version                 IN    NUMBER        := 1.0
158     ,p_init_msg_list               IN    VARCHAR2      := FND_API.G_FALSE
159     ,p_commit                      IN    VARCHAR2      := FND_API.G_FALSE
160     ,p_validate_only               IN    VARCHAR2      := FND_API.G_TRUE
161     ,p_record_version_number       IN    NUMBER        := NULL
162     ,x_return_status               OUT NOCOPY   VARCHAR2
163     ,x_msg_count                   OUT NOCOPY   NUMBER
164     ,x_msg_data                    OUT NOCOPY   VARCHAR2
165     ,p_wip_entity_id               IN    NUMBER        -- data
166     ,p_operation_seq_num           IN    NUMBER
167     ,p_actual_start_date           IN    DATE
168     ,p_actual_end_date             IN    DATE
169     ,p_actual_duration             IN    NUMBER
170     ,p_transaction_date            IN    DATE
171     ,p_transaction_type            IN    NUMBER
172     ,p_shutdown_start_date         IN    DATE
173     ,p_shutdown_end_date           IN    DATE
174     ,p_reconciliation_code         IN    VARCHAR2
175     ,p_stored_last_update_date     IN    DATE  -- old update date, for locking only
176     ,p_qa_collection_id            IN    NUMBER
177     ,p_vendor_id                   IN   NUMBER      := NULL
178     ,p_vendor_site_id              IN   NUMBER      := NULL
179     ,p_vendor_contact_id           IN   NUMBER      := NULL
180     ,p_reason_id                   IN   NUMBER      := NULL
181     ,p_reference                   IN   VARCHAR2    := NULL
182     ,p_attribute_category	   IN	VARCHAR2    := NULL
183     ,p_attribute1		   IN	VARCHAR2    := NULL
184     ,p_attribute2                  IN   VARCHAR2    := NULL
185     ,p_attribute3                  IN   VARCHAR2    := NULL
186     ,p_attribute4                  IN   VARCHAR2    := NULL
187     ,p_attribute5                  IN   VARCHAR2    := NULL
188     ,p_attribute6                  IN   VARCHAR2    := NULL
189     ,p_attribute7                  IN   VARCHAR2    := NULL
190     ,p_attribute8                  IN   VARCHAR2    := NULL
191     ,p_attribute9                  IN   VARCHAR2    := NULL
192     ,p_attribute10                 IN   VARCHAR2    := NULL
193     ,p_attribute11                 IN   VARCHAR2    := NULL
194     ,p_attribute12                 IN   VARCHAR2    := NULL
195     ,p_attribute13                 IN   VARCHAR2    := NULL
196     ,p_attribute14                 IN   VARCHAR2    := NULL
197     ,p_attribute15                 IN   VARCHAR2    := NULL
198   ) IS
199 
200   l_api_name           CONSTANT VARCHAR(30) := 'complete_operation';
201   l_api_version        CONSTANT NUMBER      := 1.0;
202   l_return_status            VARCHAR2(250);
203   l_error_msg_code           VARCHAR2(250);
204   l_msg_count                NUMBER;
205   l_msg_data                 VARCHAR2(250);
206   l_err_code                 NUMBER;
207   l_err_msg                  VARCHAR2(250);
208   l_err_stage                VARCHAR2(250);
209   l_err_stack                VARCHAR2(250);
210   l_data                     VARCHAR2(250);
211   l_msg_index_out            NUMBER;
212 
213   l_new_status   VARCHAR2(30);
214   l_db_status    VARCHAR2(30);
215   l_db_last_update_date DATE;
216   l_transaction  NUMBER;
217   l_actual_end_date  DATE;
218   l_reconciliation_code VARCHAR2(30);
219   l_shutdown_type VARCHAR2(30);
220   l_open_acct_per_date DATE;
221 
222 	l_act_st_date DATE;
223 	l_act_end_date DATE;
224 	l_act_duration NUMBER;
225 
226 
227 
228   BEGIN
229        SAVEPOINT complete_workorder;
230 
231 	l_act_st_date  :=p_actual_start_date;
232 	l_act_end_date :=p_actual_end_date;
233 	l_act_duration :=p_actual_duration;
234 
235 
236 
237     eam_debug.init_err_stack('eam_operations_jsp.complete_operation');
238 
239     IF NOT FND_API.COMPATIBLE_API_CALL(l_api_version,
240                                        p_api_version,
241                                        l_api_name,
242                                        g_pkg_name)
243     THEN
244        RAISE FND_API.G_EXC_UNEXPECTED_ERROR;
245     END IF;
246 
247     IF FND_API.TO_BOOLEAN(p_init_msg_list)
248     THEN
249        FND_MSG_PUB.initialize;
250     END IF;
251 
252     x_return_status := FND_API.G_RET_STS_SUCCESS;
253 
254     -- check if data is stale or not
255     -- using last_update_date as indicator
256     BEGIN
257       SELECT last_update_date, operation_completed, shutdown_type
258       INTO   l_db_last_update_date, l_db_status, l_shutdown_type
259       FROM wip_operations
260       WHERE wip_entity_id = p_wip_entity_id
261         and operation_seq_num = p_operation_seq_num
262       FOR UPDATE;
263 
264        IF p_transaction_type = 2 THEN
265            select actual_start_date ,actual_end_date ,actual_duration
266            into l_act_st_date ,l_act_end_date,l_act_duration
267            from eam_op_completion_txns
268            where
269             wip_entity_id      = p_wip_entity_id      and
270             operation_seq_num  = p_operation_seq_num   and
271             transaction_type = 1 and
272             last_update_date = (select max(last_update_date)
273                                  from eam_op_completion_txns
274                                 where wip_entity_id  = p_wip_entity_id and
275                                       operation_seq_num  = p_operation_seq_num and
276                                       transaction_type = 1);
277 
278        END IF;
279 
280 
281       IF  l_db_last_update_date <> p_stored_last_update_date THEN
282         eam_execution_jsp.add_message(p_app_short_name => 'EAM', p_msg_name => 'EAM_WO_STALED_DATA');
283         x_return_status := FND_API.G_RET_STS_ERROR;
284       END IF;
285       IF ( (p_transaction_type = 1 AND l_db_status = 'Y') or
286            (p_transaction_type = 2 and nvl(l_db_status,'N') = 'N' )) THEN
287         eam_execution_jsp.add_message(p_app_short_name => 'EAM', p_msg_name => 'EAM_WO_STALED_DATA');
288         x_return_status := FND_API.G_RET_STS_ERROR;
289       END IF;
290       IF ( not( p_shutdown_start_date is null and p_shutdown_end_date is null) and
291            ( p_shutdown_start_date is null or p_shutdown_end_date is null) ) THEN
292         eam_execution_jsp.add_message(p_app_short_name => 'EAM', p_msg_name => 'EAM_SHUTDOWN_DATE_MISS');
293         x_return_status := FND_API.G_RET_STS_ERROR;
294       END IF;
295 --changed the following if condition as part of bug 5476770
296 	  IF ( p_shutdown_start_date is not null and p_shutdown_end_date is not null and
297 			p_shutdown_end_date > sysdate ) THEN
298         eam_execution_jsp.add_message(p_app_short_name => 'EAM', p_msg_name => 'EAM_SHUTDOWN_DATE_IN_FUTURE');
299         x_return_status := FND_API.G_RET_STS_ERROR;
300       ELSIF ( p_shutdown_start_date is not null and p_shutdown_end_date is not null and
301            p_shutdown_start_date > p_shutdown_end_date ) THEN
302         eam_execution_jsp.add_message(p_app_short_name => 'EAM', p_msg_name => 'EAM_SHUTDOWN_DATE_BAD');
303         x_return_status := FND_API.G_RET_STS_ERROR;
304       END IF;
305 --end of change for bug 5476770
306       IF (l_act_duration  < 0) THEN
307         eam_execution_jsp.add_message(p_app_short_name => 'EAM', p_msg_name => 'EAM_COMP_DURATION_BAD');
308         x_return_status := FND_API.G_RET_STS_ERROR;
309       END IF;
310 
311     EXCEPTION WHEN NO_DATA_FOUND THEN	-- Bug 3133704 .changed WHEN OTHERS to WHEN NO_DATA_FOUND
312       eam_execution_jsp.add_message(p_app_short_name => 'EAM', p_msg_name => 'EAM_OP_NOT_FOUND');
313       x_return_status := FND_API.G_RET_STS_ERROR;
314     END;
315 
316 
317      /* Fix for Bug 2100416 */
318 
319         select nvl(min(period_start_date), sysdate+1)
320         into l_open_acct_per_date
321         from org_acct_periods
322         where organization_id = (select organization_id from wip_discrete_jobs where wip_entity_id = p_wip_entity_id)
323         and open_flag = 'Y';
324 
325         if (l_act_st_date  is not null) and (l_act_duration  is not null) then
326            if (l_act_end_date  > sysdate) then
327             eam_execution_jsp.add_message(p_app_short_name => 'EAM', p_msg_name => 'EAM_END_LATER_THAN_TODAY');
328             x_return_status := FND_API.G_RET_STS_UNEXP_ERROR;
329            end if;
330            /* The following line is commented out for bug no:2728447 */
331 --           if (p_actual_start_date < l_open_acct_per_date) then
332    /*Fix for bug 3235163*/
333    --Previously end date was checked with closed period.Changed that to check transaction_date
334            if (p_transaction_date < l_open_acct_per_date) then
335              eam_execution_jsp.add_message(p_app_short_name => 'EAM', p_msg_name => 'EAM_TRANSACTION_DATE_INVALID');
336              x_return_status := FND_API.G_RET_STS_UNEXP_ERROR;
337            end if;
338   /*End of fix for bug 3235163*/
339         end if;
340 
341     /* End of Fix 2100416 */
342 
343     BEGIN
344       l_reconciliation_code := null;
345       if( p_reconciliation_code is not null) then
346         select ml.lookup_code
347         into l_reconciliation_code
348         from mfg_lookups ml			-- Fix for Bug 3509465
349         where ml.lookup_type = 'WIP_EAM_RECONCILIATION_CODE'
350           and ml.meaning = p_reconciliation_code;
351       end if;
352     EXCEPTION WHEN NO_DATA_FOUND THEN  -- Bug 3133704,changed OTHERS to NO_DATA_FOUND
353       eam_execution_jsp.add_message(p_app_short_name => 'EAM', p_msg_name => 'EAM_RECONCILIATION_CODE_INV');
354       x_return_status := FND_API.G_RET_STS_ERROR; --Bug .
355     END;
356 
357     -- if validate not passed then raise error
358     l_msg_count := FND_MSG_PUB.count_msg;
359     IF l_msg_count = 1 THEN
360        eam_execution_jsp.Get_Messages
361          (p_encoded  => FND_API.G_FALSE,
362           p_msg_index => 1,
363           p_msg_count => l_msg_count,
364           p_msg_data  => l_msg_data,    -- removed g_miss_char
365           p_data      => l_data,
366           p_msg_index_out => l_msg_index_out);
367           x_msg_count := l_msg_count;
368           x_msg_data  := l_msg_data;
369     ELSE
370        x_msg_count  := l_msg_count;
371     END IF;
372 
373     IF l_msg_count > 0 THEN
374        x_return_status := FND_API.G_RET_STS_UNEXP_ERROR;
375        RAISE  FND_API.G_EXC_ERROR;
376     END IF;
377 
378     -------------------------------------------
379     -- how to compute date by interval, how many hours a day???
380     l_actual_end_date := l_act_st_date + (l_act_duration/24);
381 
382    begin
383    eam_op_comp.op_comp(
384 --     p_api_version         => p_api_version,
385 --     p_init_msg_list       => p_init_msg_list,
386 --     p_commit              => p_commit,
387 --     p_validation_level    => p_validation_level,
388 --     p_validation_only     => p_validate_only,
389 --     p_record_version_number => p_record_version_number,
390 --     x_return_status       => x_return_status,
391 --     x_msg_count           => x_msg_count,
392 --     x_msg_data            => x_msg_data,
393      x_err_code            => l_err_code,
394      x_err_msg             => l_err_msg,
395      p_wip_entity_id       => p_wip_entity_id,
396      p_operation_seq_num   => p_operation_seq_num,
397      p_transaction_type    => p_transaction_type,
398      p_transaction_date    => p_transaction_date,
399      p_actual_start_date   => l_act_st_date,
400      p_actual_end_date     => l_actual_end_date,
401      p_actual_duration     =>  l_act_duration,
402      p_shutdown_start_date => p_shutdown_start_date,
403      p_shutdown_end_date   => p_shutdown_end_date,
404      p_reconciliation_code => l_reconciliation_code,
405      p_qa_collection_id    => p_qa_collection_id,
406 	 p_vendor_id           => p_vendor_id,
407      p_vendor_site_id      => p_vendor_site_id,
408 	 p_vendor_contact_id   => p_vendor_contact_id,
409 	 p_reason_id           => p_reason_id,
410 	 p_reference           => p_reference,
411 	 p_attribute_category  => p_attribute_category,
412 	 p_attribute1		   => p_attribute1,
413 	 p_attribute2		   => p_attribute2,
414 	 p_attribute3		   => p_attribute3,
415 	 p_attribute4		   => p_attribute4,
416 	 p_attribute5		   => p_attribute5,
417 	 p_attribute6		   => p_attribute6,
418 	 p_attribute7		   => p_attribute7,
419 	 p_attribute8		   => p_attribute8,
420 	 p_attribute9		   => p_attribute9,
421 	 p_attribute10		   => p_attribute10,
422 	 p_attribute11		   => p_attribute11,
423 	 p_attribute12		   => p_attribute12,
424 	 p_attribute13		   => p_attribute13,
425 	 p_attribute14		   => p_attribute14,
426 	 p_attribute15		   => p_attribute15
427    );
428    exception when others then
429      fnd_msg_pub.add;
430    end;
431 
432    if( l_err_code >0) then
433 --      add_message(p_app_short_name => 'EAM', p_msg_name => l_err_msg);
434       x_return_status := FND_API.G_RET_STS_UNEXP_ERROR;
435    end if;
436 
437     l_msg_count := FND_MSG_PUB.count_msg;
438     IF l_msg_count = 1 THEN
439        eam_execution_jsp.Get_Messages
440          (p_encoded  => FND_API.G_FALSE,
441           p_msg_index => 1,
442           p_msg_count => l_msg_count,
443           p_msg_data  => l_msg_data,       -- removed g_miss_char
444           p_data      => l_data,
445           p_msg_index_out => l_msg_index_out);
446           x_msg_count := l_msg_count;
447           x_msg_data  := l_msg_data;
448     ELSE
449        x_msg_count  := l_msg_count;
450     END IF;
451 
452     IF l_msg_count > 0 THEN
453        x_return_status := FND_API.G_RET_STS_UNEXP_ERROR;
454        RAISE  FND_API.G_EXC_ERROR;
455     END IF;
456 
457     IF FND_API.TO_BOOLEAN(P_COMMIT)
458     THEN
459       COMMIT WORK;
460     END IF;
461 
462   EXCEPTION WHEN FND_API.G_EXC_UNEXPECTED_ERROR  THEN
463        ROLLBACK TO complete_workorder;
464 
465 
466     FND_MSG_PUB.add_exc_msg( p_pkg_name => 'eam_operations_jsp.complete_operation',
467     p_procedure_name => EAM_DEBUG.G_err_stack);
468     x_return_status := FND_API.G_RET_STS_UNEXP_ERROR;
469   WHEN FND_API.G_EXC_ERROR THEN
470        ROLLBACK TO complete_workorder;
471 
472 
473     FND_MSG_PUB.add_exc_msg( p_pkg_name => 'eam_operations_jsp.complete_operation',
474     p_procedure_name => EAM_DEBUG.G_err_stack);
475     x_return_status := FND_API.G_RET_STS_UNEXP_ERROR;
476   WHEN OTHERS THEN
477        ROLLBACK TO complete_workorder;
478 
479 
480     FND_MSG_PUB.add_exc_msg( p_pkg_name => 'eam_operations_jsp.complete_operation',
481     p_procedure_name => EAM_DEBUG.G_err_stack);
482     x_return_status := FND_API.G_RET_STS_UNEXP_ERROR;
483   END complete_operation;
484 
485 ------------------------------------------------------------------------------------
486 -- performing operation handover for jsp pages
487 -- use the column last_update_date for optimistic locking
488 ------------------------------------------------------------------------------------
489    procedure operation_handover
490     (  p_api_version                 IN    NUMBER        := 1.0
491       ,p_init_msg_list               IN    VARCHAR2      := FND_API.G_FALSE
492       ,p_commit                      IN    VARCHAR2      := FND_API.G_FALSE
493       ,p_validate_only               IN    VARCHAR2      := FND_API.G_TRUE
494       ,p_record_version_number       IN    NUMBER        := NULL
495       ,x_return_status               OUT NOCOPY   VARCHAR2
496       ,x_msg_count                   OUT NOCOPY   NUMBER
497       ,x_msg_data                    OUT NOCOPY   VARCHAR2
498       ,p_wip_entity_id               IN    NUMBER        -- data
499       ,p_old_op_seq_num              IN    NUMBER
500       ,p_new_op_seq_num              IN    NUMBER
501       ,p_description                 IN    VARCHAR2
502       ,p_assigned_department         IN    VARCHAR2
503       ,p_start_date                  IN    DATE
504       ,p_completion_date             IN    DATE
505       ,p_shutdown_type               IN    NUMBER
506       ,p_stored_last_update_date     IN    DATE -- old update date, for locking only
507       ,p_duration                    IN    NUMBER
508       ,p_reconciliation_value        IN    VARCHAR2
509      ) IS
510 
511     l_api_name           CONSTANT VARCHAR(30) := 'operation_handover';
512     l_api_version        CONSTANT NUMBER      := 1.0;
513     l_return_status            VARCHAR2(250);
514     l_error_msg_code           VARCHAR2(250);
515     l_msg_count                NUMBER;
516     l_msg_data                 VARCHAR2(250);
517     l_err_code                 VARCHAR2(250);
518     l_err_stage                VARCHAR2(250);
519     l_err_stack                VARCHAR2(250);
520     l_data                     VARCHAR2(250);
521     l_msg_index_out            NUMBER;
522 
523     l_db_last_update_date DATE;
524     l_actual_start_date  DATE;
525     l_actual_end_date  DATE;
526     l_completed  VARCHAR2(30);
527     l_count      NUMBER;
528     l_department_id NUMBER;
529     x_row_id VARCHAR2(250);
530     l_org_id NUMBER;
531     l_old_dept_id NUMBER;
532     l_transaction_id number;
533     l_old_op_duration number;
534     l_new_op_completion_date date;
535     TYPE OpCurType IS REF CURSOR RETURN wip_operations%ROWTYPE;
536     opCur OpCurType;
537     opRow wip_operations%ROWTYPE;
538 
539     /* added for calling WO API */
540 
541         l_eam_wo_rec EAM_PROCESS_WO_PUB.eam_wo_rec_type;
542         l_eam_op_rec  EAM_PROCESS_WO_PUB.eam_op_rec_type;
543         l_eam_op_tbl  EAM_PROCESS_WO_PUB.eam_op_tbl_type;
544         l_eam_op_network_tbl  EAM_PROCESS_WO_PUB.eam_op_network_tbl_type;
545         l_eam_res_tbl  EAM_PROCESS_WO_PUB.eam_res_tbl_type;
546         l_eam_res_inst_tbl  EAM_PROCESS_WO_PUB.eam_res_inst_tbl_type;
547         l_eam_sub_res_tbl   EAM_PROCESS_WO_PUB.eam_sub_res_tbl_type;
548         l_eam_res_usage_tbl  EAM_PROCESS_WO_PUB.eam_res_usage_tbl_type;
549         l_eam_mat_req_tbl   EAM_PROCESS_WO_PUB.eam_mat_req_tbl_type;
550         l_eam_di_tbl   EAM_PROCESS_WO_PUB.eam_direct_items_tbl_type;
551 	l_eam_wo_comp_rec               EAM_PROCESS_WO_PUB.eam_wo_comp_rec_type;
552 	l_eam_wo_quality_tbl            EAM_PROCESS_WO_PUB.eam_wo_quality_tbl_type;
553 	l_eam_meter_reading_tbl         EAM_PROCESS_WO_PUB.eam_meter_reading_tbl_type;
554 	l_eam_wo_comp_rebuild_tbl       EAM_PROCESS_WO_PUB.eam_wo_comp_rebuild_tbl_type;
555 	l_eam_wo_comp_mr_read_tbl       EAM_PROCESS_WO_PUB.eam_wo_comp_mr_read_tbl_type;
556 	l_eam_op_comp_tbl               EAM_PROCESS_WO_PUB.eam_op_comp_tbl_type;
557 	l_eam_request_tbl               EAM_PROCESS_WO_PUB.eam_request_tbl_type;
558         l_eam_counter_prop_tbl     EAM_PROCESS_WO_PUB.eam_counter_prop_tbl_type;
559 
560         l_out_eam_wo_rec EAM_PROCESS_WO_PUB.eam_wo_rec_type;
561         l_out_eam_op_tbl  EAM_PROCESS_WO_PUB.eam_op_tbl_type;
562         l_out_eam_op_network_tbl  EAM_PROCESS_WO_PUB.eam_op_network_tbl_type;
563         l_out_eam_res_tbl  EAM_PROCESS_WO_PUB.eam_res_tbl_type;
564         l_out_eam_res_inst_tbl  EAM_PROCESS_WO_PUB.eam_res_inst_tbl_type;
565         l_out_eam_sub_res_tbl   EAM_PROCESS_WO_PUB.eam_sub_res_tbl_type;
566         l_out_eam_res_usage_tbl  EAM_PROCESS_WO_PUB.eam_res_usage_tbl_type;
567         l_out_eam_mat_req_tbl   EAM_PROCESS_WO_PUB.eam_mat_req_tbl_type;
568         l_out_eam_di_tbl   EAM_PROCESS_WO_PUB.eam_direct_items_tbl_type;
569 	l_out_eam_wo_comp_rec           EAM_PROCESS_WO_PUB.eam_wo_comp_rec_type;
570 	l_out_eam_wo_quality_tbl        EAM_PROCESS_WO_PUB.eam_wo_quality_tbl_type;
571 	l_out_eam_meter_reading_tbl     EAM_PROCESS_WO_PUB.eam_meter_reading_tbl_type;
572 	l_out_eam_wo_comp_rebuild_tbl   EAM_PROCESS_WO_PUB.eam_wo_comp_rebuild_tbl_type;
573 	l_out_eam_wo_comp_mr_read_tbl   EAM_PROCESS_WO_PUB.eam_wo_comp_mr_read_tbl_type;
574 	l_out_eam_op_comp_tbl           EAM_PROCESS_WO_PUB.eam_op_comp_tbl_type;
575 	l_out_eam_request_tbl           EAM_PROCESS_WO_PUB.eam_request_tbl_type;
576         l_out_eam_counter_prop_tbl    EAM_PROCESS_WO_PUB.eam_counter_prop_tbl_type;
577 
578 	 l_output_dir  VARCHAR2(512);
579 
580     BEGIN
581          SAVEPOINT operation_handover;
582 
583 
584       eam_debug.init_err_stack('eam_operations_jsp.operation_handover');
585 
586      IF NOT FND_API.COMPATIBLE_API_CALL(l_api_version,
587                                          p_api_version,
588                                          l_api_name,
589                                          g_pkg_name)
590       THEN
591          RAISE FND_API.G_EXC_UNEXPECTED_ERROR;
592       END IF;
593 
594       IF FND_API.TO_BOOLEAN(p_init_msg_list)
595       THEN
596          FND_MSG_PUB.initialize;
597       END IF;
598 
599   EAM_WORKORDER_UTIL_PKG.log_path(l_output_dir);
600 
601 
602       x_return_status := FND_API.G_RET_STS_SUCCESS;
603 
604       -----------------------------------------------------------------
605       -- validation
606       -- check if data is stale or not
607       -- using last_update_date as indicator
608      BEGIN
609         SELECT
610              last_update_date
611             ,operation_completed
612             ,first_unit_start_date
613             ,last_unit_completion_date
614             ,organization_id  --
615             ,department_id
616         INTO
617              l_db_last_update_date
618             ,l_completed
619             ,l_actual_start_date
620             ,l_actual_end_date
621             ,l_org_id
622             ,l_old_dept_id
623         FROM wip_operations
624         WHERE
625             wip_entity_id = p_wip_entity_id
626         and operation_seq_num = p_old_op_seq_num
627         FOR UPDATE;
628 
629 
630         -- checking stuff
631         IF  l_db_last_update_date <> nvl(p_stored_last_update_date, l_db_last_update_date) THEN
632           eam_execution_jsp.add_message(p_app_short_name => 'EAM', p_msg_name => 'EAM_OP_STALED_DATA');
633           x_return_status := FND_API.G_RET_STS_ERROR;
634         END IF;
635         IF ( nvl(l_completed, 'N') = 'Y' ) THEN
636           eam_execution_jsp.add_message(p_app_short_name => 'EAM', p_msg_name => 'EAM_HANDOVER_CANT_STATUS_Y');
637           x_return_status := FND_API.G_RET_STS_ERROR;
638         END IF;
639 
640         IF (p_start_date > p_completion_date) THEN
641           eam_execution_jsp.add_message(p_app_short_name => 'EAM', p_msg_name => 'EAM_HANDOVER_DATE_BAD');
642           x_return_status := FND_API.G_RET_STS_ERROR;
643         END IF;
644 
645 
646         select count(*)
647         into l_count from wip_operations
648         where wip_entity_id = p_wip_entity_id and operation_seq_num = p_new_op_seq_num;
649         IF( l_count > 0 ) THEN
650           eam_execution_jsp.add_message(p_app_short_name => 'EAM', p_msg_name => 'EAM_OP_EXISTED');
651           x_return_status := FND_API.G_RET_STS_ERROR;
652         END IF;
653 
654 --  Bug 3133704 . removed count for department_code within an org. For a given org id , dept code is unique.
655           select department_id
656           into l_department_id
657           from bom_departments
658           where organization_id = l_org_id
659             and department_code like p_assigned_department;
660           if(l_department_id = l_old_dept_id) then
661             eam_execution_jsp.add_message(p_app_short_name => 'EAM', p_msg_name => 'EAM_HANDOVER_DEPT_SAME');
662             x_return_status := FND_API.G_RET_STS_ERROR;
663           end if;
664 
665 
666       EXCEPTION WHEN NO_DATA_FOUND THEN
667         eam_execution_jsp.add_message(p_app_short_name => 'EAM', p_msg_name => 'EAM_OP_NOT_FOUND');
668         x_return_status := FND_API.G_RET_STS_UNEXP_ERROR;
669       END;
670 
671       -- if validate not passed then raise error
672       l_msg_count := FND_MSG_PUB.count_msg;
673       IF l_msg_count = 1 THEN
674          eam_execution_jsp.Get_Messages
675            (p_encoded  => FND_API.G_FALSE,
676             p_msg_index => 1,
677             p_msg_count => l_msg_count,
678             p_msg_data  => l_msg_data,   -- removed g_miss_char
679             p_data      => l_data,
680             p_msg_index_out => l_msg_index_out);
681             x_msg_count := l_msg_count;
682             x_msg_data  := l_msg_data;
683       ELSE
684          x_msg_count  := l_msg_count;
685       END IF;
686 
687       IF l_msg_count > 0 THEN
688          x_return_status := FND_API.G_RET_STS_UNEXP_ERROR;
689          RAISE  FND_API.G_EXC_ERROR;
690       END IF;
691 
692       ---------------------------------------------------
693       -- prepare for DML
694 
695 
696       -----------------------------------
697       -- DML goes here
698 
699       -- keep the data before complete the op, use it to create new op
700       select *
701         into opRow
702         from wip_operations
703         where wip_entity_id = p_wip_entity_id
704           and operation_seq_num = p_old_op_seq_num;
705 
706       if l_actual_start_date <= sysdate then --added by akalaval for bug 4162307
707 
708           l_old_op_duration := (sysdate - l_actual_start_date)*24;
709 
710       complete_operation(
711         x_return_status => x_return_status
712        ,x_msg_count =>  x_msg_count
713        ,x_msg_data =>  x_msg_data
714        ,p_wip_entity_id => p_wip_entity_id
715        ,p_operation_seq_num => p_old_op_seq_num
716        ,p_actual_start_date => l_actual_start_date
717        ,p_actual_end_date => sysdate
718        ,p_actual_duration => l_old_op_duration
719        ,p_transaction_date => sysdate
720        ,p_transaction_type => 1
721        ,p_shutdown_start_date => null
722        ,p_shutdown_end_date => null
723        ,p_reconciliation_code => p_reconciliation_value
724        ,p_stored_last_update_date => p_stored_last_update_date
725       );
726 
727       else --condition added for handling operation completion in case of
728            --operation start date is in future
729 
730       complete_operation(
731         x_return_status => x_return_status
732        ,x_msg_count =>  x_msg_count
733        ,x_msg_data =>  x_msg_data
734        ,p_wip_entity_id => p_wip_entity_id
735        ,p_operation_seq_num => p_old_op_seq_num
736        ,p_actual_start_date => sysdate
737        ,p_actual_end_date => sysdate
738        ,p_actual_duration => 0
739        ,p_transaction_date => sysdate
740        ,p_transaction_type => 1
741        ,p_shutdown_start_date => null
742        ,p_shutdown_end_date => null
743        ,p_reconciliation_code => p_reconciliation_value
744        ,p_stored_last_update_date => p_stored_last_update_date
745       );
746 
747       end if;
748 
749       IF (x_return_status = FND_API.G_RET_STS_SUCCESS) THEN
750 
751 
752 	select max(transaction_id) into l_transaction_id
753 	from eam_op_completion_txns
754 	where wip_entity_id = p_wip_entity_id
755 	and operation_seq_num = p_old_op_seq_num;
756 
757 	update eam_op_completion_txns
758 	set handover_operation_seq_num = p_new_op_seq_num
759 	where wip_entity_id = p_wip_entity_id
760 	and operation_seq_num = p_old_op_seq_num
761 	and transaction_id = l_transaction_id;
762 
763         l_new_op_completion_date := (p_start_date + p_duration/24);
764         -- create new operation
765         opRow.Operation_Seq_Num := p_new_op_seq_num;
766         opRow.Last_Update_Date := sysdate;
767         opRow.Last_Updated_By := g_last_updated_by;
768         opRow.Last_Update_Login := g_last_update_login;
769         opRow.Creation_Date := sysdate;
770         opRow.Created_By := g_created_by;
771         opRow.Department_Id := l_department_id;
772         opRow.Description := p_description;
773         opRow.First_Unit_Start_Date := p_start_date;
774         opRow.First_Unit_Completion_Date := l_new_op_completion_date;
775         opRow.Last_Unit_Start_Date := p_start_date;
776         opRow.Last_Unit_Completion_Date := l_new_op_completion_date;
777 
778         if ((p_shutdown_type is not null) and (p_shutdown_type <> -1)) then
779         opRow.Shutdown_Type := p_shutdown_type;
780         end if;
781 
782         opRow.Operation_Sequence_Id := null;
783 
784          l_eam_op_rec.wip_entity_id := opRow.Wip_Entity_Id;
785          l_eam_op_rec.operation_seq_num := opRow.Operation_Seq_Num;
786          l_eam_op_rec.organization_id := opRow.Organization_Id;
787          l_eam_op_rec.operation_sequence_id := opRow.Operation_Sequence_Id;
788          l_eam_op_rec.standard_operation_id := opRow.Standard_Operation_Id;
789          l_eam_op_rec.department_id := opRow.Department_Id;
790          l_eam_op_rec.description := opRow.Description;
791          l_eam_op_rec.start_date := opRow.First_Unit_Start_Date;
792          l_eam_op_rec.completion_date := opRow.Last_Unit_Completion_Date;
793          l_eam_op_rec.count_point_type := opRow.Count_Point_Type;
794          l_eam_op_rec.backflush_flag := opRow.Backflush_Flag;
795          l_eam_op_rec.minimum_transfer_quantity := opRow.Minimum_Transfer_Quantity;
796          l_eam_op_rec.attribute_category := opRow.Attribute_Category;
797          l_eam_op_rec.attribute1 := opRow.Attribute1;
798          l_eam_op_rec.attribute2 := opRow.Attribute2;
799          l_eam_op_rec.attribute3 := opRow.Attribute3;
800          l_eam_op_rec.attribute4 := opRow.Attribute4;
801          l_eam_op_rec.attribute5 := opRow.Attribute5;
802          l_eam_op_rec.attribute6 := opRow.Attribute6;
803          l_eam_op_rec.attribute7 := opRow.Attribute7;
804          l_eam_op_rec.attribute8 := opRow.Attribute8;
805          l_eam_op_rec.attribute9 := opRow.Attribute9;
806          l_eam_op_rec.attribute10 := opRow.Attribute10;
807          l_eam_op_rec.attribute11 := opRow.Attribute11;
808          l_eam_op_rec.attribute12 := opRow.Attribute12;
809          l_eam_op_rec.attribute13 := opRow.Attribute13;
810          l_eam_op_rec.attribute14 := opRow.Attribute14;
811          l_eam_op_rec.attribute15 := opRow.Attribute15;
812          l_eam_op_rec.long_description := opRow.Long_Description;
813          l_eam_op_rec.shutdown_type := opRow.Shutdown_Type;
814 
815 
816 
817 
818        l_eam_op_rec.transaction_type := EAM_PROCESS_WO_PUB.G_OPR_CREATE;
819 
820 
821        l_eam_op_tbl(1) := l_eam_op_rec ;
822 
823 
824 				 EAM_PROCESS_WO_PUB.Process_WO
825 	  		         ( p_bo_identifier           => 'EAM'
826 	  		         , p_init_msg_list           => TRUE
827 	  		         , p_api_version_number      => 1.0
828 	                         , p_commit                  => 'N'
829 	  		         , p_eam_wo_rec              => l_eam_wo_rec
830 	  		         , p_eam_op_tbl              => l_eam_op_tbl
831 	  		         , p_eam_op_network_tbl      => l_eam_op_network_tbl
832 	  		         , p_eam_res_tbl             => l_eam_res_tbl
833 	  		         , p_eam_res_inst_tbl        => l_eam_res_inst_tbl
834 	  		         , p_eam_sub_res_tbl         => l_eam_sub_res_tbl
835 	  		         , p_eam_res_usage_tbl       => l_eam_res_usage_tbl
836 	  		         , p_eam_mat_req_tbl         => l_eam_mat_req_tbl
837 	                         , p_eam_direct_items_tbl    => l_eam_di_tbl
838 				 , p_eam_wo_comp_rec         => l_eam_wo_comp_rec
839 				 , p_eam_wo_quality_tbl      => l_eam_wo_quality_tbl
840 				 , p_eam_meter_reading_tbl   => l_eam_meter_reading_tbl
841 				 , p_eam_counter_prop_tbl    => l_eam_counter_prop_tbl
842 				 , p_eam_wo_comp_rebuild_tbl => l_eam_wo_comp_rebuild_tbl
843 				 , p_eam_wo_comp_mr_read_tbl => l_eam_wo_comp_mr_read_tbl
844 				 , p_eam_op_comp_tbl         => l_eam_op_comp_tbl
845 				 , p_eam_request_tbl         =>	l_eam_request_tbl
846 	  		         , x_eam_wo_rec              => l_out_eam_wo_rec
847 	  		         , x_eam_op_tbl              => l_out_eam_op_tbl
848 	  		         , x_eam_op_network_tbl      => l_out_eam_op_network_tbl
849 	  		         , x_eam_res_tbl             => l_out_eam_res_tbl
850 	  		         , x_eam_res_inst_tbl        => l_out_eam_res_inst_tbl
851 	  		         , x_eam_sub_res_tbl         => l_out_eam_sub_res_tbl
852 	  		         , x_eam_res_usage_tbl       => l_out_eam_res_usage_tbl
853 	  		         , x_eam_mat_req_tbl         => l_out_eam_mat_req_tbl
854 	                         , x_eam_direct_items_tbl    => l_out_eam_di_tbl
855 				 , x_eam_wo_comp_rec         => l_out_eam_wo_comp_rec
856 				 , x_eam_wo_quality_tbl      => l_out_eam_wo_quality_tbl
857 				 , x_eam_meter_reading_tbl   => l_out_eam_meter_reading_tbl
858 				 , x_eam_counter_prop_tbl    => l_out_eam_counter_prop_tbl
859 				 , x_eam_wo_comp_rebuild_tbl => l_out_eam_wo_comp_rebuild_tbl
860 				 , x_eam_wo_comp_mr_read_tbl => l_out_eam_wo_comp_mr_read_tbl
861 				 , x_eam_op_comp_tbl         => l_out_eam_op_comp_tbl
862 				 , x_eam_request_tbl         => l_out_eam_request_tbl
863 	  		         , x_return_status           => x_return_status
864 	  		         , x_msg_count               => x_msg_count
865 	  		         , p_debug                   => NVL(fnd_profile.value('EAM_DEBUG'), 'N')
866 	  		         , p_debug_filename          => 'ophandover.log'
867 	  		         , p_output_dir              => l_output_dir
868 	                         , p_debug_file_mode         => 'w'
869 	                       );
870 
871         -- copy network relations
872         copy_operation_network(
873            p_wip_entity_id => p_wip_entity_id
874           ,p_old_op_seq_num => p_old_op_seq_num
875           ,p_new_op_seq_num => p_new_op_seq_num
876           ,p_operation_start_date => p_start_date
877           ,p_operation_completion_date => p_completion_date
878           ,x_return_status => x_return_status
879         );
880       END IF;
881 
882       -- check error
883       l_msg_count := FND_MSG_PUB.count_msg;
884      IF l_msg_count = 1 THEN
885          eam_execution_jsp.Get_Messages
886            (p_encoded  => FND_API.G_FALSE,
887             p_msg_index => 1,
888             p_msg_count => l_msg_count,
889             p_msg_data  => l_msg_data,
890             p_data      => l_data,
891             p_msg_index_out => l_msg_index_out);
892             x_msg_count := l_msg_count;
893             x_msg_data  := l_msg_data;
894       ELSE
895          x_msg_count  := l_msg_count;
896       END IF;
897 
898       IF l_msg_count > 0 THEN
899          x_return_status := FND_API.G_RET_STS_UNEXP_ERROR;
900          RAISE  FND_API.G_EXC_ERROR;
901       END IF;
902 
903 
904       IF FND_API.TO_BOOLEAN(P_COMMIT)
905       THEN
906         COMMIT WORK;
907       END IF;
908 
909     EXCEPTION WHEN FND_API.G_EXC_UNEXPECTED_ERROR  THEN
910          ROLLBACK TO operation_handover;
911 
912       FND_MSG_PUB.add_exc_msg( p_pkg_name => 'eam_operations_jsp.operation_handover',
913       p_procedure_name => EAM_DEBUG.G_err_stack);
914       x_return_status := FND_API.G_RET_STS_UNEXP_ERROR;
915     WHEN FND_API.G_EXC_ERROR THEN
916          ROLLBACK TO operation_handover;
917 
918 
919       FND_MSG_PUB.add_exc_msg( p_pkg_name => 'eam_operations_jsp.operation_handover',
920       p_procedure_name => EAM_DEBUG.G_err_stack);
921       x_return_status := FND_API.G_RET_STS_UNEXP_ERROR;
922     WHEN OTHERS THEN
923          ROLLBACK TO operation_handover;
924 
925 
926       FND_MSG_PUB.add_exc_msg( p_pkg_name => 'eam_operations_jsp.operation_handover',
927       p_procedure_name => EAM_DEBUG.G_err_stack);
928       x_return_status := FND_API.G_RET_STS_UNEXP_ERROR;
929       g_debug_sqlerrm := SQLERRM;
930 
931   END operation_handover;
932 
933 
934 -----------------------------------------------------------------------------------------
935 -- copy the operation network data for the new operation
936 -----------------------------------------------------------------------------------------
937 
938    procedure copy_operation_network
939     (
940        p_wip_entity_id               IN    NUMBER        -- data
941       ,p_old_op_seq_num              IN    NUMBER
942       ,p_new_op_seq_num              IN    NUMBER
943       ,p_operation_start_date        IN    DATE
944       ,p_operation_completion_date   IN    DATE
945       ,x_return_status               OUT NOCOPY   VARCHAR2
946     ) IS
947 
948     l_actual_end_date  DATE;
949     l_completed  VARCHAR2(30);
950     l_actual_start_date  DATE;
951 
952 
953 -- cursor to copy: xxx-> newop
954 
955       CURSOR nxtOpCur  IS
956       SELECT prior_operation
957               ,next_operation
958               ,wip_entity_id
959               ,organization_id
960               ,created_by
961               ,creation_date
962               ,last_updated_by
963               ,last_update_date
964               ,last_update_login
965               ,attribute_category
966               ,attribute1
967               ,attribute2
968               ,attribute3
969               ,attribute4
970               ,attribute5
971               ,attribute6
972               ,attribute7
973               ,attribute8
974               ,attribute9
975               ,attribute10
976               ,attribute11
977               ,attribute12
978               ,attribute13
979               ,attribute14
980               ,attribute15
981              FROM wip_operation_networks
982              WHERE wip_entity_id =  p_wip_entity_id
983              AND next_operation =  p_old_op_seq_num;
984 
985       -- cursor to copy new op --> xxx
986 
987 
988       CURSOR prvOpCur  IS
989       SELECT prior_operation
990               ,next_operation
991               ,wip_entity_id
992               ,organization_id
993               ,created_by
994               ,creation_date
995               ,last_updated_by
996               ,last_update_date
997               ,last_update_login
998               ,attribute_category
999               ,attribute1
1000               ,attribute2
1001               ,attribute3
1002               ,attribute4
1003               ,attribute5
1004               ,attribute6
1005               ,attribute7
1006               ,attribute8
1007               ,attribute9
1008               ,attribute10
1009               ,attribute11
1010               ,attribute12
1011               ,attribute13
1012               ,attribute14
1013               ,attribute15
1014              FROM wip_operation_networks
1015              WHERE wip_entity_id =  p_wip_entity_id
1016              AND prior_operation =  p_old_op_seq_num;
1017 
1018 
1019 
1020 
1021     BEGIN
1022       -- copy: xxx-> newop
1023 
1024       x_return_status := FND_API.G_RET_STS_SUCCESS;
1025 
1026       FOR nxtOpCurVar IN nxtOpCur LOOP
1027 
1028 
1029         BEGIN
1030 
1031 		IF (nxtOpCurVar.prior_operation IS NOT NULL) THEN
1032 
1033 			SELECT
1034 			     last_unit_completion_date,
1035 			     operation_completed
1036 			INTO
1037 			     l_actual_end_date,
1038 			     l_completed
1039 			FROM wip_operations
1040 			WHERE
1041 			    wip_entity_id = p_wip_entity_id
1042 			AND operation_seq_num = nxtOpCurVar.prior_operation;
1043 
1044 		END IF;
1045 
1046 		IF (p_operation_start_date < l_actual_end_date) THEN
1047 		  eam_execution_jsp.add_message(p_app_short_name => 'EAM', p_msg_name => 'EAM_HANDOVER_INV_START_DATE');
1048 		  x_return_status := FND_API.G_RET_STS_UNEXP_ERROR;
1049 		END IF;
1050 
1051 		IF NVL(l_completed,'N') = 'N' THEN
1052 		  eam_execution_jsp.add_message(p_app_short_name => 'EAM', p_msg_name => 'EAM_INVALID_COMPLETE_OP2');
1053 		  x_return_status := FND_API.G_RET_STS_UNEXP_ERROR;
1054 		END IF;
1055 
1056 
1057         EXCEPTION WHEN  NO_DATA_FOUND THEN  -- Bug 3133704, others -> no_data_found
1058            eam_execution_jsp.add_message(p_app_short_name => 'EAM', p_msg_name => 'EAM_HANDOVER_OP_NOTFOUND');
1059           x_return_status := FND_API.G_RET_STS_ERROR;
1060         END;
1061 
1062         IF x_return_status = FND_API.G_RET_STS_SUCCESS THEN
1063 
1064 			nxtOpCurVar.next_operation  := p_new_op_seq_num;
1065 			nxtOpCurVar.last_updated_by := FND_GLOBAL.user_id;
1066 			nxtOpCurVar.last_update_login := FND_GLOBAL.user_id;
1067 			nxtOpCurVar.created_by := FND_GLOBAL.user_id;
1068 			nxtOpCurVar.last_update_date := sysdate;
1069 			nxtOpCurVar.creation_date := sysdate;
1070 
1071 			INSERT INTO wip_operation_networks
1072 			(  prior_operation
1073 			  ,next_operation
1074 			  ,wip_entity_id
1075 			  ,organization_id
1076 			  ,created_by
1077 			  ,creation_date
1078 			  ,last_updated_by
1079 			  ,last_update_date
1080 			  ,last_update_login
1081 			  ,attribute_category
1082 			  ,attribute1
1083 			  ,attribute2
1084 			  ,attribute3
1085 			  ,attribute4
1086 			  ,attribute5
1087 			  ,attribute6
1088 			  ,attribute7
1089 			  ,attribute8
1090 			  ,attribute9
1091 			  ,attribute10
1092 			  ,attribute11
1093 			  ,attribute12
1094 			  ,attribute13
1095 			  ,attribute14
1096 			  ,attribute15
1097 			) VALUES
1098 			(  nxtOpCurVar.prior_operation
1099 			  ,p_new_op_seq_num
1100 			  ,nxtOpCurVar.wip_entity_id
1101 			  ,nxtOpCurVar.organization_id
1102 			  ,nxtOpCurVar.created_by
1103 			  ,nxtOpCurVar.creation_date
1104 			  ,nxtOpCurVar.last_updated_by
1105 			  ,nxtOpCurVar.last_update_date
1106 			  ,nxtOpCurVar.last_update_login
1107 			  ,nxtOpCurVar.attribute_category
1108 			  ,nxtOpCurVar.attribute1
1109 			  ,nxtOpCurVar.attribute2
1110 			  ,nxtOpCurVar.attribute3
1111 			  ,nxtOpCurVar.attribute4
1112 			  ,nxtOpCurVar.attribute5
1113 			  ,nxtOpCurVar.attribute6
1114 			  ,nxtOpCurVar.attribute7
1115 			  ,nxtOpCurVar.attribute8
1116 			  ,nxtOpCurVar.attribute9
1117 			  ,nxtOpCurVar.attribute10
1118 			  ,nxtOpCurVar.attribute11
1119 			  ,nxtOpCurVar.attribute12
1120 			  ,nxtOpCurVar.attribute13
1121 			  ,nxtOpCurVar.attribute14
1122 			  ,nxtOpCurVar.attribute15
1123 			);
1124            END IF; -- end of check for x_return_status
1125 
1126       END LOOP;   -- end loop for nxtOpCurVar
1127 
1128 
1129       -- copy new op --> xxx
1130 
1131       FOR prvOpCurVar IN prvOpCur LOOP
1132 
1133 
1134         BEGIN
1135 
1136 		IF (prvOpCurVar.next_operation IS NOT NULL) THEN
1137 
1138 			SELECT
1139 			     operation_completed
1140 			    ,first_unit_start_date
1141 			INTO
1142 			     l_completed
1143 			    ,l_actual_start_date
1144 			FROM wip_operations
1145 			WHERE
1146 			    wip_entity_id = p_wip_entity_id
1147 			AND operation_seq_num = prvOpCurVar.next_operation;
1148 
1149 		END IF;
1150 
1151 		IF (NVL(l_completed, 'N' ) = 'Y') THEN
1152 			eam_execution_jsp.add_message(p_app_short_name => 'EAM', p_msg_name => 'EAM_INVALID_COMPLETE_OP1');
1153 			x_return_status := FND_API.G_RET_STS_ERROR;
1154 		END IF;
1155 
1156 		IF (l_actual_start_date < p_operation_completion_date ) THEN
1157 			eam_execution_jsp.add_message(p_app_short_name => 'EAM', p_msg_name => 'EAM_HANDOVER_INV_END_DATE');
1158 			x_return_status := FND_API.G_RET_STS_ERROR;
1159 		END IF;
1160 
1161         EXCEPTION WHEN  NO_DATA_FOUND THEN  -- Bug 3133704, others -> no_data_found
1162 	   eam_execution_jsp.add_message(p_app_short_name => 'EAM', p_msg_name => 'EAM_HANDOVER_OP_NOTFOUND');
1163            x_return_status := FND_API.G_RET_STS_ERROR;
1164         END;
1165 
1166         IF x_return_status = FND_API.G_RET_STS_SUCCESS THEN
1167 
1168 			prvOpCurVar.prior_operation  := p_new_op_seq_num;
1169 			prvOpCurVar.Last_Updated_By := FND_GLOBAL.user_id;
1170 			prvOpCurVar.Last_Update_Login := FND_GLOBAL.user_id;
1171 			prvOpCurVar.Created_By := FND_GLOBAL.user_id;
1172 			prvOpCurVar.Last_Update_Date := sysdate;
1173 			prvOpCurVar.Creation_Date := sysdate;
1174 
1175 
1176 			INSERT INTO wip_operation_networks
1177 			(  prior_operation
1178 			  ,next_operation
1179 			  ,wip_entity_id
1180 			  ,organization_id
1181 			  ,created_by
1182 			  ,creation_date
1183 			  ,last_updated_by
1184 			  ,last_update_date
1185 			  ,last_update_login
1186 			  ,attribute_category
1187 			  ,attribute1
1188 			  ,attribute2
1189 			  ,attribute3
1190 			  ,attribute4
1191 			  ,attribute5
1192 			  ,attribute6
1193 			  ,attribute7
1194 			  ,attribute8
1195 			  ,attribute9
1196 			  ,attribute10
1197 			  ,attribute11
1198 			  ,attribute12
1199 			  ,attribute13
1200 			  ,attribute14
1201 			  ,attribute15
1202 			) VALUES
1203 			(  p_new_op_seq_num
1204 			  ,prvOpCurVar.next_operation
1205 			  ,prvOpCurVar.wip_entity_id
1206 			  ,prvOpCurVar.organization_id
1207 			  ,prvOpCurVar.created_by
1208 			  ,prvOpCurVar.creation_date
1209 			  ,prvOpCurVar.last_updated_by
1210 			  ,prvOpCurVar.last_update_date
1211 			  ,prvOpCurVar.last_update_login
1212 			  ,prvOpCurVar.attribute_category
1213 			  ,prvOpCurVar.attribute1
1214 			  ,prvOpCurVar.attribute2
1215 			  ,prvOpCurVar.attribute3
1216 			  ,prvOpCurVar.attribute4
1217 			  ,prvOpCurVar.attribute5
1218 			  ,prvOpCurVar.attribute6
1219 			  ,prvOpCurVar.attribute7
1220 			  ,prvOpCurVar.attribute8
1221 			  ,prvOpCurVar.attribute9
1222 			  ,prvOpCurVar.attribute10
1223 			  ,prvOpCurVar.attribute11
1224 			  ,prvOpCurVar.attribute12
1225 			  ,prvOpCurVar.attribute13
1226 			  ,prvOpCurVar.attribute14
1227 			  ,prvOpCurVar.attribute15
1228 			);
1229 
1230 	END IF; -- end of check for x_return_status
1231 
1232       END LOOP;  -- end loop for prvOpCurVar
1233 
1234 
1235     EXCEPTION WHEN NO_DATA_FOUND THEN
1236       RAISE FND_API.G_EXC_ERROR;
1237   END copy_operation_network;
1238 
1239 
1240 ---------------------------------------------------------------------------------------
1241 -- handover the selected resources of one operation
1242 ---------------------------------------------------------------------------------------
1243   procedure operation_handover_resource
1244   (  p_api_version                 IN    NUMBER        := 1.0
1245     ,p_init_msg_list               IN    VARCHAR2      := FND_API.G_FALSE
1246     ,p_commit                      IN    VARCHAR2      := FND_API.G_FALSE
1247     ,p_validate_only               IN    VARCHAR2      := FND_API.G_TRUE
1248     ,p_record_version_number       IN    NUMBER        := NULL
1249     ,x_return_status               OUT NOCOPY   VARCHAR2
1250     ,x_msg_count                   OUT NOCOPY   NUMBER
1251     ,x_msg_data                    OUT NOCOPY   VARCHAR2
1252     ,p_wip_entity_id               IN    NUMBER        -- data
1253     ,p_old_op_seq_num              IN    NUMBER
1254     ,p_resource_seq_num            IN    NUMBER
1255     ,p_new_op_seq_num              IN    NUMBER
1256     ,p_department                  IN    VARCHAR2
1257     ,p_start_date                  IN    DATE
1258     ,p_duration                    IN    NUMBER
1259     ,p_new_op_start_date           IN    DATE
1260     ,p_new_op_end_date             IN    DATE
1261     ,p_employee_id		   IN    NUMBER       -- instance id
1262     ,p_complete_rollback	   IN	 VARCHAR2      := FND_API.G_FALSE -- Added parameter to handle rollback for Mobile Handover Page.
1263   ) IS
1264 
1265   curRow wip_operation_resources%ROWTYPE;
1266   newRow wip_operation_resources%ROWTYPE;
1267 
1268   l_api_name           CONSTANT VARCHAR(30) := 'operation_handover_resource';
1269   l_api_version        CONSTANT NUMBER      := 1.0;
1270   l_return_status            VARCHAR2(250);
1271   l_error_msg_code           VARCHAR2(250);
1272   l_msg_count         NUMBER;
1273   l_msg_data          VARCHAR2(250);
1274   l_data                     VARCHAR2(250);
1275   l_msg_index_out            NUMBER;
1276 
1277   l_department_id     NUMBER;
1278   l_quantity_open     NUMBER;
1279   l_start_quantity    NUMBER;
1280   l_num_non_compatible_resources NUMBER;
1281   l_duration  NUMBER;
1282   l_new_op_seq_num  NUMBER;
1283   l_resource_id     VARCHAR2(20);
1284   l_dept            NUMBER;
1285   l_res_valid       NUMBER;
1286   l_inst_valid      NUMBER;
1287   l_employee_name   VARCHAR2(165);
1288 
1289     /* added for calling WO API */
1290 
1291         l_eam_wo_rec EAM_PROCESS_WO_PUB.eam_wo_rec_type;
1292         l_eam_op_tbl  EAM_PROCESS_WO_PUB.eam_op_tbl_type;
1293         l_eam_op_network_tbl  EAM_PROCESS_WO_PUB.eam_op_network_tbl_type;
1294         l_eam_res_tbl  EAM_PROCESS_WO_PUB.eam_res_tbl_type;
1295         l_eam_res_rec  EAM_PROCESS_WO_PUB.eam_res_rec_type;
1296         l_eam_res_inst_tbl  EAM_PROCESS_WO_PUB.eam_res_inst_tbl_type;
1297         l_eam_res_inst_rec  EAM_PROCESS_WO_PUB.eam_res_inst_rec_type;
1298         l_eam_sub_res_tbl   EAM_PROCESS_WO_PUB.eam_sub_res_tbl_type;
1299         l_eam_res_usage_tbl  EAM_PROCESS_WO_PUB.eam_res_usage_tbl_type;
1300         l_eam_mat_req_tbl   EAM_PROCESS_WO_PUB.eam_mat_req_tbl_type;
1301         l_eam_di_tbl   EAM_PROCESS_WO_PUB.eam_direct_items_tbl_type;
1302 	l_eam_wo_comp_rec               EAM_PROCESS_WO_PUB.eam_wo_comp_rec_type;
1303 	l_eam_wo_quality_tbl            EAM_PROCESS_WO_PUB.eam_wo_quality_tbl_type;
1304 	l_eam_meter_reading_tbl         EAM_PROCESS_WO_PUB.eam_meter_reading_tbl_type;
1305 	l_eam_wo_comp_rebuild_tbl       EAM_PROCESS_WO_PUB.eam_wo_comp_rebuild_tbl_type;
1306 	l_eam_wo_comp_mr_read_tbl       EAM_PROCESS_WO_PUB.eam_wo_comp_mr_read_tbl_type;
1307 	l_eam_op_comp_tbl               EAM_PROCESS_WO_PUB.eam_op_comp_tbl_type;
1308 	l_eam_request_tbl               EAM_PROCESS_WO_PUB.eam_request_tbl_type;
1309         l_eam_counter_prop_tbl     EAM_PROCESS_WO_PUB.eam_counter_prop_tbl_type;
1310 
1311         l_out_eam_wo_rec EAM_PROCESS_WO_PUB.eam_wo_rec_type;
1312         l_out_eam_op_tbl  EAM_PROCESS_WO_PUB.eam_op_tbl_type;
1313         l_out_eam_op_network_tbl  EAM_PROCESS_WO_PUB.eam_op_network_tbl_type;
1314         l_out_eam_res_tbl  EAM_PROCESS_WO_PUB.eam_res_tbl_type;
1315         l_out_eam_res_inst_tbl  EAM_PROCESS_WO_PUB.eam_res_inst_tbl_type;
1316         l_out_eam_sub_res_tbl   EAM_PROCESS_WO_PUB.eam_sub_res_tbl_type;
1317         l_out_eam_res_usage_tbl  EAM_PROCESS_WO_PUB.eam_res_usage_tbl_type;
1318         l_out_eam_mat_req_tbl   EAM_PROCESS_WO_PUB.eam_mat_req_tbl_type;
1319         l_out_eam_di_tbl   EAM_PROCESS_WO_PUB.eam_direct_items_tbl_type;
1320 	l_out_eam_wo_comp_rec           EAM_PROCESS_WO_PUB.eam_wo_comp_rec_type;
1321 	l_out_eam_wo_quality_tbl        EAM_PROCESS_WO_PUB.eam_wo_quality_tbl_type;
1322 	l_out_eam_meter_reading_tbl     EAM_PROCESS_WO_PUB.eam_meter_reading_tbl_type;
1323 	l_out_eam_wo_comp_rebuild_tbl   EAM_PROCESS_WO_PUB.eam_wo_comp_rebuild_tbl_type;
1324 	l_out_eam_wo_comp_mr_read_tbl   EAM_PROCESS_WO_PUB.eam_wo_comp_mr_read_tbl_type;
1325 	l_out_eam_op_comp_tbl           EAM_PROCESS_WO_PUB.eam_op_comp_tbl_type;
1326 	l_out_eam_request_tbl           EAM_PROCESS_WO_PUB.eam_request_tbl_type;
1327         l_out_eam_counter_prop_tbl    EAM_PROCESS_WO_PUB.eam_counter_prop_tbl_type;
1328 
1329 	 l_output_dir  VARCHAR2(512);
1330 
1331   BEGIN
1332 
1333        SAVEPOINT operation_handover_resource;
1334 
1335     eam_debug.init_err_stack('eam_operations_jsp.operation_handover_resource');
1336 
1337     IF NOT FND_API.COMPATIBLE_API_CALL(l_api_version,
1338                                        p_api_version,
1339                                        l_api_name,
1340                                        g_pkg_name)
1341     THEN
1342        RAISE FND_API.G_EXC_UNEXPECTED_ERROR;
1343     END IF;
1344 
1345     IF FND_API.TO_BOOLEAN(p_init_msg_list)
1346     THEN
1347        FND_MSG_PUB.initialize;
1348     END IF;
1349 
1350   EAM_WORKORDER_UTIL_PKG.log_path(l_output_dir);
1351 
1352     x_return_status := FND_API.G_RET_STS_SUCCESS;
1353 
1354     -----------------------------------------------------------------
1355     -- validation
1356     if(p_duration <0) then
1357       eam_execution_jsp.add_message(p_app_short_name => 'EAM', p_msg_name => 'EAM_HANDOVER_DURATION');
1358       x_return_status := FND_API.G_RET_STS_UNEXP_ERROR;
1359     else
1360      l_duration := trunc(p_duration * 60 * 60, 0) / ( 24 * 60 * 60);
1361     end if;
1362 
1363    /* Fix for Bug 2108778 */
1364        -- Validate the new operation
1365        begin
1366        select operation_seq_num
1367        into l_new_op_seq_num
1368        from wip_operations
1369        where wip_entity_id = p_wip_entity_id
1370        and operation_seq_num = p_new_op_seq_num;
1371        Exception when others then
1372          eam_execution_jsp.add_message(p_app_short_name => 'EAM', p_msg_name => 'EAM_HANDOVER_OP_NOTFOUND');
1373         x_return_status := FND_API.G_RET_STS_UNEXP_ERROR;
1374        END;
1375     /* Fix for Bug 2108778 */
1376 
1377     begin
1378      l_dept :=null;
1379      select resource_id into l_resource_id
1380      from wip_operation_resources
1381      where wip_entity_id = p_wip_entity_id
1382      and operation_seq_num = p_old_op_seq_num
1383      and resource_seq_num = p_resource_seq_num;
1384 
1385      select bd.department_id into l_dept
1386      from bom_department_resources bdr,bom_departments bd
1387      where bd.department_id = bdr.department_id
1388      and resource_id = l_resource_id
1389      and bd.department_id in (select department_id
1390                              from bom_departments
1391                              where department_code=p_department);
1392      if(l_dept=null) then
1393 	  eam_execution_jsp.add_message(p_app_short_name => 'EAM', p_msg_name => 'EAM_HANDOVER_DEPT_INVALID'
1394           ,p_token1 => 'RESOURCE_SEQ_NUM', p_value1 => p_resource_seq_num ,p_token2 => 'DEPARTMENT',p_value2 =>p_department);
1395 	  x_return_status := FND_API.G_RET_STS_UNEXP_ERROR;
1396       END IF;
1397     end;
1398 
1399     -- get the resource
1400     BEGIN
1401       select *
1402       into curRow
1403       from wip_operation_resources r
1404       where r.wip_entity_id = p_wip_entity_id
1405         and r.operation_seq_num = p_old_op_seq_num
1406         and r.resource_seq_num = p_resource_seq_num;
1407 
1408       select quantity_open
1409         into l_quantity_open
1410         from wip_operation_resources_v v
1411         where v.wip_entity_id = curRow.Wip_Entity_Id
1412           and v.operation_seq_num = curRow.Operation_Seq_Num
1413           and v.resource_seq_num = curRow.Resource_Seq_Num;
1414 
1415        IF l_quantity_open < 0 THEN
1416         l_quantity_open := 0;
1417        END IF ;
1418 
1419     Exception when others then
1420       eam_execution_jsp.add_message(p_app_short_name => 'EAM', p_msg_name => 'EAM_HANDOVER_RSRC_NOTFOUND'
1421          ,p_token1 => 'RESOURCE_SEQ_NUM', p_value1 => p_resource_seq_num);
1422       x_return_status := FND_API.G_RET_STS_UNEXP_ERROR;
1423 
1424 
1425       END;
1426 
1427 
1428     if( curRow.Wip_Entity_Id is not null) then
1429       BEGIN
1430         select department_id
1431         into l_department_id
1432         from bom_departments bd
1433         where bd.department_code like p_department
1434           and bd.organization_id = curRow.Organization_Id
1435           and nvl(bd.disable_date, sysdate) >= sysdate;
1436 
1437 
1438       Exception when others then
1439         eam_execution_jsp.add_message(p_app_short_name => 'EAM', p_msg_name => 'EAM_HANDOVER_DEPT_INV'
1440          ,p_token1 => 'RESOURCE_SEQ_NUM', p_value1 => p_resource_seq_num
1441          ,p_token2 => 'ERR', p_value2 =>  SQLERRM );
1442         x_return_status := FND_API.G_RET_STS_UNEXP_ERROR;
1443       END;
1444 
1445 
1446       -- verify that resource can be handover to that department
1447       if (x_return_status = FND_API.G_RET_STS_SUCCESS ) then
1448         select count(*)
1449         into l_num_non_compatible_resources
1450         from wip_operation_resources wor
1451         where wor.wip_entity_id = p_wip_entity_id
1452           and wor.operation_seq_num = p_old_op_seq_num
1453           and wor.resource_seq_num = p_resource_seq_num
1454           and wor.resource_id not in (
1455             select bdr.resource_id
1456             from bom_department_resources bdr
1457             where bdr.department_id = l_department_id
1458           );
1459         if( l_num_non_compatible_resources >0) then
1460           eam_execution_jsp.add_message(p_app_short_name => 'EAM', p_msg_name => 'EAM_HANDOVER_DEPT_NOTOK'
1461          ,p_token1 => 'RESOURCE_SEQ_NUM', p_value1 => p_resource_seq_num);
1462           x_return_status := FND_API.G_RET_STS_UNEXP_ERROR;
1463         end if;
1464       end if;
1465    end if;
1466 
1467    -- get start quantity
1468    select start_quantity
1469    into l_start_quantity
1470    from wip_discrete_jobs wdj
1471    where wdj.wip_entity_id = p_wip_entity_id;
1472 
1473    if(l_start_quantity <> 1 ) then
1474      eam_execution_jsp.add_message(p_app_short_name => 'EAM', p_msg_name => 'EAM_HANDOVER_S_QUANTITY_INV');
1475      x_return_status := FND_API.G_RET_STS_UNEXP_ERROR;
1476    end if;
1477 
1478 
1479    if( x_return_status = FND_API.G_RET_STS_SUCCESS) then
1480      BEGIN
1481 
1482 	     SELECT 1 INTO l_res_valid
1483 	     FROM wip_operation_resources
1484 	     WHERE wip_entity_id = p_wip_entity_id
1485 	     AND operation_seq_num = p_new_op_seq_num
1486 	     AND resource_seq_num = p_resource_seq_num;
1487 
1488      EXCEPTION WHEN NO_DATA_FOUND THEN
1489 	      l_res_valid := 0;
1490      END;
1491 
1492      BEGIN
1493 
1494              SELECT 1 INTO l_inst_valid
1495 	     FROM wip_op_resource_instances
1496 	     WHERE wip_entity_id = p_wip_entity_id
1497 	     AND operation_seq_num = p_new_op_seq_num
1498 	     AND resource_seq_num = p_resource_seq_num
1499              AND instance_id = p_employee_id;
1500 
1501      EXCEPTION WHEN NO_DATA_FOUND THEN
1502               l_inst_valid := 0;
1503      END;
1504 
1505      -- copy row
1506      newRow := curRow;
1507      newRow.Operation_Seq_Num := p_new_op_seq_num;
1508      newRow.Start_Date := p_start_date;
1509      newRow.Completion_Date := p_start_date + l_duration;
1510      newRow.Department_Id := l_department_id;
1511      newRow.Usage_Rate_Or_Amount := nvl(l_quantity_open, 0) / l_start_quantity;
1512      newRow.Applied_Resource_Units := 0;
1513      newRow.Applied_Resource_Value := 0;
1514 
1515      -- row who
1516      newRow.Last_Update_Date := sysdate;
1517      newRow.Creation_Date := sysdate;
1518      newRow.Last_Updated_By := g_last_updated_by;
1519      newRow.Last_Update_Login := g_last_updated_by;
1520      newRow.Created_By := g_last_updated_by;
1521 
1522 
1523 	BEGIN
1524 
1525 		IF l_res_valid <> 1 THEN
1526 
1527 			l_eam_res_rec.transaction_type := EAM_PROCESS_WO_PUB.G_OPR_CREATE;
1528 			l_eam_res_rec.wip_entity_id := newRow.Wip_Entity_Id;
1529 			l_eam_res_rec.operation_seq_num := newRow.Operation_Seq_Num;
1530 			l_eam_res_rec.organization_id := newRow.Organization_Id;
1531 			l_eam_res_rec.resource_seq_num := newRow.resource_seq_num;
1532 			l_eam_res_rec.resource_id := newRow.resource_id;
1533 			l_eam_res_rec.uom_code := newRow.uom_code;
1534 			l_eam_res_rec.basis_type := newRow.basis_type;
1535 			l_eam_res_rec.usage_rate_or_amount := newRow.usage_rate_or_amount;
1536 			l_eam_res_rec.activity_id := newRow.activity_id;
1537 			l_eam_res_rec.scheduled_flag := newRow.scheduled_flag;
1538 			l_eam_res_rec.firm_flag := newRow.firm_flag;
1539 			l_eam_res_rec.assigned_units := newRow.assigned_units;
1540 			l_eam_res_rec.maximum_assigned_units := newRow.maximum_assigned_units;
1541 			l_eam_res_rec.autocharge_type := newRow.autocharge_type;
1542 			l_eam_res_rec.standard_rate_flag := newRow.standard_rate_flag;
1543 			l_eam_res_rec.applied_resource_units := newRow.applied_resource_units;
1544 			l_eam_res_rec.applied_resource_value := newRow.applied_resource_value;
1545 			l_eam_res_rec.start_date := newRow.start_date;
1546 			l_eam_res_rec.completion_date := newRow.completion_date;
1547 			l_eam_res_rec.schedule_seq_num := newRow.schedule_seq_num;
1548 			l_eam_res_rec.substitute_group_num := newRow.substitute_group_num;
1549 			l_eam_res_rec.attribute_category := newRow.attribute_category;
1550 			l_eam_res_rec.department_id := newRow.department_id;
1551 			l_eam_res_rec.attribute1 := newRow.Attribute1;
1552 			l_eam_res_rec.attribute2 := newRow.Attribute2;
1553 			l_eam_res_rec.attribute3 := newRow.Attribute3;
1554 			l_eam_res_rec.attribute4 := newRow.Attribute4;
1555 			l_eam_res_rec.attribute5 := newRow.Attribute5;
1556 			l_eam_res_rec.Attribute6 := newRow.Attribute6;
1557 			l_eam_res_rec.Attribute7 := newRow.Attribute7;
1558 			l_eam_res_rec.Attribute8 := newRow.Attribute8;
1559 			l_eam_res_rec.Attribute9 := newRow.Attribute9;
1560 			l_eam_res_rec.Attribute10 := newRow.Attribute10;
1561 			l_eam_res_rec.attribute11 := newRow.Attribute11;
1562 			l_eam_res_rec.attribute12 := newRow.Attribute12;
1563 			l_eam_res_rec.attribute13 := newRow.Attribute13;
1564 			l_eam_res_rec.attribute14 := newRow.Attribute14;
1565 			l_eam_res_rec.attribute15 := newRow.Attribute15;
1566 
1567 
1568 			l_eam_res_tbl(1) := l_eam_res_rec ;
1569 
1570 			IF l_inst_valid <> 1 THEN
1571 
1572 				IF p_employee_id IS NOT NULL THEN
1573 
1574 					l_eam_res_inst_rec.transaction_type		:=  EAM_PROCESS_WO_PUB.G_OPR_CREATE ;
1575 					l_eam_res_inst_rec.wip_entity_id			:= p_wip_entity_id ;
1576 					l_eam_res_inst_rec.organization_id		:= newRow.organization_id   ;
1577 					l_eam_res_inst_rec.operation_seq_num	:= p_new_op_seq_num ;
1578 					l_eam_res_inst_rec.resource_seq_num         := p_resource_seq_num ;
1579 					l_eam_res_inst_rec.instance_id			:= p_employee_id ;
1580 					l_eam_res_inst_rec.serial_number                := NULL ;
1581 					l_eam_res_inst_rec.start_date			:= p_start_date ;
1582 					l_eam_res_inst_rec.completion_date		:= (p_start_date+l_duration) ;
1583 
1584 					l_eam_res_inst_tbl(1) := l_eam_res_inst_rec ;
1585 
1586 				END IF;  -- end of p_employee_id
1587 
1588 			ELSE
1589 				SELECT full_name
1590 				INTO l_employee_name
1591 				FROM per_all_people_f papf,bom_resource_employees bre
1592 				WHERE bre.instance_id  = p_employee_id
1593 				and papf.person_id = bre.person_id
1594 				and( trunc(sysdate) between papf.effective_start_date
1595 				and papf.effective_end_date);
1596 
1597 				eam_execution_jsp.add_message(p_app_short_name => 'EAM', p_msg_name => 'EAM_RI_ALREADY_EXISTS'
1598 				,p_token1 => 'INSTANCE_NAME', p_value1 => l_employee_name);
1599 				x_return_status := FND_API.G_RET_STS_UNEXP_ERROR;
1600 			END IF;    -- end of l_inst_valid check
1601 
1602 			EAM_PROCESS_WO_PUB.Process_WO
1603 			( p_bo_identifier           => 'EAM'
1604 			, p_init_msg_list           => TRUE
1605 			, p_api_version_number      => 1.0
1606 			, p_commit                  => 'N'
1607 			, p_eam_wo_rec              => l_eam_wo_rec
1608 			, p_eam_op_tbl              => l_eam_op_tbl
1609 			, p_eam_op_network_tbl      => l_eam_op_network_tbl
1610 			, p_eam_res_tbl             => l_eam_res_tbl
1611 			, p_eam_res_inst_tbl        => l_eam_res_inst_tbl
1612 			, p_eam_sub_res_tbl         => l_eam_sub_res_tbl
1613 			, p_eam_res_usage_tbl       => l_eam_res_usage_tbl
1614 			, p_eam_mat_req_tbl         => l_eam_mat_req_tbl
1615 			, p_eam_direct_items_tbl    => l_eam_di_tbl
1616 			, p_eam_wo_comp_rec         => l_eam_wo_comp_rec
1617 			, p_eam_wo_quality_tbl      => l_eam_wo_quality_tbl
1618 			, p_eam_meter_reading_tbl   => l_eam_meter_reading_tbl
1619 			, p_eam_counter_prop_tbl    => l_eam_counter_prop_tbl
1620 			, p_eam_wo_comp_rebuild_tbl => l_eam_wo_comp_rebuild_tbl
1621 			, p_eam_wo_comp_mr_read_tbl => l_eam_wo_comp_mr_read_tbl
1622 			, p_eam_op_comp_tbl         => l_eam_op_comp_tbl
1623 			, p_eam_request_tbl         =>	l_eam_request_tbl
1624 			, x_eam_wo_rec              => l_out_eam_wo_rec
1625 			, x_eam_op_tbl              => l_out_eam_op_tbl
1626 			, x_eam_op_network_tbl      => l_out_eam_op_network_tbl
1627 			, x_eam_res_tbl             => l_out_eam_res_tbl
1628 			, x_eam_res_inst_tbl        => l_out_eam_res_inst_tbl
1629 			, x_eam_sub_res_tbl         => l_out_eam_sub_res_tbl
1630 			, x_eam_res_usage_tbl       => l_out_eam_res_usage_tbl
1631 			, x_eam_mat_req_tbl         => l_out_eam_mat_req_tbl
1632 			, x_eam_direct_items_tbl    => l_out_eam_di_tbl
1633 			, x_eam_wo_comp_rec         => l_out_eam_wo_comp_rec
1634 			, x_eam_wo_quality_tbl      => l_out_eam_wo_quality_tbl
1635 			, x_eam_meter_reading_tbl   => l_out_eam_meter_reading_tbl
1636 			, x_eam_counter_prop_tbl    => l_out_eam_counter_prop_tbl
1637 			, x_eam_wo_comp_rebuild_tbl => l_out_eam_wo_comp_rebuild_tbl
1638 			, x_eam_wo_comp_mr_read_tbl => l_out_eam_wo_comp_mr_read_tbl
1639 			, x_eam_op_comp_tbl         => l_out_eam_op_comp_tbl
1640 			, x_eam_request_tbl         => l_out_eam_request_tbl
1641 			, x_return_status           => x_return_status
1642 			, x_msg_count               => x_msg_count
1643 			, p_debug                   => NVL(fnd_profile.value('EAM_DEBUG'), 'N')
1644 			, p_debug_filename          => 'opreshandover.log'
1645 			, p_output_dir              => l_output_dir
1646 			, p_debug_file_mode         => 'w'
1647 			);
1648 
1649 		END IF ; -- end of l_res_valid check
1650 
1651 
1652 
1653 	EXCEPTION WHEN OTHERS THEN
1654 	eam_execution_jsp.add_message(p_app_short_name => 'EAM', p_msg_name => 'EAM_HANDOVER_EXCEPTION'
1655 	,p_token1 => 'RESOURCE_SEQ_NUM', p_value1 => p_resource_seq_num
1656 	,p_token2 => 'ERR_MSG', p_value2 => SQLERRM);
1657 	END;
1658 
1659   end if;
1660 
1661     -- check error
1662     l_msg_count := FND_MSG_PUB.count_msg;
1663     IF l_msg_count = 1 THEN
1664        eam_execution_jsp.Get_Messages
1665          (p_encoded  => FND_API.G_FALSE,
1666           p_msg_index => 1,
1667           p_msg_count => l_msg_count,
1668           p_msg_data  => l_msg_data,      -- removed g_miss_char
1669           p_data      => l_data,
1670           p_msg_index_out => l_msg_index_out);
1671           x_msg_count := l_msg_count;
1672           x_msg_data  := l_msg_data;
1673     ELSE
1674        x_msg_count  := l_msg_count;
1675     END IF;
1676 
1677     IF l_msg_count > 0 THEN
1678        x_return_status := FND_API.G_RET_STS_UNEXP_ERROR;
1679        RAISE  FND_API.G_EXC_ERROR;
1680     END IF;
1681 
1682     IF FND_API.TO_BOOLEAN(P_COMMIT)
1683     THEN
1684       COMMIT WORK;
1685     END IF;
1686 
1687   EXCEPTION WHEN FND_API.G_EXC_UNEXPECTED_ERROR  THEN
1688 	IF FND_API.TO_BOOLEAN(p_complete_rollback)
1689 	THEN
1690 		ROLLBACK; -- Complete rollback for Mobile Handover Page
1691 	ELSE
1692 		ROLLBACK TO operation_handover_resource; -- Method rollback for Desktop HandoverPage.
1693 	END IF;
1694     FND_MSG_PUB.add_exc_msg( p_pkg_name => 'eam_operations_jsp.operation_handover_resource',
1695     p_procedure_name => EAM_DEBUG.G_err_stack);
1696     x_return_status := FND_API.G_RET_STS_UNEXP_ERROR;
1697 
1698   WHEN FND_API.G_EXC_ERROR THEN
1699 	IF FND_API.TO_BOOLEAN(p_complete_rollback)
1700 	THEN
1701 		ROLLBACK; -- Complete rollback for Mobile Handover Page
1702 	ELSE
1703 		ROLLBACK TO operation_handover_resource; -- Method rollback for Desktop HandoverPage.
1704 	END IF;
1705     FND_MSG_PUB.add_exc_msg( p_pkg_name => 'eam_operations_jsp.operation_handover_resource',
1706     p_procedure_name => EAM_DEBUG.G_err_stack);
1707     x_return_status := FND_API.G_RET_STS_UNEXP_ERROR;
1708 
1709   WHEN OTHERS THEN
1710 	IF FND_API.TO_BOOLEAN(p_complete_rollback)
1711 	THEN
1712 		ROLLBACK; -- Complete rollback for Mobile Handover Page
1713 	ELSE
1714 		ROLLBACK TO operation_handover_resource; -- Method rollback for Desktop HandoverPage.
1715 	END IF;
1716     FND_MSG_PUB.add_exc_msg( p_pkg_name => 'eam_operations_jsp.operation_handover_resource',
1717     p_procedure_name => EAM_DEBUG.G_err_stack);
1718     x_return_status := FND_API.G_RET_STS_UNEXP_ERROR;
1719 
1720   END operation_handover_resource;
1721 
1722 
1723   --  Procedure to validate all fields entered through the Add Resource JSP
1724 
1725   procedure validate_insert (p_wip_entity_id      IN       NUMBER
1726                              ,p_operation_seq_num  IN       NUMBER
1727                              ,p_department_code    IN       VARCHAR2
1728                              ,p_organization_id    IN       NUMBER
1729                              ,p_resource_code      IN       VARCHAR2
1730                              ,p_uom_code           IN       VARCHAR2
1731                              ,p_usage_rate         IN       NUMBER
1732                              ,p_assigned_units     IN       NUMBER
1733                              ,p_start_date         IN       DATE
1734                              ,p_end_date           IN       DATE
1735                              ,p_activity           IN       VARCHAR2
1736                              ,x_uom_status         OUT NOCOPY      NUMBER
1737                              ,x_operation_status   OUT NOCOPY      NUMBER
1738                              ,x_department_status  OUT NOCOPY      NUMBER
1739                              ,x_res_status         OUT NOCOPY      NUMBER
1740                              ,x_usage_status       OUT NOCOPY      NUMBER
1741                              ,x_assigned_units     OUT NOCOPY      NUMBER
1742                              ,x_assigned           OUT NOCOPY      NUMBER
1743                              ,x_dates              OUT NOCOPY      NUMBER
1744                              ,x_activity           OUT NOCOPY      NUMBER)  IS
1745 
1746               l_res_code  varchar2(80);
1747               l_uom       varchar2(30);
1748               l_invalid_uom  number := 0;
1749               l_invalid_resource number := 0;
1750               l_stmt_num number := 0;
1751               l_invalid_usage number := 0;
1752               l_operation_seq_num  number := 0;
1753               l_department_code varchar2(80);
1754               l_invalid_operation number := 0;
1755               l_invalid_department number := 0;
1756               l_invalid_assgned_units  number := 0;
1757               l_assigned    number := 0;
1758               l_invalid_dates number := 0;
1759               l_activities  varchar2(80);
1760               l_invalid_activity  number := 0;
1761               l_capacity_units  number := 0;
1762 
1763               resource_exists number := 1;
1764               uom_exists number := 1;
1765               operation_exists  number := 1;
1766               department_exists  number := 1;
1767               activity_exists number := 1;
1768               TYPE CUR_TYP is ref cursor;
1769 
1770           --    c_res_cur                               CUR_TYP;
1771            --   c_oper_cur                              CUR_TYP;
1772            --   c_act_cur				    CUR_TYP;
1773 
1774 
1775 
1776        CURSOR c_res_cur IS    --rhshriva
1777                  select res.resource_code,
1778                          res.unit_of_measure
1779                   from cst_activities cst, mtl_uom_conversions muc, bom_resources res, bom_department_resources bdr
1780                   where nvl(res.disable_date,sysdate+2) > sysdate
1781                   and res.resource_id = bdr.resource_id
1782                   and res.default_activity_id = cst.activity_id(+)
1783                   and (cst.organization_id = res.organization_id or cst.organization_id is null)
1784                   and nvl(cst.disable_date(+), sysdate+2) > sysdate
1785                   and res.unit_of_measure = muc.uom_code
1786                   and muc.inventory_item_id = 0
1787                   and res.organization_id = p_organization_id
1788                   and department_id = (select department_id
1789                                        from wip_operations
1790                                        where wip_entity_id =  p_wip_entity_id
1791                                        and operation_seq_num = p_operation_seq_num);
1792 
1793 
1794 
1795        CURSOR c_oper_cur IS  --rhshriva
1796 	select wo.operation_seq_num, bd.department_code
1797 	 from wip_operations wo, bom_departments bd
1798 	 where bd.department_id = wo.department_id
1799 	 and bd.organization_id = wo.organization_id
1800 	 and wo.organization_id = p_organization_id
1801          and wo.wip_entity_id = p_wip_entity_id;
1802 
1803 
1804      CURSOR c_act_cur IS  --rhshriva
1805 	 select activity
1806 	      from cst_activities
1807 	      where nvl(disable_date, sysdate + 2) > sysdate and
1808 	    (organization_id is null or organization_id = p_organization_id ) ;
1809 
1810     BEGIN
1811               -- Check for Usage Rate
1812 /* Commenting out the validation as this is already present in WO API */
1813               -- Check for Resource
1814 
1815               open c_res_cur ;
1816                l_stmt_num := 10;
1817 
1818                loop
1819 
1820                fetch c_res_cur into l_res_code, l_uom;
1821                exit when c_res_cur % NOTFOUND;
1822 
1823                l_stmt_num := 20;
1824 
1825                -- Check for resource_code and uom validation
1826 
1827                if (p_resource_code = l_res_code) then
1828                        resource_exists := 0 ;
1829                end if;
1830 
1831                if (p_uom_code = l_uom) then
1832   	             uom_exists := 0;
1833                 end if;
1834 
1835 
1836                 end loop;
1837 
1838                 close c_res_cur;
1839 
1840 
1841   	      if (uom_exists = 1) then
1842   	      	 l_invalid_uom := 1;
1843   	      end if;
1844 
1845   	      if (resource_exists = 1) then
1846   	         l_invalid_resource := 1;
1847   	      end if;
1848 
1849   	     x_uom_status := l_invalid_uom;
1850 
1851   	     x_res_status := l_invalid_resource;
1852 
1853 -- Bug 3133704 changed when_others
1854     EXCEPTION WHEN NO_DATA_FOUND THEN
1855           raise FND_API.G_EXC_ERROR;
1856 
1857     END validate_insert;
1858 
1859 
1860   -- Insert into WIP_OPERATION_RESOURCES from Add Resources JSP
1861 
1862     procedure insert_into_wor(  p_api_version        IN       NUMBER
1863                   ,p_init_msg_list      IN       VARCHAR2 := fnd_api.g_false
1864                   ,p_commit             IN       VARCHAR2 := fnd_api.g_false
1865                   ,p_validation_level   IN       NUMBER   := fnd_api.g_valid_level_full
1866                   ,p_wip_entity_id      IN       NUMBER
1867                   ,p_operation_seq_num  IN       NUMBER
1868                   ,p_organization_id    IN       NUMBER
1869                   ,p_usage_rate   IN       NUMBER
1870                   ,p_resource_code      IN       VARCHAR2
1871                   ,p_uom_code           IN       VARCHAR2
1872   		,p_resource_seq_num   IN NUMBER
1873                   ,p_dept_code          IN VARCHAR2
1874   		,p_assigned_units     IN NUMBER
1875   		,p_basis              IN NUMBER
1876                   ,p_scheduled_flag     IN NUMBER
1877   		,p_charge_type        IN NUMBER
1878   		,p_schedule_sequence  IN NUMBER
1879   		,p_std_rate           IN VARCHAR2
1880   		,p_start_date         IN DATE
1881   		,p_end_date           IN DATE
1882   		,p_activity           IN VARCHAR2
1883 		,p_mod		      IN VARCHAR2
1884   		,x_update_status      OUT NOCOPY      NUMBER
1885                   ,x_return_status      OUT NOCOPY      VARCHAR2
1886                   ,x_msg_count          OUT NOCOPY      NUMBER
1887                   ,x_msg_data           OUT NOCOPY      VARCHAR2)  IS
1888 
1889      l_api_name       CONSTANT VARCHAR2(30) := 'insert_into_wor';
1890      l_api_version    CONSTANT NUMBER       := 1.0;
1891      l_full_name      CONSTANT VARCHAR2(60)   := g_pkg_name || '.' || l_api_name;
1892 
1893     l_resource_id             NUMBER;
1894     l_update_status          NUMBER := 1;
1895     l_activity_id            NUMBER;
1896     l_usage_rate      NUMBER := 0;
1897     l_stmt_num       NUMBER;
1898 
1899     -- baroy
1900     l_old_scheduled_flag    number;
1901     l_old_schedule_sequence number;
1902     l_old_start_date        date;
1903     l_old_end_date          date;
1904     l_old_usage_rate        number;
1905     l_old_uom_code          varchar2(3);
1906     l_old_assigned_units    number;
1907     l_call_scheduler        number := 0;
1908     -- baroy
1909 
1910     l_res_seq_exists      NUMBER := 0;
1911 
1912 
1913     /* added for calling WO API */
1914 
1915     l_eam_wo_rec EAM_PROCESS_WO_PUB.eam_wo_rec_type;
1916     l_eam_res_rec  EAM_PROCESS_WO_PUB.eam_res_rec_type;
1917     l_eam_op_tbl  EAM_PROCESS_WO_PUB.eam_op_tbl_type;
1918     l_eam_op_network_tbl  EAM_PROCESS_WO_PUB.eam_op_network_tbl_type;
1919     l_eam_res_tbl  EAM_PROCESS_WO_PUB.eam_res_tbl_type;
1920     l_eam_res_inst_tbl  EAM_PROCESS_WO_PUB.eam_res_inst_tbl_type;
1921     l_eam_sub_res_tbl   EAM_PROCESS_WO_PUB.eam_sub_res_tbl_type;
1922     l_eam_res_usage_tbl  EAM_PROCESS_WO_PUB.eam_res_usage_tbl_type;
1923     l_eam_mat_req_tbl   EAM_PROCESS_WO_PUB.eam_mat_req_tbl_type;
1924     l_eam_di_tbl   EAM_PROCESS_WO_PUB.eam_direct_items_tbl_type;
1925     l_eam_wo_comp_rec               EAM_PROCESS_WO_PUB.eam_wo_comp_rec_type;
1926     l_eam_wo_quality_tbl            EAM_PROCESS_WO_PUB.eam_wo_quality_tbl_type;
1927     l_eam_meter_reading_tbl         EAM_PROCESS_WO_PUB.eam_meter_reading_tbl_type;
1928     l_eam_wo_comp_rebuild_tbl       EAM_PROCESS_WO_PUB.eam_wo_comp_rebuild_tbl_type;
1929     l_eam_wo_comp_mr_read_tbl       EAM_PROCESS_WO_PUB.eam_wo_comp_mr_read_tbl_type;
1930     l_eam_op_comp_tbl               EAM_PROCESS_WO_PUB.eam_op_comp_tbl_type;
1931     l_eam_request_tbl               EAM_PROCESS_WO_PUB.eam_request_tbl_type;
1932     l_eam_counter_prop_tbl     EAM_PROCESS_WO_PUB.eam_counter_prop_tbl_type;
1933 
1934     l_out_eam_wo_rec EAM_PROCESS_WO_PUB.eam_wo_rec_type;
1935     l_out_eam_op_tbl  EAM_PROCESS_WO_PUB.eam_op_tbl_type;
1936     l_out_eam_op_network_tbl  EAM_PROCESS_WO_PUB.eam_op_network_tbl_type;
1937     l_out_eam_res_tbl  EAM_PROCESS_WO_PUB.eam_res_tbl_type;
1938     l_out_eam_res_inst_tbl  EAM_PROCESS_WO_PUB.eam_res_inst_tbl_type;
1939     l_out_eam_sub_res_tbl   EAM_PROCESS_WO_PUB.eam_sub_res_tbl_type;
1940     l_out_eam_res_usage_tbl  EAM_PROCESS_WO_PUB.eam_res_usage_tbl_type;
1941     l_out_eam_mat_req_tbl   EAM_PROCESS_WO_PUB.eam_mat_req_tbl_type;
1942     l_out_eam_di_tbl   EAM_PROCESS_WO_PUB.eam_direct_items_tbl_type;
1943     l_out_eam_wo_comp_rec           EAM_PROCESS_WO_PUB.eam_wo_comp_rec_type;
1944     l_out_eam_wo_quality_tbl        EAM_PROCESS_WO_PUB.eam_wo_quality_tbl_type;
1945     l_out_eam_meter_reading_tbl     EAM_PROCESS_WO_PUB.eam_meter_reading_tbl_type;
1946     l_out_eam_wo_comp_rebuild_tbl   EAM_PROCESS_WO_PUB.eam_wo_comp_rebuild_tbl_type;
1947     l_out_eam_wo_comp_mr_read_tbl   EAM_PROCESS_WO_PUB.eam_wo_comp_mr_read_tbl_type;
1948     l_out_eam_op_comp_tbl           EAM_PROCESS_WO_PUB.eam_op_comp_tbl_type;
1949     l_out_eam_request_tbl           EAM_PROCESS_WO_PUB.eam_request_tbl_type;
1950     l_out_eam_counter_prop_tbl    EAM_PROCESS_WO_PUB.eam_counter_prop_tbl_type;
1951 
1952 
1953    l_output_dir   VARCHAR2(512);
1954     BEGIN
1955 
1956   EAM_WORKORDER_UTIL_PKG.log_path(l_output_dir);
1957 
1958 
1959                   -- Standard Start of API savepoint
1960                    l_stmt_num    := 10;
1961                    SAVEPOINT get_insert_into_wor_pvt;
1962 
1963                    l_stmt_num    := 20;
1964                    -- Standard call to check for call compatibility.
1965                    IF NOT fnd_api.compatible_api_call(
1966                          l_api_version
1967                         ,p_api_version
1968                         ,l_api_name
1969                         ,g_pkg_name) THEN
1970                       RAISE fnd_api.g_exc_unexpected_error;
1971                    END IF;
1972 
1973                    l_stmt_num    := 30;
1974                    -- Initialize message list if p_init_msg_list is set to TRUE.
1975                    IF fnd_api.to_boolean(p_init_msg_list) THEN
1976                       fnd_msg_pub.initialize;
1977                    END IF;
1978 
1979                    l_stmt_num    := 40;
1980                    --  Initialize API return status to success
1981                    x_return_status := fnd_api.g_ret_sts_success;
1982 
1983                    l_stmt_num    := 50;
1984                    -- API body
1985 
1986     -- Check for Usage Rate
1987 
1988     if(p_usage_rate is not null) then
1989       l_usage_rate := p_usage_rate;
1990     else
1991       l_usage_rate := 0;
1992     end if;
1993 
1994 
1995     -- Derive Resource Id from Resource Code
1996 
1997       begin
1998 
1999       select resource_id
2000       into   l_resource_id
2001      from bom_resources
2002      where resource_code = p_resource_code
2003      and organization_id = p_organization_id;
2004 
2005       exception
2006   	when others then
2007   	  null;
2008       end;
2009 
2010     if (p_activity is not null) then
2011 
2012     begin
2013     select activity_id
2014     into l_activity_id
2015   from cst_activities
2016   where activity = p_activity
2017   and organization_id = organization_id;
2018 
2019   exception
2020      when others then
2021       null;
2022     end;
2023 end if;
2024 	if (p_mod='UPDATE') then
2025                         -- first query up the old resource for use in scheduling decision.
2026                         select scheduled_flag, schedule_seq_num,
2027                           start_date, completion_date, usage_rate_or_amount, uom_code, assigned_units
2028                           into l_old_scheduled_flag, l_old_schedule_sequence, l_old_start_date
2029                           , l_old_end_date, l_old_usage_rate, l_old_uom_code, l_old_assigned_units
2030                           from wip_operation_resources
2031                           where wip_entity_id = p_wip_entity_id
2032                           and operation_seq_num = p_operation_seq_num
2033                           and resource_seq_num = p_resource_seq_num
2034                           and organization_id = p_organization_id;
2035                         if p_scheduled_flag = 1 and (
2036                              l_old_scheduled_flag    <> p_scheduled_flag
2037                           or l_old_schedule_sequence <> p_schedule_sequence
2038                           or l_old_start_date        <> p_start_date
2039                           or l_old_end_date          <> p_end_date
2040                           or l_old_usage_rate        <> p_usage_rate
2041                           or l_old_uom_code          <> p_uom_code
2042                           or l_old_assigned_units    <> p_assigned_units)
2043                         then
2044                           l_call_scheduler := 1;
2045                         end if;
2046 
2047 			l_eam_res_rec.transaction_type := EAM_PROCESS_WO_PUB.G_OPR_UPDATE;
2048 			l_eam_res_rec.wip_entity_id :=  p_wip_entity_id;
2049                         l_eam_res_rec.organization_id := p_organization_id;
2050 			l_eam_res_rec.operation_seq_num :=  p_operation_seq_num;
2051 			l_eam_res_rec.resource_seq_num :=  p_resource_seq_num;
2052 			l_eam_res_rec.resource_id := l_resource_id;
2053 			l_eam_res_rec.uom_code := p_uom_code;
2054 			l_eam_res_rec.basis_type := p_basis;
2055 			l_eam_res_rec.usage_rate_or_amount := p_usage_rate;
2056 			l_eam_res_rec.activity_id := l_activity_id;
2057 			l_eam_res_rec.scheduled_flag := p_scheduled_flag;
2058 			l_eam_res_rec.assigned_units := p_assigned_units;
2059 			l_eam_res_rec.autocharge_type := p_charge_type;
2060 			if ( p_std_rate = 'Y') then
2061 			     l_eam_res_rec.standard_rate_flag := 1;
2062 		        else
2063 			     l_eam_res_rec.standard_rate_flag := 2;
2064 			end if;
2065 			l_eam_res_rec.start_date := p_start_date;
2066 			l_eam_res_rec.completion_date := p_end_date;
2067                         l_eam_res_rec.schedule_seq_num := p_schedule_sequence;
2068 
2069 			l_eam_res_tbl(1) := l_eam_res_rec ;
2070 
2071 
2072 			EAM_PROCESS_WO_PUB.Process_WO
2073   		         ( p_bo_identifier           => 'EAM'
2074   		         , p_init_msg_list           => TRUE
2075   		         , p_api_version_number      => 1.0
2076                          , p_commit                  => 'N'
2077   		         , p_eam_wo_rec              => l_eam_wo_rec
2078   		         , p_eam_op_tbl              => l_eam_op_tbl
2079   		         , p_eam_op_network_tbl      => l_eam_op_network_tbl
2080   		         , p_eam_res_tbl             => l_eam_res_tbl
2081   		         , p_eam_res_inst_tbl        => l_eam_res_inst_tbl
2082   		         , p_eam_sub_res_tbl         => l_eam_sub_res_tbl
2083   		         , p_eam_res_usage_tbl       => l_eam_res_usage_tbl
2084   		         , p_eam_mat_req_tbl         => l_eam_mat_req_tbl
2085                          , p_eam_direct_items_tbl    => l_eam_di_tbl
2086 			 , p_eam_wo_comp_rec         => l_eam_wo_comp_rec
2087 			 , p_eam_wo_quality_tbl      => l_eam_wo_quality_tbl
2088 			 , p_eam_meter_reading_tbl   => l_eam_meter_reading_tbl
2089 			 , p_eam_counter_prop_tbl    => l_eam_counter_prop_tbl
2090 			 , p_eam_wo_comp_rebuild_tbl => l_eam_wo_comp_rebuild_tbl
2091 			 , p_eam_wo_comp_mr_read_tbl => l_eam_wo_comp_mr_read_tbl
2092 			 , p_eam_op_comp_tbl         => l_eam_op_comp_tbl
2093 			 , p_eam_request_tbl         =>	l_eam_request_tbl
2094   		         , x_eam_wo_rec              => l_out_eam_wo_rec
2095   		         , x_eam_op_tbl              => l_out_eam_op_tbl
2096   		         , x_eam_op_network_tbl      => l_out_eam_op_network_tbl
2097   		         , x_eam_res_tbl             => l_out_eam_res_tbl
2098   		         , x_eam_res_inst_tbl        => l_out_eam_res_inst_tbl
2099   		         , x_eam_sub_res_tbl         => l_out_eam_sub_res_tbl
2100   		         , x_eam_res_usage_tbl       => l_out_eam_res_usage_tbl
2101   		         , x_eam_mat_req_tbl         => l_out_eam_mat_req_tbl
2102                          , x_eam_direct_items_tbl    => l_out_eam_di_tbl
2103 			 , x_eam_wo_comp_rec         => l_out_eam_wo_comp_rec
2104 			 , x_eam_wo_quality_tbl      => l_out_eam_wo_quality_tbl
2105 			 , x_eam_meter_reading_tbl   => l_out_eam_meter_reading_tbl
2106 			 , x_eam_counter_prop_tbl    => l_out_eam_counter_prop_tbl
2107 			 , x_eam_wo_comp_rebuild_tbl => l_out_eam_wo_comp_rebuild_tbl
2108 			 , x_eam_wo_comp_mr_read_tbl => l_out_eam_wo_comp_mr_read_tbl
2109 			 , x_eam_op_comp_tbl         => l_out_eam_op_comp_tbl
2110 			 , x_eam_request_tbl     => l_out_eam_request_tbl
2111   		         , x_return_status           => x_return_status
2112   		         , x_msg_count               => x_msg_count
2113   		         , p_debug                   => NVL(fnd_profile.value('EAM_DEBUG'), 'N')
2114   		         , p_debug_filename          => 'updatewor.log'
2115   		         , p_output_dir              => l_output_dir
2116                          , p_debug_file_mode         => 'w'
2117                        );
2118 
2119 			l_update_status := 0;
2120 
2121 	elsif (p_mod='INSERT') then
2122                         -- first find out whether we will need to call the
2123                         -- scheduler finally
2124                         if p_scheduled_flag = 1 then
2125                           l_call_scheduler := 1;
2126                         end if;
2127 
2128 
2129 		        l_eam_res_rec.transaction_type := EAM_PROCESS_WO_PUB.G_OPR_CREATE;
2130 			l_eam_res_rec.wip_entity_id :=  p_wip_entity_id;
2131                         l_eam_res_rec.organization_id := p_organization_id;
2132 			l_eam_res_rec.operation_seq_num :=  p_operation_seq_num;
2133 			l_eam_res_rec.resource_seq_num :=  p_resource_seq_num;
2134 			l_eam_res_rec.resource_id := l_resource_id;
2135 			l_eam_res_rec.uom_code := p_uom_code;
2136 			l_eam_res_rec.basis_type := p_basis;
2137 			l_eam_res_rec.usage_rate_or_amount := p_usage_rate;
2138 			l_eam_res_rec.activity_id := l_activity_id;
2139 			l_eam_res_rec.scheduled_flag := p_scheduled_flag;
2140 			l_eam_res_rec.assigned_units := p_assigned_units;
2141 			l_eam_res_rec.autocharge_type := p_charge_type;
2142 			if ( p_std_rate = 'Y') then
2143 			     l_eam_res_rec.standard_rate_flag := 1;
2144 		        else
2145 			     l_eam_res_rec.standard_rate_flag := 2;
2146 			end if;
2147 			l_eam_res_rec.start_date := p_start_date;
2148 			l_eam_res_rec.completion_date := p_end_date;
2149                         l_eam_res_rec.schedule_seq_num := p_schedule_sequence;
2150 
2151 			l_eam_res_tbl(1) := l_eam_res_rec ;
2152 
2153 
2154 			 EAM_PROCESS_WO_PUB.Process_WO
2155   		         ( p_bo_identifier           => 'EAM'
2156   		         , p_init_msg_list           => TRUE
2157   		         , p_api_version_number      => 1.0
2158                          , p_commit                  => 'N'
2159   		         , p_eam_wo_rec              => l_eam_wo_rec
2160   		         , p_eam_op_tbl              => l_eam_op_tbl
2161   		         , p_eam_op_network_tbl      => l_eam_op_network_tbl
2162   		         , p_eam_res_tbl             => l_eam_res_tbl
2163   		         , p_eam_res_inst_tbl        => l_eam_res_inst_tbl
2164   		         , p_eam_sub_res_tbl         => l_eam_sub_res_tbl
2165   		         , p_eam_res_usage_tbl       => l_eam_res_usage_tbl
2166   		         , p_eam_mat_req_tbl         => l_eam_mat_req_tbl
2167                          , p_eam_direct_items_tbl    => l_eam_di_tbl
2168 			 , p_eam_wo_comp_rec         => l_eam_wo_comp_rec
2169 			 , p_eam_wo_quality_tbl      => l_eam_wo_quality_tbl
2170 			 , p_eam_meter_reading_tbl   => l_eam_meter_reading_tbl
2171 			 , p_eam_counter_prop_tbl    => l_eam_counter_prop_tbl
2172 			 , p_eam_wo_comp_rebuild_tbl => l_eam_wo_comp_rebuild_tbl
2173 			 , p_eam_wo_comp_mr_read_tbl => l_eam_wo_comp_mr_read_tbl
2174 			 , p_eam_op_comp_tbl         => l_eam_op_comp_tbl
2175 			 , p_eam_request_tbl         =>	l_eam_request_tbl
2176   		         , x_eam_wo_rec              => l_out_eam_wo_rec
2177   		         , x_eam_op_tbl              => l_out_eam_op_tbl
2178   		         , x_eam_op_network_tbl      => l_out_eam_op_network_tbl
2179   		         , x_eam_res_tbl             => l_out_eam_res_tbl
2180   		         , x_eam_res_inst_tbl        => l_out_eam_res_inst_tbl
2181   		         , x_eam_sub_res_tbl         => l_out_eam_sub_res_tbl
2182   		         , x_eam_res_usage_tbl       => l_out_eam_res_usage_tbl
2183   		         , x_eam_mat_req_tbl         => l_out_eam_mat_req_tbl
2184                          , x_eam_direct_items_tbl    => l_out_eam_di_tbl
2185 			 , x_eam_wo_comp_rec         => l_out_eam_wo_comp_rec
2186 			 , x_eam_wo_quality_tbl      => l_out_eam_wo_quality_tbl
2187 			 , x_eam_meter_reading_tbl   => l_out_eam_meter_reading_tbl
2188 			 , x_eam_counter_prop_tbl    => l_out_eam_counter_prop_tbl
2189 			 , x_eam_wo_comp_rebuild_tbl => l_out_eam_wo_comp_rebuild_tbl
2190 			 , x_eam_wo_comp_mr_read_tbl => l_out_eam_wo_comp_mr_read_tbl
2191 			 , x_eam_op_comp_tbl         => l_out_eam_op_comp_tbl
2192 			 , x_eam_request_tbl      =>	l_out_eam_request_tbl
2193   		         , x_return_status           => x_return_status
2194   		         , x_msg_count               => x_msg_count
2195   		         , p_debug                   =>  NVL(fnd_profile.value('EAM_DEBUG'), 'N')
2196   		         , p_debug_filename          => 'insertwor.log'
2197   		         , p_output_dir              => l_output_dir
2198                          , p_debug_file_mode         => 'w'
2199                        );
2200 
2201 
2202 	else
2203 		x_return_status :='MODE_DOES_NOT_EXIST';
2204 	end if;-- end of insertion and updation
2205 	x_update_status := l_update_status;
2206 
2207 
2208          -- End of API body.
2209                    -- Standard check of p_commit.
2210                    IF fnd_api.to_boolean(p_commit)
2211 		       and x_return_status = 'S' THEN
2212                       COMMIT WORK;
2213                    END IF;
2214 
2215 		   IF(x_return_status <> 'S') THEN   --added for 3817679
2216 		       ROLLBACK TO get_insert_into_wor_pvt;
2217 		   END IF;
2218 
2219 
2220                    l_stmt_num    := 999;
2221                    -- Standard call to get message count and if count is 1, get message info.
2222                    fnd_msg_pub.count_and_get(
2223                       p_count => x_msg_count
2224                      ,p_data => x_msg_data);
2225                 EXCEPTION
2226                    WHEN fnd_api.g_exc_error THEN
2227                       ROLLBACK TO get_insert_into_wor_pvt;
2228                       x_return_status := fnd_api.g_ret_sts_error;
2229                       fnd_msg_pub.count_and_get(
2230              --            p_encoded => FND_API.g_false
2231                          p_count => x_msg_count
2232                         ,p_data => x_msg_data);
2233 
2234                    WHEN fnd_api.g_exc_unexpected_error THEN
2235                       ROLLBACK TO get_insert_into_wor_pvt;
2236                       x_return_status := fnd_api.g_ret_sts_unexp_error;
2237 
2238                       fnd_msg_pub.count_and_get(
2239                          p_count => x_msg_count
2240                         ,p_data => x_msg_data);
2241 
2242                    WHEN OTHERS THEN
2243                       ROLLBACK TO get_insert_into_wor_pvt;
2244                       x_return_status := fnd_api.g_ret_sts_unexp_error;
2245                       IF fnd_msg_pub.check_msg_level(
2246                             fnd_msg_pub.g_msg_lvl_unexp_error) THEN
2247                          fnd_msg_pub.add_exc_msg(g_pkg_name, l_api_name);
2248                       END IF;
2249 
2250                       fnd_msg_pub.count_and_get(
2251                          p_count => x_msg_count
2252                         ,p_data => x_msg_data);
2253 
2254 
2255 
2256   END insert_into_wor;
2257 
2258 
2259 
2260 
2261    -- API to validate entries in Material Page
2262 
2263     PROCEDURE material_validate (
2264             p_organization_id      IN       NUMBER
2265            ,p_wip_entity_id        IN       NUMBER
2266            ,p_description          IN       VARCHAR2
2267            ,p_uom                  IN       VARCHAR2
2268            ,p_concatenated_segments IN      VARCHAR2
2269   	     ,p_operation_seq_num     IN      VARCHAR2
2270   	     ,p_department_code       IN      VARCHAR2
2271   	     ,p_supply                IN      VARCHAR2
2272            ,p_subinventory_code     IN      VARCHAR2
2273            ,p_locator               IN      VARCHAR2
2274   	     ,x_invalid_asset		  OUT NOCOPY     NUMBER
2275   	     ,x_invalid_description     OUT NOCOPY     NUMBER
2276   	     ,x_invalid_uom             OUT NOCOPY     NUMBER
2277   	     ,x_invalid_subinventory    OUT NOCOPY     NUMBER
2278     	     ,x_invalid_locator         OUT NOCOPY     NUMBER
2279   	     ,x_invalid_department      OUT NOCOPY     NUMBER
2280   	     ,x_invalid_operation       OUT NOCOPY     NUMBER
2281   	     ,x_invalid_supply          OUT NOCOPY     NUMBER
2282            )
2283 
2284          IS
2285 
2286            l_concatenated_segments   VARCHAR2(2000);
2287            l_organization_id         NUMBER;
2288   	     l_description             VARCHAR2(240);
2289            l_uom                     VARCHAR2(30);
2290   	     l_operation_seq_num       NUMBER;
2291   	     l_department_code         VARCHAR2(80);
2292   	     l_supply                  VARCHAR2(80);
2293   	     l_subinventory 	   VARCHAR2(80);
2294            l_on_hand_quantity        NUMBER;
2295   	     l_locator                 VARCHAR2(2000);
2296            l_stmt_num                NUMBER:= 0;
2297 
2298            invalid_uom               NUMBER := 0;
2299            invalid_description       NUMBER := 0;
2300   	     invalid_asset             NUMBER := 0;
2301            material_exists           NUMBER := 1;
2302   	     description_exists        NUMBER := 1;
2303   	     uom_exists                NUMBER := 1;
2304 
2305            subinventory_exists       NUMBER := 1;
2306            locator_exists            NUMBER := 1;
2307   	     invalid_subinventory      NUMBER := 0;
2308            invalid_locator           NUMBER := 0;
2309 
2310   	     invalid_department        NUMBER := 0;
2311   	     invalid_operation         NUMBER := 0;
2312   	     operation_exists          NUMBER := 1;
2313   	     department_exists         NUMBER := 1;
2314 
2315   	     supply_exists             NUMBER := 1;
2316            invalid_supply            NUMBER := 0;
2317            constant_yes          VARCHAR2(1) := 'Y';
2318            constant_supply_type    VARCHAR2(30) := 'WIP_SUPPLY';
2319 
2320 
2321 
2322             TYPE CUR_TYP is ref cursor;
2323 
2324            CURSOR c_supply_cur IS  --rhshriva
2325 	    select meaning
2326 	    from mfg_lookups
2327 	    where lookup_type = g_supply_type
2328 	     and (lookup_code = 1 or  lookup_code = 4) ;
2329 
2330 	 CURSOR c_subinv_cur IS  --rhshriva
2331 	 select msinv.secondary_inventory_name,
2332 			     SUM(moq.transaction_quantity) on_hand_quantity
2333 
2334 	      from mtl_secondary_inventories msinv, mtl_onhand_quantities moq
2335 	      where  moq.organization_id=msinv.organization_id
2336 		      and nvl(msinv.disable_date, sysdate+2) > sysdate
2337 		     and moq.subinventory_code = msinv.secondary_inventory_name
2338 		     and msinv.organization_id = p_organization_id
2339 		     and moq.inventory_item_id = (select inventory_item_id from mtl_system_items_kfv
2340 		     where organization_id = p_organization_id
2341 		     and concatenated_segments =p_concatenated_segments)
2342 	      group by msinv.secondary_inventory_name, moq.inventory_item_id, msinv.organization_id, msinv.description, msinv.locator_type
2343 		     order by msinv.secondary_inventory_name;
2344 
2345 
2346            CURSOR  c_locator_cur  IS   --rhshriva
2347            select concatenated_segments
2348             from mtl_item_locations_kfv
2349             where (disable_date > sysdate or disable_date is null)
2350             and organization_id = p_organization_id
2351             and subinventory_code = p_subinventory_code ;
2352 
2353 
2354 
2355 
2356            BEGIN
2357 
2358             -- API body
2359 
2360             l_organization_id := p_organization_id;
2361 
2362             l_stmt_num := 60;
2363 
2364   	if (material_exists = 1) then
2365 
2366            invalid_asset := 1;
2367 
2368   	end if;
2369 
2370   	if (description_exists = 1) then
2371 
2372   	   invalid_description := 1;
2373 
2374           end if;
2375 
2376   	if (uom_exists = 1) then
2377 
2378   	    invalid_uom := 1;
2379 
2380   	end if;
2381 
2382 
2383           l_stmt_num := 70;
2384 
2385 
2386        -- Check whether the operation is valid and matches with assigned department
2387        /* Commenting out the validation on  department as it is present in WO API */
2388   	   l_stmt_num := 80;
2389 
2390        -- Check Supply Type
2391        /* Commenting out the validation on supply type as it is present in WO API */
2392        l_stmt_num := 90;
2393 
2394 
2395        -- Check for Subinventory
2396   	 if (p_subinventory_code is not null) then
2397 
2398             open c_subinv_cur ;
2399            l_stmt_num := 95;
2400 
2401            loop
2402            fetch c_subinv_cur into l_subinventory, l_on_hand_quantity;
2403            EXIT WHEN c_subinv_cur%NOTFOUND;
2404 
2405   		if (l_subinventory = p_subinventory_code) then
2406   			subinventory_exists := 0;
2407   	        end if;
2408 
2409            end loop;
2410            close c_subinv_cur;
2411 
2412            if (subinventory_exists = 1) then
2413               invalid_subinventory := 1;
2414            end if;
2415 
2416           end if ;  -- end of p_subinventory not null
2417 
2418   	 l_stmt_num := 100;
2419 
2420 
2421            -- Check for Locator
2422 
2423 
2424   	if (p_locator is not null) then
2425 
2426            open c_locator_cur ;
2427   	  l_stmt_num := 105;
2428 
2429             loop
2430             fetch c_locator_cur into l_concatenated_segments;
2431             EXIT WHEN c_locator_cur%NOTFOUND;
2432 
2433 
2434                   if (l_concatenated_segments = p_locator) then
2435 
2436   	            locator_exists := 0;
2437 
2438   	        end if;
2439 
2440             end loop;
2441             close c_locator_cur;
2442 
2443             if (locator_exists = 1) then
2444 
2445                invalid_locator := 1;
2446 
2447             end if;
2448 
2449   	end if;  -- end of check for p_locator
2450 
2451 
2452 
2453            l_stmt_num := 110;
2454 
2455            x_invalid_asset  := invalid_asset;
2456   	     x_invalid_description  := invalid_description;
2457   	     x_invalid_uom     := invalid_uom;
2458   	     x_invalid_subinventory := invalid_subinventory;
2459     	     x_invalid_locator  := invalid_locator;
2460   	     x_invalid_department := invalid_department;
2461   	     x_invalid_operation := invalid_operation;
2462   	     x_invalid_supply := invalid_supply;
2463 
2464 
2465          END material_validate;
2466 
2467 
2468 
2469          --- Insert into WRO
2470 
2471 
2472    PROCEDURE insert_into_wro(
2473                    p_api_version        IN       NUMBER
2474                   ,p_init_msg_list      IN       VARCHAR2 := fnd_api.g_false
2475                   ,p_commit             IN       VARCHAR2 := fnd_api.g_false
2476                   ,p_validation_level   IN       NUMBER   := fnd_api.g_valid_level_full
2477                   ,p_wip_entity_id      IN       NUMBER
2478                   ,p_organization_id    IN       NUMBER
2479   		,p_concatenated_segments  IN   VARCHAR2
2480   	 	,p_description            IN   VARCHAR2
2481                   ,p_operation_seq_num    IN     NUMBER
2482    		,p_supply             	IN     VARCHAR2
2483   		,p_required_date        IN     DATE
2484   		,p_quantity            IN      NUMBER
2485   		,p_comments            IN      VARCHAR2
2486   		,p_supply_subinventory  IN     VARCHAR2
2487   		,p_locator 		IN     VARCHAR2
2488   		,p_mrp_net_flag         IN     VARCHAR2
2489   		,p_material_release     IN     VARCHAR2
2490   		,x_invalid_update_operation  OUT NOCOPY  NUMBER
2491   		,x_invalid_update_department OUT NOCOPY  NUMBER
2492   		,x_invalid_update_description OUT NOCOPY NUMBER
2493                           ,x_return_status      OUT NOCOPY      VARCHAR2
2494                   ,x_msg_count          OUT NOCOPY      NUMBER
2495                   ,x_msg_data           OUT NOCOPY      VARCHAR2
2496                   ,x_update_status        OUT NOCOPY   NUMBER
2497 				  ,p_supply_code          IN     NUMBER :=NULL
2498   				  ,p_one_step_issue       IN   varchar2:=fnd_api.g_false
2499 				  ,p_released_quantity     IN    NUMBER := NULL)
2500 
2501                 IS
2502                    l_api_name       CONSTANT VARCHAR2(30) := 'insert_into_wro';
2503                    l_api_version    CONSTANT NUMBER       := 1.0;
2504                    l_full_name      CONSTANT VARCHAR2(60)   := g_pkg_name || '.' || l_api_name;
2505 
2506   		   l_stmt_num                   NUMBER;
2507   		   l_wip_entity_id              NUMBER;
2508   		   l_inventory_item_id          NUMBER;
2509   		   l_department_id              NUMBER;
2510   		   l_supply                     NUMBER;
2511   		   l_locator                    NUMBER;
2512   		   l_mrp_net_flag               NUMBER;
2513   		   l_material_release           VARCHAR2(1);
2514   		   l_material_exists            NUMBER := 0;
2515                    l_existing_operation         NUMBER;
2516                    l_existing_department        NUMBER;
2517                    l_existing_description       VARCHAR2(240);
2518                    l_req_qty                    NUMBER := 0;
2519                    l_status_type                NUMBER := 0;
2520                    l_material_issue_by_mo       VARCHAR2(1);
2521                    l_auto_request_material      VARCHAR2(1);
2522   		   invalid_update_operation     NUMBER := 0;
2523                    invalid_update_department    NUMBER := 0;
2524   		   invalid_update_description   NUMBER := 0;
2525                    l_update_status              NUMBER := 0;
2526                    l_return_status              NUMBER := 0;
2527                    l_msg_count                  NUMBER := 0;
2528                    l_msg_data                   VARCHAR2(2000) ;
2529                    l_return_status1             VARCHAR2(30) ;
2530 		   l_material_issue_by_mo_temp       VARCHAR2(1) ;
2531 				   l_wo_changed                 BOOLEAN := FALSE;
2532 
2533 
2534 
2535 		   l_eam_wo_rec EAM_PROCESS_WO_PUB.eam_wo_rec_type;
2536                    l_eam_mat_req_rec  EAM_PROCESS_WO_PUB.eam_mat_req_rec_type;
2537 		   l_eam_op_tbl  EAM_PROCESS_WO_PUB.eam_op_tbl_type;
2538                    l_eam_op_network_tbl  EAM_PROCESS_WO_PUB.eam_op_network_tbl_type;
2539                    l_eam_res_tbl  EAM_PROCESS_WO_PUB.eam_res_tbl_type;
2540                    l_eam_res_inst_tbl  EAM_PROCESS_WO_PUB.eam_res_inst_tbl_type;
2541                    l_eam_sub_res_tbl   EAM_PROCESS_WO_PUB.eam_sub_res_tbl_type;
2542                    l_eam_res_usage_tbl  EAM_PROCESS_WO_PUB.eam_res_usage_tbl_type;
2543                    l_eam_mat_req_tbl   EAM_PROCESS_WO_PUB.eam_mat_req_tbl_type;
2544                    l_eam_di_tbl   EAM_PROCESS_WO_PUB.eam_direct_items_tbl_type;
2545 		   l_eam_wo_comp_rec               EAM_PROCESS_WO_PUB.eam_wo_comp_rec_type;
2546 		   l_eam_wo_quality_tbl            EAM_PROCESS_WO_PUB.eam_wo_quality_tbl_type;
2547 		   l_eam_meter_reading_tbl         EAM_PROCESS_WO_PUB.eam_meter_reading_tbl_type;
2548 		   l_eam_wo_comp_rebuild_tbl       EAM_PROCESS_WO_PUB.eam_wo_comp_rebuild_tbl_type;
2549 		   l_eam_wo_comp_mr_read_tbl       EAM_PROCESS_WO_PUB.eam_wo_comp_mr_read_tbl_type;
2550 		   l_eam_op_comp_tbl               EAM_PROCESS_WO_PUB.eam_op_comp_tbl_type;
2551 		   l_eam_request_tbl               EAM_PROCESS_WO_PUB.eam_request_tbl_type;
2552 		   l_eam_counter_prop_tbl     EAM_PROCESS_WO_PUB.eam_counter_prop_tbl_type;
2553 
2554 		   l_out_eam_wo_rec EAM_PROCESS_WO_PUB.eam_wo_rec_type;
2555                    l_out_eam_op_tbl  EAM_PROCESS_WO_PUB.eam_op_tbl_type;
2556                    l_out_eam_op_network_tbl  EAM_PROCESS_WO_PUB.eam_op_network_tbl_type;
2557                    l_out_eam_res_tbl  EAM_PROCESS_WO_PUB.eam_res_tbl_type;
2558                    l_out_eam_res_inst_tbl  EAM_PROCESS_WO_PUB.eam_res_inst_tbl_type;
2559                    l_out_eam_sub_res_tbl   EAM_PROCESS_WO_PUB.eam_sub_res_tbl_type;
2560                    l_out_eam_res_usage_tbl  EAM_PROCESS_WO_PUB.eam_res_usage_tbl_type;
2561                    l_out_eam_mat_req_tbl   EAM_PROCESS_WO_PUB.eam_mat_req_tbl_type;
2562                    l_out_eam_di_tbl   EAM_PROCESS_WO_PUB.eam_direct_items_tbl_type;
2563 		   l_out_eam_wo_comp_rec           EAM_PROCESS_WO_PUB.eam_wo_comp_rec_type;
2564 		   l_out_eam_wo_quality_tbl        EAM_PROCESS_WO_PUB.eam_wo_quality_tbl_type;
2565 		   l_out_eam_meter_reading_tbl     EAM_PROCESS_WO_PUB.eam_meter_reading_tbl_type;
2566 		   l_out_eam_wo_comp_rebuild_tbl   EAM_PROCESS_WO_PUB.eam_wo_comp_rebuild_tbl_type;
2567 		   l_out_eam_wo_comp_mr_read_tbl   EAM_PROCESS_WO_PUB.eam_wo_comp_mr_read_tbl_type;
2568 		   l_out_eam_op_comp_tbl           EAM_PROCESS_WO_PUB.eam_op_comp_tbl_type;
2569 		   l_out_eam_request_tbl           EAM_PROCESS_WO_PUB.eam_request_tbl_type;
2570 		   l_out_eam_counter_prop_tbl    EAM_PROCESS_WO_PUB.eam_counter_prop_tbl_type;
2571 
2572 		   l_output_dir   VARCHAR2(512);
2573 
2574            BEGIN
2575                    -- Standard Start of API savepoint
2576                    l_stmt_num    := 10;
2577                    SAVEPOINT get_insert_into_wro_pvt;
2578 
2579                    l_stmt_num    := 20;
2580                    -- Standard call to check for call compatibility.
2581                    IF NOT fnd_api.compatible_api_call(
2582                          l_api_version
2583                         ,p_api_version
2584                         ,l_api_name
2585                         ,g_pkg_name) THEN
2586                       RAISE fnd_api.g_exc_unexpected_error;
2587                    END IF;
2588 
2589                    l_stmt_num    := 30;
2590                    -- Initialize message list if p_init_msg_list is set to TRUE.
2591                    IF fnd_api.to_boolean(p_init_msg_list) THEN
2592                       fnd_msg_pub.initialize;
2593                    END IF;
2594 
2595                    l_stmt_num    := 40;
2596                    --  Initialize API return status to success
2597                    x_return_status := fnd_api.g_ret_sts_success;
2598 
2599                    l_stmt_num    := 50;
2600                    -- API body
2601 
2602  EAM_WORKORDER_UTIL_PKG.log_path(l_output_dir);
2603 
2604 
2605   	l_wip_entity_id := p_wip_entity_id ;
2606 
2607           -- Get Inventory Item Id
2608           select inventory_item_id
2609           into l_inventory_item_id
2610           from mtl_system_items_kfv
2611           where concatenated_segments = p_concatenated_segments
2612           and organization_id = p_organization_id;
2613 
2614           begin
2615 
2616   	select 1, wro.operation_seq_num,wro.department_id,msikfv.description
2617           into l_material_exists, l_existing_operation, l_existing_department, l_existing_description
2618           from wip_requirement_operations wro, mtl_system_items_kfv msikfv
2619           where wro.inventory_item_id = l_inventory_item_id
2620           and  wro.organization_id = p_organization_id
2621   	and  wro.wip_entity_id = p_wip_entity_id
2622           and  wro.organization_id = msikfv.organization_id
2623 	  and wro.operation_seq_num = p_operation_seq_num
2624   	and  wro.inventory_item_id = msikfv.inventory_item_id;
2625 
2626   	exception
2627   	when others then
2628   	  null;
2629   	end;
2630 
2631           -- Get Department Id
2632           select department_id
2633           into l_department_id
2634   	from wip_operations
2635   	where wip_entity_id = l_wip_entity_id
2636           and operation_seq_num = p_operation_seq_num
2637   	and organization_id = p_organization_id;
2638 
2639          -- Get Supply TYpe
2640        if(p_supply is not null) then
2641           select lookup_code
2642   	      into l_supply
2643           from mfg_lookups
2644           where lookup_type = g_supply_type
2645           and meaning = p_supply;
2646         else
2647 		  l_supply := p_supply_code;
2648 		end if;
2649   	-- Get Locator Id
2650           if (p_locator is not null) then
2651 
2652   	select inventory_location_id
2653           into l_locator
2654   	from mtl_item_locations_kfv
2655   	where organization_id = p_organization_id
2656   	and concatenated_segments = p_locator
2657   	and subinventory_code = p_supply_subinventory ;
2658 
2659   	end if;
2660   	-- Get MRP Net Flag
2661 
2662   	if (p_mrp_net_flag is not null) then
2663              l_mrp_net_flag := 1;
2664   	else
2665   	  l_mrp_net_flag := 2;
2666   	end if;
2667 
2668   	if (p_material_release is null) then
2669   	  l_material_release := 'N';
2670         else
2671           if upper(p_material_release) = 'ON' then
2672             l_material_release := 'Y';
2673           else
2674             l_material_release := 'N';
2675           end if;
2676   	end if;
2677 
2678 /* To avoid the material allocation from the WO API
2679 ** for OneStep Issue page since allocation api will
2680 ** be called seperatly.
2681 */
2682 if(p_one_step_issue = fnd_api.g_true) then
2683   l_wo_changed := TRUE;
2684    select material_issue_by_mo into l_material_issue_by_mo_temp
2685      from wip_discrete_jobs
2686      where
2687      wip_entity_id = p_wip_entity_id and
2688 	 organization_id = p_organization_id;
2689    update wip_discrete_jobs set material_issue_by_mo='N'
2690    where
2691      wip_entity_id = p_wip_entity_id and
2692 	 organization_id = p_organization_id;
2693 end if; -- end of p_one_step_issue check
2694 
2695 
2696         IF (l_material_exists = 1) THEN
2697 
2698   	   if (l_existing_operation <> p_operation_seq_num) then
2699   		invalid_update_operation := 1;
2700              end if;
2701 
2702   	    if (l_existing_department <> l_department_id ) then
2703   		invalid_update_department := 1;
2704              end if;
2705 
2706              if (l_existing_description <> p_description) then
2707   		invalid_update_description := 1;
2708   	     end if;
2709 
2710 
2711   	    if ((invalid_update_operation = 0) and (invalid_update_department = 0)
2712                and (invalid_update_description = 0)) then
2713 
2714 	        l_eam_mat_req_rec.transaction_type := EAM_PROCESS_WO_PUB.G_OPR_UPDATE;
2715                 l_eam_mat_req_rec.wip_entity_id := p_wip_entity_id;
2716                 l_eam_mat_req_rec.organization_id := p_organization_id;
2717                 l_eam_mat_req_rec.operation_seq_num := p_operation_seq_num;
2718                 l_eam_mat_req_rec.inventory_item_id := l_inventory_item_id;
2719                 l_eam_mat_req_rec.quantity_per_assembly := p_quantity;
2720                 l_eam_mat_req_rec.department_id := l_department_id;
2721 		l_eam_mat_req_rec.wip_supply_type := l_supply;
2722 		l_eam_mat_req_rec.date_required := p_required_date;
2723 		l_eam_mat_req_rec.required_quantity := p_quantity;
2724 		l_eam_mat_req_rec.supply_subinventory := p_supply_subinventory;
2725                 l_eam_mat_req_rec.supply_locator_id := l_locator;
2726 		l_eam_mat_req_rec.mrp_net_flag := l_mrp_net_flag;
2727 		l_eam_mat_req_rec.comments := p_comments;
2728 
2729 
2730     		l_eam_mat_req_tbl(1) := l_eam_mat_req_rec;
2731 
2732 		 EAM_PROCESS_WO_PUB.Process_WO
2733   		         ( p_bo_identifier           => 'EAM'
2734   		         , p_init_msg_list           => TRUE
2735   		         , p_api_version_number      => 1.0
2736                          , p_commit                  => 'N'
2737   		         , p_eam_wo_rec              => l_eam_wo_rec
2738   		         , p_eam_op_tbl              => l_eam_op_tbl
2739   		         , p_eam_op_network_tbl      => l_eam_op_network_tbl
2740   		         , p_eam_res_tbl             => l_eam_res_tbl
2741   		         , p_eam_res_inst_tbl        => l_eam_res_inst_tbl
2742   		         , p_eam_sub_res_tbl         => l_eam_sub_res_tbl
2743   		         , p_eam_res_usage_tbl       => l_eam_res_usage_tbl
2744   		         , p_eam_mat_req_tbl         => l_eam_mat_req_tbl
2745                          , p_eam_direct_items_tbl    => l_eam_di_tbl
2746 			 , p_eam_wo_comp_rec         => l_eam_wo_comp_rec
2747 			 , p_eam_wo_quality_tbl      => l_eam_wo_quality_tbl
2748 			 , p_eam_meter_reading_tbl   => l_eam_meter_reading_tbl
2749 			 , p_eam_counter_prop_tbl    => l_eam_counter_prop_tbl
2750 			 , p_eam_wo_comp_rebuild_tbl => l_eam_wo_comp_rebuild_tbl
2751 			 , p_eam_wo_comp_mr_read_tbl => l_eam_wo_comp_mr_read_tbl
2752 			 , p_eam_op_comp_tbl         => l_eam_op_comp_tbl
2753 			 , p_eam_request_tbl        =>	l_eam_request_tbl
2754   		         , x_eam_wo_rec              => l_out_eam_wo_rec
2755   		         , x_eam_op_tbl              => l_out_eam_op_tbl
2756   		         , x_eam_op_network_tbl      => l_out_eam_op_network_tbl
2757   		         , x_eam_res_tbl             => l_out_eam_res_tbl
2758   		         , x_eam_res_inst_tbl        => l_out_eam_res_inst_tbl
2759   		         , x_eam_sub_res_tbl         => l_out_eam_sub_res_tbl
2760   		         , x_eam_res_usage_tbl       => l_out_eam_res_usage_tbl
2761   		         , x_eam_mat_req_tbl         => l_out_eam_mat_req_tbl
2762                          , x_eam_direct_items_tbl    => l_out_eam_di_tbl
2763 			 , x_eam_wo_comp_rec         => l_out_eam_wo_comp_rec
2764 			 , x_eam_wo_quality_tbl      => l_out_eam_wo_quality_tbl
2765 			 , x_eam_meter_reading_tbl   => l_out_eam_meter_reading_tbl
2766 			 , x_eam_counter_prop_tbl    => l_out_eam_counter_prop_tbl
2767 			 , x_eam_wo_comp_rebuild_tbl => l_out_eam_wo_comp_rebuild_tbl
2768 			 , x_eam_wo_comp_mr_read_tbl => l_out_eam_wo_comp_mr_read_tbl
2769 			 , x_eam_op_comp_tbl         => l_out_eam_op_comp_tbl
2770 			 , x_eam_request_tbl     => l_out_eam_request_tbl
2771   		         , x_return_status           => x_return_status
2772   		         , x_msg_count               => x_msg_count
2773   		         , p_debug                   =>  NVL(fnd_profile.value('EAM_DEBUG'), 'N')
2774   		         , p_debug_filename          => 'updatewro.log'
2775   		         , p_output_dir              => l_output_dir
2776                          , p_debug_file_mode         => 'w'
2777                        );
2778                  l_update_status := 1;
2779 
2780 
2781            end if;
2782 
2783       ELSE
2784 
2785          -- If entry does not exists in WIP_REQUIREMENT_OPERATIONS then place a new
2786          -- entry into WIP_REQUIREMENT_OPERATIONS
2787 
2788 		l_eam_mat_req_rec.transaction_type := EAM_PROCESS_WO_PUB.G_OPR_CREATE;
2789                 l_eam_mat_req_rec.wip_entity_id := p_wip_entity_id;
2790                 l_eam_mat_req_rec.organization_id := p_organization_id;
2791                 l_eam_mat_req_rec.operation_seq_num := p_operation_seq_num;
2792                 l_eam_mat_req_rec.inventory_item_id := l_inventory_item_id;
2793                 l_eam_mat_req_rec.quantity_per_assembly := p_quantity;
2794                 l_eam_mat_req_rec.department_id := l_department_id;
2795 		l_eam_mat_req_rec.wip_supply_type := l_supply;
2796 		l_eam_mat_req_rec.date_required := p_required_date;
2797 		l_eam_mat_req_rec.required_quantity := p_quantity;
2798 		l_eam_mat_req_rec.supply_subinventory := p_supply_subinventory;
2799                 l_eam_mat_req_rec.supply_locator_id := l_locator;
2800 		l_eam_mat_req_rec.mrp_net_flag := l_mrp_net_flag;
2801 		l_eam_mat_req_rec.comments := p_comments;
2802 	        l_eam_mat_req_rec.released_quantity   := p_released_quantity;
2803 
2804     		l_eam_mat_req_tbl(1) := l_eam_mat_req_rec;
2805 
2806 
2807 		 EAM_PROCESS_WO_PUB.Process_WO
2808   		         ( p_bo_identifier           => 'EAM'
2809   		         , p_init_msg_list           => TRUE
2810   		         , p_api_version_number      => 1.0
2811                          , p_commit                  => 'N'
2812   		         , p_eam_wo_rec              => l_eam_wo_rec
2813   		         , p_eam_op_tbl              => l_eam_op_tbl
2814   		         , p_eam_op_network_tbl      => l_eam_op_network_tbl
2815   		         , p_eam_res_tbl             => l_eam_res_tbl
2816   		         , p_eam_res_inst_tbl        => l_eam_res_inst_tbl
2817   		         , p_eam_sub_res_tbl         => l_eam_sub_res_tbl
2818   		         , p_eam_res_usage_tbl       => l_eam_res_usage_tbl
2819   		         , p_eam_mat_req_tbl         => l_eam_mat_req_tbl
2820                          , p_eam_direct_items_tbl    => l_eam_di_tbl
2821 			 , p_eam_wo_comp_rec         => l_eam_wo_comp_rec
2822 			 , p_eam_wo_quality_tbl      => l_eam_wo_quality_tbl
2823 			 , p_eam_meter_reading_tbl   => l_eam_meter_reading_tbl
2824 			 , p_eam_counter_prop_tbl    => l_eam_counter_prop_tbl
2825 			 , p_eam_wo_comp_rebuild_tbl => l_eam_wo_comp_rebuild_tbl
2826 			 , p_eam_wo_comp_mr_read_tbl => l_eam_wo_comp_mr_read_tbl
2827 			 , p_eam_op_comp_tbl         => l_eam_op_comp_tbl
2828 			 , p_eam_request_tbl        =>	l_eam_request_tbl
2829   		         , x_eam_wo_rec              => l_out_eam_wo_rec
2830   		         , x_eam_op_tbl              => l_out_eam_op_tbl
2831   		         , x_eam_op_network_tbl      => l_out_eam_op_network_tbl
2832   		         , x_eam_res_tbl             => l_out_eam_res_tbl
2833   		         , x_eam_res_inst_tbl        => l_out_eam_res_inst_tbl
2834   		         , x_eam_sub_res_tbl         => l_out_eam_sub_res_tbl
2835   		         , x_eam_res_usage_tbl       => l_out_eam_res_usage_tbl
2836   		         , x_eam_mat_req_tbl         => l_out_eam_mat_req_tbl
2837                          , x_eam_direct_items_tbl    => l_out_eam_di_tbl
2838 			 , x_eam_wo_comp_rec         => l_out_eam_wo_comp_rec
2839 			 , x_eam_wo_quality_tbl      => l_out_eam_wo_quality_tbl
2840 			 , x_eam_meter_reading_tbl   => l_out_eam_meter_reading_tbl
2841 			 , x_eam_counter_prop_tbl    => l_out_eam_counter_prop_tbl
2842 			 , x_eam_wo_comp_rebuild_tbl => l_out_eam_wo_comp_rebuild_tbl
2843 			 , x_eam_wo_comp_mr_read_tbl => l_out_eam_wo_comp_mr_read_tbl
2844 			 , x_eam_op_comp_tbl         => l_out_eam_op_comp_tbl
2845 			 , x_eam_request_tbl      =>	l_out_eam_request_tbl
2846   		         , x_return_status           => x_return_status
2847   		         , x_msg_count               => x_msg_count
2848   		         , p_debug                   =>  NVL(fnd_profile.value('EAM_DEBUG'), 'N')
2849   		         , p_debug_filename          => 'insertwro.log'
2850   		         , p_output_dir              => l_output_dir
2851                          , p_debug_file_mode         => 'w'
2852                        );
2853 
2854 
2855 
2856      END IF ;  -- Material does not exist
2857 
2858  /* To check whether the WDJ table was changed before call to WO API */
2859   if(l_wo_changed = true) then
2860    update wip_discrete_jobs set material_issue_by_mo=l_material_issue_by_mo_temp
2861    where
2862      wip_entity_id = p_wip_entity_id and
2863 	 organization_id = p_organization_id;
2864   end if; -- end of l_wo_changed check
2865 
2866       x_invalid_update_operation  := invalid_update_operation ;
2867       x_invalid_update_department := invalid_update_department;
2868       x_invalid_update_description  := invalid_update_description;
2869       x_update_status := l_update_status;
2870 
2871 
2872                    -- End of API body.
2873                    -- Standard check of p_commit.
2874                    IF fnd_api.to_boolean(p_commit)
2875 		       and x_return_status = 'S' THEN
2876                       COMMIT WORK;
2877                    END IF;
2878 
2879 		   IF(x_return_status <> 'S') THEN
2880 		        ROLLBACK TO get_insert_into_wro_pvt;
2881 		   END IF;
2882 
2883                    l_stmt_num    := 999;
2884                    -- Standard call to get message count and if count is 1, get message info.
2885                    fnd_msg_pub.count_and_get(
2886                       p_count => x_msg_count
2887                      ,p_data => x_msg_data);
2888                 EXCEPTION
2889                    WHEN fnd_api.g_exc_error THEN
2890                       ROLLBACK TO get_insert_into_wro_pvt;
2891                       x_return_status := fnd_api.g_ret_sts_error;
2892                       fnd_msg_pub.count_and_get(
2893              --            p_encoded => FND_API.g_false
2894                          p_count => x_msg_count
2895                         ,p_data => x_msg_data);
2896                    WHEN fnd_api.g_exc_unexpected_error THEN
2897                       ROLLBACK TO get_insert_into_wro_pvt;
2898                       x_return_status := fnd_api.g_ret_sts_unexp_error;
2899 
2900                       fnd_msg_pub.count_and_get(
2901                          p_count => x_msg_count
2902                         ,p_data => x_msg_data);
2903                    WHEN OTHERS THEN
2904                       ROLLBACK TO get_insert_into_wro_pvt;
2905                       x_return_status := fnd_api.g_ret_sts_unexp_error;
2906                       IF fnd_msg_pub.check_msg_level(
2907                             fnd_msg_pub.g_msg_lvl_unexp_error) THEN
2908                          fnd_msg_pub.add_exc_msg(g_pkg_name, l_api_name);
2909                       END IF;
2910 
2911                       fnd_msg_pub.count_and_get(
2912                          p_count => x_msg_count
2913                         ,p_data => x_msg_data);
2914 
2915 
2916     END insert_into_wro;
2917 
2918 
2919    PROCEDURE delete_resources (
2920             p_api_version        IN       NUMBER
2921   	   ,p_init_msg_list      IN       VARCHAR2 := fnd_api.g_false
2922   	   ,p_commit             IN       VARCHAR2 := fnd_api.g_false
2923            ,p_validation_level   IN       NUMBER   := fnd_api.g_valid_level_full
2924            ,p_wip_entity_id      IN       NUMBER
2925            ,p_operation_seq_num  IN       NUMBER
2926            ,p_resource_seq_num   IN       NUMBER
2927            ,x_return_status      OUT NOCOPY      VARCHAR2
2928            ,x_msg_count          OUT NOCOPY      NUMBER
2929            ,x_msg_data           OUT NOCOPY      VARCHAR2)  IS
2930 
2931 
2932          l_api_name       CONSTANT VARCHAR2(30) := 'delete_resources';
2933   	 l_api_version    CONSTANT NUMBER       := 1.0;
2934   	 l_full_name      CONSTANT VARCHAR2(60)   := g_pkg_name || '.' || l_api_name;
2935 
2936   	   l_stmt_num       NUMBER;
2937            l_wip_entity_id  NUMBER;
2938            l_operation_seq_num  NUMBER;
2939            l_resource_seq_num   NUMBER;
2940            l_organization_id    NUMBER;
2941            l_resource_id        NUMBER;
2942            l_applied_units      NUMBER;
2943            l_exists             NUMBER := 0;
2944            l_msg_count                NUMBER;
2945            l_msg_data                 VARCHAR2(250);
2946            l_data                     VARCHAR2(250);
2947     	  l_msg_index_out            NUMBER;
2948 
2949            l_validate_st        NUMBER := 0;
2950 
2951 
2952 	   /* added for calling WO API */
2953 
2954     l_eam_wo_rec EAM_PROCESS_WO_PUB.eam_wo_rec_type;
2955     l_eam_res_rec  EAM_PROCESS_WO_PUB.eam_res_rec_type;
2956     l_eam_op_tbl  EAM_PROCESS_WO_PUB.eam_op_tbl_type;
2957     l_eam_op_network_tbl  EAM_PROCESS_WO_PUB.eam_op_network_tbl_type;
2958     l_eam_res_tbl  EAM_PROCESS_WO_PUB.eam_res_tbl_type;
2959     l_eam_res_inst_tbl  EAM_PROCESS_WO_PUB.eam_res_inst_tbl_type;
2960     l_eam_sub_res_tbl   EAM_PROCESS_WO_PUB.eam_sub_res_tbl_type;
2961     l_eam_res_usage_tbl  EAM_PROCESS_WO_PUB.eam_res_usage_tbl_type;
2962     l_eam_mat_req_tbl   EAM_PROCESS_WO_PUB.eam_mat_req_tbl_type;
2963     l_eam_di_tbl   EAM_PROCESS_WO_PUB.eam_direct_items_tbl_type;
2964     l_eam_wo_comp_rec               EAM_PROCESS_WO_PUB.eam_wo_comp_rec_type;
2965     l_eam_wo_quality_tbl            EAM_PROCESS_WO_PUB.eam_wo_quality_tbl_type;
2966     l_eam_meter_reading_tbl         EAM_PROCESS_WO_PUB.eam_meter_reading_tbl_type;
2967     l_eam_wo_comp_rebuild_tbl       EAM_PROCESS_WO_PUB.eam_wo_comp_rebuild_tbl_type;
2968     l_eam_wo_comp_mr_read_tbl       EAM_PROCESS_WO_PUB.eam_wo_comp_mr_read_tbl_type;
2969     l_eam_op_comp_tbl               EAM_PROCESS_WO_PUB.eam_op_comp_tbl_type;
2970     l_eam_request_tbl               EAM_PROCESS_WO_PUB.eam_request_tbl_type;
2971     l_eam_counter_prop_tbl     EAM_PROCESS_WO_PUB.eam_counter_prop_tbl_type;
2972 
2973     l_out_eam_wo_rec EAM_PROCESS_WO_PUB.eam_wo_rec_type;
2974     l_out_eam_op_tbl  EAM_PROCESS_WO_PUB.eam_op_tbl_type;
2975     l_out_eam_op_network_tbl  EAM_PROCESS_WO_PUB.eam_op_network_tbl_type;
2976     l_out_eam_res_tbl  EAM_PROCESS_WO_PUB.eam_res_tbl_type;
2977     l_out_eam_res_inst_tbl  EAM_PROCESS_WO_PUB.eam_res_inst_tbl_type;
2978     l_out_eam_sub_res_tbl   EAM_PROCESS_WO_PUB.eam_sub_res_tbl_type;
2979     l_out_eam_res_usage_tbl  EAM_PROCESS_WO_PUB.eam_res_usage_tbl_type;
2980     l_out_eam_mat_req_tbl   EAM_PROCESS_WO_PUB.eam_mat_req_tbl_type;
2981     l_out_eam_di_tbl   EAM_PROCESS_WO_PUB.eam_direct_items_tbl_type;
2982     l_out_eam_wo_comp_rec           EAM_PROCESS_WO_PUB.eam_wo_comp_rec_type;
2983     l_out_eam_wo_quality_tbl        EAM_PROCESS_WO_PUB.eam_wo_quality_tbl_type;
2984     l_out_eam_meter_reading_tbl     EAM_PROCESS_WO_PUB.eam_meter_reading_tbl_type;
2985     l_out_eam_wo_comp_rebuild_tbl   EAM_PROCESS_WO_PUB.eam_wo_comp_rebuild_tbl_type;
2986     l_out_eam_wo_comp_mr_read_tbl   EAM_PROCESS_WO_PUB.eam_wo_comp_mr_read_tbl_type;
2987     l_out_eam_op_comp_tbl           EAM_PROCESS_WO_PUB.eam_op_comp_tbl_type;
2988     l_out_eam_request_tbl           EAM_PROCESS_WO_PUB.eam_request_tbl_type;
2989     l_out_eam_counter_prop_tbl    EAM_PROCESS_WO_PUB.eam_counter_prop_tbl_type;
2990 
2991    l_output_dir   VARCHAR2(512);
2992 
2993    BEGIN
2994                    -- Standard Start of API savepoint
2995                    l_stmt_num    := 10;
2996                    SAVEPOINT get_delete_resources_pvt;
2997 
2998                    l_stmt_num    := 20;
2999                    -- Standard call to check for call compatibility.
3000                    IF NOT fnd_api.compatible_api_call(
3001                          l_api_version
3002                         ,p_api_version
3003                         ,l_api_name
3004                         ,g_pkg_name) THEN
3005                       RAISE fnd_api.g_exc_unexpected_error;
3006                    END IF;
3007 
3008                    l_stmt_num    := 30;
3009 
3010                    -- Initialize message list if p_init_msg_list is set to TRUE.
3011                    IF fnd_api.to_boolean(p_init_msg_list) THEN
3012                       fnd_msg_pub.initialize;
3013                    END IF;
3014 
3015                    l_stmt_num    := 40;
3016                    --  Initialize API return status to success
3017                    x_return_status := fnd_api.g_ret_sts_success;
3018 
3019                    l_stmt_num    := 50;
3020     -- API body
3021 
3022  EAM_WORKORDER_UTIL_PKG.log_path(l_output_dir);
3023 
3024 
3025     l_wip_entity_id := p_wip_entity_id;
3026     l_operation_seq_num := p_operation_seq_num;
3027     l_resource_seq_num := p_resource_seq_num;
3028     if ((l_wip_entity_id is not null) AND (l_operation_seq_num is not null) and (l_resource_seq_num is not null)) then
3029 
3030       begin
3031 
3032       select organization_id, resource_id
3033       into l_organization_id, l_resource_id
3034       from wip_operation_resources
3035       where wip_entity_id = l_wip_entity_id
3036       and operation_seq_num = l_operation_seq_num
3037       and resource_seq_num = l_resource_seq_num;
3038 
3039       exception
3040       when others then
3041       null;
3042       end;
3043 
3044    end if;
3045 
3046 
3047    if (( l_resource_id is not null) AND (l_resource_seq_num is not null) AND (l_operation_seq_num is not null)) then
3048 
3049         --check if there are any instances attached to the resource
3050         select count(*)
3051         into  l_exists
3052         from wip_op_resource_instances
3053         where wip_entity_id     = l_wip_entity_id and
3054               operation_seq_num = l_operation_seq_num and
3055               resource_seq_num  = l_resource_seq_num;
3056 
3057         if(l_exists <> 0) then
3058 
3059           l_validate_st := 1;
3060           eam_execution_jsp.add_message(p_app_short_name => 'EAM', p_msg_name => 'EAM_INSTANCES_EXIST');
3061           x_return_status := FND_API.G_RET_STS_ERROR;
3062         end if;
3063 
3064    end if;  -- End of l_resource_id is not null ........
3065 
3066     -- if validate not passed then raise error
3067        l_msg_count := FND_MSG_PUB.count_msg;
3068        IF l_msg_count = 1 THEN
3069 
3070           eam_execution_jsp.Get_Messages
3071             (p_encoded  => FND_API.G_FALSE,
3072              p_msg_index => 1,
3073              p_msg_count => l_msg_count,
3074              p_msg_data  => l_msg_data,
3075              p_data      => l_data,
3076              p_msg_index_out => l_msg_index_out);
3077              x_msg_count := l_msg_count;
3078              x_msg_data  := l_msg_data;
3079        ELSE
3080           x_msg_count  := l_msg_count;
3081        END IF;
3082 
3083        IF l_msg_count > 0 THEN
3084           x_return_status := FND_API.G_RET_STS_UNEXP_ERROR;
3085           RAISE  FND_API.G_EXC_ERROR;
3086        END IF;
3087 
3088 
3089 
3090    -- Perform delete if all the validations have passed
3091 
3092   if (l_validate_st = 0) then
3093         l_eam_res_rec.transaction_type := EAM_PROCESS_WO_PUB.G_OPR_DELETE;
3094         l_eam_res_rec.wip_entity_id :=  p_wip_entity_id;
3095         l_eam_res_rec.organization_id := l_organization_id;
3096 	l_eam_res_rec.operation_seq_num :=  p_operation_seq_num;
3097 	l_eam_res_rec.resource_seq_num :=  p_resource_seq_num;
3098 	l_eam_res_rec.resource_id := l_resource_id;
3099 
3100 	l_eam_res_tbl(1) := l_eam_res_rec ;
3101 
3102                     EAM_PROCESS_WO_PUB.Process_WO
3103   		         ( p_bo_identifier           => 'EAM'
3104   		         , p_init_msg_list           => TRUE
3105   		         , p_api_version_number      => 1.0
3106                          , p_commit                  => 'N'
3107   		         , p_eam_wo_rec              => l_eam_wo_rec
3108   		         , p_eam_op_tbl              => l_eam_op_tbl
3109   		         , p_eam_op_network_tbl      => l_eam_op_network_tbl
3110   		         , p_eam_res_tbl             => l_eam_res_tbl
3111   		         , p_eam_res_inst_tbl        => l_eam_res_inst_tbl
3112   		         , p_eam_sub_res_tbl         => l_eam_sub_res_tbl
3113   		         , p_eam_res_usage_tbl       => l_eam_res_usage_tbl
3114   		         , p_eam_mat_req_tbl         => l_eam_mat_req_tbl
3115                          , p_eam_direct_items_tbl    => l_eam_di_tbl
3116 			 , p_eam_wo_comp_rec         => l_eam_wo_comp_rec
3117 			 , p_eam_wo_quality_tbl      => l_eam_wo_quality_tbl
3118 			 , p_eam_meter_reading_tbl   => l_eam_meter_reading_tbl
3119 			 , p_eam_counter_prop_tbl    => l_eam_counter_prop_tbl
3120 			 , p_eam_wo_comp_rebuild_tbl => l_eam_wo_comp_rebuild_tbl
3121 			 , p_eam_wo_comp_mr_read_tbl => l_eam_wo_comp_mr_read_tbl
3122 			 , p_eam_op_comp_tbl         => l_eam_op_comp_tbl
3123 			 , p_eam_request_tbl        =>	l_eam_request_tbl
3124   		         , x_eam_wo_rec              => l_out_eam_wo_rec
3125   		         , x_eam_op_tbl              => l_out_eam_op_tbl
3126   		         , x_eam_op_network_tbl      => l_out_eam_op_network_tbl
3127   		         , x_eam_res_tbl             => l_out_eam_res_tbl
3128   		         , x_eam_res_inst_tbl        => l_out_eam_res_inst_tbl
3129   		         , x_eam_sub_res_tbl         => l_out_eam_sub_res_tbl
3130   		         , x_eam_res_usage_tbl       => l_out_eam_res_usage_tbl
3131   		         , x_eam_mat_req_tbl         => l_out_eam_mat_req_tbl
3132                          , x_eam_direct_items_tbl    => l_out_eam_di_tbl
3133 			 , x_eam_wo_comp_rec         => l_out_eam_wo_comp_rec
3134 			 , x_eam_wo_quality_tbl      => l_out_eam_wo_quality_tbl
3135 			 , x_eam_meter_reading_tbl   => l_out_eam_meter_reading_tbl
3136 			 , x_eam_counter_prop_tbl    => l_out_eam_counter_prop_tbl
3137 			 , x_eam_wo_comp_rebuild_tbl => l_out_eam_wo_comp_rebuild_tbl
3138 			 , x_eam_wo_comp_mr_read_tbl => l_out_eam_wo_comp_mr_read_tbl
3139 			 , x_eam_op_comp_tbl         => l_out_eam_op_comp_tbl
3140 			 , x_eam_request_tbl      =>	l_out_eam_request_tbl
3141   		         , x_return_status           => x_return_status
3142   		         , x_msg_count               => x_msg_count
3143   		         , p_debug                   => NVL(fnd_profile.value('EAM_DEBUG'), 'N')
3144   		         , p_debug_filename          => 'delwor.log'
3145   		         , p_output_dir              => l_output_dir
3146                          , p_debug_file_mode         => 'w'
3147                        );
3148 
3149    end if;
3150 
3151 
3152 
3153     -- End of API body.
3154                      -- Standard check of p_commit.
3155                      IF fnd_api.to_boolean(p_commit)
3156 		          and x_return_status = 'S' THEN
3157                         COMMIT WORK;
3158                      END IF;
3159 
3160 		     IF(x_return_status <> 'S') THEN
3161 		         ROLLBACK TO get_delete_resources_pvt;
3162 		     END IF;
3163 
3164                      l_stmt_num    := 999;
3165 
3166                      -- Standard call to get message count and if count is 1, get message info.
3167                      fnd_msg_pub.count_and_get(
3168                         p_count => x_msg_count
3169                        ,p_data => x_msg_data);
3170 
3171                   EXCEPTION
3172                      WHEN fnd_api.g_exc_error THEN
3173                         ROLLBACK TO get_delete_resources_pvt;
3174                         x_return_status := fnd_api.g_ret_sts_error;
3175                         fnd_msg_pub.count_and_get(
3176                --            p_encoded => FND_API.g_false
3177                            p_count => x_msg_count
3178                           ,p_data => x_msg_data);
3179 
3180                      WHEN fnd_api.g_exc_unexpected_error THEN
3181                         ROLLBACK TO get_delete_resources_pvt;
3182                         x_return_status := fnd_api.g_ret_sts_unexp_error;
3183 
3184                         fnd_msg_pub.count_and_get(
3185                            p_count => x_msg_count
3186                           ,p_data => x_msg_data);
3187 
3188                      WHEN OTHERS THEN
3189                         ROLLBACK TO get_delete_resources_pvt;
3190                         x_return_status := fnd_api.g_ret_sts_unexp_error;
3191                         IF fnd_msg_pub.check_msg_level(
3192                               fnd_msg_pub.g_msg_lvl_unexp_error) THEN
3193                            fnd_msg_pub.add_exc_msg(g_pkg_name, l_api_name);
3194                         END IF;
3195 
3196                         fnd_msg_pub.count_and_get(
3197                            p_count => x_msg_count
3198                           ,p_data => x_msg_data);
3199 
3200       END delete_resources;
3201 
3202 
3203    --------------------------------------------------------------------------
3204     -- Procedure to validate department
3205     -- Used in Operations Page
3206     -- Author : rethakur
3207     --------------------------------------------------------------------------
3208 
3209 procedure validate_dept (   p_wip_entity_id		 IN       NUMBER
3210                            ,p_operation_seq_num		 IN       NUMBER
3211 			   ,p_organization_id		 IN       NUMBER
3212                            ,p_department_code	         IN       VARCHAR2
3213 			   ,x_department_id		 OUT NOCOPY      NUMBER
3214                            ,x_return_status	         OUT NOCOPY      NUMBER)  IS
3215 
3216 	l_department_id    NUMBER := null;
3217 	l_return_status    NUMBER := 0;
3218 
3219 BEGIN
3220 
3221 SELECT department_id
3222   INTO l_department_id
3223   FROM BOM_DEPARTMENTS bd
3224  WHERE bd.organization_id = p_organization_id
3225    AND department_code = p_department_code
3226    AND NVL (bd.disable_date, sysdate+2) > sysdate
3227    AND NOT EXISTS
3228    (
3229    SELECT '1'
3230      FROM WIP_OPERATION_RESOURCES wor
3231     WHERE wor.organization_id = p_organization_id
3232       AND wor.wip_entity_id = p_wip_entity_id
3233       AND wor.operation_seq_num = p_operation_seq_num
3234       AND wor.resource_id not in
3235       (
3236 	SELECT bdr.resource_id
3237 	FROM BOM_DEPARTMENT_RESOURCES bdr
3238 	WHERE bdr.department_id = bd.department_id
3239       )
3240     );
3241 
3242   x_return_status := l_return_status;
3243   x_department_id := l_department_id;
3244 
3245 EXCEPTION
3246    WHEN NO_DATA_FOUND THEN
3247         l_return_status := 1;
3248         x_return_status := l_return_status ;
3249 	x_department_id := null;
3250 
3251 END validate_dept;
3252 
3253 
3254     --------------------------------------------------------------------------
3255     -- Procedure to validate shutdown type
3256     -- Used in Operations Page
3257     -- Author : rethakur
3258     --------------------------------------------------------------------------
3259 
3260 procedure validate_shutdown_type (   p_meaning                   IN       VARCHAR2
3261 				    ,x_lookup_code		 OUT NOCOPY      NUMBER
3262 				    ,x_return_status	         OUT NOCOPY      NUMBER)  IS
3263 
3264 	l_meaning	   VARCHAR2(80);
3265 	l_lookup_code      NUMBER := 0;
3266 	l_return_status    NUMBER := 0;
3267 
3268 BEGIN
3269 
3270 SELECT lookup_code
3271   INTO l_lookup_code
3272   FROM MFG_LOOKUPS
3273  WHERE lookup_type = g_shutdown_type
3274    AND meaning     = p_meaning ;
3275 
3276   x_return_status := l_return_status;
3277   x_lookup_code   := l_lookup_code;
3278 
3279 EXCEPTION
3280    WHEN NO_DATA_FOUND THEN
3281         l_return_status := 1;
3282         x_return_status := l_return_status ;
3283 	x_lookup_code   := null;
3284 
3285 END validate_shutdown_type;
3286 
3287 
3288 
3289     --------------------------------------------------------------------------
3290     -- Procedure to validate standard operation
3291     -- Used in Operations Page
3292     -- Author : rethakur
3293     --------------------------------------------------------------------------
3294 
3295 procedure validate_std_operation (   p_organization_id		 IN       NUMBER
3296 				    ,p_operation_code		 IN       VARCHAR2
3297 				    ,x_standard_operation_id	 OUT NOCOPY      NUMBER
3298 				    ,x_department_id		 OUT NOCOPY      NUMBER
3299 				    ,x_shutdown_type             OUT NOCOPY      VARCHAR2
3300 				    ,x_return_status	         OUT NOCOPY      NUMBER)  IS
3301 
3302 	l_standard_operation_id  NUMBER := null;
3303 	l_department_id		 NUMBER := null;
3304 	l_shutdown_type		 VARCHAR2(10);
3305 	l_return_status		 NUMBER := 0;
3306 
3307 BEGIN
3308 
3309 SELECT bdp.department_id, bso.standard_operation_id,
3310        bso.shutdown_type
3311   INTO l_department_id, l_standard_operation_id,
3312        l_shutdown_type
3313   FROM BOM_DEPARTMENTS bdp,
3314        BOM_STANDARD_OPERATIONS bso
3315  WHERE bso.organization_id = p_organization_id
3316    AND bso.operation_code = p_operation_code
3317    AND bso.line_id IS NULL
3318    AND NVL ( bso.operation_type, 1) = 1
3319    AND bdp.organization_id = p_organization_id
3320    AND bso.department_id = bdp.department_id
3321    AND NVL ( bdp.disable_date, sysdate + 2) > sysdate ;
3322 
3323    x_return_status	   := l_return_status;
3324    x_department_id	   := l_department_id;
3325    x_standard_operation_id := l_standard_operation_id;
3326    x_shutdown_type	   := l_shutdown_type;
3327 
3328 EXCEPTION
3329    WHEN NO_DATA_FOUND THEN
3330         l_return_status		:= 1;
3331         x_return_status		:= l_return_status ;
3332 	x_department_id         := null;
3333         x_standard_operation_id := null;
3334         x_shutdown_type	        := null;
3335 END validate_std_operation;
3336 
3337     --------------------------------------------------------------------------
3338     -- Procedure to add an operation to a work order
3339     -- Used in Operations Page
3340     -- Author : rethakur
3341     --------------------------------------------------------------------------
3342 procedure insert_into_wo (  p_wip_entity_id		 IN       NUMBER
3343                            ,p_operation_seq_num		 IN       NUMBER
3344                            ,p_standard_operation_id	 IN	  NUMBER
3345 			   ,p_organization_id		 IN       NUMBER
3346                            ,p_description		 IN       VARCHAR2
3347                            ,p_department_id	         IN       NUMBER
3348                            ,p_shutdown_type		 IN       VARCHAR2
3349 			   ,p_first_unit_start_date	 IN	  VARCHAR2
3350 			   ,p_last_unit_completion_date  IN       VARCHAR2
3351 			   ,p_duration			 IN       NUMBER
3352 			   ,p_long_description           IN       VARCHAR2 := null
3353                            ,x_return_status	         OUT NOCOPY      NUMBER
3354 			   ,x_msg_count                    OUT NOCOPY      NUMBER )  IS
3355 
3356 
3357      l_return_status              VARCHAR2(1);
3358      x_row_id			  VARCHAR2(250);
3359      l_first_unit_start_date      DATE := SYSDATE;
3360      l_last_unit_completion_date  DATE := SYSDATE;
3361      l_duration			  NUMBER := 0;
3362 
3363 
3364 
3365      /* Added for WO API */
3366 
3367     l_eam_wo_rec EAM_PROCESS_WO_PUB.eam_wo_rec_type;
3368     l_eam_op_rec  EAM_PROCESS_WO_PUB.eam_op_rec_type;
3369     l_eam_op_tbl  EAM_PROCESS_WO_PUB.eam_op_tbl_type;
3370     l_eam_op_network_tbl  EAM_PROCESS_WO_PUB.eam_op_network_tbl_type;
3371     l_eam_res_tbl  EAM_PROCESS_WO_PUB.eam_res_tbl_type;
3372     l_eam_res_inst_tbl  EAM_PROCESS_WO_PUB.eam_res_inst_tbl_type;
3373     l_eam_sub_res_tbl   EAM_PROCESS_WO_PUB.eam_sub_res_tbl_type;
3374     l_eam_res_usage_tbl  EAM_PROCESS_WO_PUB.eam_res_usage_tbl_type;
3375     l_eam_mat_req_tbl   EAM_PROCESS_WO_PUB.eam_mat_req_tbl_type;
3376     l_eam_di_tbl   EAM_PROCESS_WO_PUB.eam_direct_items_tbl_type;
3377     l_eam_wo_comp_rec               EAM_PROCESS_WO_PUB.eam_wo_comp_rec_type;
3378     l_eam_wo_quality_tbl            EAM_PROCESS_WO_PUB.eam_wo_quality_tbl_type;
3379     l_eam_meter_reading_tbl         EAM_PROCESS_WO_PUB.eam_meter_reading_tbl_type;
3380     l_eam_wo_comp_rebuild_tbl       EAM_PROCESS_WO_PUB.eam_wo_comp_rebuild_tbl_type;
3381     l_eam_wo_comp_mr_read_tbl       EAM_PROCESS_WO_PUB.eam_wo_comp_mr_read_tbl_type;
3382     l_eam_op_comp_tbl               EAM_PROCESS_WO_PUB.eam_op_comp_tbl_type;
3383     l_eam_request_tbl               EAM_PROCESS_WO_PUB.eam_request_tbl_type;
3384     l_eam_counter_prop_tbl     EAM_PROCESS_WO_PUB.eam_counter_prop_tbl_type;
3385 
3386     l_out_eam_wo_rec EAM_PROCESS_WO_PUB.eam_wo_rec_type;
3387     l_out_eam_op_tbl  EAM_PROCESS_WO_PUB.eam_op_tbl_type;
3388     l_out_eam_op_network_tbl  EAM_PROCESS_WO_PUB.eam_op_network_tbl_type;
3389     l_out_eam_res_tbl  EAM_PROCESS_WO_PUB.eam_res_tbl_type;
3390     l_out_eam_res_inst_tbl  EAM_PROCESS_WO_PUB.eam_res_inst_tbl_type;
3391     l_out_eam_sub_res_tbl   EAM_PROCESS_WO_PUB.eam_sub_res_tbl_type;
3392     l_out_eam_res_usage_tbl  EAM_PROCESS_WO_PUB.eam_res_usage_tbl_type;
3393     l_out_eam_mat_req_tbl   EAM_PROCESS_WO_PUB.eam_mat_req_tbl_type;
3394     l_out_eam_di_tbl   EAM_PROCESS_WO_PUB.eam_direct_items_tbl_type;
3395     l_out_eam_wo_comp_rec           EAM_PROCESS_WO_PUB.eam_wo_comp_rec_type;
3396     l_out_eam_wo_quality_tbl        EAM_PROCESS_WO_PUB.eam_wo_quality_tbl_type;
3397     l_out_eam_meter_reading_tbl     EAM_PROCESS_WO_PUB.eam_meter_reading_tbl_type;
3398     l_out_eam_wo_comp_rebuild_tbl   EAM_PROCESS_WO_PUB.eam_wo_comp_rebuild_tbl_type;
3399     l_out_eam_wo_comp_mr_read_tbl   EAM_PROCESS_WO_PUB.eam_wo_comp_mr_read_tbl_type;
3400     l_out_eam_op_comp_tbl           EAM_PROCESS_WO_PUB.eam_op_comp_tbl_type;
3401     l_out_eam_request_tbl           EAM_PROCESS_WO_PUB.eam_request_tbl_type;
3402     l_out_eam_counter_prop_tbl    EAM_PROCESS_WO_PUB.eam_counter_prop_tbl_type;
3403 
3404     l_output_dir  VARCHAR2(512);
3405     invalid_autochrg_exp      EXCEPTION;
3406 
3407     CURSOR chk_autocharge IS
3408 	  SELECT 1
3409 	  FROM  bom_standard_operations bso,
3410 	        bom_std_op_resources bsor
3411 	  WHERE bso.standard_operation_id = bsor.standard_operation_id
3412 	  AND   bsor.standard_operation_id = p_standard_operation_id
3413 	  AND   bso.organization_id = p_organization_id
3414 	  AND   bsor.autocharge_type NOT IN (2,3);
3415 
3416   BEGIN
3417        -- Fix for Bug 3582756
3418        SAVEPOINT label_insert_into_wo;
3419 
3420  EAM_WORKORDER_UTIL_PKG.log_path(l_output_dir);
3421 
3422 
3423     IF (p_first_unit_start_date is NOT NULL AND p_last_unit_completion_date is NOT NULL) THEN
3424       l_first_unit_start_date		:= to_date(p_first_unit_start_date,'YYYY/MM/DD HH24:MI:SS'); --,WIP_CONSTANTS.DATETIME_FMT);
3425       l_last_unit_completion_date	:= to_date(p_last_unit_completion_date,'YYYY/MM/DD HH24:MI:SS'); --,WIP_CONSTANTS.DATETIME_FMT);
3426     ELSIF ( p_last_unit_completion_date is NULL) THEN
3427       l_duration			:= p_duration/24;
3428       l_first_unit_start_date	        := to_date(p_first_unit_start_date,'YYYY/MM/DD HH24:MI:SS'); --,WIP_CONSTANTS.DATETIME_FMT);
3429       l_last_unit_completion_date	:= l_first_unit_start_date + l_duration;
3430     ELSIF ( p_first_unit_start_date is NULL) THEN
3431       l_duration			:= p_duration/24;
3432       l_last_unit_completion_date       := to_date(p_last_unit_completion_date,'YYYY/MM/DD HH24:MI:SS'); --,WIP_CONSTANTS.DATETIME_FMT);
3433       l_first_unit_start_date		:= l_last_unit_completion_date + l_duration;
3434     END IF ; /* end if of duration check if */
3435         l_eam_op_rec.transaction_type := EAM_PROCESS_WO_PUB.G_OPR_CREATE;
3436 	l_eam_op_rec.wip_entity_id := p_wip_entity_id;
3437 	l_eam_op_rec.organization_id := p_organization_id;
3438 	l_eam_op_rec.operation_seq_num := p_operation_seq_num;
3439 	l_eam_op_rec.description := p_description;
3440 	l_eam_op_rec.long_description := p_long_description;
3441 	l_eam_op_rec.shutdown_type := p_shutdown_type;
3442 	l_eam_op_rec.start_date := l_first_unit_start_date;
3443 	l_eam_op_rec.completion_date := l_last_unit_completion_date;
3444 	if ( nvl(p_standard_operation_id,0)= 0 ) then -- added OR clause for bug#3541316
3445              l_eam_op_rec.standard_operation_id := null ;
3446         else  -- added else clause for bug#3518663
3447 	    l_eam_op_rec.standard_operation_id := p_standard_operation_id;
3448 	end if;
3449         l_eam_op_rec.department_id := p_department_id;
3450 
3451 	l_eam_op_tbl(1) := l_eam_op_rec ;
3452 
3453 	 EAM_PROCESS_WO_PUB.Process_WO
3454   		         ( p_bo_identifier           => 'EAM'
3455   		         , p_init_msg_list           => TRUE
3456   		         , p_api_version_number      => 1.0
3457                          , p_commit                  => 'N'
3458   		         , p_eam_wo_rec              => l_eam_wo_rec
3459   		         , p_eam_op_tbl              => l_eam_op_tbl
3460   		         , p_eam_op_network_tbl      => l_eam_op_network_tbl
3461   		         , p_eam_res_tbl             => l_eam_res_tbl
3462   		         , p_eam_res_inst_tbl        => l_eam_res_inst_tbl
3463   		         , p_eam_sub_res_tbl         => l_eam_sub_res_tbl
3464   		         , p_eam_res_usage_tbl       => l_eam_res_usage_tbl
3465   		         , p_eam_mat_req_tbl         => l_eam_mat_req_tbl
3466                          , p_eam_direct_items_tbl    => l_eam_di_tbl
3467 			 , p_eam_wo_comp_rec         => l_eam_wo_comp_rec
3468 			 , p_eam_wo_quality_tbl      => l_eam_wo_quality_tbl
3469 			 , p_eam_meter_reading_tbl   => l_eam_meter_reading_tbl
3470 			 , p_eam_counter_prop_tbl    => l_eam_counter_prop_tbl
3471 			 , p_eam_wo_comp_rebuild_tbl => l_eam_wo_comp_rebuild_tbl
3472 			 , p_eam_wo_comp_mr_read_tbl => l_eam_wo_comp_mr_read_tbl
3473 			 , p_eam_op_comp_tbl         => l_eam_op_comp_tbl
3474 			 , p_eam_request_tbl        =>	l_eam_request_tbl
3475   		         , x_eam_wo_rec              => l_out_eam_wo_rec
3476   		         , x_eam_op_tbl              => l_out_eam_op_tbl
3477   		         , x_eam_op_network_tbl      => l_out_eam_op_network_tbl
3478   		         , x_eam_res_tbl             => l_out_eam_res_tbl
3479   		         , x_eam_res_inst_tbl        => l_out_eam_res_inst_tbl
3480   		         , x_eam_sub_res_tbl         => l_out_eam_sub_res_tbl
3481   		         , x_eam_res_usage_tbl       => l_out_eam_res_usage_tbl
3482   		         , x_eam_mat_req_tbl         => l_out_eam_mat_req_tbl
3483                          , x_eam_direct_items_tbl    => l_out_eam_di_tbl
3484 			 , x_eam_wo_comp_rec         => l_out_eam_wo_comp_rec
3485 			 , x_eam_wo_quality_tbl      => l_out_eam_wo_quality_tbl
3486 			 , x_eam_meter_reading_tbl   => l_out_eam_meter_reading_tbl
3487 			 , x_eam_counter_prop_tbl    => l_out_eam_counter_prop_tbl
3488 			 , x_eam_wo_comp_rebuild_tbl => l_out_eam_wo_comp_rebuild_tbl
3489 			 , x_eam_wo_comp_mr_read_tbl => l_out_eam_wo_comp_mr_read_tbl
3490 			 , x_eam_op_comp_tbl         => l_out_eam_op_comp_tbl
3491 			 , x_eam_request_tbl      =>	l_out_eam_request_tbl
3492   		         , x_return_status           => l_return_status
3493   		         , x_msg_count               => x_msg_count
3494   		         , p_debug                   => NVL(fnd_profile.value('EAM_DEBUG'), 'N')
3495   		         , p_debug_filename          => 'insertwo.log'
3496   		         , p_output_dir              =>l_output_dir
3497                          , p_debug_file_mode         => 'w'
3498                        );
3499 
3500 	IF ( l_return_status = 'S' ) THEN
3501 	     x_return_status := 0 ;
3502 	     COMMIT;
3503 	ELSE
3504 	     x_return_status := 1 ;
3505 	     ROLLBACK TO label_insert_into_wo;	-- Fix for 3582756
3506 	END IF;
3507 
3508   EXCEPTION
3509     WHEN invalid_autochrg_exp THEN
3510 	l_return_status := 3;
3511 	x_return_status := l_return_status;
3512         ROLLBACK TO label_insert_into_wo;	-- Fix for 3823415
3513     WHEN DUP_VAL_ON_INDEX THEN
3514 	l_return_status := 2;
3515 	x_return_status := l_return_status;
3516         ROLLBACK TO label_insert_into_wo;	-- Fix for 3582756
3517     WHEN OTHERS THEN
3518        l_return_status := 1;
3519        x_return_status := l_return_status ;
3520        ROLLBACK TO label_insert_into_wo;	-- Fix for 3582756
3521 
3522   END insert_into_wo;
3523     --------------------------------------------------------------------------
3524     -- Procedure to update operations in wip_operations
3525     -- Used in Operations Page
3526     -- Author : rethakur
3527     --------------------------------------------------------------------------
3528 procedure update_wo ( p_wip_entity_id		   IN       NUMBER
3529                      ,p_operation_seq_num	   IN       NUMBER
3530 		     ,p_organization_id		   IN       NUMBER
3531                      ,p_description		   IN       VARCHAR2
3532                      ,p_shutdown_type		   IN       VARCHAR2
3533 		     ,p_first_unit_start_date	   IN	    VARCHAR2
3534 	             ,p_last_unit_completion_date  IN       VARCHAR2
3535 		     ,p_duration		   IN       NUMBER
3536 		     ,p_long_description           IN       VARCHAR2 := null
3537 		     ,x_return_status              OUT NOCOPY      NUMBER
3538 		     ,x_msg_count                  OUT NOCOPY      NUMBER )  IS
3539 
3540      l_return_status              VARCHAR2(1);
3541      l_first_unit_start_date      DATE := SYSDATE;
3542      l_last_unit_completion_date  DATE := SYSDATE;
3543      l_duration			  NUMBER := 0;
3544 
3545 
3546      -- baroy
3547      l_call_scheduler number := 0;
3548 
3549 
3550      /* Added for WO API */
3551 
3552     l_eam_wo_rec EAM_PROCESS_WO_PUB.eam_wo_rec_type;
3553     l_eam_op_rec  EAM_PROCESS_WO_PUB.eam_op_rec_type;
3554     l_eam_op_tbl  EAM_PROCESS_WO_PUB.eam_op_tbl_type;
3555     l_eam_op_network_tbl  EAM_PROCESS_WO_PUB.eam_op_network_tbl_type;
3556     l_eam_res_tbl  EAM_PROCESS_WO_PUB.eam_res_tbl_type;
3557     l_eam_res_inst_tbl  EAM_PROCESS_WO_PUB.eam_res_inst_tbl_type;
3558     l_eam_sub_res_tbl   EAM_PROCESS_WO_PUB.eam_sub_res_tbl_type;
3559     l_eam_res_usage_tbl  EAM_PROCESS_WO_PUB.eam_res_usage_tbl_type;
3560     l_eam_mat_req_tbl   EAM_PROCESS_WO_PUB.eam_mat_req_tbl_type;
3561     l_eam_di_tbl   EAM_PROCESS_WO_PUB.eam_direct_items_tbl_type;
3562     l_eam_wo_comp_rec               EAM_PROCESS_WO_PUB.eam_wo_comp_rec_type;
3563     l_eam_wo_quality_tbl            EAM_PROCESS_WO_PUB.eam_wo_quality_tbl_type;
3564     l_eam_meter_reading_tbl         EAM_PROCESS_WO_PUB.eam_meter_reading_tbl_type;
3565     l_eam_wo_comp_rebuild_tbl       EAM_PROCESS_WO_PUB.eam_wo_comp_rebuild_tbl_type;
3566     l_eam_wo_comp_mr_read_tbl       EAM_PROCESS_WO_PUB.eam_wo_comp_mr_read_tbl_type;
3567     l_eam_op_comp_tbl               EAM_PROCESS_WO_PUB.eam_op_comp_tbl_type;
3568     l_eam_request_tbl               EAM_PROCESS_WO_PUB.eam_request_tbl_type;
3569     l_eam_counter_prop_tbl     EAM_PROCESS_WO_PUB.eam_counter_prop_tbl_type;
3570 
3571     l_out_eam_wo_rec EAM_PROCESS_WO_PUB.eam_wo_rec_type;
3572     l_out_eam_op_tbl  EAM_PROCESS_WO_PUB.eam_op_tbl_type;
3573     l_out_eam_op_network_tbl  EAM_PROCESS_WO_PUB.eam_op_network_tbl_type;
3574     l_out_eam_res_tbl  EAM_PROCESS_WO_PUB.eam_res_tbl_type;
3575     l_out_eam_res_inst_tbl  EAM_PROCESS_WO_PUB.eam_res_inst_tbl_type;
3576     l_out_eam_sub_res_tbl   EAM_PROCESS_WO_PUB.eam_sub_res_tbl_type;
3577     l_out_eam_res_usage_tbl  EAM_PROCESS_WO_PUB.eam_res_usage_tbl_type;
3578     l_out_eam_mat_req_tbl   EAM_PROCESS_WO_PUB.eam_mat_req_tbl_type;
3579     l_out_eam_di_tbl   EAM_PROCESS_WO_PUB.eam_direct_items_tbl_type;
3580     l_out_eam_wo_comp_rec           EAM_PROCESS_WO_PUB.eam_wo_comp_rec_type;
3581     l_out_eam_wo_quality_tbl        EAM_PROCESS_WO_PUB.eam_wo_quality_tbl_type;
3582     l_out_eam_meter_reading_tbl     EAM_PROCESS_WO_PUB.eam_meter_reading_tbl_type;
3583     l_out_eam_wo_comp_rebuild_tbl   EAM_PROCESS_WO_PUB.eam_wo_comp_rebuild_tbl_type;
3584     l_out_eam_wo_comp_mr_read_tbl   EAM_PROCESS_WO_PUB.eam_wo_comp_mr_read_tbl_type;
3585     l_out_eam_op_comp_tbl           EAM_PROCESS_WO_PUB.eam_op_comp_tbl_type;
3586     l_out_eam_request_tbl           EAM_PROCESS_WO_PUB.eam_request_tbl_type;
3587     l_out_eam_counter_prop_tbl    EAM_PROCESS_WO_PUB.eam_counter_prop_tbl_type;
3588 
3589   l_output_dir   VARCHAR2(512);
3590 BEGIN
3591 SAVEPOINT UPDATE_WO;
3592 
3593  EAM_WORKORDER_UTIL_PKG.log_path(l_output_dir);
3594 
3595 
3596     IF (p_first_unit_start_date is NOT NULL AND p_last_unit_completion_date is NOT NULL) THEN
3597       l_first_unit_start_date		:= to_date(p_first_unit_start_date,'YYYY/MM/DD HH24:MI:SS'); -- ,WIP_CONSTANTS.DATETIME_FMT);
3598       l_last_unit_completion_date	:= to_date(p_last_unit_completion_date,'YYYY/MM/DD HH24:MI:SS'); -- ,WIP_CONSTANTS.DATETIME_FMT);
3599     ELSIF ( p_last_unit_completion_date is NULL) THEN
3600       l_duration			:= p_duration/24;
3601       l_first_unit_start_date	        := to_date(p_first_unit_start_date,'YYYY/MM/DD HH24:MI:SS'); -- ,WIP_CONSTANTS.DATETIME_FMT);
3602       l_last_unit_completion_date	:= l_first_unit_start_date + l_duration;
3603     ELSIF ( p_first_unit_start_date is NULL) THEN
3604       l_duration			:= p_duration/24;
3605       l_last_unit_completion_date       := to_date(p_last_unit_completion_date,'YYYY/MM/DD HH24:MI:SS'); --,WIP_CONSTANTS.DATETIME_FMT);
3606       l_first_unit_start_date		:= l_last_unit_completion_date + l_duration;
3607     END IF ; /* end if of duration check if */
3608 
3609     l_eam_op_rec.transaction_type := EAM_PROCESS_WO_PUB.G_OPR_UPDATE;
3610 	l_eam_op_rec.wip_entity_id := p_wip_entity_id;
3611 	l_eam_op_rec.operation_seq_num := p_operation_seq_num;
3612 	l_eam_op_rec.description := p_description;
3613 	l_eam_op_rec.long_description := p_long_description;
3614 	l_eam_op_rec.shutdown_type := p_shutdown_type;
3615 	l_eam_op_rec.start_date := l_first_unit_start_date;
3616 	l_eam_op_rec.completion_date := l_last_unit_completion_date;
3617 	l_eam_op_rec.organization_id := p_organization_id;
3618 
3619 	l_eam_op_tbl(1) := l_eam_op_rec ;
3620 
3621 
3622 	 EAM_PROCESS_WO_PUB.Process_WO
3623   		         ( p_bo_identifier           => 'EAM'
3624   		         , p_init_msg_list           => TRUE
3625   		         , p_api_version_number      => 1.0
3626                          , p_commit                  => 'N'
3627   		         , p_eam_wo_rec              => l_eam_wo_rec
3628   		         , p_eam_op_tbl              => l_eam_op_tbl
3629   		         , p_eam_op_network_tbl      => l_eam_op_network_tbl
3630   		         , p_eam_res_tbl             => l_eam_res_tbl
3631   		         , p_eam_res_inst_tbl        => l_eam_res_inst_tbl
3632   		         , p_eam_sub_res_tbl         => l_eam_sub_res_tbl
3633   		         , p_eam_res_usage_tbl       => l_eam_res_usage_tbl
3634   		         , p_eam_mat_req_tbl         => l_eam_mat_req_tbl
3635                          , p_eam_direct_items_tbl    => l_eam_di_tbl
3636 			 , p_eam_wo_comp_rec         => l_eam_wo_comp_rec
3637 			 , p_eam_wo_quality_tbl      => l_eam_wo_quality_tbl
3638 			 , p_eam_meter_reading_tbl   => l_eam_meter_reading_tbl
3639 			 , p_eam_counter_prop_tbl    => l_eam_counter_prop_tbl
3640 			 , p_eam_wo_comp_rebuild_tbl => l_eam_wo_comp_rebuild_tbl
3641 		 	 , p_eam_wo_comp_mr_read_tbl => l_eam_wo_comp_mr_read_tbl
3642 			 , p_eam_op_comp_tbl         => l_eam_op_comp_tbl
3643 			 , p_eam_request_tbl        =>	l_eam_request_tbl
3644   		         , x_eam_wo_rec              => l_out_eam_wo_rec
3645   		         , x_eam_op_tbl              => l_out_eam_op_tbl
3646   		         , x_eam_op_network_tbl      => l_out_eam_op_network_tbl
3647   		         , x_eam_res_tbl             => l_out_eam_res_tbl
3648   		         , x_eam_res_inst_tbl        => l_out_eam_res_inst_tbl
3649   		         , x_eam_sub_res_tbl         => l_out_eam_sub_res_tbl
3650   		         , x_eam_res_usage_tbl       => l_out_eam_res_usage_tbl
3651   		         , x_eam_mat_req_tbl         => l_out_eam_mat_req_tbl
3652                          , x_eam_direct_items_tbl    => l_out_eam_di_tbl
3653 			 , x_eam_wo_comp_rec         => l_out_eam_wo_comp_rec
3654 			 , x_eam_wo_quality_tbl      => l_out_eam_wo_quality_tbl
3655 			 , x_eam_meter_reading_tbl   => l_out_eam_meter_reading_tbl
3656 			 , x_eam_counter_prop_tbl    => l_out_eam_counter_prop_tbl
3657 			 , x_eam_wo_comp_rebuild_tbl => l_out_eam_wo_comp_rebuild_tbl
3658 			 , x_eam_wo_comp_mr_read_tbl => l_out_eam_wo_comp_mr_read_tbl
3659 			 , x_eam_op_comp_tbl         => l_out_eam_op_comp_tbl
3660 			 , x_eam_request_tbl      =>	l_out_eam_request_tbl
3661   		         , x_return_status           => l_return_status
3662   		         , x_msg_count               => x_msg_count
3663   		         , p_debug                   => NVL(fnd_profile.value('EAM_DEBUG'), 'N')
3664   		         , p_debug_filename          => 'updatewo.log'
3665   		         , p_output_dir              => l_output_dir
3666                          , p_debug_file_mode         => 'w'
3667                        );
3668 
3669 	IF ( l_return_status = 'S' ) THEN
3670            x_return_status := 0 ;
3671 	   COMMIT;  -- Fix for Bug 3521871
3672 	ELSE
3673 	   ROLLBACK TO UPDATE_WO;
3674 	   x_return_status := 1 ;
3675 	END IF;
3676 
3677 EXCEPTION
3678 
3679 WHEN OTHERS THEN
3680     ROLLBACK TO UPDATE_WO;
3681     l_return_status := 4;
3682     x_return_status := l_return_status;
3683 
3684 END update_wo;
3685 
3686 -- ------------------------------------------------------------------------
3687 -- Validation API for new link between operaions in
3688 -- Dependency definitions
3689 -- ------------------------------------------------------------------------
3690 
3691 Procedure validate_new_link(p_from_operation IN NUMBER,
3692                              p_to_operation     IN NUMBER,
3693                              p_dep_direction    IN NUMBER,
3694                              p_wip_entity_id    IN NUMBER,
3695 							 p_sche_start_date  IN DATE,
3696 							 p_sche_end_date    IN DATE,
3697                              x_error_flag     OUT NOCOPY VARCHAR2,
3698                              x_error_mssg  OUT NOCOPY VARCHAR2
3699 							 ) IS
3700 l_to_scheduled_start_date       DATE;
3701 l_to_scheduled_end_date        DATE;
3702 l_to_operation_completed        VARCHAR2(1);
3703 l_from_scheduled_start_date   DATE;
3704 l_from_scheduled_end_date    DATE;
3705 l_from_operation_completed        VARCHAR2(1);
3706 l_op_already_available            NUMBER;
3707 l_loop_available NUMBER :=0 ;
3708 l_available_value NUMBER := 0;
3709 l_restrict_date_change NUMBER := 0;
3710 Begin
3711 
3712 l_op_already_available := 0;
3713 x_error_flag := FND_API.G_RET_STS_SUCCESS;
3714 x_error_mssg := '';
3715 
3716 
3717 --check for the availability of all the values
3718 if(p_dep_direction is null or p_from_operation is null or
3719    p_to_operation is null or p_sche_start_date is null or
3720    p_sche_end_date is null) then
3721  x_error_flag := FND_API.G_RET_STS_ERROR;
3722  x_error_mssg := 'EAM_NOT_ENOUGH_VALUES';
3723  return;
3724 end if;
3725 
3726 -- check for from and to operation
3727 if(p_from_operation = p_to_operation) then
3728  x_error_flag := FND_API.G_RET_STS_ERROR;
3729  x_error_mssg := 'EAM_FROM_TO_OPERATION_EQUAL';
3730  return;
3731 end if;
3732 
3733 if(p_sche_end_date < p_sche_start_date) then
3734  x_error_flag := FND_API.G_RET_STS_ERROR;
3735  x_error_mssg := 'EAM_START_LESS_END_DATE';
3736  return;
3737 end if;
3738 
3739 -- initialize scheduled dates of from and to operations .
3740 Begin
3741 select
3742 first_unit_start_date ,
3743 last_unit_completion_date,
3744 operation_completed
3745 into
3746 l_from_scheduled_start_date,
3747 l_from_scheduled_end_date,
3748 l_from_operation_completed
3749 from
3750 wip_operations
3751 where
3752 wip_entity_id = p_wip_entity_id and
3753 operation_seq_num = p_from_operation ;
3754 Exception
3755 when NO_DATA_FOUND then
3756  x_error_flag := FND_API.G_RET_STS_ERROR;
3757  x_error_mssg := 'EAM_FROM_OPERATION_NOT_FOUND';
3758  return;
3759 End; -- end of
3760 
3761 Begin
3762 select
3763 first_unit_start_date ,
3764 last_unit_completion_date,
3765 operation_completed
3766 into
3767 l_to_scheduled_start_date,
3768 l_to_scheduled_end_date,
3769 l_to_operation_completed
3770 from
3771 wip_operations
3772 where
3773 wip_entity_id = p_wip_entity_id and
3774 operation_seq_num = p_to_operation ;
3775 Exception
3776 when NO_DATA_FOUND then
3777  x_error_flag := FND_API.G_RET_STS_ERROR;
3778  x_error_mssg := 'EAM_TO_OPERATION_NOT_FOUND';
3779  return;
3780 End; -- end of
3781 
3782 -- check for the scheduled atart/end date updation
3783 if(p_dep_direction = 1) then
3784   if(p_sche_start_date <> l_from_scheduled_start_date or
3785 	 p_sche_end_date <> l_from_scheduled_end_date) then
3786 
3787     -- check Prior/Next Operation conflict with the modified Start and End Date .
3788 	select
3789     count(*) into l_restrict_date_change
3790     from
3791     dual
3792     where
3793     exists
3794     (select '1' from eam_prior_operations_v
3795      where next_operation = p_from_operation
3796      and schedule_end_date > p_sche_start_date
3797 	 and wip_entity_id  = p_wip_entity_id);
3798 
3799      if(l_restrict_date_change = 0) then
3800 	 select count(*) into l_restrict_date_change
3801      from dual
3802 	 where
3803 	 exists
3804 	 (select '1' from eam_next_operations_v
3805 	  where prior_operation =  p_from_operation
3806 	  and schedule_start_date < p_sche_end_date
3807 	  and wip_entity_id  = p_wip_entity_id);
3808 	  end if;
3809 
3810 
3811 	if(l_restrict_date_change > 0) then
3812 	  x_error_flag := FND_API.G_RET_STS_ERROR;
3813 	  x_error_mssg := 'EAM_SCHEDULED_DATE_CHANGE';
3814      return;
3815     elsif(l_restrict_date_change = 0) then
3816 	  update wip_operations
3817 	  set
3818 	  first_unit_start_date = p_sche_start_date,
3819 	  last_unit_start_date = p_sche_start_date,
3820 	  first_unit_completion_date = p_sche_end_date,
3821 	  last_unit_completion_date  = p_sche_end_date
3822 	  where
3823 	  wip_entity_id = p_wip_entity_id and
3824 	  operation_seq_num = p_from_operation ;
3825 	  l_from_scheduled_start_date := p_sche_start_date ;
3826 	  l_from_scheduled_end_date   := p_sche_end_date;
3827     end if;
3828    end if; -- end of date check
3829 elsif(p_dep_direction = 2) then
3830   if(p_sche_start_date <> l_to_scheduled_start_date or
3831 	 p_sche_end_date <> l_to_scheduled_end_date) then
3832 
3833     -- check Prior/Next Operation conflict with the modified Start and End Date .
3834 	select
3835     count(*) into l_restrict_date_change
3836     from
3837     dual
3838     where
3839     exists
3840     (select '1' from eam_prior_operations_v
3841      where next_operation = p_to_operation
3842      and schedule_end_date > p_sche_start_date
3843 	 and wip_entity_id  = p_wip_entity_id);
3844 
3845      if(l_restrict_date_change = 0) then
3846 	 select count(*) into l_restrict_date_change
3847 	 from dual
3848 	 where
3849 	 exists
3850 	 (select '1' from eam_next_operations_v
3851 	  where prior_operation =  p_to_operation
3852 	  and schedule_start_date < p_sche_start_date
3853 	  and wip_entity_id  = p_wip_entity_id);
3854 	  end if;
3855 
3856 	if(l_restrict_date_change > 0) then
3857      x_error_flag := FND_API.G_RET_STS_ERROR;
3858      x_error_mssg := 'EAM_SCHEDULED_DATE_CHANGE';
3859      return;
3860     elsif(l_restrict_date_change = 0) then
3861 	  update wip_operations
3862 	  set
3863 	  first_unit_start_date = p_sche_start_date,
3864 	  last_unit_start_date = p_sche_start_date,
3865 	  first_unit_completion_date = p_sche_end_date,
3866 	  last_unit_completion_date  = p_sche_end_date
3867 	  where
3868 	  wip_entity_id = p_wip_entity_id and
3869 	  operation_seq_num = p_to_operation ;
3870        l_to_scheduled_start_date := p_sche_start_date ;
3871 	   l_to_scheduled_end_date   := p_sche_end_date;
3872     end if;
3873   end if; --  end of date check
3874 end if;-- end of dep_direction check if
3875 
3876 
3877 -- check for the scheduled completion and start date of from and to operation respectively
3878 if (l_to_scheduled_start_date < l_from_scheduled_end_date ) then
3879   x_error_flag := FND_API.G_RET_STS_ERROR;
3880   x_error_mssg :=  'EAM_DEP_OP_START_DATE_INVALID';
3881   return;
3882 end if;
3883 
3884 -- check for loop in the dependency network
3885 select count(1) into l_loop_available
3886 from dual
3887 where
3888 p_from_operation in (select next_operation
3889                                 from (select * from wip_operation_networks
3890                                          where next_operation <> p_to_operation and
3891                                           wip_entity_id = p_wip_entity_id)
3892                                 start with prior_operation = p_to_operation
3893                                 connect by prior_operation = prior next_operation) ;
3894 
3895 if(l_loop_available <> 0) then
3896   x_error_flag := FND_API.G_RET_STS_ERROR;
3897   x_error_mssg := 'EAM_OPMDF_OP_DEP_LOOP';
3898 end if;
3899 
3900 End validate_new_link;
3901 
3902 
3903   Procedure create_new_link(              p_from_operation IN NUMBER,
3904                                           p_to_operation     IN NUMBER,
3905                                           p_dep_direction    IN NUMBER,
3906                                           p_wip_entity_id    IN NUMBER,
3907                                           p_organization_id  IN NUMBER,
3908                                           p_user_id            IN NUMBER,
3909 										  p_sche_start_date   IN DATE,
3910 										  p_sche_end_date     IN DATE,
3911                                           x_error_flag     OUT NOCOPY VARCHAR2,
3912                                           x_error_mssg  OUT NOCOPY VARCHAR2 ) IS
3913 
3914 /* Added for implementing the WO API */
3915 
3916      l_eam_wo_rec EAM_PROCESS_WO_PUB.eam_wo_rec_type;
3917      l_eam_op_network_rec EAM_PROCESS_WO_PUB.eam_op_network_rec_type;
3918      l_eam_op_tbl  EAM_PROCESS_WO_PUB.eam_op_tbl_type;
3919      l_eam_op_network_tbl  EAM_PROCESS_WO_PUB.eam_op_network_tbl_type;
3920      l_eam_res_tbl  EAM_PROCESS_WO_PUB.eam_res_tbl_type;
3921      l_eam_res_inst_tbl  EAM_PROCESS_WO_PUB.eam_res_inst_tbl_type;
3922      l_eam_sub_res_tbl   EAM_PROCESS_WO_PUB.eam_sub_res_tbl_type;
3923      l_eam_res_usage_tbl  EAM_PROCESS_WO_PUB.eam_res_usage_tbl_type;
3924      l_eam_mat_req_tbl   EAM_PROCESS_WO_PUB.eam_mat_req_tbl_type;
3925      l_eam_di_tbl   EAM_PROCESS_WO_PUB.eam_direct_items_tbl_type;
3926      l_eam_wo_comp_rec               EAM_PROCESS_WO_PUB.eam_wo_comp_rec_type;
3927      l_eam_wo_quality_tbl            EAM_PROCESS_WO_PUB.eam_wo_quality_tbl_type;
3928      l_eam_meter_reading_tbl         EAM_PROCESS_WO_PUB.eam_meter_reading_tbl_type;
3929      l_eam_wo_comp_rebuild_tbl       EAM_PROCESS_WO_PUB.eam_wo_comp_rebuild_tbl_type;
3930      l_eam_wo_comp_mr_read_tbl       EAM_PROCESS_WO_PUB.eam_wo_comp_mr_read_tbl_type;
3931      l_eam_op_comp_tbl               EAM_PROCESS_WO_PUB.eam_op_comp_tbl_type;
3932      l_eam_request_tbl               EAM_PROCESS_WO_PUB.eam_request_tbl_type;
3933      l_eam_counter_prop_tbl     EAM_PROCESS_WO_PUB.eam_counter_prop_tbl_type;
3934 
3935    l_out_eam_wo_rec EAM_PROCESS_WO_PUB.eam_wo_rec_type;
3936    l_out_eam_op_tbl  EAM_PROCESS_WO_PUB.eam_op_tbl_type;
3937    l_out_eam_op_network_tbl  EAM_PROCESS_WO_PUB.eam_op_network_tbl_type;
3938    l_out_eam_res_tbl  EAM_PROCESS_WO_PUB.eam_res_tbl_type;
3939    l_out_eam_res_inst_tbl  EAM_PROCESS_WO_PUB.eam_res_inst_tbl_type;
3940    l_out_eam_sub_res_tbl   EAM_PROCESS_WO_PUB.eam_sub_res_tbl_type;
3941    l_out_eam_res_usage_tbl  EAM_PROCESS_WO_PUB.eam_res_usage_tbl_type;
3942    l_out_eam_mat_req_tbl   EAM_PROCESS_WO_PUB.eam_mat_req_tbl_type;
3943    l_out_eam_di_tbl   EAM_PROCESS_WO_PUB.eam_direct_items_tbl_type;
3944    l_out_eam_wo_comp_rec           EAM_PROCESS_WO_PUB.eam_wo_comp_rec_type;
3945    l_out_eam_wo_quality_tbl        EAM_PROCESS_WO_PUB.eam_wo_quality_tbl_type;
3946    l_out_eam_meter_reading_tbl     EAM_PROCESS_WO_PUB.eam_meter_reading_tbl_type;
3947    l_out_eam_wo_comp_rebuild_tbl   EAM_PROCESS_WO_PUB.eam_wo_comp_rebuild_tbl_type;
3948    l_out_eam_wo_comp_mr_read_tbl   EAM_PROCESS_WO_PUB.eam_wo_comp_mr_read_tbl_type;
3949    l_out_eam_op_comp_tbl           EAM_PROCESS_WO_PUB.eam_op_comp_tbl_type;
3950    l_out_eam_request_tbl           EAM_PROCESS_WO_PUB.eam_request_tbl_type;
3951    l_out_eam_counter_prop_tbl    EAM_PROCESS_WO_PUB.eam_counter_prop_tbl_type;
3952 
3953 l_mssg_token_tbl_type EAM_ERROR_MESSAGE_PVT.Mesg_Token_Tbl_Type;
3954 l_return_status VARCHAR2(240);
3955 l_data VARCHAR2(2000);
3956 l_mssg_index_out NUMBER;
3957 l_mssg_index NUMBER;
3958 l_mssg_data VARCHAR2(250);
3959 l_msg_count NUMBER := 0;
3960 l_output_dir  VARCHAR2(512);
3961 Begin
3962 
3963  EAM_WORKORDER_UTIL_PKG.log_path(l_output_dir);
3964 
3965 
3966 x_error_flag := FND_API.G_RET_STS_SUCCESS;
3967 x_error_mssg := '';
3968 
3969 -- validate  the link
3970 validate_new_link(
3971                          p_from_operation,
3972                          p_to_operation     ,
3973                          p_dep_direction    ,
3974                          p_wip_entity_id    ,
3975 						 p_sche_start_date,
3976 						 p_sche_end_date,
3977                          x_error_flag     ,
3978                          x_error_mssg  ) ;
3979 
3980 if(x_error_flag <> FND_API.G_RET_STS_SUCCESS) then
3981  FND_MSG_PUB.Initialize;
3982  eam_execution_jsp.add_message(p_app_short_name => 'EAM', p_msg_name => x_error_mssg);
3983  eam_execution_jsp.Get_Messages(
3984           p_encoded  => FND_API.G_FALSE,
3985           p_msg_index => 1,
3986           p_msg_count => 1,
3987 	  p_msg_data => l_mssg_data,
3988           p_data      => l_data,
3989           p_msg_index_out => l_mssg_index_out);
3990 -- fnd_message.set_name('EAM',x_error_mssg);
3991  x_error_mssg := l_data;
3992  return;
3993 end if;
3994 
3995 SAVEPOINT add_op_network;
3996 
3997 -- initializing the structure of dependency network
3998 l_eam_op_network_rec.transaction_type := EAM_PROCESS_WO_PVT.G_OPR_CREATE;
3999 l_eam_op_network_rec.wip_entity_id := p_wip_entity_id;
4000 l_eam_op_network_rec.organization_id := p_organization_id;
4001 l_eam_op_network_rec.prior_operation := p_from_operation;
4002 l_eam_op_network_rec.next_operation :=  p_to_operation;
4003 
4004 l_eam_op_network_tbl(1) := l_eam_op_network_rec ;
4005 
4006    EAM_PROCESS_WO_PUB.Process_WO
4007   		         ( p_bo_identifier           => 'EAM'
4008   		         , p_init_msg_list           => TRUE
4009   		         , p_api_version_number      => 1.0
4010                          , p_commit                  => 'N'
4011   		         , p_eam_wo_rec              => l_eam_wo_rec
4012   		         , p_eam_op_tbl              => l_eam_op_tbl
4013   		         , p_eam_op_network_tbl      => l_eam_op_network_tbl
4014   		         , p_eam_res_tbl             => l_eam_res_tbl
4015   		         , p_eam_res_inst_tbl        => l_eam_res_inst_tbl
4016   		         , p_eam_sub_res_tbl         => l_eam_sub_res_tbl
4017   		         , p_eam_res_usage_tbl       => l_eam_res_usage_tbl
4018   		         , p_eam_mat_req_tbl         => l_eam_mat_req_tbl
4019                          , p_eam_direct_items_tbl    => l_eam_di_tbl
4020 			 , p_eam_wo_comp_rec         => l_eam_wo_comp_rec
4021 			 , p_eam_wo_quality_tbl      => l_eam_wo_quality_tbl
4022 			 , p_eam_meter_reading_tbl   => l_eam_meter_reading_tbl
4023 			 , p_eam_counter_prop_tbl    => l_eam_counter_prop_tbl
4024 			 , p_eam_wo_comp_rebuild_tbl => l_eam_wo_comp_rebuild_tbl
4025 			 , p_eam_wo_comp_mr_read_tbl => l_eam_wo_comp_mr_read_tbl
4026 			 , p_eam_op_comp_tbl         => l_eam_op_comp_tbl
4027 			 , p_eam_request_tbl        =>	l_eam_request_tbl
4028   		         , x_eam_wo_rec              => l_out_eam_wo_rec
4029   		         , x_eam_op_tbl              => l_out_eam_op_tbl
4030   		         , x_eam_op_network_tbl      => l_out_eam_op_network_tbl
4031   		         , x_eam_res_tbl             => l_out_eam_res_tbl
4032   		         , x_eam_res_inst_tbl        => l_out_eam_res_inst_tbl
4033   		         , x_eam_sub_res_tbl         => l_out_eam_sub_res_tbl
4034   		         , x_eam_res_usage_tbl       => l_out_eam_res_usage_tbl
4035   		         , x_eam_mat_req_tbl         => l_out_eam_mat_req_tbl
4036                          , x_eam_direct_items_tbl    => l_out_eam_di_tbl
4037 			 , x_eam_wo_comp_rec         => l_out_eam_wo_comp_rec
4038 			 , x_eam_wo_quality_tbl      => l_out_eam_wo_quality_tbl
4039 			 , x_eam_meter_reading_tbl   => l_out_eam_meter_reading_tbl
4040 			 , x_eam_counter_prop_tbl    => l_out_eam_counter_prop_tbl
4041 			 , x_eam_wo_comp_rebuild_tbl => l_out_eam_wo_comp_rebuild_tbl
4042 			 , x_eam_wo_comp_mr_read_tbl => l_out_eam_wo_comp_mr_read_tbl
4043 			 , x_eam_op_comp_tbl         => l_out_eam_op_comp_tbl
4044 			 , x_eam_request_tbl      =>	l_out_eam_request_tbl
4045   		         , x_return_status           => x_error_flag
4046   		         , x_msg_count               => l_msg_count
4047   		         , p_debug                   => NVL(fnd_profile.value('EAM_DEBUG'), 'N')
4048   		         , p_debug_filename          => 'createopdep.log'
4049   		         , p_output_dir              => l_output_dir
4050                          , p_debug_file_mode         => 'w'
4051                        );
4052 
4053              IF(x_error_flag <> 'S') THEN
4054 	         ROLLBACK TO add_op_network;
4055 	     END IF;
4056 
4057 End create_new_link;
4058 
4059 
4060 PROCEDURE delete_link(p_from_operation IN NUMBER,
4061                                           p_to_operation     IN NUMBER,
4062                                           p_dep_direction    IN NUMBER,
4063                                           p_wip_entity_id    IN NUMBER,
4064                                           p_organization_id  IN NUMBER,
4065                                           p_user_id            IN NUMBER,
4066                                           x_error_flag     OUT NOCOPY VARCHAR2,
4067                                           x_error_mssg  OUT NOCOPY VARCHAR2 ) IS
4068 
4069     /* Added for implementing WO API */
4070      l_eam_wo_rec EAM_PROCESS_WO_PUB.eam_wo_rec_type;
4071      l_eam_op_network_rec EAM_PROCESS_WO_PUB.eam_op_network_rec_type;
4072      l_eam_op_tbl  EAM_PROCESS_WO_PUB.eam_op_tbl_type;
4073      l_eam_op_network_tbl  EAM_PROCESS_WO_PUB.eam_op_network_tbl_type;
4074      l_eam_res_tbl  EAM_PROCESS_WO_PUB.eam_res_tbl_type;
4075      l_eam_res_inst_tbl  EAM_PROCESS_WO_PUB.eam_res_inst_tbl_type;
4076      l_eam_sub_res_tbl   EAM_PROCESS_WO_PUB.eam_sub_res_tbl_type;
4077      l_eam_res_usage_tbl  EAM_PROCESS_WO_PUB.eam_res_usage_tbl_type;
4078      l_eam_mat_req_tbl   EAM_PROCESS_WO_PUB.eam_mat_req_tbl_type;
4079      l_eam_di_tbl   EAM_PROCESS_WO_PUB.eam_direct_items_tbl_type;
4080      l_eam_wo_comp_rec               EAM_PROCESS_WO_PUB.eam_wo_comp_rec_type;
4081      l_eam_wo_quality_tbl            EAM_PROCESS_WO_PUB.eam_wo_quality_tbl_type;
4082      l_eam_meter_reading_tbl         EAM_PROCESS_WO_PUB.eam_meter_reading_tbl_type;
4083      l_eam_wo_comp_rebuild_tbl       EAM_PROCESS_WO_PUB.eam_wo_comp_rebuild_tbl_type;
4084      l_eam_wo_comp_mr_read_tbl       EAM_PROCESS_WO_PUB.eam_wo_comp_mr_read_tbl_type;
4085      l_eam_op_comp_tbl               EAM_PROCESS_WO_PUB.eam_op_comp_tbl_type;
4086      l_eam_request_tbl               EAM_PROCESS_WO_PUB.eam_request_tbl_type;
4087      l_eam_counter_prop_tbl     EAM_PROCESS_WO_PUB.eam_counter_prop_tbl_type;
4088 
4089    l_out_eam_wo_rec EAM_PROCESS_WO_PUB.eam_wo_rec_type;
4090    l_out_eam_op_tbl  EAM_PROCESS_WO_PUB.eam_op_tbl_type;
4091    l_out_eam_op_network_tbl  EAM_PROCESS_WO_PUB.eam_op_network_tbl_type;
4092    l_out_eam_res_tbl  EAM_PROCESS_WO_PUB.eam_res_tbl_type;
4093    l_out_eam_res_inst_tbl  EAM_PROCESS_WO_PUB.eam_res_inst_tbl_type;
4094    l_out_eam_sub_res_tbl   EAM_PROCESS_WO_PUB.eam_sub_res_tbl_type;
4095    l_out_eam_res_usage_tbl  EAM_PROCESS_WO_PUB.eam_res_usage_tbl_type;
4096    l_out_eam_mat_req_tbl   EAM_PROCESS_WO_PUB.eam_mat_req_tbl_type;
4097    l_out_eam_di_tbl   EAM_PROCESS_WO_PUB.eam_direct_items_tbl_type;
4098    l_out_eam_wo_comp_rec           EAM_PROCESS_WO_PUB.eam_wo_comp_rec_type;
4099    l_out_eam_wo_quality_tbl        EAM_PROCESS_WO_PUB.eam_wo_quality_tbl_type;
4100    l_out_eam_meter_reading_tbl     EAM_PROCESS_WO_PUB.eam_meter_reading_tbl_type;
4101    l_out_eam_wo_comp_rebuild_tbl   EAM_PROCESS_WO_PUB.eam_wo_comp_rebuild_tbl_type;
4102    l_out_eam_wo_comp_mr_read_tbl   EAM_PROCESS_WO_PUB.eam_wo_comp_mr_read_tbl_type;
4103    l_out_eam_op_comp_tbl           EAM_PROCESS_WO_PUB.eam_op_comp_tbl_type;
4104    l_out_eam_request_tbl           EAM_PROCESS_WO_PUB.eam_request_tbl_type;
4105    l_out_eam_counter_prop_tbl    EAM_PROCESS_WO_PUB.eam_counter_prop_tbl_type;
4106 
4107 l_mssg_token_tbl_type EAM_ERROR_MESSAGE_PVT.Mesg_Token_Tbl_Type;
4108 l_return_status VARCHAR2(240);
4109 l_data VARCHAR2(2000);
4110 l_mssg_index_out NUMBER;
4111 l_mssg_data VARCHAR2(250);
4112 l_msg_count NUMBER := 0;
4113 l_output_dir VARCHAR2(512);
4114 Begin
4115 
4116  EAM_WORKORDER_UTIL_PKG.log_path(l_output_dir);
4117 
4118 
4119 x_error_flag := FND_API.G_RET_STS_SUCCESS;
4120 x_error_mssg := '';
4121 
4122 -- initializing the structure of dependency network
4123 l_eam_op_network_rec.transaction_type := EAM_PROCESS_WO_PVT.G_OPR_DELETE;
4124 l_eam_op_network_rec.wip_entity_id := p_wip_entity_id;
4125 l_eam_op_network_rec.organization_id := p_organization_id;
4126 l_eam_op_network_rec.prior_operation := p_from_operation;
4127 l_eam_op_network_rec.next_operation :=  p_to_operation;
4128 
4129 l_eam_op_network_tbl(1) := l_eam_op_network_rec ;
4130 
4131 SAVEPOINT delete_op_network;
4132 
4133      EAM_PROCESS_WO_PUB.Process_WO
4134   		         ( p_bo_identifier           => 'EAM'
4135   		         , p_init_msg_list           => TRUE
4136   		         , p_api_version_number      => 1.0
4137                          , p_commit                  => 'N'
4138   		         , p_eam_wo_rec              => l_eam_wo_rec
4139   		         , p_eam_op_tbl              => l_eam_op_tbl
4140   		         , p_eam_op_network_tbl      => l_eam_op_network_tbl
4141   		         , p_eam_res_tbl             => l_eam_res_tbl
4142   		         , p_eam_res_inst_tbl        => l_eam_res_inst_tbl
4143   		         , p_eam_sub_res_tbl         => l_eam_sub_res_tbl
4144   		         , p_eam_res_usage_tbl       => l_eam_res_usage_tbl
4145   		         , p_eam_mat_req_tbl         => l_eam_mat_req_tbl
4146                          , p_eam_direct_items_tbl    => l_eam_di_tbl
4147 			 , p_eam_wo_comp_rec         => l_eam_wo_comp_rec
4148 			 , p_eam_wo_quality_tbl      => l_eam_wo_quality_tbl
4149 			 , p_eam_meter_reading_tbl   => l_eam_meter_reading_tbl
4150 			 , p_eam_counter_prop_tbl    => l_eam_counter_prop_tbl
4151 			 , p_eam_wo_comp_rebuild_tbl => l_eam_wo_comp_rebuild_tbl
4152 			 , p_eam_wo_comp_mr_read_tbl => l_eam_wo_comp_mr_read_tbl
4153 			 , p_eam_op_comp_tbl         => l_eam_op_comp_tbl
4154 			 , p_eam_request_tbl        =>	l_eam_request_tbl
4155   		         , x_eam_wo_rec              => l_out_eam_wo_rec
4156   		         , x_eam_op_tbl              => l_out_eam_op_tbl
4157   		         , x_eam_op_network_tbl      => l_out_eam_op_network_tbl
4158   		         , x_eam_res_tbl             => l_out_eam_res_tbl
4159   		         , x_eam_res_inst_tbl        => l_out_eam_res_inst_tbl
4160   		         , x_eam_sub_res_tbl         => l_out_eam_sub_res_tbl
4161   		         , x_eam_res_usage_tbl       => l_out_eam_res_usage_tbl
4162   		         , x_eam_mat_req_tbl         => l_out_eam_mat_req_tbl
4163                          , x_eam_direct_items_tbl    => l_out_eam_di_tbl
4164 			 , x_eam_wo_comp_rec         => l_out_eam_wo_comp_rec
4165 			 , x_eam_wo_quality_tbl      => l_out_eam_wo_quality_tbl
4166 			 , x_eam_meter_reading_tbl   => l_out_eam_meter_reading_tbl
4167 			 , x_eam_counter_prop_tbl    => l_out_eam_counter_prop_tbl
4168 			 , x_eam_wo_comp_rebuild_tbl => l_out_eam_wo_comp_rebuild_tbl
4169 			 , x_eam_wo_comp_mr_read_tbl => l_out_eam_wo_comp_mr_read_tbl
4170 			 , x_eam_op_comp_tbl         => l_out_eam_op_comp_tbl
4171 			 , x_eam_request_tbl      =>	l_out_eam_request_tbl
4172   		         , x_return_status           => x_error_flag
4173   		         , x_msg_count               => l_msg_count
4174   		         , p_debug                   => NVL(fnd_profile.value('EAM_DEBUG'), 'N')
4175   		         , p_debug_filename          => 'delopdep.log'
4176   		         , p_output_dir              => l_output_dir
4177                          , p_debug_file_mode         => 'w'
4178                        );
4179 
4180       IF(x_error_flag='S') THEN
4181         COMMIT;
4182       END IF;
4183 
4184       IF(x_error_flag <> 'S') THEN
4185           ROLLBACK TO delete_op_network;
4186       END IF;
4187 
4188 End delete_link;
4189 
4190 
4191 
4192 procedure schedule_workorders ( p_organization_id  IN NUMBER,
4193                                 p_wip_entity_id    IN NUMBER
4194                               ) IS
4195 
4196   l_organization_id  NUMBER;
4197   l_wip_entity_id   NUMBER;
4198   l_status_type  NUMBER;
4199   l_use_finite_scheduler  NUMBER;
4200   l_material_constrained  NUMBER;
4201   l_horizon_length  NUMBER;
4202   l_firm  NUMBER;
4203   l_date                  VARCHAR2(100);
4204   l_user_id  NUMBER;
4205   l_responsibility_id  NUMBER;
4206   l_request_id  NUMBER;
4207   l_final_status NUMBER;
4208   l_start_date DATE;
4209   l_completion_date DATE;
4210   l_err_text  VARCHAR2(240) ;
4211   l_return_status VARCHAR2(30) := 'S';
4212   l_first_unit_start_date      DATE := SYSDATE;
4213   l_last_unit_completion_date  DATE := SYSDATE;
4214 
4215 begin
4216 
4217   l_organization_id := p_organization_id;
4218   l_wip_entity_id := p_wip_entity_id;
4219 
4220   select status_type , nvl(firm_planned_flag,2), scheduled_start_date,
4221     scheduled_completion_date
4222   into l_status_type, l_firm, l_start_date, l_completion_date
4223   from wip_discrete_jobs
4224   where wip_entity_id = l_wip_entity_id
4225     and organization_id = l_organization_id;
4226 
4227   -- Get WPS Parameters
4228 
4229   IF(WPS_COMMON.Get_Install_Status = 'I') THEN
4230                      WPS_COMMON.GetParameters(
4231                      P_Org_Id               => l_organization_id,
4232                      X_Use_Finite_Scheduler => l_use_finite_scheduler,
4233                      X_Material_Constrained => l_material_constrained,
4234                      X_Horizon_Length       => l_horizon_length);
4235   ELSE
4236                      l_use_finite_scheduler := 2;
4237                      l_material_constrained := 2;
4238                      l_horizon_length := 0;
4239   END IF;
4240 
4241 
4242   IF (l_status_type in (1,3,6,17) ) then
4243 
4244     -- baroy
4245     -- Finite scheduler has been decommisioned for 11.5.10
4246     -- Hence commenting out this code. Also, hardcode the value
4247     -- of the l_use_finite_scheduler flag
4248 
4249     l_use_finite_scheduler := 2;
4250 
4251     if ((l_status_type = 3) and (l_use_finite_scheduler = 1) and (l_firm = 2) ) then
4252 
4253       null;
4254 
4255     else
4256           SAVEPOINT schedule_wo_pvt;
4257 
4258       EAM_WO_SCHEDULE_PVT.SCHEDULE_WO
4259                   (  p_organization_id               => l_organization_id
4260                   ,  p_wip_entity_id                 =>  l_wip_entity_id
4261                   ,  p_start_date                    =>  l_start_date
4262                   ,  p_completion_date               => l_completion_date
4263                   ,  p_validation_level              =>  null
4264                   ,  p_commit                        =>  'N'
4265                   ,  x_error_message                 =>  l_err_text
4266                   ,  x_return_status                 =>  l_return_status
4267             );
4268              IF(l_err_text <> 'S') THEN
4269 	          ROLLBACK TO schedule_wo_pvt;
4270               END IF;
4271 
4272     end if;
4273 
4274   END IF;
4275 
4276 END schedule_workorders;
4277 
4278 /*-------------------------------------------------------------------------
4279 -- API for geting the operation_seq_num and the department_code
4280 -- for the wip_entity_id.Added for the bug 2762202
4281 -------------------------------------------------------------------------*/
4282 PROCEDURE count_op_seq_num(p_organization_id  IN NUMBER,
4283                            p_wip_entity_id    IN NUMBER,
4284                            op_seq_num        OUT NOCOPY   NUMBER,
4285 			   op_dept_code      OUT NOCOPY   VARCHAR2,
4286 		           op_count          OUT NOCOPY   NUMBER,
4287                            l_return_status   OUT NOCOPY   VARCHAR2,
4288                            l_msg_data        OUT NOCOPY   VARCHAR2,
4289                            l_msg_count       OUT NOCOPY   NUMBER)
4290                            IS
4291  l_op_count       NUMBER;
4292  l_op_dept_code   VARCHAR2(240);
4293  l_op_seq_num     NUMBER;
4294 BEGIN
4295 
4296   SELECT count(operation_seq_num)
4297     INTO  l_op_count
4298     FROM  wip_operations
4299    WHERE wip_entity_id = p_wip_entity_id and
4300          organization_id = p_organization_id;
4301    op_count := l_op_count;
4302 
4303    if (l_op_count = 1 ) then
4304       SELECT wo.operation_seq_num, bd.department_code
4305         INTO  op_seq_num, op_dept_code
4306         FROM  wip_operations wo, bom_departments bd
4307        WHERE  wo.wip_entity_id = p_wip_entity_id and
4308               wo.organization_id = p_organization_id and
4309               wo.organization_id = bd.organization_id and
4310               wo.department_id = bd.department_id;
4311    end if;
4312 
4313 END count_op_seq_num;
4314 /*-------------------------------------------------------------------------
4315 -- API for geting the operation_seq_num,the department_code and start/end dates
4316 -- for a given wip entity id. Added for bug#3544893
4317 -------------------------------------------------------------------------*/
4318 PROCEDURE default_operation (p_organization_id    IN NUMBER,
4319                              p_wip_entity_id      IN NUMBER,
4320                              x_op_seq_num         OUT NOCOPY   NUMBER,
4321 			     x_op_dept_code	  OUT NOCOPY   VARCHAR2,
4322 		             x_op_count           OUT NOCOPY   NUMBER,
4323 			     x_op_start_date      OUT NOCOPY DATE,
4324 			     x_op_end_date        OUT NOCOPY DATE,
4325                              x_return_status      OUT NOCOPY   VARCHAR2,
4326                              x_msg_data           OUT NOCOPY   VARCHAR2,
4327                              x_msg_count          OUT NOCOPY   NUMBER)
4328                            IS
4329  l_op_count       NUMBER;
4330  l_op_dept_code   VARCHAR2(240);
4331  l_op_seq_num     NUMBER;
4332  l_op_start_date   DATE;
4333  l_op_end_date     DATE;
4334 BEGIN
4335 
4336   SELECT count(operation_seq_num)
4337     INTO  l_op_count
4338     FROM  wip_operations
4339    WHERE wip_entity_id = p_wip_entity_id and
4340          organization_id = p_organization_id;
4341    x_op_count := l_op_count;
4342 
4343    if (l_op_count = 1 ) then
4344       SELECT wo.operation_seq_num, wo.first_unit_start_date, wo.last_unit_completion_date, bd.department_code
4345         INTO  x_op_seq_num, x_op_start_date, x_op_end_date, x_op_dept_code
4346         FROM  wip_operations wo, bom_departments bd
4347         WHERE  wo.wip_entity_id = p_wip_entity_id and
4348                wo.organization_id = p_organization_id and
4349                wo.organization_id = bd.organization_id and
4350                wo.department_id = bd.department_id;
4351    end if;
4352 
4353 END default_operation;
4354 
4355 
4356 /* ------------------------------------------------------------------------
4357    API for checking whether the resources associated with a work order and
4358    an operation are available in the department chosen.
4359  --------------------------------------------------------------------------*/
4360   procedure handover_department_validate
4361   ( p_wip_entity_id               IN NUMBER,
4362     p_operation_seq_num		  IN NUMBER,
4363     p_department                  IN VARCHAR2,
4364     p_organization_id		  IN NUMBER,
4365     p_resource_code               IN VARCHAR2,
4366     x_return_status               OUT NOCOPY NUMBER
4367   ) IS
4368 
4369     l_count			  NUMBER;
4370     l_department_id                NUMBER;
4371     l_resource_id                 NUMBER;
4372 
4373     BEGIN
4374      x_return_status := 0;
4375      l_resource_id   := 0;
4376 
4377     SELECT department_id
4378     INTO l_department_id
4379     FROM bom_departments
4380     WHERE department_code like p_department
4381     AND organization_id = p_organization_id;
4382 
4383     -- get resources  available in the assigned department
4384      IF(p_resource_code IS NOT NULL) THEN
4385       SELECT bdr.resource_id
4386       INTO l_resource_id
4387       FROM bom_department_resources bdr , bom_resources br
4388       WHERE bdr.department_id = l_department_id
4389       AND bdr.resource_id = br.resource_id
4390       AND br.resource_code like p_resource_code
4391       AND br.organization_id = p_organization_id;
4392 
4393       IF (l_resource_id=0) THEN
4394        x_return_status := 0;
4395       END IF;
4396      END IF;
4397 
4398      EXCEPTION
4399        WHEN NO_DATA_FOUND THEN
4400         x_return_status := 1;
4401 	return ;
4402 
4403    END handover_department_validate;
4404 
4405   /* API to check if operation can be deleted from self service side */
4406 
4407    procedure check_op_deletion
4408   ( p_wip_entity_id               IN NUMBER,
4409     p_operation_seq_num		  IN NUMBER,
4410     x_return_status               OUT NOCOPY NUMBER
4411   ) IS
4412     l_wip_entity_id		  NUMBER;
4413     l_operation_seq_num           NUMBER;
4414     l_count_routing               NUMBER;
4415     l_count_mat                   NUMBER;
4416     l_count_di                    NUMBER;
4417     l_count_res                   NUMBER;
4418     l_completed 	          varchar2(10);
4419 
4420     BEGIN
4421       -- Check whether there are material requirements or resource requirements
4422       -- or operation has been completed
4423 
4424      l_wip_entity_id := p_wip_entity_id;
4425      l_operation_seq_num := p_operation_seq_num;
4426 
4427     select count(*)
4428       into l_count_routing
4429       from wip_operation_networks
4430     where wip_entity_id = l_wip_entity_id and ( prior_operation  = p_operation_seq_num or next_operation   = p_operation_seq_num);
4431 
4432      select count(*)
4433        into l_count_mat
4434        from wip_requirement_operations
4435      where wip_entity_id = l_wip_entity_id
4436         and operation_seq_num = l_operation_seq_num;
4437 
4438     select count(*)
4439        into l_count_di
4440      from wip_eam_direct_items
4441     where wip_entity_id = l_wip_entity_id
4442     and operation_seq_num         = l_operation_seq_num
4443     and rownum =1;
4444 
4445     select count(*)
4446       into l_count_res
4447      from wip_operation_resources
4448     where wip_entity_id = l_wip_entity_id
4449     and operation_seq_num = l_operation_seq_num;
4450 
4451     begin
4452      select operation_completed
4453      into l_completed
4454       from wip_operations
4455      where wip_entity_id = l_wip_entity_id
4456        and operation_seq_num = l_operation_seq_num;
4457     exception
4458      when others then
4459        null;
4460     end;
4461 
4462    if l_count_routing >0 or l_count_mat > 0 or l_count_res > 0 or l_count_di > 0 or nvl(l_completed, 'N') = 'Y' then
4463     x_return_status := 1;
4464     else
4465      x_return_status := 0;
4466   end if;
4467 
4468      EXCEPTION
4469        WHEN NO_DATA_FOUND THEN
4470         x_return_status := 1;
4471 	return ;
4472    END check_op_deletion;
4473 
4474 
4475   /* API to delete operation from self service side */
4476 
4477     procedure delete_operation (
4478       p_api_version                  IN    NUMBER         := 1.0
4479       ,p_init_msg_list               IN    VARCHAR2      := FND_API.G_TRUE
4480       ,p_commit                      IN    VARCHAR2      := FND_API.G_FALSE
4481       ,p_organization_id             IN    NUMBER
4482       ,p_wip_entity_id   	     IN	   NUMBER
4483       ,p_operation_seq_num	     IN	   NUMBER
4484       ,p_department_id  	     IN	   NUMBER
4485       ,x_return_status               OUT NOCOPY   VARCHAR2
4486       ,x_msg_count                   OUT NOCOPY   NUMBER
4487       ,x_msg_data                    OUT NOCOPY   VARCHAR2
4488      ) is
4489 
4490 	l_api_name constant varchar2(30) := 'Delete_Operations';
4491 	l_api_version  CONSTANT NUMBER   := 1.0;
4492 	l_msg_data VARCHAR2(10000) ;
4493 	l_return_status             VARCHAR2(1) := FND_API.G_RET_STS_SUCCESS;
4494 	l_msg_count                 NUMBER;
4495 	l_message_text               VARCHAR2(1000);
4496 
4497         l_eam_wo_rec EAM_PROCESS_WO_PUB.eam_wo_rec_type;
4498         l_eam_op_rec  EAM_PROCESS_WO_PUB.eam_op_rec_type;
4499         l_eam_op_tbl  EAM_PROCESS_WO_PUB.eam_op_tbl_type;
4500         l_eam_op_network_tbl  EAM_PROCESS_WO_PUB.eam_op_network_tbl_type;
4501         l_eam_res_tbl  EAM_PROCESS_WO_PUB.eam_res_tbl_type;
4502         l_eam_res_inst_tbl  EAM_PROCESS_WO_PUB.eam_res_inst_tbl_type;
4503         l_eam_sub_res_tbl   EAM_PROCESS_WO_PUB.eam_sub_res_tbl_type;
4504         l_eam_res_usage_tbl  EAM_PROCESS_WO_PUB.eam_res_usage_tbl_type;
4505         l_eam_mat_req_tbl   EAM_PROCESS_WO_PUB.eam_mat_req_tbl_type;
4506         l_eam_di_tbl   EAM_PROCESS_WO_PUB.eam_direct_items_tbl_type;
4507 	l_eam_wo_comp_rec               EAM_PROCESS_WO_PUB.eam_wo_comp_rec_type;
4508 	l_eam_wo_quality_tbl            EAM_PROCESS_WO_PUB.eam_wo_quality_tbl_type;
4509 	l_eam_meter_reading_tbl         EAM_PROCESS_WO_PUB.eam_meter_reading_tbl_type;
4510 	l_eam_wo_comp_rebuild_tbl       EAM_PROCESS_WO_PUB.eam_wo_comp_rebuild_tbl_type;
4511 	l_eam_wo_comp_mr_read_tbl       EAM_PROCESS_WO_PUB.eam_wo_comp_mr_read_tbl_type;
4512 	l_eam_op_comp_tbl               EAM_PROCESS_WO_PUB.eam_op_comp_tbl_type;
4513 	l_eam_request_tbl               EAM_PROCESS_WO_PUB.eam_request_tbl_type;
4514 	l_eam_counter_prop_tbl     EAM_PROCESS_WO_PUB.eam_counter_prop_tbl_type;
4515 
4516         l_out_eam_wo_rec EAM_PROCESS_WO_PUB.eam_wo_rec_type;
4517         l_out_eam_op_tbl  EAM_PROCESS_WO_PUB.eam_op_tbl_type;
4518         l_out_eam_op_network_tbl  EAM_PROCESS_WO_PUB.eam_op_network_tbl_type;
4519         l_out_eam_res_tbl  EAM_PROCESS_WO_PUB.eam_res_tbl_type;
4520         l_out_eam_res_inst_tbl  EAM_PROCESS_WO_PUB.eam_res_inst_tbl_type;
4521         l_out_eam_sub_res_tbl   EAM_PROCESS_WO_PUB.eam_sub_res_tbl_type;
4522         l_out_eam_res_usage_tbl  EAM_PROCESS_WO_PUB.eam_res_usage_tbl_type;
4523         l_out_eam_mat_req_tbl   EAM_PROCESS_WO_PUB.eam_mat_req_tbl_type;
4524         l_out_eam_di_tbl   EAM_PROCESS_WO_PUB.eam_direct_items_tbl_type;
4525 	l_out_eam_wo_comp_rec           EAM_PROCESS_WO_PUB.eam_wo_comp_rec_type;
4526 	l_out_eam_wo_quality_tbl        EAM_PROCESS_WO_PUB.eam_wo_quality_tbl_type;
4527 	l_out_eam_meter_reading_tbl     EAM_PROCESS_WO_PUB.eam_meter_reading_tbl_type;
4528 	l_out_eam_wo_comp_rebuild_tbl   EAM_PROCESS_WO_PUB.eam_wo_comp_rebuild_tbl_type;
4529 	l_out_eam_wo_comp_mr_read_tbl   EAM_PROCESS_WO_PUB.eam_wo_comp_mr_read_tbl_type;
4530 	l_out_eam_op_comp_tbl           EAM_PROCESS_WO_PUB.eam_op_comp_tbl_type;
4531 	l_out_eam_request_tbl           EAM_PROCESS_WO_PUB.eam_request_tbl_type;
4532         l_out_eam_counter_prop_tbl    EAM_PROCESS_WO_PUB.eam_counter_prop_tbl_type;
4533 
4534         l_output_dir  VARCHAR2(512);
4535 	begin
4536 
4537 EAM_WORKORDER_UTIL_PKG.log_path(l_output_dir);
4538 
4539 
4540 	       SAVEPOINT DELETE_OPERATION_JSP;
4541 
4542 
4543 	 IF NOT FND_API.COMPATIBLE_API_CALL(l_api_version,
4544 					       p_api_version,
4545 					       l_api_name,
4546 					       g_pkg_name)
4547 	 THEN
4548 	       RAISE FND_API.G_EXC_UNEXPECTED_ERROR;
4549 	 END IF;
4550 
4551         IF FND_API.TO_BOOLEAN(p_init_msg_list)
4552         THEN
4553             FND_MSG_PUB.initialize;
4554         END IF;
4555 
4556 
4557        l_eam_op_rec.WIP_ENTITY_ID             :=p_wip_entity_id;
4558        l_eam_op_rec.ORGANIZATION_ID           :=p_organization_id;
4559        l_eam_op_rec.OPERATION_SEQ_NUM         :=p_operation_seq_num;
4560        l_eam_op_rec.DEPARTMENT_ID             :=p_department_id;
4561        l_eam_op_rec.TRANSACTION_TYPE          :=EAM_PROCESS_WO_PUB.G_OPR_DELETE;
4562 
4563        l_eam_op_tbl(1) := l_eam_op_rec;
4564 
4565           EAM_PROCESS_WO_PUB.Process_WO
4566   		         ( p_bo_identifier           => 'EAM'
4567   		         , p_init_msg_list           => TRUE
4568   		         , p_api_version_number      => 1.0
4569                          , p_commit                  => 'N'
4570   		         , p_eam_wo_rec              => l_eam_wo_rec
4571   		         , p_eam_op_tbl              => l_eam_op_tbl
4572   		         , p_eam_op_network_tbl      => l_eam_op_network_tbl
4573   		         , p_eam_res_tbl             => l_eam_res_tbl
4574   		         , p_eam_res_inst_tbl        => l_eam_res_inst_tbl
4575   		         , p_eam_sub_res_tbl         => l_eam_sub_res_tbl
4576   		         , p_eam_res_usage_tbl       => l_eam_res_usage_tbl
4577   		         , p_eam_mat_req_tbl         => l_eam_mat_req_tbl
4578                          , p_eam_direct_items_tbl    => l_eam_di_tbl
4579 			 , p_eam_wo_comp_rec         => l_eam_wo_comp_rec
4580 			 , p_eam_wo_quality_tbl      => l_eam_wo_quality_tbl
4581 			 , p_eam_meter_reading_tbl   => l_eam_meter_reading_tbl
4582 			 , p_eam_counter_prop_tbl    => l_eam_counter_prop_tbl
4583 			 , p_eam_wo_comp_rebuild_tbl => l_eam_wo_comp_rebuild_tbl
4584 			 , p_eam_wo_comp_mr_read_tbl => l_eam_wo_comp_mr_read_tbl
4585 			 , p_eam_op_comp_tbl         => l_eam_op_comp_tbl
4586 			 , p_eam_request_tbl        =>	l_eam_request_tbl
4587   		         , x_eam_wo_rec              => l_out_eam_wo_rec
4588   		         , x_eam_op_tbl              => l_out_eam_op_tbl
4589   		         , x_eam_op_network_tbl      => l_out_eam_op_network_tbl
4590   		         , x_eam_res_tbl             => l_out_eam_res_tbl
4591   		         , x_eam_res_inst_tbl        => l_out_eam_res_inst_tbl
4592   		         , x_eam_sub_res_tbl         => l_out_eam_sub_res_tbl
4593   		         , x_eam_res_usage_tbl       => l_out_eam_res_usage_tbl
4594   		         , x_eam_mat_req_tbl         => l_out_eam_mat_req_tbl
4595                          , x_eam_direct_items_tbl    => l_out_eam_di_tbl
4596 			 , x_eam_wo_comp_rec         => l_out_eam_wo_comp_rec
4597 			 , x_eam_wo_quality_tbl      => l_out_eam_wo_quality_tbl
4598 			 , x_eam_meter_reading_tbl   => l_out_eam_meter_reading_tbl
4599 			 , x_eam_counter_prop_tbl    => l_out_eam_counter_prop_tbl
4600 			 , x_eam_wo_comp_rebuild_tbl => l_out_eam_wo_comp_rebuild_tbl
4601 			 , x_eam_wo_comp_mr_read_tbl => l_out_eam_wo_comp_mr_read_tbl
4602 			 , x_eam_op_comp_tbl         => l_out_eam_op_comp_tbl
4603 			 , x_eam_request_tbl      =>	l_out_eam_request_tbl
4604   		         , x_return_status           => l_return_status
4605   		         , x_msg_count               => l_msg_count
4606   		         , p_debug                   => NVL(fnd_profile.value('EAM_DEBUG'), 'N')
4607   		         , p_debug_filename          => 'delop.log'
4608   		         , p_output_dir              => l_output_dir
4609                          , p_debug_file_mode         => 'w'
4610                        );
4611 
4612 	l_msg_count := FND_MSG_PUB.count_msg;
4613 	x_return_status := l_return_status;
4614 	x_msg_count := l_msg_count;
4615 
4616     IF(l_return_status <> FND_API.G_RET_STS_SUCCESS) THEN
4617 	          ROLLBACK TO DELETE_OPERATION_JSP;
4618         fnd_msg_pub.get(p_msg_index => FND_MSG_PUB.G_NEXT,
4619                     p_encoded   => 'F',
4620                     p_data      => l_message_text,
4621                     p_msg_index_out => l_msg_count);
4622            fnd_message.set_name('EAM','EAM_ERROR_UPDATE_WO');
4623 
4624            fnd_message.set_token(token => 'MESG',
4625              value => l_message_text,
4626              translate => FALSE);
4627              APP_EXCEPTION.RAISE_EXCEPTION;
4628 
4629 		x_msg_data := 'Error ';
4630       END IF;
4631 
4632       IF p_commit = FND_API.G_TRUE THEN
4633          COMMIT WORK;
4634      end if;
4635     EXCEPTION
4636 
4637          when others then
4638 		  ROLLBACK TO DELETE_OPERATION_JSP;
4639 
4640            x_return_status := FND_API.G_RET_STS_UNEXP_ERROR ;
4641             return;
4642 
4643 
4644 end delete_operation;
4645 
4646 /*---------------------------------------------------------------------------
4647    API for updating/deleting material used in one step issue page
4648   -----------------------------------------------------------------------------*/
4649 
4650  PROCEDURE update_wro
4651             (
4652 	       p_commit            IN  VARCHAR2 := FND_API.G_FALSE
4653 	      ,p_organization_id             IN    NUMBER
4654 	      ,p_wip_entity_id   	     IN	   NUMBER
4655 	      ,p_operation_seq_num	     IN	   NUMBER
4656 	      ,p_inventory_item_id          IN    NUMBER
4657 	      ,p_update                     IN  NUMBER
4658 	      ,p_required_qty               IN  NUMBER
4659 	      ,x_return_status               OUT NOCOPY   VARCHAR2
4660 	      ,x_msg_count                   OUT NOCOPY   NUMBER
4661 	      ,x_msg_data                    OUT NOCOPY   VARCHAR2
4662 	      )
4663  IS
4664                  l_eam_wo_rec EAM_PROCESS_WO_PUB.eam_wo_rec_type;
4665 		l_eam_op_rec  EAM_PROCESS_WO_PUB.eam_op_rec_type;
4666 		l_eam_mat_req_rec   EAM_PROCESS_WO_PUB.eam_mat_req_rec_type;
4667 		l_eam_op_tbl  EAM_PROCESS_WO_PUB.eam_op_tbl_type;
4668 		l_eam_op_network_tbl  EAM_PROCESS_WO_PUB.eam_op_network_tbl_type;
4669 		l_eam_res_tbl  EAM_PROCESS_WO_PUB.eam_res_tbl_type;
4670 		l_eam_res_inst_tbl  EAM_PROCESS_WO_PUB.eam_res_inst_tbl_type;
4671 		l_eam_sub_res_tbl   EAM_PROCESS_WO_PUB.eam_sub_res_tbl_type;
4672 		l_eam_res_usage_tbl  EAM_PROCESS_WO_PUB.eam_res_usage_tbl_type;
4673 		l_eam_mat_req_tbl   EAM_PROCESS_WO_PUB.eam_mat_req_tbl_type;
4674 		l_eam_di_tbl   EAM_PROCESS_WO_PUB.eam_direct_items_tbl_type;
4675 		l_eam_wo_comp_rec               EAM_PROCESS_WO_PUB.eam_wo_comp_rec_type;
4676 		l_eam_wo_quality_tbl            EAM_PROCESS_WO_PUB.eam_wo_quality_tbl_type;
4677 		l_eam_meter_reading_tbl         EAM_PROCESS_WO_PUB.eam_meter_reading_tbl_type;
4678 		l_eam_wo_comp_rebuild_tbl       EAM_PROCESS_WO_PUB.eam_wo_comp_rebuild_tbl_type;
4679 		l_eam_wo_comp_mr_read_tbl       EAM_PROCESS_WO_PUB.eam_wo_comp_mr_read_tbl_type;
4680 		l_eam_op_comp_tbl               EAM_PROCESS_WO_PUB.eam_op_comp_tbl_type;
4681 		l_eam_request_tbl               EAM_PROCESS_WO_PUB.eam_request_tbl_type;
4682 		l_eam_counter_prop_tbl     EAM_PROCESS_WO_PUB.eam_counter_prop_tbl_type;
4683 
4684 		l_out_eam_wo_rec EAM_PROCESS_WO_PUB.eam_wo_rec_type;
4685 		l_out_eam_op_tbl  EAM_PROCESS_WO_PUB.eam_op_tbl_type;
4686 		l_out_eam_op_network_tbl  EAM_PROCESS_WO_PUB.eam_op_network_tbl_type;
4687 		l_out_eam_res_tbl  EAM_PROCESS_WO_PUB.eam_res_tbl_type;
4688 		l_out_eam_res_inst_tbl  EAM_PROCESS_WO_PUB.eam_res_inst_tbl_type;
4689 		l_out_eam_sub_res_tbl   EAM_PROCESS_WO_PUB.eam_sub_res_tbl_type;
4690 		l_out_eam_res_usage_tbl  EAM_PROCESS_WO_PUB.eam_res_usage_tbl_type;
4691 		l_out_eam_mat_req_tbl   EAM_PROCESS_WO_PUB.eam_mat_req_tbl_type;
4692 		l_out_eam_di_tbl   EAM_PROCESS_WO_PUB.eam_direct_items_tbl_type;
4693 		l_out_eam_wo_comp_rec           EAM_PROCESS_WO_PUB.eam_wo_comp_rec_type;
4694 		l_out_eam_wo_quality_tbl        EAM_PROCESS_WO_PUB.eam_wo_quality_tbl_type;
4695 		l_out_eam_meter_reading_tbl     EAM_PROCESS_WO_PUB.eam_meter_reading_tbl_type;
4696 		l_out_eam_wo_comp_rebuild_tbl   EAM_PROCESS_WO_PUB.eam_wo_comp_rebuild_tbl_type;
4697 		l_out_eam_wo_comp_mr_read_tbl   EAM_PROCESS_WO_PUB.eam_wo_comp_mr_read_tbl_type;
4698 		l_out_eam_op_comp_tbl           EAM_PROCESS_WO_PUB.eam_op_comp_tbl_type;
4699 		l_out_eam_request_tbl           EAM_PROCESS_WO_PUB.eam_request_tbl_type;
4700 		l_out_eam_counter_prop_tbl    EAM_PROCESS_WO_PUB.eam_counter_prop_tbl_type;
4701 
4702 		l_output_dir  VARCHAR2(512);
4703  BEGIN
4704      SAVEPOINT update_wro;
4705 
4706     EAM_WORKORDER_UTIL_PKG.log_path(l_output_dir);
4707 
4708 
4709      IF(p_update=1) THEN                  --update wro
4710 		l_eam_mat_req_rec.transaction_type := EAM_PROCESS_WO_PUB.G_OPR_UPDATE;
4711                 l_eam_mat_req_rec.wip_entity_id := p_wip_entity_id;
4712                 l_eam_mat_req_rec.organization_id := p_organization_id;
4713                 l_eam_mat_req_rec.operation_seq_num := p_operation_seq_num;
4714                 l_eam_mat_req_rec.inventory_item_id := p_inventory_item_id;
4715 		l_eam_mat_req_rec.required_quantity := p_required_qty;
4716 
4717     		l_eam_mat_req_tbl(1) := l_eam_mat_req_rec;
4718 
4719 		 EAM_PROCESS_WO_PUB.Process_WO
4720   		         ( p_bo_identifier           => 'EAM'
4721   		         , p_init_msg_list           => FALSE
4722   		         , p_api_version_number      => 1.0
4723                          , p_commit                  => 'N'
4724   		         , p_eam_wo_rec              => l_eam_wo_rec
4725   		         , p_eam_op_tbl              => l_eam_op_tbl
4726   		         , p_eam_op_network_tbl      => l_eam_op_network_tbl
4727   		         , p_eam_res_tbl             => l_eam_res_tbl
4728   		         , p_eam_res_inst_tbl        => l_eam_res_inst_tbl
4729   		         , p_eam_sub_res_tbl         => l_eam_sub_res_tbl
4730   		         , p_eam_res_usage_tbl       => l_eam_res_usage_tbl
4731   		         , p_eam_mat_req_tbl         => l_eam_mat_req_tbl
4732                          , p_eam_direct_items_tbl    => l_eam_di_tbl
4733 			 , p_eam_wo_comp_rec         => l_eam_wo_comp_rec
4734 			 , p_eam_wo_quality_tbl      => l_eam_wo_quality_tbl
4735 			 , p_eam_meter_reading_tbl   => l_eam_meter_reading_tbl
4736 			 , p_eam_counter_prop_tbl    => l_eam_counter_prop_tbl
4737 			 , p_eam_wo_comp_rebuild_tbl => l_eam_wo_comp_rebuild_tbl
4738 			 , p_eam_wo_comp_mr_read_tbl => l_eam_wo_comp_mr_read_tbl
4739 			 , p_eam_op_comp_tbl         => l_eam_op_comp_tbl
4740 			 , p_eam_request_tbl        =>	l_eam_request_tbl
4741   		         , x_eam_wo_rec              => l_out_eam_wo_rec
4742   		         , x_eam_op_tbl              => l_out_eam_op_tbl
4743   		         , x_eam_op_network_tbl      => l_out_eam_op_network_tbl
4744   		         , x_eam_res_tbl             => l_out_eam_res_tbl
4745   		         , x_eam_res_inst_tbl        => l_out_eam_res_inst_tbl
4746   		         , x_eam_sub_res_tbl         => l_out_eam_sub_res_tbl
4747   		         , x_eam_res_usage_tbl       => l_out_eam_res_usage_tbl
4748   		         , x_eam_mat_req_tbl         => l_out_eam_mat_req_tbl
4749                          , x_eam_direct_items_tbl    => l_out_eam_di_tbl
4750 			 , x_eam_wo_comp_rec         => l_out_eam_wo_comp_rec
4751 			 , x_eam_wo_quality_tbl      => l_out_eam_wo_quality_tbl
4752 			 , x_eam_meter_reading_tbl   => l_out_eam_meter_reading_tbl
4753 			 , x_eam_counter_prop_tbl    => l_out_eam_counter_prop_tbl
4754 			 , x_eam_wo_comp_rebuild_tbl => l_out_eam_wo_comp_rebuild_tbl
4755 			 , x_eam_wo_comp_mr_read_tbl => l_out_eam_wo_comp_mr_read_tbl
4756 			 , x_eam_op_comp_tbl         => l_out_eam_op_comp_tbl
4757 			 , x_eam_request_tbl         =>	l_out_eam_request_tbl
4758   		         , x_return_status           => x_return_status
4759   		         , x_msg_count               => x_msg_count
4760   		         , p_debug                   =>  NVL(fnd_profile.value('EAM_DEBUG'), 'N')
4761   		         , p_debug_filename          => 'onestepwro.log'
4762   		         , p_output_dir              => l_output_dir
4763                          , p_debug_file_mode         => 'w'
4764                        );
4765      ELSE        --delete from wro
4766                 l_eam_mat_req_rec.transaction_type := EAM_PROCESS_WO_PUB.G_OPR_DELETE;
4767                 l_eam_mat_req_rec.wip_entity_id := p_wip_entity_id;
4768                 l_eam_mat_req_rec.organization_id := p_organization_id;
4769                 l_eam_mat_req_rec.operation_seq_num := p_operation_seq_num;
4770                 l_eam_mat_req_rec.inventory_item_id := p_inventory_item_id;
4771 
4772     		l_eam_mat_req_tbl(1) := l_eam_mat_req_rec;
4773 
4774 		 EAM_PROCESS_WO_PUB.Process_WO
4775   		         ( p_bo_identifier           => 'EAM'
4776   		         , p_init_msg_list           => FALSE
4777   		         , p_api_version_number      => 1.0
4778                          , p_commit                  => 'N'
4779   		         , p_eam_wo_rec              => l_eam_wo_rec
4780   		         , p_eam_op_tbl              => l_eam_op_tbl
4781   		         , p_eam_op_network_tbl      => l_eam_op_network_tbl
4782   		         , p_eam_res_tbl             => l_eam_res_tbl
4783   		         , p_eam_res_inst_tbl        => l_eam_res_inst_tbl
4784   		         , p_eam_sub_res_tbl         => l_eam_sub_res_tbl
4785   		         , p_eam_res_usage_tbl       => l_eam_res_usage_tbl
4786   		         , p_eam_mat_req_tbl         => l_eam_mat_req_tbl
4787                          , p_eam_direct_items_tbl    => l_eam_di_tbl
4788 			 , p_eam_wo_comp_rec         => l_eam_wo_comp_rec
4789 			 , p_eam_wo_quality_tbl      => l_eam_wo_quality_tbl
4790 			 , p_eam_meter_reading_tbl   => l_eam_meter_reading_tbl
4791 			 , p_eam_counter_prop_tbl    => l_eam_counter_prop_tbl
4792 			 , p_eam_wo_comp_rebuild_tbl => l_eam_wo_comp_rebuild_tbl
4793 			 , p_eam_wo_comp_mr_read_tbl => l_eam_wo_comp_mr_read_tbl
4794 		 	 , p_eam_op_comp_tbl         => l_eam_op_comp_tbl
4795 			 , p_eam_request_tbl        =>	l_eam_request_tbl
4796   		         , x_eam_wo_rec              => l_out_eam_wo_rec
4797   		         , x_eam_op_tbl              => l_out_eam_op_tbl
4798   		         , x_eam_op_network_tbl      => l_out_eam_op_network_tbl
4799   		         , x_eam_res_tbl             => l_out_eam_res_tbl
4800   		         , x_eam_res_inst_tbl        => l_out_eam_res_inst_tbl
4801   		         , x_eam_sub_res_tbl         => l_out_eam_sub_res_tbl
4802   		         , x_eam_res_usage_tbl       => l_out_eam_res_usage_tbl
4803   		         , x_eam_mat_req_tbl         => l_out_eam_mat_req_tbl
4804                          , x_eam_direct_items_tbl    => l_out_eam_di_tbl
4805 			 , x_eam_wo_comp_rec         => l_out_eam_wo_comp_rec
4806 			 , x_eam_wo_quality_tbl      => l_out_eam_wo_quality_tbl
4807 			 , x_eam_meter_reading_tbl   => l_out_eam_meter_reading_tbl
4808 			 , x_eam_counter_prop_tbl    => l_out_eam_counter_prop_tbl
4809 			 , x_eam_wo_comp_rebuild_tbl => l_out_eam_wo_comp_rebuild_tbl
4810 			 , x_eam_wo_comp_mr_read_tbl => l_out_eam_wo_comp_mr_read_tbl
4811 			 , x_eam_op_comp_tbl         => l_out_eam_op_comp_tbl
4812 			 , x_eam_request_tbl         =>	l_out_eam_request_tbl
4813   		         , x_return_status           => x_return_status
4814   		         , x_msg_count               => x_msg_count
4815   		         , p_debug                   =>  NVL(fnd_profile.value('EAM_DEBUG'), 'N')
4816   		         , p_debug_filename          => 'onestepwro.log'
4817   		         , p_output_dir              => l_output_dir
4818                          , p_debug_file_mode         => 'w'
4819                        );
4820      END IF;
4821 
4822 		 IF(x_return_status <>'S') THEN
4823 		      ROLLBACK TO update_wro;
4824 		 END IF;
4825 
4826                    -- Standard check of p_commit.
4827                    IF fnd_api.to_boolean(p_commit)
4828 		       and x_return_status = 'S' THEN
4829                       COMMIT WORK;
4830                    END IF;
4831 
4832 
4833    EXCEPTION
4834 	   WHEN OTHERS THEN
4835 	      ROLLBACK TO update_wro;
4836 	      x_return_status := fnd_api.g_ret_sts_unexp_error;
4837 
4838  END update_wro;
4839 
4840    PROCEDURE delete_instance (
4841             p_api_version        IN       NUMBER
4842   	   ,p_init_msg_list      IN       VARCHAR2 := fnd_api.g_false
4843   	   ,p_commit             IN       VARCHAR2 := fnd_api.g_false
4844            ,p_validation_level   IN       NUMBER   := fnd_api.g_valid_level_full
4845            ,p_wip_entity_id      IN       NUMBER
4846            ,p_organization_id      IN       NUMBER
4847            ,p_operation_seq_num  IN       NUMBER
4848            ,p_resource_seq_num   IN       NUMBER
4849            ,p_instance_id	   IN       NUMBER
4850            ,x_return_status      OUT NOCOPY      VARCHAR2
4851            ,x_msg_count          OUT NOCOPY      NUMBER
4852            ,x_msg_data           OUT NOCOPY      VARCHAR2)  IS
4853 
4854 
4855          l_api_name       CONSTANT VARCHAR2(30) := 'delete_instance';
4856   	 l_api_version    CONSTANT NUMBER       := 1.0;
4857   	 l_full_name      CONSTANT VARCHAR2(60)   := g_pkg_name || '.' || l_api_name;
4858 
4859   	   l_stmt_num       NUMBER;
4860            l_msg_count                NUMBER;
4861            l_msg_data                 VARCHAR2(250);
4862            l_data                     VARCHAR2(250);
4863     	  l_msg_index_out            NUMBER;
4864 
4865 
4866 	   /* added for calling WO API */
4867 
4868     l_eam_wo_rec EAM_PROCESS_WO_PUB.eam_wo_rec_type;
4869     l_eam_res_inst_rec  EAM_PROCESS_WO_PUB.eam_res_inst_rec_type;
4870     l_eam_op_tbl  EAM_PROCESS_WO_PUB.eam_op_tbl_type;
4871     l_eam_op_network_tbl  EAM_PROCESS_WO_PUB.eam_op_network_tbl_type;
4872     l_eam_res_tbl  EAM_PROCESS_WO_PUB.eam_res_tbl_type;
4873     l_eam_res_inst_tbl  EAM_PROCESS_WO_PUB.eam_res_inst_tbl_type;
4874     l_eam_sub_res_tbl   EAM_PROCESS_WO_PUB.eam_sub_res_tbl_type;
4875     l_eam_res_usage_tbl  EAM_PROCESS_WO_PUB.eam_res_usage_tbl_type;
4876     l_eam_mat_req_tbl   EAM_PROCESS_WO_PUB.eam_mat_req_tbl_type;
4877     l_eam_di_tbl   EAM_PROCESS_WO_PUB.eam_direct_items_tbl_type;
4878     l_eam_wo_comp_rec               EAM_PROCESS_WO_PUB.eam_wo_comp_rec_type;
4879     l_eam_wo_quality_tbl            EAM_PROCESS_WO_PUB.eam_wo_quality_tbl_type;
4880     l_eam_meter_reading_tbl         EAM_PROCESS_WO_PUB.eam_meter_reading_tbl_type;
4881     l_eam_wo_comp_rebuild_tbl       EAM_PROCESS_WO_PUB.eam_wo_comp_rebuild_tbl_type;
4882     l_eam_wo_comp_mr_read_tbl       EAM_PROCESS_WO_PUB.eam_wo_comp_mr_read_tbl_type;
4883     l_eam_op_comp_tbl               EAM_PROCESS_WO_PUB.eam_op_comp_tbl_type;
4884     l_eam_request_tbl               EAM_PROCESS_WO_PUB.eam_request_tbl_type;
4885     l_eam_counter_prop_tbl     EAM_PROCESS_WO_PUB.eam_counter_prop_tbl_type;
4886 
4887     l_out_eam_wo_rec EAM_PROCESS_WO_PUB.eam_wo_rec_type;
4888     l_out_eam_op_tbl  EAM_PROCESS_WO_PUB.eam_op_tbl_type;
4889     l_out_eam_op_network_tbl  EAM_PROCESS_WO_PUB.eam_op_network_tbl_type;
4890     l_out_eam_res_tbl  EAM_PROCESS_WO_PUB.eam_res_tbl_type;
4891     l_out_eam_res_inst_tbl  EAM_PROCESS_WO_PUB.eam_res_inst_tbl_type;
4892     l_out_eam_sub_res_tbl   EAM_PROCESS_WO_PUB.eam_sub_res_tbl_type;
4893     l_out_eam_res_usage_tbl  EAM_PROCESS_WO_PUB.eam_res_usage_tbl_type;
4894     l_out_eam_mat_req_tbl   EAM_PROCESS_WO_PUB.eam_mat_req_tbl_type;
4895     l_out_eam_di_tbl   EAM_PROCESS_WO_PUB.eam_direct_items_tbl_type;
4896     l_out_eam_wo_comp_rec           EAM_PROCESS_WO_PUB.eam_wo_comp_rec_type;
4897     l_out_eam_wo_quality_tbl        EAM_PROCESS_WO_PUB.eam_wo_quality_tbl_type;
4898     l_out_eam_meter_reading_tbl     EAM_PROCESS_WO_PUB.eam_meter_reading_tbl_type;
4899     l_out_eam_wo_comp_rebuild_tbl   EAM_PROCESS_WO_PUB.eam_wo_comp_rebuild_tbl_type;
4900     l_out_eam_wo_comp_mr_read_tbl   EAM_PROCESS_WO_PUB.eam_wo_comp_mr_read_tbl_type;
4901     l_out_eam_op_comp_tbl           EAM_PROCESS_WO_PUB.eam_op_comp_tbl_type;
4902     l_out_eam_request_tbl           EAM_PROCESS_WO_PUB.eam_request_tbl_type;
4903     l_out_eam_counter_prop_tbl    EAM_PROCESS_WO_PUB.eam_counter_prop_tbl_type;
4904 
4905    l_output_dir   VARCHAR2(512);
4906 
4907    BEGIN
4908                    -- Standard Start of API savepoint
4909                    l_stmt_num    := 10;
4910                    SAVEPOINT delete_instance_pvt;
4911 
4912                    l_stmt_num    := 20;
4913                    -- Standard call to check for call compatibility.
4914                    IF NOT fnd_api.compatible_api_call(
4915                          l_api_version
4916                         ,p_api_version
4917                         ,l_api_name
4918                         ,g_pkg_name) THEN
4919                       RAISE fnd_api.g_exc_unexpected_error;
4920                    END IF;
4921 
4922                    l_stmt_num    := 30;
4923 
4924                    -- Initialize message list if p_init_msg_list is set to TRUE.
4925                    IF fnd_api.to_boolean(p_init_msg_list) THEN
4926                       fnd_msg_pub.initialize;
4927                    END IF;
4928 
4929                    l_stmt_num    := 40;
4930                    --  Initialize API return status to success
4931                    x_return_status := fnd_api.g_ret_sts_success;
4932 
4933                    l_stmt_num    := 50;
4934     -- API body
4935 
4936 	 EAM_WORKORDER_UTIL_PKG.log_path(l_output_dir);
4937 
4938 
4939 
4940         l_eam_res_inst_rec.transaction_type := EAM_PROCESS_WO_PUB.G_OPR_DELETE;
4941         l_eam_res_inst_rec.wip_entity_id :=  p_wip_entity_id;
4942         l_eam_res_inst_rec.organization_id := p_organization_id;
4943 	l_eam_res_inst_rec.operation_seq_num :=  p_operation_seq_num;
4944 	l_eam_res_inst_rec.resource_seq_num :=  p_resource_seq_num;
4945 	l_eam_res_inst_rec.instance_id := p_instance_id;
4946 
4947 	l_eam_res_inst_tbl(1) := l_eam_res_inst_rec ;
4948 
4949                     EAM_PROCESS_WO_PUB.Process_WO
4950   		         ( p_bo_identifier           => 'EAM'
4951   		         , p_init_msg_list           => TRUE
4952   		         , p_api_version_number      => 1.0
4953                          , p_commit                  => 'N'
4954   		         , p_eam_wo_rec              => l_eam_wo_rec
4955   		         , p_eam_op_tbl              => l_eam_op_tbl
4956   		         , p_eam_op_network_tbl      => l_eam_op_network_tbl
4957   		         , p_eam_res_tbl             => l_eam_res_tbl
4958   		         , p_eam_res_inst_tbl        => l_eam_res_inst_tbl
4959   		         , p_eam_sub_res_tbl         => l_eam_sub_res_tbl
4960   		         , p_eam_res_usage_tbl       => l_eam_res_usage_tbl
4961   		         , p_eam_mat_req_tbl         => l_eam_mat_req_tbl
4962                          , p_eam_direct_items_tbl    => l_eam_di_tbl
4963 			 , p_eam_wo_comp_rec         => l_eam_wo_comp_rec
4964 			 , p_eam_wo_quality_tbl      => l_eam_wo_quality_tbl
4965 			 , p_eam_meter_reading_tbl   => l_eam_meter_reading_tbl
4966 			 , p_eam_counter_prop_tbl    => l_eam_counter_prop_tbl
4967 			 , p_eam_wo_comp_rebuild_tbl => l_eam_wo_comp_rebuild_tbl
4968 			 , p_eam_wo_comp_mr_read_tbl => l_eam_wo_comp_mr_read_tbl
4969 			 , p_eam_op_comp_tbl         => l_eam_op_comp_tbl
4970 			 , p_eam_request_tbl        =>	l_eam_request_tbl
4971   		         , x_eam_wo_rec              => l_out_eam_wo_rec
4972   		         , x_eam_op_tbl              => l_out_eam_op_tbl
4973   		         , x_eam_op_network_tbl      => l_out_eam_op_network_tbl
4974   		         , x_eam_res_tbl             => l_out_eam_res_tbl
4975   		         , x_eam_res_inst_tbl        => l_out_eam_res_inst_tbl
4976   		         , x_eam_sub_res_tbl         => l_out_eam_sub_res_tbl
4977   		         , x_eam_res_usage_tbl       => l_out_eam_res_usage_tbl
4978   		         , x_eam_mat_req_tbl         => l_out_eam_mat_req_tbl
4979                          , x_eam_direct_items_tbl    => l_out_eam_di_tbl
4980 			 , x_eam_wo_comp_rec         => l_out_eam_wo_comp_rec
4981 			 , x_eam_wo_quality_tbl      => l_out_eam_wo_quality_tbl
4982 			 , x_eam_meter_reading_tbl   => l_out_eam_meter_reading_tbl
4983 			 , x_eam_counter_prop_tbl    => l_out_eam_counter_prop_tbl
4984 			 , x_eam_wo_comp_rebuild_tbl => l_out_eam_wo_comp_rebuild_tbl
4985 			 , x_eam_wo_comp_mr_read_tbl => l_out_eam_wo_comp_mr_read_tbl
4986 			 , x_eam_op_comp_tbl         => l_out_eam_op_comp_tbl
4987 			 , x_eam_request_tbl      =>	l_out_eam_request_tbl
4988   		         , x_return_status           => x_return_status
4989   		         , x_msg_count               => x_msg_count
4990   		         , p_debug                   => NVL(fnd_profile.value('EAM_DEBUG'), 'N')
4991   		         , p_debug_filename          => 'delwor.log'
4992   		         , p_output_dir              => l_output_dir
4993                          , p_debug_file_mode         => 'w'
4994                        );
4995 
4996 
4997     -- End of API body.
4998                      -- Standard check of p_commit.
4999                      IF fnd_api.to_boolean(p_commit)
5000 		          and x_return_status = 'S' THEN
5001                         COMMIT WORK;
5002                      END IF;
5003 
5004 		     IF(x_return_status <> 'S') THEN
5005 		         ROLLBACK TO delete_instance_pvt;
5006 		     END IF;
5007 
5008                      l_stmt_num    := 999;
5009 
5010                      -- Standard call to get message count and if count is 1, get message info.
5011                      fnd_msg_pub.count_and_get(
5012                         p_count => x_msg_count
5013                        ,p_data => x_msg_data);
5014 
5015                   EXCEPTION
5016                      WHEN fnd_api.g_exc_error THEN
5017                         ROLLBACK TO get_delete_resources_pvt;
5018                         x_return_status := fnd_api.g_ret_sts_error;
5019                         fnd_msg_pub.count_and_get(
5020                --            p_encoded => FND_API.g_false
5021                            p_count => x_msg_count
5022                           ,p_data => x_msg_data);
5023 
5024                      WHEN fnd_api.g_exc_unexpected_error THEN
5025                         ROLLBACK TO get_delete_resources_pvt;
5026                         x_return_status := fnd_api.g_ret_sts_unexp_error;
5027 
5028                         fnd_msg_pub.count_and_get(
5029                            p_count => x_msg_count
5030                           ,p_data => x_msg_data);
5031 
5032                      WHEN OTHERS THEN
5033                         ROLLBACK TO get_delete_resources_pvt;
5034                         x_return_status := fnd_api.g_ret_sts_unexp_error;
5035                         IF fnd_msg_pub.check_msg_level(
5036                               fnd_msg_pub.g_msg_lvl_unexp_error) THEN
5037                            fnd_msg_pub.add_exc_msg(g_pkg_name, l_api_name);
5038                         END IF;
5039 
5040                         fnd_msg_pub.count_and_get(
5041                            p_count => x_msg_count
5042                           ,p_data => x_msg_data);
5043 
5044       END delete_instance;
5045 
5046 end eam_operations_jsp;