DBA Data[Home] [Help]

PACKAGE BODY: APPS.OKL_AM_OM_REMARKET_WF

Source


1 PACKAGE BODY  OKL_AM_OM_REMARKET_WF AS
2 /* $Header: OKLROWFB.pls 120.4 2007/06/20 13:53:45 akrangan noship $ */
3 
4   -- Start of comments
5   --
6   -- Procedure Name	: set_context
7   -- Description    : This resets the org context if the context is lost
8   -- Business Rules	:
9   -- Parameters		: itemtype, itemkey, actid, resultout
10   -- Version		: 1.0
11   -- History        : 21-JUN-07 AKRANGAN CREATED
12   -- End of comments
13   PROCEDURE set_context( itemtype	IN VARCHAR2,
14 			 itemkey  	IN VARCHAR2,
15 			 actid		IN NUMBER,
16 			 resultout      OUT NOCOPY VARCHAR2 )
17   IS
18   l_resultout      VARCHAR2(20);
19   BEGIN
20     --this call is to test the context is alive or not
21     OE_STANDARD_WF.OEOL_SELECTOR
22            (p_itemtype => itemtype
23            ,p_itemkey => itemkey
24            ,p_actid => actid
25            ,p_funcmode => 'TEST_CTX'
26            ,p_result => l_resultout
27            );
28     --if the context is not alive then we can re set
29     --the context by calling this api
30     IF l_resultout = 'FALSE' THEN
31       OE_STANDARD_WF.OEOL_SELECTOR
32            (p_itemtype => itemtype
33            ,p_itemkey => itemkey
34            ,p_actid => actid
35            ,p_funcmode => 'SET_CTX'
36            ,p_result => l_resultout
37            );
38     END IF;
39     --set the out variable
40     resultout := l_resultout;
41 
42   END set_context;
43 
44   -- Start of comments
45   --
46   -- Procedure Name	: reduce_item_quantity
47   -- Description    : This procedure is used to reduce the item quantity
48   -- Business Rules	:
49   -- Parameters		: itemtype, itemkey, actid, funcmode, resultout
50   -- Version		: 1.0
51   -- History        : 21-OCT-04 SECHAWLA 3924244 : Modified procedures to work on order line instead of header
52   -- End of comments
53   PROCEDURE reduce_item_quantity(
54                                  itemtype	IN VARCHAR2,
55 				                 itemkey  	IN VARCHAR2,
56 			                 	 actid		IN NUMBER,
57 			                     funcmode	IN VARCHAR2,
58 				                 resultout OUT NOCOPY VARCHAR2 )IS
59 
60 	x_return_status                 VARCHAR2(1)  := OKC_API.G_RET_STS_SUCCESS;
61     x_msg_count                     NUMBER;
62     x_msg_data                      VARCHAR2(2000);
63     p_api_version                   NUMBER       := 1;
64     p_init_msg_list                 VARCHAR2(1) := 'T';
65     l_id		                    NUMBER;
66     error_reducing_quantity         EXCEPTION ;
67     --ADDED BY AKRANGAN FOR SETTING THE CONTEXT FOR THE WF CALL
68     l_ctxt_result                   VARCHAR2(20);
69     BEGIN
70       --ADDED BY AKRANGAN FOR SETTING THE CONTEXT FOR THE WF CALL BEGIN
71       set_context(itemtype => itemtype,
72                   itemkey => itemkey,
73 		  actid => actid,
74 		  resultout => l_ctxt_result
75 		  );
76       --ADDED BY AKRANGAN FOR SETTING THE CONTEXT FOR THE WF CALL END
77 
78 
79         IF (funcmode = 'RUN') THEN
80 
81         -- SECHAWLA 21-OCT-04 3924244 : l_id will now be the order line id as this step is moved to the line WF
82           l_id := to_number(itemkey);
83 
84 		OKL_AM_REMARKET_ASSET_PUB.remove_rmk_item(    p_api_version          => p_api_version,
85                                                       p_init_msg_list        => p_init_msg_list,
86                                                       p_order_line_Id        => l_id,
87                                                       x_return_status        => x_return_status,
88                                                       x_msg_count            => x_msg_count,
89                                                       x_msg_data             => x_msg_data);
90 
91           IF x_return_status = OKC_API.G_RET_STS_SUCCESS THEN
92 			resultout := 'COMPLETE:PASS';
93 		ELSE
94 			resultout := 'COMPLETE:';
95             RAISE error_reducing_quantity;
96 		END IF;
97 
98           RETURN ;
99 
100         END IF;
101 
102 
103       --
104       -- CANCEL mode
105       --
106       IF (funcmode = 'CANCEL') THEN
107         --
108         resultout := 'COMPLETE:';
109         RETURN;
110         --
111       END IF;
112       --
113       -- TIMEOUT mode
114       --
115       IF (funcmode = 'TIMEOUT') THEN
116         --
117         resultout := 'COMPLETE:';
118         RETURN;
119         --
120       END IF;
121 
122   EXCEPTION
123      WHEN error_reducing_quantity THEN
124         wf_core.context('OKL_AM_OM_REMARKET_WF' , 'reduce_item_quantity', itemtype, itemkey, actid, funcmode);
125         RAISE;
126      WHEN OTHERS THEN
127         wf_core.context('OKL_AM_OM_REMARKET_WF' , 'reduce_item_quantity', itemtype, itemkey, actid, funcmode);
128         RAISE;
129 
130   END reduce_item_quantity;
131 
132 
133 
134     -- Start of comments
135   --
136   -- Procedure Name	: dispose_asset
137   -- Description    : Dispose Asset request from WF
138   -- Business Rules	:
139   -- Parameters		: itemtype, itemkey, actid, funcmode, resultout
140   -- Version		: 1.0
141   -- History        : 21-OCT-04 SECHAWLA 3924244 : Modified procedures to work on order line instead of header
142   -- End of comments
143   PROCEDURE dispose_asset(  itemtype	IN VARCHAR2,
144 				            itemkey  	IN VARCHAR2,
145 			                actid		IN NUMBER,
146 			                funcmode	IN VARCHAR2,
147 				            resultout OUT NOCOPY VARCHAR2 )IS
148 
149 	x_return_status                 VARCHAR2(1)  := OKC_API.G_RET_STS_SUCCESS;
150     x_msg_count                     NUMBER;
151     x_msg_data                      VARCHAR2(2000);
152     p_api_version                   NUMBER       := 1;
153     p_init_msg_list                 VARCHAR2(1) := 'T';
154     l_id		                    NUMBER;
155     error_disposing_asset           EXCEPTION;
156     --ADDED BY AKRANGAN FOR SETTING THE CONTEXT FOR THE WF CALL
157     l_ctxt_result                   VARCHAR2(20);
158     BEGIN
159       --ADDED BY AKRANGAN FOR SETTING THE CONTEXT FOR THE WF CALL BEGIN
160       set_context(itemtype => itemtype,
161                   itemkey => itemkey,
162 		  actid => actid,
163 		  resultout => l_ctxt_result
164 		  );
165       --ADDED BY AKRANGAN FOR SETTING THE CONTEXT FOR THE WF CALL END
166 
167       IF (funcmode = 'RUN') THEN
168 		-- SECHAWLA 21-OCT-04 3924244 : l_id will now be the order line id as this step is moved to the line WF
169      	l_id := to_number(itemkey);
170 
171 		OKL_AM_ASSET_DISPOSE_PUB.dispose_asset (      p_api_version          => p_api_version,
172                                                       p_init_msg_list        => p_init_msg_list,
173                                                       x_return_status        => x_return_status,
174                                                       x_msg_count            => x_msg_count,
175                                                       x_msg_data             => x_msg_data,
176                                                       p_order_line_Id        => l_id);
177 
178 
179         IF x_return_status = OKC_API.G_RET_STS_SUCCESS THEN
180 			resultout := 'COMPLETE:PASS';
181 		ELSE
182 			resultout := 'COMPLETE:';
183             RAISE error_disposing_asset;
184 		END IF;
185 
186         RETURN ;
187 
188       END IF;
189       --
190       -- CANCEL mode
191       --
192       IF (funcmode = 'CANCEL') THEN
193         --
194         resultout := 'COMPLETE:';
195         RETURN;
196         --
197       END IF;
198       --
199       -- TIMEOUT mode
200       --
201       IF (funcmode = 'TIMEOUT') THEN
202         --
203         resultout := 'COMPLETE:';
204         RETURN;
205         --
206       END IF;
207 
208   EXCEPTION
209      WHEN error_disposing_asset THEN
210         wf_core.context('OKL_AM_OM_REMARKET_WF' , 'dispose_asset', itemtype, itemkey, actid, funcmode);
211         RAISE;
212      WHEN OTHERS THEN
213         wf_core.context('OKL_AM_OM_REMARKET_WF' , 'dispose_asset', itemtype, itemkey, actid, funcmode);
214         RAISE;
215 
216   END dispose_asset;
217 
218       -- Start of comments
219   --
220   -- Procedure Name	: set_asset_return_status
221   -- Description    : Set The asset return status to 'Remarketed' if all units are sold
222   -- Business Rules	:
223   -- Parameters		: itemtype, itemkey, actid, funcmode, resultout
224   -- Version		: 1.0
225   -- History        : 21-OCT-04 SECHAWLA 3924244 : Modified procedures to work on order line instead of header
226   -- End of comments
227   PROCEDURE set_asset_return_status(
228                             itemtype	IN VARCHAR2,
229 				            itemkey  	IN VARCHAR2,
230 			                actid		IN NUMBER,
231 			                funcmode	IN VARCHAR2,
232 				            resultout OUT NOCOPY VARCHAR2 )IS
233 
234 	x_return_status                 VARCHAR2(1)  := OKC_API.G_RET_STS_SUCCESS;
235     x_msg_count                     NUMBER;
236     x_msg_data                      VARCHAR2(2000);
237     p_api_version                   NUMBER       := 1;
238     p_init_msg_list                 VARCHAR2(1) := 'T';
239     l_id		                    NUMBER;
240     l_total_quantity                NUMBER;
241     l_original_quantity             NUMBER;
242     l_ars_code                      VARCHAR2(30);
243     lp_artv_rec                     artv_rec_type;
244     lx_artv_rec                     artv_rec_type;
245     l_asset_return_id               NUMBER;
246     error_setting_status            EXCEPTION;
247 
248     /* -- SECHAWLA 21-OCT-04 3924244
249     -- This cursor is used to get all the Order Lines for a given Order
250     CURSOR l_orderlines_csr(p_id NUMBER) IS
251     SELECT line_id, inventory_item_id
252     FROM   oe_order_lines_all
253     WHERE  header_id = p_id;
254     */
255 
256     -- SECHAWLA 21-OCT-04 3924244
257     -- This cursor is used to get all the Order Lines for a given Order
258     CURSOR l_orderlines_csr(cp_line_id NUMBER) IS
259     SELECT inventory_item_id
260     FROM   oe_order_lines_all
261     WHERE  line_id = cp_line_id;
262 
263     -- This cursor is used to get the ordered quantity for all the orders booked against a given inventory item
264     -- For a given inventory Item, this cursor will return all rows with same asset return Id (art_id) and possibly
265     -- different order header Ids
266     --Changed following queries to directly use base tables instead of uv for performance --dkagrawa
267     CURSOR l_assetsale_csr(p_item_id NUMBER) IS
268     SELECT ar.id art_id ,l.ordered_quantity ordered_quantity
269     FROM   oe_order_headers_all h,
270            oe_order_lines_all l,
271            mtl_system_items_b i,
272            okl_asset_returns_b ar
273     WHERE h.header_id = l.header_id
274     and l.ship_from_org_id = i.organization_id
275     AND l.inventory_item_id = i.inventory_item_id
276     AND l.inventory_item_id = ar.imr_id
277     AND h.flow_status_code = 'BOOKED'
278     AND i.inventory_item_id = p_item_id
279     AND l.inventory_item_id = p_item_id;
280 
281     -- This cursor is used to get the Original Asset Return Quantity for an inventory item.
282     CURSOR l_assetreturns_csr(p_id NUMBER) IS
283     SELECT cim.number_of_items quantity, oar.ars_code ars_code
284     FROM   okc_k_lines_b kle,
285            okl_asset_returns_all_b oar,
286            okc_k_lines_b kle2,
287            okc_line_styles_b lse,
288            okc_k_items cim
289     WHERE  oar.kle_id = kle.id
290     AND kle.id = kle2.cle_id
291     AND kle2.lse_id = lse.id
292     AND lse.lty_code = 'ITEM'
293     AND kle2.id = cim.cle_id
294     AND oar.id = p_id;
295 
296     --ADDED BY AKRANGAN FOR SETTING THE CONTEXT FOR THE WF CALL
297     l_ctxt_result                   VARCHAR2(20);
298     BEGIN
299       --ADDED BY AKRANGAN FOR SETTING THE CONTEXT FOR THE WF CALL BEGIN
300       set_context(itemtype => itemtype,
301                   itemkey => itemkey,
302 		  actid => actid,
303 		  resultout => l_ctxt_result
304 		  );
305       --ADDED BY AKRANGAN FOR SETTING THE CONTEXT FOR THE WF CALL END
306 
307       IF (funcmode = 'RUN') THEN
308 
309         -- SECHAWLA 21-OCT-04 3924244 : l_id will now be the order line id as this step is moved to the line WF
310      	l_id := to_number(itemkey);
311 
312 		-- SECHAWLA 21-OCT-04 3924244 : the following loop on l_orderlines_csr will return only 1 row
313         -- Loop thru all the order lines for a particular order
314         FOR l_orderlines_rec IN l_orderlines_csr(l_id) LOOP
315             l_total_quantity := 0;
316             l_asset_return_id := NULL;
317 
318             -- Calculate the total Sold quantity for an inventory item of each Order Line
319             FOR l_assetsale_rec IN l_assetsale_csr(l_orderlines_rec.inventory_item_id) LOOP
320                 l_asset_return_id := l_assetsale_rec.art_id; -- should be same for all the rows
321                 l_total_quantity := l_total_quantity +  l_assetsale_rec.ordered_quantity;
322 
323             END LOOP;
324 
325             IF l_asset_return_id IS NOT NULL THEN
326                 -- get the Original quantity corresponding to an asset return.
327                 OPEN  l_assetreturns_csr(l_asset_return_id);
328                 FETCH l_assetreturns_csr INTO l_original_quantity, l_ars_code;
329                 CLOSE l_assetreturns_csr;
330 
331 
332                 IF l_total_quantity >= l_original_quantity THEN
333                     IF l_ars_code = 'AVAILABLE_FOR_SALE' THEN
334                         -- call update of tapi
335                         lp_artv_rec.id := l_asset_return_id;
336                         lp_artv_rec.ars_code := 'REMARKETED';
337 
338                         OKL_ASSET_RETURNS_PUB.update_asset_returns(
339                         p_api_version        => p_api_version,
340                         p_init_msg_list      => OKL_API.G_FALSE,
341                         x_return_status      => x_return_status,
342                         x_msg_count          => x_msg_count,
343                         x_msg_data           => x_msg_data,
344                         p_artv_rec           => lp_artv_rec,
345                         x_artv_rec           => lx_artv_rec);
346 
347                         IF x_return_status <> OKC_API.G_RET_STS_SUCCESS THEN
348                            resultout := 'COMPLETE:';
349                            RAISE error_setting_status;
350 
351                         END IF;
352 
353 
354                      END IF;
355                 END IF;
356             END IF;
357 
358 
359         END LOOP;
360 
361 
362         resultout := 'COMPLETE:PASS';
363         RETURN ;
364 
365       END IF;
366       --
367       -- CANCEL mode
368       --
369       IF (funcmode = 'CANCEL') THEN
370         --
371         resultout := 'COMPLETE:';
372         RETURN;
373         --
374       END IF;
375       --
376       -- TIMEOUT mode
377       --
378       IF (funcmode = 'TIMEOUT') THEN
379         --
380         resultout := 'COMPLETE:';
381         RETURN;
382         --
383       END IF;
384 
385   EXCEPTION
386      WHEN error_setting_status THEN
387         IF l_orderlines_csr%ISOPEN THEN
388            CLOSE l_orderlines_csr;
389         END IF;
390         IF l_assetsale_csr%ISOPEN THEN
391            CLOSE l_assetsale_csr;
392         END IF;
393         IF l_assetreturns_csr%ISOPEN THEN
394            CLOSE l_assetreturns_csr;
395         END IF;
396         wf_core.context('OKL_AM_OM_REMARKET_WF' , 'set_asset_return_status', itemtype, itemkey, actid, funcmode);
397         RAISE;
398      WHEN OTHERS THEN
399         IF l_orderlines_csr%ISOPEN THEN
400            CLOSE l_orderlines_csr;
401         END IF;
402         IF l_assetsale_csr%ISOPEN THEN
403            CLOSE l_assetsale_csr;
404         END IF;
405         IF l_assetreturns_csr%ISOPEN THEN
406            CLOSE l_assetreturns_csr;
407         END IF;
408         wf_core.context('OKL_AM_OM_REMARKET_WF' , 'set_asset_return_status', itemtype, itemkey, actid, funcmode);
409         RAISE;
410 
411   END set_asset_return_status;
412 
413   -- Start of comments
414   --
415   -- Procedure Name	: create_invoice
416   -- Description    : Create a remarket invoice for each order line
417   -- Business Rules	:
418   -- Parameters		: itemtype, itemkey, actid, funcmode, resultout
419   -- Version		: 1.0
420   -- History        : 21-OCT-04 SECHAWLA 3924244 : Modified procedures to work on order line instead of header
421   -- End of comments
422   PROCEDURE create_invoice(
423                             itemtype	IN VARCHAR2,
424 				            itemkey  	IN VARCHAR2,
425 			                actid		IN NUMBER,
426 			                funcmode	IN VARCHAR2,
427 				            resultout   OUT NOCOPY VARCHAR2 )IS
428 
429 	x_return_status                 VARCHAR2(1)  := OKC_API.G_RET_STS_SUCCESS;
430     x_msg_count                     NUMBER;
431     x_msg_data                      VARCHAR2(2000);
432     p_api_version                   NUMBER       := 1;
433     p_init_msg_list                 VARCHAR2(1) := 'T';
434     l_id		                    NUMBER;
435     l_total_quantity                NUMBER;
436     l_original_quantity             NUMBER;
437     l_ars_code                      VARCHAR2(30);
438     lp_artv_rec                     artv_rec_type;
439     lx_artv_rec                     artv_rec_type;
440     l_asset_return_id               NUMBER;
441     lx_taiv_tbl                     taiv_tbl_type;
442     error_creating_invoice          EXCEPTION;
443 
444     /* -- SECHAWLA 21-OCT-04 3924244
445     -- This cursor is used to get all the Order Lines for a given Order
446     CURSOR l_orderlines_csr(p_id NUMBER) IS
447     SELECT line_id, inventory_item_id
448     FROM   oe_order_lines_all
449     WHERE  header_id = p_id;
450     */
451 
452     --ADDED BY AKRANGAN FOR SETTING THE CONTEXT FOR THE WF CALL
453     l_ctxt_result                   VARCHAR2(20);
454     BEGIN
455       --ADDED BY AKRANGAN FOR SETTING THE CONTEXT FOR THE WF CALL BEGIN
456       set_context(itemtype => itemtype,
457                   itemkey => itemkey,
458 		  actid => actid,
459 		  resultout => l_ctxt_result
460 		  );
461       --ADDED BY AKRANGAN FOR SETTING THE CONTEXT FOR THE WF CALL END
462 
463       IF (funcmode = 'RUN') THEN
464 
465         -- SECHAWLA 21-OCT-04 3924244 : l_id will now be the order line id as this step is moved to the line WF
466      	l_id := to_number(itemkey);
467 
468         -- SECHAWLA 21-OCT-04 3924244 : commented out the loop
469 	    --FOR l_orderlines_rec IN l_orderlines_csr(l_id) LOOP
470 
471             okl_am_invoices_pvt.Create_Remarket_Invoice (
472 	                                   p_api_version		=> p_api_version,
473 	                                   p_init_msg_list		=> p_init_msg_list,
474 	                                   x_msg_count		    => x_msg_count,
475 	                                   x_msg_data		    => x_msg_data,
476 	                                   x_return_status		=> x_return_status,
477 	                                   p_order_line_id		=> l_id,
478                                        x_taiv_tbl		    => lx_taiv_tbl);
479 
480             IF x_return_status <> OKC_API.G_RET_STS_SUCCESS THEN
481                 resultout := 'COMPLETE:';
482                 RAISE error_creating_invoice;
483             END IF;
484 
485        -- END LOOP;
486 
487 
488         resultout := 'COMPLETE:PASS';
489         RETURN ;
490 
491       END IF;
492       --
493       -- CANCEL mode
494       --
495       IF (funcmode = 'CANCEL') THEN
496         --
497         resultout := 'COMPLETE:';
498         RETURN;
499         --
500       END IF;
501       --
502       -- TIMEOUT mode
503       --
504       IF (funcmode = 'TIMEOUT') THEN
505         --
506         resultout := 'COMPLETE:';
507         RETURN;
508         --
509       END IF;
510 
511   EXCEPTION
512      WHEN error_creating_invoice THEN
513         /*IF l_orderlines_csr%ISOPEN THEN
514            CLOSE l_orderlines_csr;
515         END IF;*/
516         wf_core.context('OKL_AM_OM_REMARKET_WF' , 'create_invoice', itemtype, itemkey, actid, funcmode);
517         RAISE;
518      WHEN OTHERS THEN
519         /*IF l_orderlines_csr%ISOPEN THEN
520            CLOSE l_orderlines_csr;
521         END IF; */
522         wf_core.context('OKL_AM_OM_REMARKET_WF' , 'create_invoice', itemtype, itemkey, actid, funcmode);
523         RAISE;
524 
525   END create_invoice;
526 
527 
528 
529 END OKL_AM_OM_REMARKET_WF;