DBA Data[Home] [Help]

PACKAGE BODY: APPS.GME_INCREMENTAL_BACKFLUSH_PVT

Source


1 PACKAGE BODY gme_incremental_backflush_pvt AS
2 /* $Header: GMEVIBFB.pls 120.28.12020000.2 2012/07/26 15:37:53 gmurator ship $
3 
4  This file contains the procedure for partial certifying batches in OPM.
5 
6  **********************************************************************
7  *                                                                    *
8  * FILE:    GMEVIBFB.pls                                              *
9  * PURPOSE: Package Body for GME_INCREMENTAL_BACKFLUSH_PVT routines   *
10  * AUTHOR:  A. Newbury                                                *
11  * DATE:    June 2005                                                 *
12  * CONTENTS:                                                          *
13  *                                                                    *
14  * HISTORY:                                                           *
15  * ========                                                           *
16 
17  * G. Muratore    02-Jul-2009 Bug 8639523
18  *   No need to do negative inventory checking for phantom prods or ingredients.
19  *   PROCEDURE: revert_material_partial
20 
21  * G. Muratore    26-Jan-2010 Bug 10378355
22  *   Institute new algorithm for deriving factor to be applied to resources.
23  *   This is to account for the fact that wip plan qty concept does not exist
24  *   on the resource side.
25  *   PROCEDURE: derive_factor
26  **********************************************************************
27 */
28 /*  Global variables   */
29 G_PKG_NAME  CONSTANT  VARCHAR2(30):='GME_INCREMENTAL_BACKFLUSH_PVT';
30 G_DEBUG VARCHAR2(5) := FND_PROFILE.VALUE('AFLOG_LEVEL');
31 
32 /* ===========================================================================================
33 Procedure
34   incremental_backflush
35 Description
36   This procedure performs incremental backflush for a batch based on a material detail
37 Parameters
38   p_batch_header_rec            The batch header record
39   p_material_detail_rec         The material detail record to base IB from
40   p_qty                         Incremental qty
41   p_qty_type                    Incremental qty type:
42                                   increment qty (0),
43                                   new act qty   (1) or
44                                   % wip_plan    (2)
45   p_trans_date                  Date for transactions
46   p_resource_backflush          This is calculated in gme_api_main because for phantom
47                                 IB, the material detail always comes in as a product.
48                                 The resource backflushing should be carried through from
49                                 parent to child batches as determined by the material that
50                                 the backflush was originated from, not from each iteration
51                                 of the backflushing.  Therefore, as a central point, gme_api_main
52                                 is the best place to determine this (for use by form and pub) and
53                                 this will be passed down through each phantom iteration (not recalculated).
54   x_return_status               Outcome of the API call
55                                 S - Success
56                                 E - Error
57                                 U - Unexpected error
58                                 X - Batch Exception occurred
59 
60 History
61  Sivakumar.G FPBug#4667093 05-NOV-2005
62    Changed code to respect new gme parameter, when deriving factor to be used against the detail lines.
63    Also, introduced code that respects integer scaling setting once new actual is derived.
64 
65  Sivakumar.G Bug#5111078 29-MAR-2006
66   validate_material_for_IB is changed for not allowing IB for Lab Batches with update inventory off. And
67   plan_qty = 0 check is replaced by wip_plan_qty
68 
69  G. Muratore     12-Feb-2009   Bug 7709971
70   Back out and rework 7286054 as now phantom ingredient gets double posting. Reinstated elsif
71   phantom ingredients are reconciled by the phantom prod yield.
72   Note: We could not duplicate this problem with lot control items even with 7286054 in place.
73   New fix works for all item types.
74 
75  G. Muratore     04-Mar-2009   Bug 8267588
76   Once a new_actual is derived for a given line, round it to 5 decimal places.
77 
78  G. Muratore     21-May-2009   Bug 8508788
79   Update any new transaction that was created for this item/step and all dependent steps with the
80   trans_date passed in by the user or sysdate.
81   Also, reworked 8516257 which was an additional rework of bug Bug 7709971 and 7286054. Typo was corrected.
82 
83  G. Muratore     02-Jun-2009   Bug 8508788 - Backout resource txn date piece of previous fix by commenting the lines.
84   We may need to reinstitute this code as part of a bigger fix down the road after getting full design.
85 
86  G. Muratore     19-Jun-2009   Bug 8508788
87   Reinstating the original fix with PM approval. One modification. The trans_date passed in, or sysdate,
88   will be used only if it is later than the actual start date of the resource.
89 
90  G. Muratore     19-MAR-2010   Bug 8751983
91   Changed order by clause to fetch material transactions so that for negative IB
92   they are processed in reverse trans order. Also, stamp resource transactions
93   affected by IB with user entered IB date. Additional issue addressed here is bug 9072371.
94   Do not reverse lot transactions if it will lead to a negative inventory balance.
95   PROCEDURE: revert_material_partial
96 
97  G. Muratore     09-APR-2010   Bug 9560022
98   Round new actual before comparing to original actual.
99 
100  G. Muratore     05-MAY-2010   Bug 9628831
101   Do not update the actual quantity for non transactable material items.
102 ========================================================================================================*/
103   PROCEDURE incremental_backflush
104     (p_batch_header_rec           IN GME_BATCH_HEADER%ROWTYPE
105     ,p_material_detail_rec        IN GME_MATERIAL_DETAILS%ROWTYPE
106     ,p_qty                        IN NUMBER
107     ,p_qty_type                   IN NUMBER
108     ,p_trans_date                 IN DATE
109     ,p_backflush_rsrc_usg_ind     IN NUMBER
110     ,x_exception_material_tbl     IN OUT NOCOPY gme_common_pvt.exceptions_tab
111     ,x_return_status              OUT NOCOPY VARCHAR2) IS
112 
113     l_api_name   CONSTANT VARCHAR2(30) := 'incremental_backflush';
114 
115     CURSOR Cur_fetch_incr_mat_dtl(v_batch_id NUMBER, v_matl_dtl_id NUMBER) IS
116       SELECT *
117       FROM   gme_material_details
118       WHERE  batch_id = v_batch_id
119       AND    (release_type = gme_common_pvt.g_mtl_incremental_release
120               OR
121               (release_type = gme_common_pvt.g_mtl_manual_release AND material_detail_id = v_matl_dtl_id)
122              )
123       AND    wip_plan_qty <> 0
124       ORDER BY line_type,line_no;
125 
126     CURSOR Cur_assoc_step(v_batch_id NUMBER) IS
127       SELECT *
128       FROM   gme_batch_steps
129       WHERE  batchstep_id IN (SELECT DISTINCT batchstep_id
130                               FROM   gme_batch_step_items
131                               WHERE  batch_id = v_batch_id);
132 
133     CURSOR Cur_prod_assoc(V_batch_id NUMBER, V_material_detail_id NUMBER) IS
134       SELECT s.*
135       FROM   gme_batch_step_items m, gme_batch_steps s
136       WHERE  m.batch_id = V_batch_id
137       AND    m.material_detail_id = V_material_detail_id
138       AND    s.batch_id = m.batch_id
139       AND    s.batchstep_id = m.batchstep_id
140       AND    s.step_status = gme_common_pvt.g_step_wip;
141 
142     --FPBug#4667093 get the IB Factor settings
143     CURSOR Cur_ib_factor(V_org_id VARCHAR2) IS
144      SELECT ib_factor_ind
145        FROM gme_parameters
146       WHERE organization_id = V_org_id;
147 
148     l_item_rec                    mtl_system_items%ROWTYPE;
149 
150     l_phantom_batch_rec           gme_batch_header%ROWTYPE;
151     l_batch_header_rec            gme_batch_header%ROWTYPE;
152     l_material_detail_rec         gme_material_details%ROWTYPE;
153     l_in_material_detail_rec      gme_material_details%ROWTYPE;
154     l_phantom_material_rec        gme_material_details%ROWTYPE;
155     l_material_detail_tbl         gme_common_pvt.material_details_tab;
156 
157     l_batch_step_rec              gme_batch_steps%ROWTYPE;
158     l_in_batch_step_rec           gme_batch_steps%ROWTYPE;
159     l_step_tbl                    gme_common_pvt.steps_tab;
160 
161     l_incr_qty                    NUMBER;
162     l_decr_qty                    NUMBER;
163     l_incr_factor                 NUMBER;
164     l_incr_factor_res             NUMBER;
165     l_new_actual                  NUMBER;
166     l_actual_qty                  NUMBER;
167     l_upd_material                BOOLEAN;
168     l_lot_divisible_flag          VARCHAR2(1);
169 
170     l_return_status               VARCHAR2 (1);
171     l_msg_count                   NUMBER;
172     l_msg_stack                   VARCHAR2 (2000);
173 
174     --FPBug#4667093
175     l_hold_new_actual             NUMBER;
176     l_ib_factor                   NUMBER := 0;
177     l_scale_rec                   gmd_common_scale.scale_rec;
178     l_scale_rec_out               gmd_common_scale.scale_rec;
179 
180     qty_create_negative_actual    EXCEPTION;
181     error_derive_factor           EXCEPTION;
182     error_get_item                EXCEPTION;
183     error_revert_matl_full        EXCEPTION;
184     ERROR_UPDATING_STEPS          EXCEPTION;
185     error_phantom_backflush       EXCEPTION;
186     error_fetch_batch             EXCEPTION;
187     error_fetch_matl              EXCEPTION;
188     error_update_row              EXCEPTION;
189     error_consum_yield            EXCEPTION;
190     update_step_qty_error         EXCEPTION;
191     error_revert_matl_part        EXCEPTION;
192     error_cant_go_neg             EXCEPTION;
193 
194 
195   BEGIN
196     IF nvl(g_debug, gme_debug.g_log_procedure + 1) <= gme_debug.g_log_procedure THEN
197       gme_debug.put_line('Entering api '||g_pkg_name||'.'||l_api_name);
198       gme_debug.put_line(g_pkg_name||'.'||l_api_name||' batch_id='||p_batch_header_rec.batch_id);
199       gme_debug.put_line(g_pkg_name||'.'||l_api_name||' material_detail_id='||p_material_detail_rec.material_detail_id);
200       gme_debug.put_line(g_pkg_name||'.'||l_api_name||' line_no='||p_material_detail_rec.line_no);
201       gme_debug.put_line(g_pkg_name||'.'||l_api_name||' line_type='||p_material_detail_rec.line_type);
202       gme_debug.put_line(g_pkg_name||'.'||l_api_name||' p_qty='||p_qty);
203       gme_debug.put_line(g_pkg_name||'.'||l_api_name||' p_qty_type='||p_qty_type);
204       gme_debug.put_line(g_pkg_name||'.'||l_api_name||' p_backflush_rsrc_usg_ind='||p_backflush_rsrc_usg_ind);
205       IF p_trans_date IS NULL THEN
206         gme_debug.put_line(g_pkg_name||'.'||l_api_name||' p_trans_date IS NULL');
207       ELSE
208         gme_debug.put_line(g_pkg_name||'.'||l_api_name||' p_trans_date='||to_char(p_trans_date, 'DD-MON-YYYY HH24:MI:SS'));
209       END IF;
210       gme_debug.put_line(g_pkg_name||'.'||l_api_name||' gme_common_pvt.g_move_to_temp='||gme_common_pvt.g_move_to_temp);
211     END IF;
212 
213     /* Set the return status to success initially */
214     x_return_status       := FND_API.G_RET_STS_SUCCESS;
215 
216     -- set local variables for batch and detail...
217     l_batch_header_rec       := p_batch_header_rec;
218     l_in_material_detail_rec := p_material_detail_rec;
219 
220     --FPBug#4667093 Begin
221     OPEN Cur_ib_factor(l_batch_header_rec.organization_id);
222     FETCH Cur_ib_factor INTO l_ib_factor;
223     CLOSE Cur_ib_factor;
224     --FPBug#4667093 End
225 
226     -- derive factor
227     IF nvl(l_batch_header_rec.parentline_id,0) = 0 THEN
228       --FPBug#4667093 added p_gme_ib_factor parameter with value 0
229       derive_factor
230           (p_material_detail_rec       => l_in_material_detail_rec
231           ,p_qty                       => p_qty
232           ,p_qty_type                  => p_qty_type
233 	  ,p_gme_ib_factor             => 0
234           ,x_pct_plan                  => l_incr_factor
235           ,x_pct_plan_res              => l_incr_factor_res
236           ,x_return_status             => l_return_status);
237 
238       --FPBug#4667093 Begin
239       IF ( NVL(G_DEBUG,-1) <= GME_DEBUG.G_LOG_STATEMENT ) THEN
240         gme_debug.put_line (g_pkg_name||'.'||l_api_name||'Single Product:l_incr_factor= '||l_incr_factor);
241       END IF;
242 
243       /* add the incr qty to old actual to come up with new actual
244          as l_incr_factor now depicts the percent increase from previous actual
245        */
246       l_hold_new_actual := l_in_material_detail_rec.actual_qty +
247                       ((l_in_material_detail_rec.wip_plan_qty * l_incr_factor) / 100);
248 
249       /* if IB is driven off by product line and ib factor calculaion is total products */
250       IF l_in_material_detail_rec.line_type =  1 AND l_ib_factor = 1 THEN
251         derive_factor
252           (p_material_detail_rec       => l_in_material_detail_rec
253           ,p_qty                       => p_qty
254           ,p_qty_type                  => p_qty_type
255 	  ,p_gme_ib_factor             => 1
256           ,x_pct_plan                  => l_incr_factor
257           ,x_pct_plan_res              => l_incr_factor_res
258           ,x_return_status             => l_return_status);
259       END IF;
260 
261       IF l_return_status <> FND_API.G_RET_STS_SUCCESS THEN
262         RAISE error_derive_factor;
263       END IF;
264 
265       IF ( NVL(G_DEBUG,-1) = GME_DEBUG.G_LOG_STATEMENT ) THEN
266         gme_debug.put_line (g_pkg_name||'.'||l_api_name||' l_incr_factor= '||l_incr_factor);
267         gme_debug.put_line (g_pkg_name||'.'||l_api_name||' l_incr_factor_res= '||l_incr_factor_res);
268 	gme_debug.put_line (g_pkg_name||'.'||l_api_name||' l_hold_new_actual= '||l_hold_new_actual);
269       END IF;
270       --FPBug#4667093 End
271     ELSE
272       -- if this is a phantom batch, the qty passed is the incr factor as already calculated
273       -- in the parent batch
274       l_incr_factor := p_qty;
275 
276       --FPBug#4667093 Begin
277       /* add the incr qty to old actual to come up with new actual
278          as l_incr_factor now depicts the percent increase from previous actual
279        */
280       l_hold_new_actual := l_in_material_detail_rec.actual_qty +
281                       ((l_in_material_detail_rec.wip_plan_qty * l_incr_factor) / 100);
282 
283       IF ( NVL(G_DEBUG,-1) = GME_DEBUG.G_LOG_STATEMENT ) THEN
284        gme_debug.put_line (g_pkg_name||'.'||l_api_name||' phantom batch; l_incr_factor= '||l_incr_factor);
285        gme_debug.put_line (g_pkg_name||'.'||l_api_name||' l_hold_new_actual= '||l_hold_new_actual);
286       END IF;
287       --FPBug#4667093 End
288 
289     END IF;
290 
291     -- Fetch all the incremental material lines of the batch and the passed in material line if manual
292     OPEN Cur_fetch_incr_mat_dtl(l_in_material_detail_rec.batch_id
293                                ,l_in_material_detail_rec.material_detail_id);
294     FETCH Cur_fetch_incr_mat_dtl BULK COLLECT INTO l_material_detail_tbl;
295     CLOSE Cur_fetch_incr_mat_dtl;
296 
297     FOR i IN 1 .. l_material_detail_tbl.COUNT LOOP
298       l_material_detail_rec := l_material_detail_tbl (i);
299 
300       IF ( NVL(G_DEBUG,-1) = GME_DEBUG.G_LOG_STATEMENT ) THEN
301         gme_debug.put_line (g_pkg_name||'.'||l_api_name||' -------------------------------------');
302         gme_debug.put_line (g_pkg_name||'.'||l_api_name||' TOP of material detail loop; processing material_detail_id: '||l_material_detail_rec.material_detail_id);
303       END IF;
304 
305       --FPBug#4667093 add IF condition
306       /* if material line is same as the line which drives IB then don't calculate new actual */
307       IF l_material_detail_rec.material_detail_id = l_in_material_detail_rec.material_detail_id THEN
308         l_new_actual := l_hold_new_actual;
309 	IF ( NVL(G_DEBUG,-1) <= GME_DEBUG.G_LOG_STATEMENT ) THEN
310          gme_debug.put_line (g_pkg_name||'.'||l_api_name||'IB Driven new actual: '||l_new_actual);
311         END IF;
312       ELSE
313         IF (l_material_detail_rec.scale_type = 0) THEN
314           -- set actual qty for fixed line only if it is zero
315           -- fixed items will have already been set the first time through
316           IF (l_material_detail_rec.actual_qty = 0) THEN
317             l_new_actual := l_material_detail_rec.wip_plan_qty;
318 
319             IF ( NVL(G_DEBUG,-1) = GME_DEBUG.G_LOG_STATEMENT ) THEN
320               gme_debug.put_line (g_pkg_name||'.'||l_api_name||' fixed scale: new actual: '||l_new_actual);
321             END IF;
322           ELSE
323             l_new_actual := l_material_detail_rec.actual_qty;
324             IF ( NVL(G_DEBUG,-1) = GME_DEBUG.G_LOG_STATEMENT ) THEN
325               gme_debug.put_line (g_pkg_name||'.'||l_api_name||' fixed scale: same actual: '||l_new_actual);
326             END IF;
327           END IF; /* l_material_detail_rec.actual_qty = 0 */
328         ELSE
329           IF ( NVL(G_DEBUG,-1) = GME_DEBUG.G_LOG_STATEMENT ) THEN
330             gme_debug.put_line (g_pkg_name||'.'||l_api_name||' actual_qty= '||l_material_detail_rec.actual_qty);
331             gme_debug.put_line (g_pkg_name||'.'||l_api_name||' wip_plan_qty= '||l_material_detail_rec.wip_plan_qty);
332           END IF;
333 
334 	  -- add the incr qty to old actual to come up with new actual
335           -- as p_incr_factor now depicts the percent increase from previous actual.
336           l_new_actual := l_material_detail_rec.actual_qty +
337                           ((l_material_detail_rec.wip_plan_qty * l_incr_factor) / 100);
338           IF ( NVL(G_DEBUG,-1) = GME_DEBUG.G_LOG_STATEMENT ) THEN
339             gme_debug.put_line (g_pkg_name||'.'||l_api_name||' not fixed scale: new actual: '||l_new_actual);
340           END IF;
341 
342           --FPBug#4667093 Begin
343           IF (l_material_detail_rec.scale_type = 2) THEN
344               l_scale_rec.scale_rounding_variance := l_material_detail_rec.scale_rounding_variance;
345               l_scale_rec.qty := l_new_actual;
346               l_scale_rec.scale_multiple := l_material_detail_rec.scale_multiple;
347               l_scale_rec.rounding_direction := l_material_detail_rec.rounding_direction;
348 
349 	      IF (NVL(G_DEBUG,-1) = GME_DEBUG.G_LOG_STATEMENT) THEN
350                 gme_debug.put_line('values going to int mult scale are: ');
351                 gme_debug.put_line('qty '||l_scale_rec.qty);
352                 gme_debug.put_line('rnd variance '||l_scale_rec.scale_rounding_variance);
353                 gme_debug.put_line('multiple '||l_scale_rec.scale_multiple);
354                 gme_debug.put_line('rnd direction '||l_scale_rec.rounding_direction);
355               END IF;
356 
357 	      gmd_common_scale.integer_multiple_scale
358                  (  p_scale_rec          => l_scale_rec
359                    ,x_scale_rec          => l_scale_rec_out
360                    ,x_return_status      => l_return_status
361                  );
362 
363 	      IF l_return_status <> FND_API.G_RET_STS_SUCCESS THEN
364                  RAISE error_cant_go_neg;
365               END IF;
366 
367               l_new_actual := l_scale_rec_out.qty;
368 
369               IF (NVL(G_DEBUG,-1) = GME_DEBUG.G_LOG_STATEMENT) THEN
370                  gme_debug.put_line('new actual after integer scaling is '||l_new_actual);
371               END IF;
372            END IF; /* l_material_detail_rec.scale_type = 2 */
373 	   --FPBug#4667093 End
374         END IF;  -- IF (l_material_detail_rec.scale_type = 0)
375      END IF; /*l_material_detail_rec.material_detail_id = p_material_detail_rec.material_detail_id*/
376 
377       -- Bug 8267588 - Round the actual qty to 5 decimal places.
378       l_new_actual := ROUND(l_new_actual, 5);
379       IF (NVL(G_DEBUG,-1) = GME_DEBUG.G_LOG_STATEMENT) THEN
380          gme_debug.put_line('new actual after rounding is '||l_new_actual);
381       END IF;
382 
383       -- Bug 9560022 - Moved this check so that it happens after rounding is done.
384       IF l_new_actual < 0 THEN
385         IF ( NVL(G_DEBUG,-1) = GME_DEBUG.G_LOG_STATEMENT ) THEN
386           gme_debug.put_line (g_pkg_name||'.'||l_api_name||' raising error; new actual= '||l_new_actual);
387         END IF;
388         RAISE error_cant_go_neg;
389       END IF;
390 
391       l_incr_qty := ROUND(l_new_actual - l_material_detail_rec.actual_qty, 5);
392 
393       gme_material_detail_pvt.get_item_rec
394                         (p_org_id                => l_material_detail_rec.organization_id
395                         ,p_item_id               => l_material_detail_rec.inventory_item_id
396                         ,x_item_rec              => l_item_rec
397                         ,x_return_status         => l_return_status);
398 
399       IF l_return_status <> FND_API.G_RET_STS_SUCCESS THEN
400         x_return_status := l_return_status;
401         RAISE error_get_item;
402       END IF;
403 
404       IF l_item_rec.lot_control_code = 2 AND NVL(l_item_rec.lot_divisible_flag,'Y') = 'N' THEN
405         l_lot_divisible_flag := 'N';
406       ELSE
407         l_lot_divisible_flag := 'Y';
408       END IF;
409 
410       IF l_material_detail_rec.phantom_id IS NOT NULL THEN
411         l_phantom_batch_rec.batch_id := l_material_detail_rec.phantom_id;
412 
413         IF NOT gme_batch_header_dbl.fetch_row(l_phantom_batch_rec, l_phantom_batch_rec) THEN
414           RAISE error_fetch_batch;
415         END IF;
416 
417         l_phantom_material_rec.material_detail_id := l_material_detail_rec.phantom_line_id;
418 
419         IF NOT gme_material_details_dbl.fetch_row(l_phantom_material_rec, l_phantom_material_rec) THEN
420           RAISE error_fetch_matl;
421         END IF;
422 
423         IF ( NVL(G_DEBUG,-1) = GME_DEBUG.G_LOG_STATEMENT ) THEN
424           gme_debug.put_line (g_pkg_name||'.'||l_api_name||' processing phantom batch with batch_id/material_detail_id: '||l_phantom_batch_rec.batch_id||'/'||l_phantom_material_rec.material_detail_id);
425         END IF;
426 
427         incremental_backflush
428             (p_batch_header_rec        => l_phantom_batch_rec
429             ,p_material_detail_rec     => l_phantom_material_rec
430             ,p_qty                     => l_incr_factor
431             ,p_qty_type                => NULL
432             ,p_trans_date              => p_trans_date
433             ,p_backflush_rsrc_usg_ind  => p_backflush_rsrc_usg_ind
434             ,x_exception_material_tbl  => x_exception_material_tbl
435             ,x_return_status           => l_return_status);
436 
437         IF l_return_status NOT IN (FND_API.G_RET_STS_SUCCESS, gme_common_pvt.g_exceptions_err) THEN
438           x_return_status := l_return_status;
439           RAISE error_phantom_backflush;
440         END IF;
441 
442         IF l_return_status = gme_common_pvt.g_exceptions_err THEN
443           x_return_status := gme_common_pvt.g_exceptions_err;
444         END IF;
445 
446         -- Bug 7709971 back out 7286054 as now phantom ingredient gets double posting.
447         -- Reinstated elsif since phantom ingredients are reconciled by the phantom prod yield.
448 
449 --      END IF; /*Bug#7286054 Moved the end if before to the actual qty
450 -- calculation so that the logic would become applicable for the phantom item also*/
451 
452       ELSIF l_batch_header_rec.update_inventory_ind = 'Y' AND
453             l_item_rec.mtl_transactions_enabled_flag = 'Y' THEN
454         IF l_new_actual = 0 THEN
455           -- full revert
456           IF ( NVL(G_DEBUG,-1) = GME_DEBUG.G_LOG_STATEMENT ) THEN
457             gme_debug.put_line (g_pkg_name||'.'||l_api_name||' new actual = 0; calling gme_unrelease_batch_pvt.revert_material_full');
458           END IF;
459 
460           -- Bug 8751983 - Set to 2 if user is going negative.
461           IF gme_common_pvt.g_ib_timestamp_set = 1 THEN
462              gme_common_pvt.g_ib_timestamp_set := 2;
463           END IF;
464 
465           gme_unrelease_batch_pvt.revert_material_full
466               (p_material_detail_rec     => l_material_detail_rec
467               ,p_create_resv_pend_lots   => 1
468               ,p_ignore_transactable     => TRUE
469               ,x_actual_qty              => l_actual_qty
470               ,x_exception_material_tbl  => x_exception_material_tbl
471               ,x_return_status           => l_return_status);
472 
473           IF l_return_status NOT IN (FND_API.G_RET_STS_SUCCESS, gme_common_pvt.g_exceptions_err) THEN
474             x_return_status := l_return_status;
475             RAISE error_revert_matl_full;
476           END IF;
477 
478           IF l_return_status = gme_common_pvt.g_exceptions_err THEN
479             x_return_status := gme_common_pvt.g_exceptions_err;
480           END IF;
481 
482           l_upd_material := TRUE;
483         ELSIF l_incr_qty < 0 THEN
484           -- partial revert
485           l_decr_qty := -1 * l_incr_qty;
486           IF ( NVL(G_DEBUG,-1) = GME_DEBUG.G_LOG_STATEMENT ) THEN
487             gme_debug.put_line (g_pkg_name||'.'||l_api_name||' call revert_material_partial: incr_qty/decr_qty= '||l_incr_qty||'/'||l_decr_qty);
488           END IF;
489 
490           -- Bug 8751983 - Set to 2 if user is going negative.
491           IF gme_common_pvt.g_ib_timestamp_set = 1 THEN
492              gme_common_pvt.g_ib_timestamp_set := 2;
493           END IF;
494 
495           revert_material_partial
496               (p_material_detail_rec        => l_material_detail_rec
497               ,p_qty                        => l_decr_qty
498               ,p_lot_control_code           => l_item_rec.lot_control_code
499               ,p_create_resv_pend_lots      => 1
500               ,p_lot_divisible_flag         => l_lot_divisible_flag
501               ,x_actual_qty                 => l_actual_qty
502               ,x_exception_material_tbl     => x_exception_material_tbl
503               ,x_return_status              => l_return_status);
504           IF l_return_status NOT IN (FND_API.G_RET_STS_SUCCESS, gme_common_pvt.g_exceptions_err) THEN
505             x_return_status := l_return_status;
506             RAISE error_revert_matl_part;
507           END IF;
508 
509           IF l_return_status = gme_common_pvt.g_exceptions_err THEN
510             x_return_status := gme_common_pvt.g_exceptions_err;
511           END IF;
512           l_upd_material := TRUE;
513         ELSIF l_incr_qty = 0 THEN
514           -- nothing to do
515           IF ( NVL(G_DEBUG,-1) = GME_DEBUG.G_LOG_STATEMENT ) THEN
516             gme_debug.put_line (g_pkg_name||'.'||l_api_name||' incr_qty calculated to 0... nothing to do');
517           END IF;
518           l_upd_material := FALSE;
519         ELSE
520           -- consume or yield based on line type
521           IF l_material_detail_rec.line_type = gme_common_pvt.g_line_type_ing THEN
522             IF ( NVL(G_DEBUG,-1) = GME_DEBUG.G_LOG_STATEMENT ) THEN
523               gme_debug.put_line (g_pkg_name||'.'||l_api_name||' calling gme_release_batch_pvt.consume_material with target_qty= '||l_new_actual);
524             END IF;
525             gme_release_batch_pvt.consume_material
526                         (p_material_dtl_rec      => l_material_detail_rec
527                         ,p_trans_date            => p_trans_date
528                         ,p_item_rec              => l_item_rec
529                         ,p_consume_qty           => l_new_actual
530                         ,x_exception_material_tbl => x_exception_material_tbl
531                         ,x_actual_qty            => l_actual_qty
532                         ,x_return_status         => l_return_status);
533           ELSE
534             IF ( NVL(G_DEBUG,-1) = GME_DEBUG.G_LOG_STATEMENT ) THEN
535               gme_debug.put_line (g_pkg_name||'.'||l_api_name||' calling gme_complete_batch_pvt.yield_material with target_qty= '||l_new_actual);
536             END IF;
537             gme_complete_batch_pvt.yield_material
538                         (p_material_dtl_rec      => l_material_detail_rec
539                         ,p_yield_qty             => l_new_actual
540                         ,p_trans_date            => p_trans_date
541                         ,p_item_rec              => l_item_rec
542                         ,p_force_unconsumed      => fnd_api.g_true
543                         ,x_exception_material_tbl => x_exception_material_tbl
544                         ,x_actual_qty            => l_actual_qty
545                         ,x_return_status         => l_return_status);
546           END IF;
547 
548           IF l_return_status NOT IN (FND_API.G_RET_STS_SUCCESS, gme_common_pvt.g_exceptions_err) THEN
549             x_return_status := l_return_status;
550             IF ( NVL(G_DEBUG,-1) = GME_DEBUG.G_LOG_STATEMENT ) THEN
551               gme_debug.put_line (g_pkg_name||'.'||l_api_name||' raising exception with x_return_status= '||x_return_status);
552             END IF;
553             RAISE error_consum_yield;
554           END IF;
555 
556           IF l_return_status = gme_common_pvt.g_exceptions_err THEN
557             x_return_status := gme_common_pvt.g_exceptions_err;
558           END IF;
559           l_upd_material := TRUE;
560         END IF; -- IF l_new_actual = 0 THEN
561 
562         IF l_upd_material THEN
563           l_material_detail_rec.actual_qty := l_actual_qty;
564 
565           IF ( NVL(G_DEBUG,-1) = GME_DEBUG.G_LOG_STATEMENT ) THEN
566             gme_debug.put_line (g_pkg_name||'.'||l_api_name||' calling update material actual qty= '||l_material_detail_rec.actual_qty);
567           END IF;
568 
569           IF NOT gme_material_details_dbl.update_row (l_material_detail_rec) THEN
570             RAISE error_update_row;
571           END IF;
572 
573           -- Bug 7709971 - When yielding or changing a phantom product then we must update the parent ingredient.
574           IF nvl(l_batch_header_rec.parentline_id,0) <> 0 AND
575              l_material_detail_rec.material_detail_id = l_in_material_detail_rec.material_detail_id THEN
576              -- Update the parent ingredient actual_qty. Phantom product updated accounted for.
577              -- in previous update. The transactions would have been taken care of.
578               IF ( NVL(G_DEBUG,-1) = GME_DEBUG.G_LOG_STATEMENT ) THEN
579                 gme_debug.put_line (g_pkg_name||'.'||l_api_name||'Updating actual qty for parent ingred to '||l_actual_qty);
580                 gme_debug.put_line ('parent line is '||l_batch_header_rec.parentline_id);
581               END IF;
582 
583              UPDATE gme_material_details
584                 SET actual_qty = l_actual_qty,
585                     last_updated_by = gme_common_pvt.g_user_ident,
586                     last_update_date = gme_common_pvt.g_timestamp,
587                     last_update_login = gme_common_pvt.g_login_id
588               WHERE material_detail_id = l_batch_header_rec.parentline_id;
589           END IF;
590         END IF;  -- IF l_upd_material THEN
591       ELSE  -- lab batches or non transactable materials
592         -- Bug 9628831 - Only update the actual quantity for lab batches, not for non transactable material items.
593         -- Back out 9628831.
594         -- IF l_batch_header_rec.laboratory_ind = 1 THEN
595            l_material_detail_rec.actual_qty := l_new_actual;
596 
597            IF ( NVL(G_DEBUG,-1) = GME_DEBUG.G_LOG_STATEMENT ) THEN
598              gme_debug.put_line (g_pkg_name||'.'||l_api_name||' calling update material actual qty= '||l_material_detail_rec.actual_qty);
599            END IF;
600 
601            IF NOT gme_material_details_dbl.update_row (l_material_detail_rec) THEN
602              RAISE error_update_row;
603            END IF;
604 
605            -- Bug 8516257 - Additional rework of bug Bug 7709971 and 7286054
606            -- When yielding or changing a phantom product then we must update the parent ingredient.
607            IF nvl(l_batch_header_rec.parentline_id, 0) <> 0 AND
608               l_material_detail_rec.material_detail_id = l_in_material_detail_rec.material_detail_id THEN
609               -- Update the parent ingredient actual_qty. Phantom product updated accounted for.
610               -- in previous update. The transactions would have been taken care of.
611                IF ( NVL(G_DEBUG,-1) = GME_DEBUG.G_LOG_STATEMENT ) THEN
612                  gme_debug.put_line (g_pkg_name||'.'||l_api_name||'Updating actual qty for parent ingred to '||l_new_actual);
613                  gme_debug.put_line ('parent line is '||l_batch_header_rec.parentline_id);
614                END IF;
615 
616               -- Bug 8508788 - Let's update the parent ingredient with the correct actual qty.
617               UPDATE gme_material_details
618                  SET actual_qty = l_new_actual,
619                      last_updated_by = gme_common_pvt.g_user_ident,
620                      last_update_date = gme_common_pvt.g_timestamp,
621                      last_update_login = gme_common_pvt.g_login_id
622                WHERE material_detail_id = l_batch_header_rec.parentline_id;
623            END IF;
624         -- END IF; -- IF l_batch_header_rec.laboratory_ind = 1
625       END IF; -- IF l_material_detail_rec.phantom_id IS NOT NULL THEN
626     END LOOP;  -- FOR i IN 1 .. l_material_detail_tbl.COUNT LOOP
627 
628     IF l_batch_header_rec.automatic_step_calculation = 1  THEN
629       -- Update POC Data if steps are associated to a material line
630       -- First fetch all the steps associated to a batch
631       OPEN Cur_assoc_step(l_batch_header_rec.batch_id);
632       FETCH Cur_assoc_step BULK COLLECT INTO l_step_tbl;
633       CLOSE Cur_assoc_step;
634 
635 
636       FOR i IN 1..l_step_tbl.count LOOP
637         gme_update_step_qty_pvt.update_step_qty
638           (p_batch_step_rec         => l_step_tbl(i)
639           ,x_message_count          => l_msg_count
640           ,x_message_list           => l_msg_stack
641           ,x_return_status          => l_return_status
642           ,x_batch_step_rec         => l_batch_step_rec);
643 
644         IF l_return_status <> FND_API.G_RET_STS_SUCCESS THEN
645           RAISE update_step_qty_error;
646         END IF;
647       END LOOP;
648     ELSIF p_backflush_rsrc_usg_ind = 1 THEN
649       -- if p_backflush_rsrc_usg_ind is set to 1, this means that the material passed in
650       -- is a product; this holds for parent/phantom batches as well as non phantom batches
651       OPEN Cur_prod_assoc(l_batch_header_rec.batch_id, l_in_material_detail_rec.material_detail_id);
652       FETCH Cur_prod_assoc INTO l_in_batch_step_rec;
653       CLOSE Cur_prod_assoc;
654 
655       IF l_in_batch_step_rec.batchstep_id IS NOT NULL THEN
656         gme_update_step_qty_pvt.update_step_qty
657           (p_batch_step_rec         => l_in_batch_step_rec
658           ,p_backflush_factor       => l_incr_factor_res/100
659           ,x_message_count          => l_msg_count
660           ,x_message_list           => l_msg_stack
661           ,x_return_status          => l_return_status
662           ,x_batch_step_rec         => l_batch_step_rec);
663 
664         IF l_return_status <> FND_API.G_RET_STS_SUCCESS THEN
665           RAISE update_step_qty_error;
666         END IF;
667 
668         -- Get all previous steps of the product step
669         update_dependent_steps
670             (p_batchstep_id     => l_in_batch_step_rec.batchstep_id
671             ,p_backflush_factor => l_incr_factor_res/100
672             ,x_return_status    => l_return_status);
673 
674         IF l_return_status <> FND_API.G_RET_STS_SUCCESS THEN
675           RAISE ERROR_UPDATING_STEPS;
676         END IF;
677 
678         IF gme_common_pvt.g_ib_timestamp_set > 0 THEN
679            -- Bug 8508788 - Update any new transaction that was created for this item/step and all dependent steps
680            -- with the date value passed in by the user or sysdate if it is later than the start date of the resource.
681 
682            -- Bug 8751983 - Added DEL action to where clause so we stamp reversals also.
683            -- Transaction engine will decide whether to keep this date or not.
684            update gme_resource_txns_gtmp
685            set trans_date = p_trans_date
686            where poc_trans_id in
687               (select t.poc_trans_id
688                FROM   gme_batch_steps s, gme_batch_step_activities a, gme_batch_step_resources r, gme_resource_txns_gtmp t
689                WHERE  s.batch_id = l_batch_header_rec.batch_id
690                -- Comment out following update as original fix was just for one step.
691                -- AND    a.batchstep_id = l_in_batch_step_rec.batchstep_id
692                AND    a.batchstep_id = s.batchstep_id
693                AND    r.batchstep_activity_id = a.batchstep_activity_id
694                AND    t.action_code = 'DEL'
695                AND    t.line_id = r.batchstep_resource_id
696                AND    p_trans_date >= r.actual_start_date);
697 
698 
699            -- Bug 8751983 - We do not want to stamp new transactions caused by negative IB at this time.
700            -- New transaction should maintain original trans date being reversed, unless it is in a closed period.
701            IF gme_common_pvt.g_ib_timestamp_set = 1 THEN
702               update gme_resource_txns_gtmp
703               set trans_date = p_trans_date
704               where poc_trans_id in
705                  (select t.poc_trans_id
706                   FROM   gme_batch_steps s, gme_batch_step_activities a, gme_batch_step_resources r, gme_resource_txns_gtmp t
707                   WHERE  s.batch_id = l_batch_header_rec.batch_id
708                   -- Comment out following update as original fix was just for one step.
709                   -- AND    a.batchstep_id = l_in_batch_step_rec.batchstep_id
710                   AND    a.batchstep_id = s.batchstep_id
711                   AND    r.batchstep_activity_id = a.batchstep_activity_id
712                   AND    t.action_code = 'ADD'
713                   AND    t.line_id = r.batchstep_resource_id
714                   AND    p_trans_date >= r.actual_start_date);
715            END IF;
716          END IF;  -- IF gme_common_pvt.g_ib_timestamp_set > 0
717       END IF;  -- IF l_in_batch_step_rec.batchstep_id IS NOT NULL THEN
718     END IF;  -- IF l_batch_header_rec.automatic_step_calculation = 1  THEN
719 
720     IF nvl(g_debug, gme_debug.g_log_procedure + 1) <= gme_debug.g_log_procedure THEN
721       gme_debug.put_line('Exiting api '||g_pkg_name||'.'||l_api_name||' for batch_id= '||p_batch_header_rec.batch_id||' and x_return_status= '||x_return_status);
722     END IF;
723 
724   EXCEPTION
725   WHEN error_fetch_batch OR error_fetch_matl OR error_update_row THEN
726     gme_common_pvt.log_message ('GME_UNEXPECTED_ERROR', 'ERROR', SQLERRM);
727     x_return_status := FND_API.g_ret_sts_unexp_error;
728   WHEN error_cant_go_neg THEN
729     gme_common_pvt.log_message ('GME_API_ACTUAL_CANT_GO_NEG');
730     x_return_status := FND_API.g_ret_sts_error;
731   WHEN error_derive_factor OR error_get_item OR error_phantom_backflush OR
732        error_revert_matl_full OR error_consum_yield OR error_revert_matl_part THEN
733     NULL;
734   WHEN update_step_qty_error OR ERROR_UPDATING_STEPS THEN
735     x_return_status := l_return_status;
736   WHEN OTHERS THEN
737     fnd_msg_pub.add_exc_msg (g_pkg_name, l_api_name);
738     IF g_debug <= gme_debug.g_log_procedure THEN
739       gme_debug.put_line ('Unexpected error: '||g_pkg_name||'.'||l_api_name||': '||SQLERRM);
740     END IF;
741     x_return_status := FND_API.g_ret_sts_unexp_error;
742   END incremental_backflush;
743 
744 
745   /*FPBug#4667093 Code added to consider new gme parameter for calculating factor */
746   PROCEDURE derive_factor
747     (p_material_detail_rec   IN         gme_material_details%ROWTYPE
748     ,p_qty                   IN         NUMBER
749     ,p_qty_type              IN         NUMBER
750     ,p_gme_ib_factor         IN         NUMBER DEFAULT 0
751     ,x_pct_plan              OUT NOCOPY NUMBER
752     ,x_pct_plan_res          OUT NOCOPY NUMBER
753     ,x_return_status         OUT NOCOPY VARCHAR2) IS
754 
755     l_required_qty             NUMBER;
756     l_old_actual_qty           NUMBER;
757     l_new_actual               NUMBER;
758     l_api_name        CONSTANT VARCHAR2 (30)   := 'derive_factor';
759 
760     --FPBug#4667093
761     l_gme_ib_factor            NUMBER;
762     l_actual_qty               NUMBER;
763     l_plan_qty                 NUMBER;
764     l_uom                      VARCHAR2(3);
765     l_return_status            VARCHAR2(1);
766 
767     l_incr_qty                 NUMBER;
768 
769     ERROR_IN_GET_TOTAL_QTY     EXCEPTION;
770 
771     -- p_qty_type 0 increment qty
772     -- p_qty_type 1 new act qty
773     -- p_qty_type 2 % plan
774 
775   BEGIN
776 
777     IF nvl(g_debug, gme_debug.g_log_procedure + 1) <= gme_debug.g_log_procedure THEN
778       gme_debug.put_line('Entering api '||g_pkg_name||'.'||l_api_name);
779       gme_debug.put_line(g_pkg_name||'.'||l_api_name||' material_detail_id='||p_material_detail_rec.material_detail_id);
780       gme_debug.put_line(g_pkg_name||'.'||l_api_name||' p_qty='||p_qty);
781       gme_debug.put_line(g_pkg_name||'.'||l_api_name||' p_qty_type='||p_qty_type);
782       --FPBug#4667093 rework
783       gme_debug.put_line(g_pkg_name||'.'||l_api_name||'p_gme_ib_factor ='||p_gme_ib_factor||' line type='||p_material_detail_rec.line_type);
784     END IF;
785 
786     /* Set the return status to success initially */
787     x_return_status       := FND_API.G_RET_STS_SUCCESS;
788 
789     l_old_actual_qty := p_material_detail_rec.actual_qty;
790 
791     --FPBug#4667093 Begin
792     l_gme_ib_factor := p_gme_ib_factor;
793     IF l_gme_ib_factor = 1 AND p_material_detail_rec.line_type = 1 THEN
794       gme_api_grp.get_total_qty(
795                    p_batch_id           => p_material_detail_rec.batch_id
796                   ,p_line_type          => 1
797                   ,p_uom                => p_material_detail_rec.dtl_um
798                   ,x_total_plan_qty     => l_plan_qty
799 		  /*Bug#5111078 we should take wip plan qty while deriving the factor */
800 		  ,x_total_wip_plan_qty => l_required_qty
801                   ,x_total_actual_qty   => l_actual_qty
802                   ,x_uom                => l_uom
803                   ,x_return_status      => l_return_status );
804 
805       IF l_return_status <> FND_API.G_RET_STS_SUCCESS THEN
806        RAISE ERROR_IN_GET_TOTAL_QTY;
807       END IF;
808     ELSE
809       l_plan_qty := p_material_detail_rec.plan_qty;
810       l_required_qty := p_material_detail_rec.wip_plan_qty;
811     END IF;
812 
813     IF nvl(g_debug,-1) <= gme_debug.g_log_statement THEN
814      gme_debug.put_line(g_pkg_name||'.'||l_api_name||'l_required_qty: '||l_required_qty);
815     END IF;
816     --FPBug#4667093 End
817 
818     -- x_pct_plan is the percent to be applied to WIP plan to come up with the incremental qty
819     -- to add to actual; examples in each
820 
821     -- Note: l_required_qty = wip plan qty or sum of wip plan qty for all prods.
822     IF p_qty_type = 0 THEN
823       -- p_qty : 20  --> increment qty
824       -- wip_plan_qty : 100
825       -- x_pct_plan : 20 %
826       -- incremental qty : wip_plan_qty * x_pct_plan --> 20% * 100 = 20; this is applied to each of the items
827       -- actual qty : 40
828       -- new actual : 60
829 
830       x_pct_plan :=  (p_qty / l_required_qty ) * 100;
831 
832       -- Bug 10378355 - Account for change between plan and wip plan qty.
833       -- Steps do not have wip plan qty's so % has to account for that.
834       -- x_pct_plan_res := ( p_qty  / l_required_qty ) * 100;
835 
836       -- New % is    ((incr qty / wip_plan) * (wip_plan / plan)) * 100
837       x_pct_plan_res := (( p_qty  / l_required_qty ) * (l_required_qty / l_plan_qty)) * 100;
838     ELSIF p_qty_type = 1 THEN
839       -- p_qty : 60  --> new actual qty
840       -- actual_qty : 40
841       -- wip_plan_qty : 100
842       -- x_pct_plan : (60 - 40)/100 = 20%
843       -- incremental qty : wip_plan_qty * x_pct_plan --> 20% * 100 = 20; this is applied to each of the items
844       -- actual qty : 40
845       -- new actual : 60
846 
847       l_incr_qty := p_qty - l_old_actual_qty;
848       -- x_pct_plan := ((p_qty - l_old_actual_qty)/l_required_qty) * 100;
849       x_pct_plan := (l_incr_qty/l_required_qty) * 100;
850 
851       -- Bug 10378355 - Account for change between plan and wip plan qty.
852       -- Steps do not have wip plan qty's so % has to account for that.
853       -- x_pct_plan_res := ((p_qty - l_old_actual_qty)/l_required_qty) * 100;
854 
855       -- New % is    ((incr qty / wip_plan) * (wip_plan / plan)) * 100
856       x_pct_plan_res := (( l_incr_qty  / l_required_qty ) * (l_required_qty / l_plan_qty)) * 100;
857 
858     ELSIF p_qty_type = 2 THEN
859       -- p_qty : 60%  --> % wip plan
860       -- wip_plan_qty : 100
861       -- new actual qty : 60% * 100 = 60
862       -- x_pct_plan : (60 - 40) / 100 = 20%
863       -- incremental qty : wip_plan_qty * x_pct_plan --> 20% * 100 = 20; this is applied to each of the items
864       -- actual qty : 40
865       -- new actual : 60
866 
867       l_new_actual := (l_required_qty * p_qty) / 100;
868       l_incr_qty := l_new_actual - l_old_actual_qty;
869 
870       -- x_pct_plan := ((l_new_actual - l_old_actual_qty)/l_required_qty) * 100;
871       x_pct_plan := (l_incr_qty/l_required_qty) * 100;
872 
873       -- Bug 10378355 - Account for change between plan and wip plan qty.
874       -- Steps do not have wip plan qty's so % has to account for that.
875       -- x_pct_plan_res := p_qty - ((l_old_actual_qty/l_required_qty))*100 ; -- This may have been wrong anyway !
876 
877       -- New % is    ((incr qty / wip_plan) * (wip_plan / plan)) * 100
878       x_pct_plan_res := (( l_incr_qty  / l_required_qty ) * (l_required_qty / l_plan_qty)) * 100;
879     END IF;
880 
881     IF ( NVL(G_DEBUG,-1) = GME_DEBUG.G_LOG_STATEMENT ) THEN
882       gme_debug.put_line (g_pkg_name||'.'||l_api_name||' x_pct_plan= '||x_pct_plan);
883     END IF;
884 
885     IF nvl(g_debug, gme_debug.g_log_procedure + 1) <= gme_debug.g_log_procedure THEN
886       gme_debug.put_line('Exiting api '||g_pkg_name||'.'||l_api_name||' with x_return_status= '||x_return_status);
887     END IF;
888 
889   EXCEPTION
890     --FPBug#4667093
891     WHEN ERROR_IN_GET_TOTAL_QTY THEN
892       x_return_status := l_return_status;
893     WHEN OTHERS THEN
894       fnd_msg_pub.add_exc_msg (g_pkg_name, l_api_name);
895       IF g_debug <= gme_debug.g_log_procedure THEN
896         gme_debug.put_line ('Unexpected error: '||g_pkg_name||'.'||l_api_name||': '||SQLERRM);
897       END IF;
898       x_return_status := FND_API.g_ret_sts_unexp_error;
899   END derive_factor;
900 
901   PROCEDURE update_dependent_steps(p_batchstep_id     IN  NUMBER
902                                   ,p_backflush_factor IN  NUMBER
903                                   ,x_return_status    OUT NOCOPY VARCHAR2) IS
904 
905     l_api_name        CONSTANT VARCHAR2 (30)   := 'update_dependent_steps';
906 
907     CURSOR Cur_prev_steps(V_batchstep_id NUMBER) IS
908       SELECT d.dep_step_id, d.dep_type, s.step_status
909       FROM   gme_batch_step_dependencies d, gme_batch_steps s
910       WHERE  d.batchstep_id = V_batchstep_id
911       AND    s.batchstep_id = d.dep_step_id;
912 
913     l_batch_step_rec           GME_BATCH_STEPS%ROWTYPE;
914     l_in_batch_step_rec        GME_BATCH_STEPS%ROWTYPE;
915 
916     l_message_count        NUMBER;
917     l_backflush_factor     NUMBER;
918     l_message_list         VARCHAR2(2000);
919 
920     error_updating_steps   EXCEPTION;
921 
922   BEGIN
923     IF nvl(g_debug, gme_debug.g_log_procedure + 1) <= gme_debug.g_log_procedure THEN
924       gme_debug.put_line('Entering api '||g_pkg_name||'.'||l_api_name);
925       gme_debug.put_line(g_pkg_name||'.'||l_api_name||' batchstep_id='||p_batchstep_id);
926     END IF;
927 
928     -- Set the return status to success initially
929     x_return_status := FND_API.G_RET_STS_SUCCESS;
930 
931     -- Get all previous depenedent steps for current step
932 
933     FOR get_rec IN Cur_prev_steps(p_batchstep_id) LOOP
934       -- If dependency is start to start and step is WIP then apply factor and process steps that
935       -- this step is dependent on, Pending and completed steps will not be touched
936       -- If dependency is finish to start and step is WIP then apply 100% of plan to actual and process steps that
937       -- this step is dependent on, Pending and completed steps will not be touched
938       IF (get_rec.step_status = gme_common_pvt.g_step_wip) THEN
939         IF (get_rec.dep_type = gme_common_pvt.g_dep_type_finish_start) THEN
940           l_backflush_factor := 1;
941         ELSE
942           l_backflush_factor := p_backflush_factor;
943         END IF;
944         l_in_batch_step_rec.batchstep_id := get_rec.dep_step_id;
945 
946         gme_update_step_qty_pvt.update_step_qty
947             (p_batch_step_rec          => l_in_batch_step_rec
948             ,x_message_count           => l_message_count
949             ,x_message_list            => l_message_list
950             ,x_return_status           => x_return_status
951             ,x_batch_step_rec          => l_batch_step_rec
952             ,p_backflush_factor        => l_backflush_factor
953             ,p_dependency_type         => get_rec.dep_type);
954 
955         IF x_return_status <> FND_API.G_RET_STS_SUCCESS THEN
956           RAISE error_updating_steps;
957         END IF;
958         update_dependent_steps
959             (p_batchstep_id     => get_rec.dep_step_id
960             ,p_backflush_factor => p_backflush_factor
961             ,x_return_status    => x_return_status);
962 
963         IF x_return_status <> FND_API.G_RET_STS_SUCCESS THEN
964           RAISE error_updating_steps;
965         END IF;
966       END IF;
967     END LOOP;
968 
969     IF nvl(g_debug, gme_debug.g_log_procedure + 1) <= gme_debug.g_log_procedure THEN
970       gme_debug.put_line('Exiting api '||g_pkg_name||'.'||l_api_name);
971     END IF;
972 
973   EXCEPTION
974     WHEN error_updating_steps THEN
975       NULL;
976     WHEN OTHERS THEN
977       fnd_msg_pub.add_exc_msg (g_pkg_name, l_api_name);
978       IF g_debug <= gme_debug.g_log_procedure THEN
979         gme_debug.put_line ('Unexpected error: '||g_pkg_name||'.'||l_api_name||': '||SQLERRM);
980       END IF;
981       x_return_status := FND_API.g_ret_sts_unexp_error;
982   END update_dependent_steps;
983 
984   PROCEDURE revert_material_partial
985     (p_material_detail_rec        IN gme_material_details%ROWTYPE
986     ,p_qty                        IN NUMBER
987     ,p_lot_control_code           IN NUMBER  -- 1 = not lot control; 2 = lot control
988     ,p_create_resv_pend_lots      IN NUMBER
989     ,p_lot_divisible_flag         IN VARCHAR2
990     ,x_actual_qty                 OUT NOCOPY NUMBER
991     ,x_exception_material_tbl     IN OUT NOCOPY gme_common_pvt.exceptions_tab
992     ,x_return_status              OUT NOCOPY VARCHAR2) IS
993 
994     CURSOR cur_lot_qty
995         (v_item_id           IN   NUMBER
996         ,v_organization_id   IN   NUMBER
997         ,v_batch_id          IN   NUMBER
998         ,v_mat_det_id        IN   NUMBER)
999       IS
1000            SELECT lot_number, SUM (l.transaction_quantity) sum_trx
1001              FROM mtl_material_transactions m, mtl_transaction_lot_numbers l
1002             WHERE l.transaction_id = m.transaction_id
1003               AND m.inventory_item_id = v_item_id
1004               AND m.organization_id = v_organization_id
1005               AND m.transaction_source_id = v_batch_id
1006               AND m.trx_source_line_id = v_mat_det_id
1007               AND m.transaction_source_type_id = gme_common_pvt.g_txn_source_type
1008          GROUP BY l.lot_number;
1009 
1010     TYPE lot_qty_tab IS TABLE OF NUMBER INDEX BY mtl_transaction_lot_numbers.lot_number%TYPE;
1011 
1012     l_lot_qty_tab     lot_qty_tab;
1013     l_last_lot_qty_tab lot_qty_tab;
1014 
1015     l_qty             NUMBER;
1016     l_last_qty        NUMBER;
1017 
1018     l_decr_qty        NUMBER;
1019     l_total_decr_qty  NUMBER;
1020 
1021     l_trxn_type       NUMBER;
1022     l_trxn_qty        NUMBER;
1023     l_trxn_sum        NUMBER;
1024     l_temp_qty        NUMBER;
1025     l_whole_qty       BOOLEAN;
1026     l_return_status   VARCHAR2(1);
1027     l_trxn_success    BOOLEAN;
1028 
1029     i                 NUMBER;
1030     j                 NUMBER;
1031     k                 NUMBER;
1032 
1033     -- Bug 13017256
1034     l_trans_date      DATE;
1035 
1036     l_mmt_rec         mtl_material_transactions%ROWTYPE;
1037     l_mmt_tbl         gme_common_pvt.mtl_mat_tran_tbl;
1038 
1039     l_mmln_tbl        gme_common_pvt.mtl_trans_lots_num_tbl;
1040     l_mmln_tbl_orig   gme_common_pvt.mtl_trans_lots_num_tbl;
1041     l_mmln_tbl_new    gme_common_pvt.mtl_trans_lots_num_tbl;
1042 
1043     -- Bug 9072371 add this table to allow checking for one lot.
1044     l_mmln_tbl_lot    gme_common_pvt.mtl_trans_lots_num_tbl;
1045     ln                mtl_transaction_lot_numbers.lot_number%TYPE;
1046     l_lot_number      mtl_transaction_lot_numbers.lot_number%TYPE;
1047     /* Jalaj Srivastava Bug 5021522*/
1048     l_item_no         varchar2(2000);
1049     inv_negative      EXCEPTION;
1050 
1051     l_api_name        CONSTANT VARCHAR2 (30)   := 'revert_material_partial';
1052 
1053     error_get_lot       EXCEPTION;
1054     error_get_trans     EXCEPTION;
1055     error_trans         EXCEPTION;
1056 
1057     l_lot_record_used NUMBER;
1058     l_skip_lot        NUMBER;
1059   BEGIN
1060 
1061     IF nvl(g_debug, gme_debug.g_log_procedure + 1) <= gme_debug.g_log_procedure THEN
1062       gme_debug.put_line('Entering api '||g_pkg_name||'.'||l_api_name);
1063       gme_debug.put_line(g_pkg_name||'.'||l_api_name||' material_detail_id='||p_material_detail_rec.material_detail_id);
1064       gme_debug.put_line(g_pkg_name||'.'||l_api_name||' p_qty='||p_qty);
1065       gme_debug.put_line(g_pkg_name||'.'||l_api_name||' p_lot_control_code='||p_lot_control_code);
1066       gme_debug.put_line(g_pkg_name||'.'||l_api_name||' p_create_resv_pend_lots='||p_create_resv_pend_lots);
1067       gme_debug.put_line(g_pkg_name||'.'||l_api_name||' p_lot_divisible_flag='||p_lot_divisible_flag);
1068     END IF;
1069 
1070     -- Set the return status to success initially
1071     x_return_status := FND_API.G_RET_STS_SUCCESS;
1072 
1073     l_qty := p_qty;
1074     l_total_decr_qty := 0;
1075 
1076     -- Bug 13017256 - Let's initialize the variable with the user entered date.
1077     l_trans_date := NVL(gme_common_pvt.g_ib_timestamp_date, gme_common_pvt.g_timestamp);
1078 
1079     -- Bug 8751983 - Added order by clause to fetch in reverse trans order.
1080     gme_transactions_pvt.get_mat_trans
1081         (p_mat_det_id      => p_material_detail_rec.material_detail_id
1082         ,p_batch_id        => p_material_detail_rec.batch_id
1083         ,p_order_by        => 2
1084         ,x_mmt_tbl         => l_mmt_tbl
1085         ,x_return_status   => x_return_status);
1086 
1087     IF ( NVL(G_DEBUG,-1) = GME_DEBUG.G_LOG_STATEMENT ) THEN
1088       gme_debug.put_line (g_pkg_name||'.'||l_api_name||' gme_transactions_pvt.get_mat_trans returned '||l_mmt_tbl.count||' trxns with return_status='||x_return_status);
1089     END IF;
1090 
1091     IF x_return_status <> FND_API.G_RET_STS_SUCCESS THEN
1092       RAISE error_get_trans;
1093     END IF;
1094 
1095     -- Make all qties positive for comparison; if updating, the trxn mgr will take care of sign
1096     FOR i IN 1..l_mmt_tbl.count LOOP
1097       l_mmt_tbl(i).transaction_quantity := ABS(l_mmt_tbl(i).transaction_quantity);
1098     END LOOP;
1099 
1100     -- set the transaction type to consider for deleting/updating
1101     IF p_material_detail_rec.line_type = gme_common_pvt.g_line_type_prod THEN
1102       l_trxn_type := gme_common_pvt.g_prod_completion;
1103     ELSIF p_material_detail_rec.line_type = gme_common_pvt.g_line_type_byprod THEN
1104       l_trxn_type := gme_common_pvt.g_byprod_completion;
1105     ELSE
1106       l_trxn_type := gme_common_pvt.g_ing_issue;
1107     END IF;
1108 
1109     /* Jalaj Srivastava Bug 5021522
1110        get item_no only for prod/byprod.
1111        In IB, there is no ing return transaction*/
1112     IF (l_trxn_type IN (gme_common_pvt.g_prod_completion, gme_common_pvt.g_byprod_completion)) THEN
1113       SELECT concatenated_segments
1114       INTO   l_item_no
1115       FROM   mtl_system_items_kfv
1116       WHERE  inventory_item_id = p_material_detail_rec.inventory_item_id
1117       AND    organization_id   = p_material_detail_rec.organization_id;
1118     END IF;
1119 
1120     IF p_material_detail_rec.line_type = gme_common_pvt.g_line_type_ing THEN
1121       IF p_lot_divisible_flag = 'N' THEN
1122         l_whole_qty := TRUE;
1123         IF ( NVL(G_DEBUG,-1) = GME_DEBUG.G_LOG_STATEMENT ) THEN
1124           gme_debug.put_line (g_pkg_name||'.'||l_api_name||' l_whole_qty = TRUE because lot indivisible item');
1125         END IF;
1126       ELSE
1127         l_whole_qty := FALSE;
1128         IF ( NVL(G_DEBUG,-1) = GME_DEBUG.G_LOG_STATEMENT ) THEN
1129           gme_debug.put_line (g_pkg_name||'.'||l_api_name||' l_whole_qty = FALSE because lot is divisible; next check if dispensed');
1130         END IF;
1131       END IF;
1132 
1133       -- test again for dispensed items
1134       IF NOT l_whole_qty THEN
1135         IF NVL(p_material_detail_rec.dispense_ind,'N') = 'Y' THEN
1136           l_whole_qty := TRUE;
1137           IF ( NVL(G_DEBUG,-1) = GME_DEBUG.G_LOG_STATEMENT ) THEN
1138             gme_debug.put_line (g_pkg_name||'.'||l_api_name||' l_whole_qty = TRUE because dispensed item');
1139           END IF;
1140         END IF;
1141       END IF;
1142     ELSE -- product and byproduct doesn't apply for either dispensed or lot divisible... don't have to take whole qty
1143       l_whole_qty := FALSE;
1144       IF ( NVL(G_DEBUG,-1) = GME_DEBUG.G_LOG_STATEMENT ) THEN
1145         gme_debug.put_line (g_pkg_name||'.'||l_api_name||' l_whole_qty = FALSE because prod/byprod');
1146       END IF;
1147     END IF;
1148 
1149     IF ( NVL(G_DEBUG,-1) = GME_DEBUG.G_LOG_STATEMENT ) THEN
1150       gme_debug.put_line (g_pkg_name||'.'||l_api_name||' l_trxn_type='||l_trxn_type);
1151     END IF;
1152 
1153     IF p_lot_control_code = 1 THEN
1154 
1155       IF ( NVL(G_DEBUG,-1) = GME_DEBUG.G_LOG_STATEMENT ) THEN
1156         gme_debug.put_line (g_pkg_name||'.'||l_api_name||' ********** NOT LOT CONTROL **********');
1157       END IF;
1158 
1159       i := 1;
1160       WHILE i <= l_mmt_tbl.count AND l_qty > 0 LOOP
1161         l_mmt_rec := l_mmt_tbl(i);
1162 
1163         IF ( NVL(G_DEBUG,-1) = GME_DEBUG.G_LOG_STATEMENT ) THEN
1164           gme_debug.put_line (g_pkg_name||'.'||l_api_name||' in trxn loop; ******************* ');
1165           gme_debug.put_line (g_pkg_name||'.'||l_api_name||' in trxn loop; processing i='||i);
1166           gme_debug.put_line (g_pkg_name||'.'||l_api_name||' in trxn loop; processing trxns_id='||l_mmt_rec.transaction_id);
1167           gme_debug.put_line (g_pkg_name||'.'||l_api_name||' in trxn loop; qty to reduce='||l_qty);
1168         END IF;
1169 
1170         IF l_mmt_rec.transaction_type_id = l_trxn_type THEN
1171           l_trxn_qty := l_mmt_rec.transaction_quantity;
1172           IF l_trxn_qty <= l_qty OR l_whole_qty THEN
1173              /* Jalaj Srivastava Bug 5021522
1174                 call check_inv_negative only for prod/byprod. in IB, there is no ing return transaction */
1175              IF (l_trxn_type IN (gme_common_pvt.g_prod_completion, gme_common_pvt.g_byprod_completion)) THEN
1176                 -- Bug 8639523 - No need to do negative inventory checking for phantom prods or ingredients.
1177                 IF (NVL(p_material_detail_rec.phantom_line_id, 0) = 0) THEN
1178                    IF gme_unrelease_batch_pvt.check_inv_negative
1179                      ( p_mmt_rec   => l_mmt_rec
1180                       ,p_mmln_tbl  => l_mmln_tbl
1181                       ,p_item_no   => l_item_no) THEN
1182                      RAISE inv_negative;
1183                    END IF;
1184                 END IF;
1185              END IF;
1186 
1187             IF ( NVL(G_DEBUG,-1) = GME_DEBUG.G_LOG_STATEMENT ) THEN
1188               gme_debug.put_line (g_pkg_name||'.'||l_api_name||' in trxn loop; calling gme_transactions_pvt.delete_material_txn for trxns_id='||l_mmt_rec.transaction_id);
1189             END IF;
1190 
1191             -- Bug 13017256 - Let's pass in user entered date. It will get used if necessary.
1192             -- delete this transaction, reduce the qty to decrement
1193             gme_transactions_pvt.delete_material_txn
1194               (p_transaction_id       => l_mmt_rec.transaction_id
1195               ,p_trans_date           => l_trans_date
1196               ,p_txns_pair            => NULL
1197               ,x_return_status        => l_return_status);
1198 
1199             IF l_return_status = gme_common_pvt.g_not_transactable THEN
1200               -- do nothing... move on to the next, to try to reduce
1201               IF ( NVL(G_DEBUG,-1) = GME_DEBUG.G_LOG_STATEMENT ) THEN
1202                 gme_debug.put_line (g_pkg_name||'.'||l_api_name||' in trxn loop; gme_transactions_pvt.delete_material_txn returned '||l_return_status);
1203               END IF;
1204             ELSIF l_return_status <> FND_API.G_RET_STS_SUCCESS THEN
1205               x_return_status := l_return_status;
1206               RAISE error_trans;
1207             ELSE -- success
1208               l_total_decr_qty := l_total_decr_qty + l_trxn_qty;
1209               -- set target qty; need to test in case this is a whole qty revert and the qty reverting is greater than that requested.
1210               IF l_trxn_qty < l_qty THEN
1211                 l_qty := l_qty - l_trxn_qty;
1212               ELSE
1213                 l_qty := 0;
1214               END IF;
1215 
1216               gme_unrelease_batch_pvt.create_resv_pplot
1217                       (p_material_detail_rec    => p_material_detail_rec
1218                       ,p_mmt_rec                => l_mmt_rec
1219                       ,p_mmln_tbl               => l_mmln_tbl
1220                       ,x_return_status          => l_return_status);
1221               -- don't care if resv or pplot was not recreated...
1222             END IF;
1223           ELSE  -- l_trxn_qty > l_qty AND NOT whole_qty
1224 
1225             l_mmt_rec.transaction_quantity := l_mmt_rec.transaction_quantity - l_qty;
1226             l_mmt_rec.secondary_transaction_quantity := NULL;
1227             l_mmt_rec.primary_quantity := NULL;
1228 
1229             -- Bug 13017256 - Let's stamp the trans record with user entered date.
1230             IF NOT gme_common_pvt.check_close_period(p_org_id     => l_mmt_rec.organization_id
1231                                                     ,p_trans_date => l_mmt_rec.transaction_date) THEN
1232 
1233                -- Let's default to timestamp and overwrite if the user entered a different date.
1234                l_mmt_rec.transaction_date := l_trans_date;
1235             END IF;
1236 
1237              /* Jalaj Srivastava Bug 5021522
1238                 call check_inv_negative only for prod/byprod.
1239                 in IB, there is no ing return transaction*/
1240              IF (l_trxn_type IN (gme_common_pvt.g_prod_completion, gme_common_pvt.g_byprod_completion)) THEN
1241                IF gme_unrelease_batch_pvt.check_inv_negative
1242                  ( p_mmt_rec   => l_mmt_rec
1243                   ,p_mmln_tbl  => l_mmln_tbl
1244                   ,p_item_no   => l_item_no) THEN
1245                  RAISE inv_negative;
1246                END IF;
1247              END IF;
1248 
1249             IF ( NVL(G_DEBUG,-1) = GME_DEBUG.G_LOG_STATEMENT ) THEN
1250               gme_debug.put_line (g_pkg_name||'.'||l_api_name||' in trxn loop; calling gme_transactions_pvt.update_material_txn for trxns_id='||l_mmt_rec.transaction_id);
1251               gme_debug.put_line (g_pkg_name||'.'||l_api_name||' in trxn loop; update trxn with qty='||l_mmt_rec.transaction_quantity);
1252             END IF;
1253 
1254             gme_transactions_pvt.update_material_txn
1255               (p_mmt_rec         => l_mmt_rec
1256               ,p_mmln_tbl        => l_mmln_tbl
1257               ,x_return_status   => l_return_status);
1258 
1259             IF l_return_status = gme_common_pvt.g_not_transactable THEN
1260               -- do nothing... move on to the next, to try to reduce
1261               IF ( NVL(G_DEBUG,-1) = GME_DEBUG.G_LOG_STATEMENT ) THEN
1262                 gme_debug.put_line (g_pkg_name||'.'||l_api_name||' in trxn loop; gme_transactions_pvt.update_material_txn returned '||l_return_status);
1263               END IF;
1264             ELSIF l_return_status <> FND_API.G_RET_STS_SUCCESS THEN
1265               x_return_status := l_return_status;
1266               RAISE error_trans;
1267             ELSE -- success
1268               l_total_decr_qty := l_total_decr_qty + l_qty;
1269 
1270               -- set the transaction qty back to what was decremented... this record won't be used again
1271               l_mmt_rec.transaction_quantity := l_qty;
1272               l_qty := 0;
1273 
1274               l_return_status := FND_API.G_RET_STS_SUCCESS;
1275               IF l_mmt_rec.secondary_uom_code IS NOT NULL THEN
1276                 -- also need to set the secondary_transaction_quantity if applicable
1277                 get_converted_qty (
1278                     p_org_id                    => p_material_detail_rec.organization_id
1279                    ,p_item_id                   => p_material_detail_rec.inventory_item_id
1280                    ,p_lot_number                => NULL
1281                    ,p_qty                       => l_mmt_rec.transaction_quantity
1282                    ,p_from_um                   => p_material_detail_rec.dtl_um
1283                    ,p_to_um                     => l_mmt_rec.secondary_uom_code
1284                    ,x_conv_qty                  => l_mmt_rec.secondary_transaction_quantity
1285                    ,x_return_status             => l_return_status);
1286               END IF;
1287 
1288               IF l_return_status = FND_API.G_RET_STS_SUCCESS THEN
1289                 gme_unrelease_batch_pvt.create_resv_pplot
1290                       (p_material_detail_rec    => p_material_detail_rec
1291                       ,p_mmt_rec                => l_mmt_rec
1292                       ,p_mmln_tbl               => l_mmln_tbl
1293                       ,x_return_status          => l_return_status);
1294               END IF;
1295               -- don't care if resv or pplot was not recreated...
1296             END IF;
1297 
1298           END IF;  -- IF l_trxn_qty <= l_qty THEN
1299         ELSE
1300           IF ( NVL(G_DEBUG,-1) = GME_DEBUG.G_LOG_STATEMENT ) THEN
1301             gme_debug.put_line (g_pkg_name||'.'||l_api_name||' cant process because not the same transaction_type_id: trxns_id='||l_mmt_rec.transaction_id);
1302           END IF;
1303         END IF; -- IF l_mmt_rec.transaction_type_id = l_trxn_type THEN
1304 
1305         i := i + 1;
1306 
1307       END LOOP;
1308     ELSE  -- p_lot_control_code = 2 which means lot control
1309 
1310 
1311       IF ( NVL(G_DEBUG,-1) = GME_DEBUG.G_LOG_STATEMENT ) THEN
1312         gme_debug.put_line (g_pkg_name||'.'||l_api_name||' ********** LOT CONTROL **********');
1313         gme_debug.put_line (g_pkg_name||'.'||l_api_name||' right before cursor cur_lot_qty');
1314       END IF;
1315 
1316       FOR cur_lot_qty_rec IN cur_lot_qty(
1317                        p_material_detail_rec.inventory_item_id
1318                       ,p_material_detail_rec.organization_id
1319                       ,p_material_detail_rec.batch_id
1320                       ,p_material_detail_rec.material_detail_id) LOOP
1321         l_lot_qty_tab(cur_lot_qty_rec.lot_number) := ABS(cur_lot_qty_rec.sum_trx);
1322         IF ( NVL(G_DEBUG,-1) = GME_DEBUG.G_LOG_STATEMENT ) THEN
1323           gme_debug.put_line (g_pkg_name||'.'||l_api_name||' lot tab index: lot_number:'||cur_lot_qty_rec.lot_number);
1324           gme_debug.put_line (g_pkg_name||'.'||l_api_name||' lot tab qty sum: '||l_lot_qty_tab(cur_lot_qty_rec.lot_number));
1325         END IF;
1326       END LOOP;
1327 
1328       -- loop the trxns checking each lot trxn against lot sum to see if
1329       -- that lot trxn can be used.
1330       -- loop trxn types based on matl type
1331       -- decrement lot sum and l_qty
1332 
1333       i := 1;
1334       WHILE i <= l_mmt_tbl.count AND l_qty > 0 LOOP
1335         l_mmt_rec := l_mmt_tbl(i);
1336 
1337         IF ( NVL(G_DEBUG,-1) = GME_DEBUG.G_LOG_STATEMENT ) THEN
1338           gme_debug.put_line (g_pkg_name||'.'||l_api_name||' in trxn loop; ******************* ');
1339           gme_debug.put_line (g_pkg_name||'.'||l_api_name||' in trxn loop; processing i='||i);
1340           gme_debug.put_line (g_pkg_name||'.'||l_api_name||' in trxn loop; processing trxns_id='||l_mmt_rec.transaction_id);
1341           gme_debug.put_line (g_pkg_name||'.'||l_api_name||' in trxn loop; qty to reduce='||l_qty);
1342         END IF;
1343 
1344 
1345         IF l_mmt_rec.transaction_type_id = l_trxn_type THEN
1346           -- look at each lot in the table
1347           -- decrement in place what is available according to l_lot_qty_tab
1348           -- if all qties are 0 delete the transaction
1349           -- if any lot transactions remain, transaction must be updated
1350 
1351           gme_transactions_pvt.get_lot_trans
1352                 (p_transaction_id      => l_mmt_rec.transaction_id
1353                 ,x_mmln_tbl            => l_mmln_tbl
1354                 ,x_return_status       => x_return_status);
1355 
1356           IF x_return_status <> FND_API.G_RET_STS_SUCCESS THEN
1357             RAISE error_get_lot;
1358           END IF;
1359 
1360           -- Make all lot qties positive for comparison; if updating, the trxn mgr will take care of sign
1361           FOR i IN 1..l_mmln_tbl.count LOOP
1362             l_mmln_tbl(i).transaction_quantity := ABS(l_mmln_tbl(i).transaction_quantity);
1363           END LOOP;
1364 
1365           l_decr_qty := 0;
1366           j:= 1;
1367 
1368           IF ( NVL(G_DEBUG,-1) = GME_DEBUG.G_LOG_STATEMENT ) THEN
1369             gme_debug.put_line (g_pkg_name||'.'||l_api_name||' before lot loop; l_mmln_tbl.COUNT='||l_mmln_tbl.COUNT);
1370           END IF;
1371 
1372           -- keep last successful qties; in case update or delete is not successful, and you have to go back
1373           l_last_lot_qty_tab := l_lot_qty_tab;
1374           l_last_qty := l_qty;
1375           l_mmln_tbl_orig := l_mmln_tbl;
1376 
1377           -- Bug 9072371 - Check potential negative inventory for each specific lot.
1378           l_lot_record_used := 0;
1379           WHILE j <= l_mmln_tbl.COUNT AND l_qty > 0 LOOP
1380             IF ( NVL(G_DEBUG,-1) = GME_DEBUG.G_LOG_STATEMENT ) THEN
1381               gme_debug.put_line (g_pkg_name||'.'||l_api_name||' in lot loop; j='||j);
1382               gme_debug.put_line (g_pkg_name||'.'||l_api_name||' in lot loop; l_decr_qty='||l_decr_qty);
1383             END IF;
1384 
1385             -- Bug 9072371 - Check potential negative inventory for each specific lot.
1386             -- Continue to next lot if this one cannot be used.
1387             l_skip_lot := 0;
1388             IF (l_trxn_type IN (gme_common_pvt.g_prod_completion, gme_common_pvt.g_byprod_completion)) THEN
1389               l_mmln_tbl_lot(1) := l_mmln_tbl(j);
1390               IF gme_unrelease_batch_pvt.check_inv_negative
1391                 ( p_mmt_rec   => l_mmt_rec
1392                  ,p_mmln_tbl  => l_mmln_tbl_lot
1393                  ,p_item_no   => l_item_no) THEN
1394                 l_skip_lot := 1;
1395               END IF;
1396             END IF;
1397 
1398             -- Bug 9072371 - Don't process this lot if it will drive inventory negative.
1399             IF l_skip_lot = 0 THEN
1400                ln := l_mmln_tbl(j).lot_number;
1401 
1402                IF ( NVL(G_DEBUG,-1) = GME_DEBUG.G_LOG_STATEMENT ) THEN
1403                  gme_debug.put_line (g_pkg_name||'.'||l_api_name||' in lot loop; processing lot number='||ln);
1404                  gme_debug.put_line (g_pkg_name||'.'||l_api_name||' in lot loop; sum lot trxn for this lot='||l_lot_qty_tab(ln));
1405                  gme_debug.put_line (g_pkg_name||'.'||l_api_name||' in lot loop; l_qty='||l_qty);
1406                END IF;
1407 
1408                -- if you need to take the entire lot qty, then take it... else, go on to figure out how much you can take
1409                IF l_whole_qty THEN
1410                  l_temp_qty := l_mmln_tbl(j).transaction_quantity;
1411                ELSE
1412                  IF l_mmln_tbl(j).transaction_quantity < l_qty THEN
1413                    IF l_lot_qty_tab(ln) < l_mmln_tbl(j).transaction_quantity THEN
1414                      l_temp_qty := l_lot_qty_tab(ln);
1415                    ELSE
1416                      l_temp_qty := l_mmln_tbl(j).transaction_quantity;
1417                    END IF;
1418                  ELSE  -- l_qty is less than the transaction qty; still need to compare to lot sum
1419                    IF l_lot_qty_tab(ln) < l_qty THEN
1420                      l_temp_qty := l_lot_qty_tab(ln);
1421                    ELSE
1422                      l_temp_qty := l_qty;
1423                    END IF;
1424                  END IF;
1425                END IF;
1426 
1427                IF ( NVL(G_DEBUG,-1) = GME_DEBUG.G_LOG_STATEMENT ) THEN
1428                  gme_debug.put_line (g_pkg_name||'.'||l_api_name||' in lot loop; reducing lot qty by='||l_temp_qty);
1429                END IF;
1430 
1431                l_mmln_tbl(j).transaction_quantity := l_mmln_tbl(j).transaction_quantity - l_temp_qty;
1432                l_mmln_tbl(j).primary_quantity := NULL;
1433                l_mmln_tbl(j).secondary_transaction_quantity := NULL;
1434                l_lot_qty_tab(ln) := l_lot_qty_tab(ln) - l_temp_qty;
1435 
1436                -- following can happen if whole qty is taken, decr may be greater than that requested
1437                IF l_temp_qty < l_qty THEN
1438                  l_qty := l_qty - l_temp_qty;
1439                ELSE
1440                  l_qty := 0;
1441                END IF;
1442 
1443                l_decr_qty := l_decr_qty + l_temp_qty;
1444 
1445 
1446                -- Bug 9072371 - Set flag which says at least one valid lot record was found.
1447                l_lot_record_used := 1;
1448 
1449                IF ( NVL(G_DEBUG,-1) = GME_DEBUG.G_LOG_STATEMENT ) THEN
1450                  gme_debug.put_line (g_pkg_name||'.'||l_api_name||' in lot loop; l_mmln_tbl(j).transaction_quantity='||l_mmln_tbl(j).transaction_quantity);
1451                  gme_debug.put_line (g_pkg_name||'.'||l_api_name||' in lot loop; l_lot_qty_tab(ln)='||l_lot_qty_tab(ln));
1452                  gme_debug.put_line (g_pkg_name||'.'||l_api_name||' in lot loop; l_qty='||l_qty);
1453                  gme_debug.put_line (g_pkg_name||'.'||l_api_name||' in lot loop; l_decr_qty='||l_decr_qty);
1454                END IF;
1455             END IF; -- skip lot check.
1456             j := j + 1;
1457           END LOOP;
1458 
1459           IF ( NVL(G_DEBUG,-1) = GME_DEBUG.G_LOG_STATEMENT ) THEN
1460             gme_debug.put_line (g_pkg_name||'.'||l_api_name||' after lot loop; l_decr_qty='||l_decr_qty);
1461             gme_debug.put_line (g_pkg_name||'.'||l_api_name||' after lot loop; l_mmt_rec.transaction_quantity='||l_mmt_rec.transaction_quantity);
1462           END IF;
1463 
1464           -- Bug 9072371 - If at least one valid lot record was found then process.
1465           IF l_lot_record_used = 1 THEN
1466              IF l_decr_qty = l_mmt_rec.transaction_quantity THEN
1467 
1468                /* Jalaj Srivastava Bug 5021522
1469                   call check_inv_negative only for prod/byprod.
1470                  in IB, there is no ing return transaction*/
1471                IF (l_trxn_type IN (gme_common_pvt.g_prod_completion, gme_common_pvt.g_byprod_completion)) THEN
1472                  IF gme_unrelease_batch_pvt.check_inv_negative
1473                    ( p_mmt_rec   => l_mmt_rec
1474                     ,p_mmln_tbl  => l_mmln_tbl_orig
1475                     ,p_item_no   => l_item_no) THEN
1476                    RAISE inv_negative;
1477                  END IF;
1478                END IF;
1479 
1480                IF ( NVL(G_DEBUG,-1) = GME_DEBUG.G_LOG_STATEMENT ) THEN
1481                  gme_debug.put_line (g_pkg_name||'.'||l_api_name||' in trxn loop; calling gme_transactions_pvt.delete_material_txn with trxn_id='||l_mmt_tbl(i).transaction_id);
1482                END IF;
1483 
1484                -- Bug 13017256 - Let's pass in user entered date. It will get used if necessary.
1485                -- delete this transaction, reduce the qty to decrement
1486                -- delete the transaction... all lots were used
1487                gme_transactions_pvt.delete_material_txn
1488                  (p_transaction_id       => l_mmt_tbl(i).transaction_id
1489                  ,p_txns_pair            => NULL
1490                  ,p_trans_date           => l_trans_date
1491                  ,x_return_status        => l_return_status);
1492 
1493                IF l_return_status = gme_common_pvt.g_not_transactable THEN
1494                  l_trxn_success := FALSE;
1495                  -- do nothing... move on to the next, to try to reduce
1496                  IF ( NVL(G_DEBUG,-1) = GME_DEBUG.G_LOG_STATEMENT ) THEN
1497                    gme_debug.put_line (g_pkg_name||'.'||l_api_name||' in trxn loop; gme_transactions_pvt.delete_material_txn returned '||l_return_status);
1498                  END IF;
1499                ELSIF l_return_status <> FND_API.G_RET_STS_SUCCESS THEN
1500                  x_return_status := l_return_status;
1501                  RAISE error_trans;
1502                ELSE
1503                  l_trxn_success := TRUE;
1504                  -- l_mmt_rec.transaction_quantity was not updated, so l_mmt_rec can be used with no modifications
1505                  gme_unrelease_batch_pvt.create_resv_pplot
1506                          (p_material_detail_rec    => p_material_detail_rec
1507                          ,p_mmt_rec                => l_mmt_rec
1508                          ,p_mmln_tbl               => l_mmln_tbl_orig
1509                          ,x_return_status          => l_return_status);
1510                  -- don't care if resv or pplot was not recreated...
1511 
1512                  -- Bug 8751983/9072371 - Add to summary bucket.
1513                  l_total_decr_qty := l_total_decr_qty + l_decr_qty;
1514                END IF;
1515              ELSE
1516                -- update the transaction; some lots were left
1517                -- copy the lots to a new lot table excluding any lot records that are zero
1518                k := 1;
1519                FOR j IN 1..l_mmln_tbl.COUNT LOOP
1520                  IF l_mmln_tbl(j).transaction_quantity <> 0 THEN
1521                    l_mmln_tbl_new(k) := l_mmln_tbl(j);
1522                    k := k + 1;
1523                  END IF;
1524                END LOOP;
1525 
1526                l_mmt_rec.transaction_quantity := l_mmt_rec.transaction_quantity - l_decr_qty;
1527                l_mmt_rec.secondary_transaction_quantity := NULL;
1528                l_mmt_rec.primary_quantity := NULL;
1529 
1530                -- Bug 13017256 - Let's stamp the trans record with user entered date.
1531                IF NOT gme_common_pvt.check_close_period(p_org_id     => l_mmt_rec.organization_id
1532                                                        ,p_trans_date => l_mmt_rec.transaction_date) THEN
1533 
1534                   -- Let's default to timestamp and overwrite if the user entered a different date.
1535                   l_mmt_rec.transaction_date := l_trans_date;
1536                END IF;
1537 
1538                /* Jalaj Srivastava Bug 5021522
1539                   call check_inv_negative only for prod/byprod.
1540                  in IB, there is no ing return transaction*/
1541                IF (l_trxn_type IN (gme_common_pvt.g_prod_completion, gme_common_pvt.g_byprod_completion)) THEN
1542                  IF gme_unrelease_batch_pvt.check_inv_negative
1543                    ( p_mmt_rec   => l_mmt_rec
1544                     ,p_mmln_tbl  => l_mmln_tbl_new
1545                     ,p_item_no   => l_item_no) THEN
1546                    RAISE inv_negative;
1547                  END IF;
1548                END IF;
1549 
1550                IF ( NVL(G_DEBUG,-1) = GME_DEBUG.G_LOG_STATEMENT ) THEN
1551                  gme_debug.put_line (g_pkg_name||'.'||l_api_name||' quantity decremented from transaction:'||l_decr_qty);
1552 
1553                  FOR j IN 1..l_mmln_tbl.COUNT LOOP
1554                    gme_debug.put_line (g_pkg_name||'.'||l_api_name||' l_mmln_tbl lot number:'||l_mmln_tbl(j).lot_number);
1555                    gme_debug.put_line (g_pkg_name||'.'||l_api_name||' l_mmln_tbl lot quantity: '||l_mmln_tbl(j).transaction_quantity);
1556                  END LOOP;
1557 
1558                  gme_debug.put_line (g_pkg_name||'.'||l_api_name||' new transaction quantity:'||l_mmt_rec.transaction_quantity);
1559 
1560                  FOR j IN 1..l_mmln_tbl_new.COUNT LOOP
1561                    gme_debug.put_line (g_pkg_name||'.'||l_api_name||' l_mmln_tbl_new lot number:'||l_mmln_tbl_new(j).lot_number);
1562                    gme_debug.put_line (g_pkg_name||'.'||l_api_name||' l_mmln_tbl_new lot quantity: '||l_mmln_tbl_new(j).transaction_quantity);
1563                  END LOOP;
1564 
1565                  gme_debug.put_line (g_pkg_name||'.'||l_api_name||' calling gme_transactions_pvt.update_material_txn with updatd l_mmt_rec and new l_mmln_tbl_new');
1566                END IF;
1567 
1568                gme_transactions_pvt.update_material_txn
1569                  (p_mmt_rec         => l_mmt_rec
1570                  ,p_mmln_tbl        => l_mmln_tbl_new
1571                  ,x_return_status   => l_return_status);
1572 
1573                IF l_return_status = gme_common_pvt.g_not_transactable THEN
1574                  l_trxn_success := FALSE;
1575                  -- do nothing... move on to the next, to try to reduce
1576                  IF ( NVL(G_DEBUG,-1) = GME_DEBUG.G_LOG_STATEMENT ) THEN
1577                    gme_debug.put_line (g_pkg_name||'.'||l_api_name||' in trxn loop; gme_transactions_pvt.update_material_txn returned '||l_return_status);
1578                  END IF;
1579                ELSIF l_return_status <> FND_API.G_RET_STS_SUCCESS THEN
1580                  x_return_status := l_return_status;
1581                  RAISE error_trans;
1582                ELSE
1583                  l_trxn_success := TRUE;
1584                  l_mmt_rec.transaction_quantity := l_decr_qty;
1585                  -- also need to set the secondary_transaction_quantity if applicable
1586 
1587                  l_return_status := FND_API.G_RET_STS_SUCCESS;
1588                  IF l_mmt_rec.secondary_uom_code IS NOT NULL THEN
1589                    get_converted_qty (
1590                        p_org_id                    => p_material_detail_rec.organization_id
1591                       ,p_item_id                   => p_material_detail_rec.inventory_item_id
1592                       ,p_lot_number                => NULL
1593                       ,p_qty                       => l_mmt_rec.transaction_quantity
1594                       ,p_from_um                   => p_material_detail_rec.dtl_um
1595                       ,p_to_um                     => l_mmt_rec.secondary_uom_code
1596                       ,x_conv_qty                  => l_mmt_rec.secondary_transaction_quantity
1597                       ,x_return_status             => l_return_status);
1598                  END IF;
1599 
1600                  FOR j IN 1..l_mmln_tbl_orig.COUNT LOOP
1601                    l_mmln_tbl_orig(j).transaction_quantity := l_mmln_tbl_orig(j).transaction_quantity - l_mmln_tbl(j).transaction_quantity;
1602                    IF l_mmt_rec.secondary_uom_code IS NOT NULL THEN
1603                      get_converted_qty (
1604                        p_org_id                    => p_material_detail_rec.organization_id
1605                       ,p_item_id                   => p_material_detail_rec.inventory_item_id
1606                       ,p_lot_number                => l_mmln_tbl_orig(j).lot_number
1607                       ,p_qty                       => l_mmln_tbl_orig(j).transaction_quantity
1608                       ,p_from_um                   => p_material_detail_rec.dtl_um
1609                       ,p_to_um                     => l_mmt_rec.secondary_uom_code
1610                       ,x_conv_qty                  => l_mmln_tbl_orig(j).secondary_transaction_quantity
1611                       ,x_return_status             => l_return_status);
1612                    END IF;
1613                  END LOOP;
1614 
1615                  IF l_return_status = FND_API.G_RET_STS_SUCCESS THEN
1616                    gme_unrelease_batch_pvt.create_resv_pplot
1617                          (p_material_detail_rec    => p_material_detail_rec
1618                          ,p_mmt_rec                => l_mmt_rec
1619                          ,p_mmln_tbl               => l_mmln_tbl_orig
1620                          ,x_return_status          => l_return_status);
1621                  END IF;
1622                  -- don't care if resv or pplot was not recreated...
1623                END IF;
1624 
1625                 -- if the transactions went through successfully, update the lot sums to reflect the returned lots
1626                 -- if not, go back to the last successful qties
1627                 IF l_trxn_success THEN
1628                   l_last_lot_qty_tab := l_lot_qty_tab;
1629                   l_last_qty := l_qty;
1630 
1631                   -- Bug 8571983 - Add to summary bucket.
1632                   l_total_decr_qty := l_total_decr_qty + l_decr_qty;
1633                 ELSE
1634                   l_lot_qty_tab := l_last_lot_qty_tab;
1635                   l_qty := l_last_qty;
1636                 END IF;
1637              END IF;  -- IF l_decr_qty = l_mmt_rec.transaction_quantity THEN
1638           END IF;  -- IF l_lot_record_used = 1 THEN
1639         ELSE
1640           IF ( NVL(G_DEBUG,-1) = GME_DEBUG.G_LOG_STATEMENT ) THEN
1641             gme_debug.put_line (g_pkg_name||'.'||l_api_name||' cant process because not the same transaction_type_id: trxns_id='||l_mmt_rec.transaction_id);
1642           END IF;
1643         END IF;  -- IF l_mmt_rec.transaction_type_id = l_trxn_type THEN
1644 
1645         i := i + 1;
1646       END LOOP;
1647     END IF;
1648 
1649     -- actual qty is reduced by the amount requested less what couldn't be reduced
1650     x_actual_qty := p_material_detail_rec.actual_qty - l_total_decr_qty;
1651 
1652     IF ( NVL(G_DEBUG,-1) = GME_DEBUG.G_LOG_STATEMENT ) THEN
1653       gme_debug.put_line (g_pkg_name||'.'||l_api_name||' total decremented='||l_total_decr_qty);
1654       gme_debug.put_line (g_pkg_name||'.'||l_api_name||' new actual='||x_actual_qty);
1655     END IF;
1656 
1657     -- raise exception if couldn't reduce by requested
1658     IF l_total_decr_qty < p_qty THEN
1659         gme_release_batch_pvt.create_batch_exception
1660                     (p_material_dtl_rec         => p_material_detail_rec
1661                     ,p_pending_move_order_ind   => NULL
1662                     ,p_pending_rsrv_ind         => NULL
1663                     ,p_transacted_qty           => l_total_decr_qty
1664                     ,p_exception_qty            => l_total_decr_qty - p_qty
1665                     ,p_force_unconsumed         => fnd_api.g_true
1666                     ,x_exception_material_tbl   => x_exception_material_tbl
1667                     ,x_return_status            => x_return_status);
1668     END IF;
1669 
1670     IF nvl(g_debug, gme_debug.g_log_procedure + 1) <= gme_debug.g_log_procedure THEN
1671       gme_debug.put_line('Exiting api '||g_pkg_name||'.'||l_api_name||' with return status= '||x_return_status);
1672     END IF;
1673 
1674   EXCEPTION
1675     WHEN error_get_trans OR error_get_lot OR error_trans OR inv_negative THEN
1676       NULL;
1677     WHEN OTHERS THEN
1678       fnd_msg_pub.add_exc_msg (g_pkg_name, l_api_name);
1679       IF g_debug <= gme_debug.g_log_procedure THEN
1680         gme_debug.put_line ('Unexpected error: '||g_pkg_name||'.'||l_api_name||': '||SQLERRM);
1681       END IF;
1682       x_return_status := FND_API.g_ret_sts_unexp_error;
1683   END revert_material_partial;
1684 
1685   PROCEDURE validate_material_for_IB(p_material_detail_rec IN gme_material_details%ROWTYPE
1686                                     ,p_batch_header_rec    IN gme_batch_header%ROWTYPE
1687                                     ,p_adjust_cmplt        IN VARCHAR2
1688                                     ,x_return_status       OUT NOCOPY VARCHAR2) IS
1689 
1690     l_api_name        CONSTANT VARCHAR2 (30)   := 'validate_material_for_IB';
1691 
1692     l_step_no           NUMBER;
1693     l_step_status       NUMBER;
1694 
1695     CURSOR cur_get_step_status(v_material_detail_id NUMBER) IS
1696       SELECT s.batchstep_no, step_status
1697       FROM   gme_batch_steps s, gme_batch_step_items i
1698       WHERE  s.batchstep_id = i.batchstep_id
1699       AND    i.material_detail_id = v_material_detail_id;
1700 
1701     ERROR_INV_ACTION_FPO      EXCEPTION;
1702     ERROR_INV_BATCH_STATUS    EXCEPTION;
1703     ERROR_ADJ_CMPLT_NOT_ALLOW EXCEPTION;
1704     ERROR_INV_WIP_PLAN_QTY    EXCEPTION;
1705     ERROR_INV_RELEASE_TYPE    EXCEPTION;
1706     error_step_closed         EXCEPTION;
1707     error_step_cancelled      EXCEPTION;
1708     error_inv_action_phantom  EXCEPTION;
1709     --Bug#5111078
1710     error_inv_action_lab      EXCEPTION;
1711 
1712   BEGIN
1713     IF nvl(g_debug, gme_debug.g_log_procedure + 1) <= gme_debug.g_log_procedure THEN
1714       gme_debug.put_line('Entering api '||g_pkg_name||'.'||l_api_name);
1715       gme_debug.put_line(g_pkg_name||'.'||l_api_name||' material_detail_id='||p_material_detail_rec.material_detail_id);
1716       gme_debug.put_line(g_pkg_name||'.'||l_api_name||' batch_id='||p_batch_header_rec.batch_id);
1717       gme_debug.put_line(g_pkg_name||'.'||l_api_name||' p_adjust_cmplt='||p_adjust_cmplt);
1718     END IF;
1719 
1720     -- Set the return status to success initially
1721     x_return_status := FND_API.G_RET_STS_SUCCESS;
1722 
1723     -- IB not allowed for FPO
1724     IF p_batch_header_rec.batch_type = gme_common_pvt.g_doc_type_fpo THEN
1725       RAISE ERROR_INV_ACTION_FPO;
1726     END IF;
1727 
1728     --Bug#5111078 IB not allowed for lab batches with update inventory OFF
1729     IF p_batch_header_rec.update_inventory_ind <> 'Y' THEN
1730       RAISE error_inv_action_lab;
1731     END IF;
1732 
1733     -- IB not allowed for phantom batch
1734     IF NVL(p_batch_header_rec.parentline_id ,0) <> 0 THEN
1735       RAISE error_inv_action_phantom;
1736     END IF;
1737 
1738     -- IB allowed if batch status is WIP or Complete
1739     IF p_batch_header_rec.batch_status NOT IN (gme_common_pvt.g_batch_wip
1740                                               ,gme_common_pvt.g_batch_completed) THEN
1741       RAISE ERROR_INV_BATCH_STATUS;
1742     END IF;
1743 
1744     -- If batch is complete then proceed only if user wants to adjust qty
1745     IF p_batch_header_rec.batch_status = gme_common_pvt.g_batch_completed THEN
1746       IF p_adjust_cmplt = fnd_api.g_false THEN
1747         RAISE ERROR_ADJ_CMPLT_NOT_ALLOW;
1748       END IF;
1749     END IF;
1750 
1751     --Bug#5111078 changed to wip plan qty, wip plan qty can't be zero
1752     IF p_material_detail_rec.wip_plan_qty = 0 THEN
1753       RAISE ERROR_INV_WIP_PLAN_QTY;
1754     END IF;
1755 
1756     -- Check Release Type
1757     IF p_material_detail_rec.release_type IN (gme_common_pvt.g_mtl_auto_release
1758                                              ,gme_common_pvt.g_mtl_autobystep_release) THEN
1759       RAISE ERROR_INV_RELEASE_TYPE;
1760     END IF;
1761 
1762     -- If the step associated with the material line is closed or cancelled
1763     OPEN Cur_get_step_status (p_material_detail_rec.material_detail_id);
1764     FETCH Cur_get_step_status INTO l_step_no, l_step_status;
1765     CLOSE Cur_get_step_status;
1766     IF NVL(l_step_status, 0) = gme_common_pvt.g_step_closed THEN
1767       RAISE error_step_closed;
1768     END IF;
1769     IF NVL(l_step_status, 0) = gme_common_pvt.g_step_cancelled THEN
1770       RAISE error_step_cancelled;
1771     END IF;
1772 
1773     IF nvl(g_debug, gme_debug.g_log_procedure + 1) <= gme_debug.g_log_procedure THEN
1774       gme_debug.put_line('Exiting api '||g_pkg_name||'.'||l_api_name);
1775     END IF;
1776 
1777   EXCEPTION
1778   WHEN ERROR_INV_ACTION_FPO THEN
1779     x_return_status := FND_API.G_RET_STS_ERROR;
1780     gme_common_pvt.log_message('GME_INV_ACTION_FPO');
1781   --Bug#5111078
1782   WHEN error_inv_action_lab THEN
1783     x_return_status := FND_API.G_RET_STS_ERROR;
1784     gme_common_pvt.log_message('GME_IB_FOR_UPDINV_NT_ALWD');
1785   WHEN ERROR_INV_BATCH_STATUS THEN
1786     x_return_status := FND_API.G_RET_STS_ERROR;
1787     gme_common_pvt.log_message('GME_API_INV_BATCH_STATUS_PC');
1788   WHEN ERROR_INV_RELEASE_TYPE THEN
1789     x_return_status := FND_API.G_RET_STS_ERROR;
1790     gme_common_pvt.log_message('GME_API_INV_RELEASE_TYPE');
1791   WHEN ERROR_INV_WIP_PLAN_QTY THEN
1792     x_return_status := FND_API.G_RET_STS_ERROR;
1793     gme_common_pvt.log_message('GME_API_INV_WIP_PLAN_QTY_PC');
1794   WHEN ERROR_ADJ_CMPLT_NOT_ALLOW THEN
1795     x_return_status := FND_API.G_RET_STS_ERROR;
1796     gme_common_pvt.log_message('GME_API_ASK_ADJUST_CERTIFY');
1797   WHEN error_step_closed THEN
1798     x_return_status := FND_API.G_RET_STS_ERROR;
1799     GME_COMMON_PVT.log_message ('GME_STEP_CLOSED_ERR', 'STEP_NO', l_step_no);
1800   WHEN error_step_cancelled THEN
1801     x_return_status := FND_API.G_RET_STS_ERROR;
1802     GME_COMMON_PVT.log_message ('GME_STEP_CANCELLED_ERR', 'STEP_NO', l_step_no);
1803   WHEN error_inv_action_phantom THEN
1804     x_return_status := FND_API.G_RET_STS_ERROR;
1805     gme_common_pvt.log_message('PM_INVALID_PHANTOM_ACTION');
1806   WHEN OTHERS THEN
1807     fnd_msg_pub.add_exc_msg (g_pkg_name, l_api_name);
1808     IF g_debug <= gme_debug.g_log_procedure THEN
1809       gme_debug.put_line ('Unexpected error: '||g_pkg_name||'.'||l_api_name||': '||SQLERRM);
1810     END IF;
1811     x_return_status := FND_API.g_ret_sts_unexp_error;
1812   END validate_material_for_IB;
1813 
1814   PROCEDURE validate_qty_for_IB (p_qty_type   IN NUMBER
1815                                 ,p_qty        IN NUMBER
1816                                 ,p_actual_qty IN NUMBER
1817                                 ,x_return_status OUT NOCOPY VARCHAR2) IS
1818     l_api_name        CONSTANT VARCHAR2 (30)   := 'validate_qty_for_IB';
1819 
1820     ERROR_INV_INCR_TYPE           EXCEPTION;
1821     ERROR_QTY_CANT_BE_ZERO        EXCEPTION;
1822     ERROR_QTY_CREATE_NEG_ACTUAL   EXCEPTION;
1823   BEGIN
1824     IF nvl(g_debug, gme_debug.g_log_procedure + 1) <= gme_debug.g_log_procedure THEN
1825       gme_debug.put_line('Entering api '||g_pkg_name||'.'||l_api_name);
1826       gme_debug.put_line(g_pkg_name||'.'||l_api_name||' p_qty_type='||p_qty_type);
1827       gme_debug.put_line(g_pkg_name||'.'||l_api_name||' p_qty='||p_qty);
1828       gme_debug.put_line(g_pkg_name||'.'||l_api_name||' p_actual_qty='||p_actual_qty);
1829     END IF;
1830 
1831     -- Set the return status to success initially
1832     x_return_status := FND_API.G_RET_STS_SUCCESS;
1833 
1834     -- p_qty_type 0 increment qty
1835     -- p_qty_type 1 new act qty
1836     -- p_qty_type 2 % plan
1837 
1838     IF p_qty_type NOT IN (0,1,2) THEN
1839       RAISE ERROR_INV_INCR_TYPE;
1840     END IF;
1841 
1842     -- INCREMENTAL
1843     IF p_qty_type = 0 THEN
1844       IF p_qty = 0 THEN
1845         RAISE ERROR_QTY_CANT_BE_ZERO;
1846       ELSIF p_qty < 0 THEN
1847         IF ((p_qty * -1 ) > p_actual_qty) THEN
1848           RAISE ERROR_QTY_CREATE_NEG_ACTUAL ;
1849         END IF;
1850       END IF;
1851     -- NEW ACTUAL
1852     ELSIF p_qty_type = 1 THEN
1853       IF p_qty < 0 THEN
1854         RAISE ERROR_QTY_CREATE_NEG_ACTUAL;
1855       END IF;
1856     -- % PLAN
1857     ELSIF p_qty_type = 2 THEN
1858       IF p_qty < 0 THEN
1859         RAISE ERROR_QTY_CREATE_NEG_ACTUAL;
1860       END IF;
1861     END IF;
1862 
1863     IF nvl(g_debug, gme_debug.g_log_procedure + 1) <= gme_debug.g_log_procedure THEN
1864       gme_debug.put_line('Exiting api '||g_pkg_name||'.'||l_api_name);
1865     END IF;
1866 
1867   EXCEPTION
1868   WHEN ERROR_INV_INCR_TYPE THEN
1869     x_return_status := FND_API.G_RET_STS_ERROR;
1870     gme_common_pvt.log_message( 'GME_API_INVALID_INCR_TYPE');
1871   WHEN ERROR_QTY_CREATE_NEG_ACTUAL THEN
1872     x_return_status := FND_API.G_RET_STS_ERROR;
1873     gme_common_pvt.log_message( 'GME_API_ACTUAL_CANT_GO_NEG');
1874   WHEN ERROR_QTY_CANT_BE_ZERO THEN
1875     x_return_status := FND_API.G_RET_STS_ERROR;
1876     gme_common_pvt.log_message( 'GME_API_QTY_CANT_BE_ZERO');
1877   WHEN OTHERS THEN
1878     fnd_msg_pub.add_exc_msg (g_pkg_name, l_api_name);
1879     IF g_debug <= gme_debug.g_log_procedure THEN
1880       gme_debug.put_line ('Unexpected error: '||g_pkg_name||'.'||l_api_name||': '||SQLERRM);
1881     END IF;
1882     x_return_status := FND_API.g_ret_sts_unexp_error;
1883   END validate_qty_for_IB;
1884 
1885   PROCEDURE get_converted_qty (
1886       p_org_id                    IN NUMBER
1887      ,p_item_id                   IN NUMBER
1888      ,p_lot_number                IN VARCHAR2 DEFAULT NULL
1889      ,p_qty                       IN NUMBER
1890      ,p_from_um                   IN VARCHAR2
1891      ,p_to_um                     IN VARCHAR2
1892      ,x_conv_qty                  OUT NOCOPY NUMBER
1893      ,x_return_status             OUT NOCOPY VARCHAR2) IS
1894 
1895       l_api_name           CONSTANT VARCHAR2 (30)     := 'get_converted_qty';
1896 
1897       um_convert_error     EXCEPTION;
1898 
1899   BEGIN
1900       IF nvl(g_debug, gme_debug.g_log_procedure + 1) <= gme_debug.g_log_procedure THEN
1901         gme_debug.put_line('Entering api '||g_pkg_name||'.'||l_api_name);
1902         gme_debug.put_line(g_pkg_name||'.'||l_api_name||' p_item_id='||p_item_id);
1903         gme_debug.put_line(g_pkg_name||'.'||l_api_name||' p_lot_number='||p_lot_number);
1904         gme_debug.put_line(g_pkg_name||'.'||l_api_name||' p_qty='||p_qty);
1905         gme_debug.put_line(g_pkg_name||'.'||l_api_name||' p_from_um='||p_from_um);
1906         gme_debug.put_line(g_pkg_name||'.'||l_api_name||' p_to_um='||p_to_um);
1907       END IF;
1908 
1909       /* Set the return status to success initially */
1910       x_return_status       := FND_API.G_RET_STS_SUCCESS;
1911 
1912       IF p_to_um = p_from_um THEN
1913          x_conv_qty := p_qty;
1914       ELSE
1915          IF (NVL (g_debug, -1) = gme_debug.g_log_statement) THEN
1916                gme_debug.put_line
1917                                  (   g_pkg_name
1918                                   || '.'
1919                                   || l_api_name
1920                                   || ' before call to inv_convert.inv_um_convert');
1921          END IF;
1922 
1923          x_conv_qty := inv_convert.inv_um_convert
1924                (item_id              => p_item_id
1925                ,lot_number           => p_lot_number
1926                ,organization_id      => p_org_id
1927                ,precision            => gme_common_pvt.g_precision
1928                ,from_quantity        => p_qty
1929                ,from_unit            => p_from_um
1930                ,to_unit              => p_to_um
1931                ,from_name            => NULL
1932                ,to_name              => NULL);
1933 
1934          -- Note: -99999 should be in gme_common_pvt
1935          IF x_conv_qty = -99999 THEN
1936                IF (NVL (g_debug, -1) = gme_debug.g_log_statement) THEN
1937                   gme_debug.put_line
1938                                 (   g_pkg_name
1939                                  || '.'
1940                                  || l_api_name
1941                                  || ' inv_convert.inv_um_convert returned error');
1942                END IF;
1943 
1944                RAISE um_convert_error;
1945          END IF;
1946       END IF;  --  IF p_to_um = p_from_um THEN
1947 
1948       IF (NVL (g_debug, -1) = gme_debug.g_log_statement) THEN
1949                gme_debug.put_line
1950                                  (   g_pkg_name
1951                                   || '.'
1952                                   || l_api_name
1953                                   || ' converted qty = '||x_conv_qty);
1954       END IF;
1955 
1956       IF nvl(g_debug, gme_debug.g_log_procedure + 1) <= gme_debug.g_log_procedure THEN
1957          gme_debug.put_line('Exiting api '||g_pkg_name||'.'||l_api_name);
1958       END IF;
1959    EXCEPTION
1960       WHEN um_convert_error THEN
1961          FND_MESSAGE.SET_NAME('INV','INV_NO_CONVERSION_ERR');
1962          FND_MESSAGE.SET_TOKEN('PGM_NAME',g_pkg_name||'.'||l_api_name);
1963          fnd_msg_pub.ADD;
1964          x_return_status := fnd_api.g_ret_sts_error;
1965       WHEN OTHERS THEN
1966          fnd_msg_pub.add_exc_msg (g_pkg_name, l_api_name);
1967 
1968          IF (NVL (g_debug, -1) = gme_debug.g_log_statement) THEN
1969             gme_debug.put_line (   'Unexpected error: '
1970                                 || g_pkg_name
1971                                 || '.'
1972                                 || l_api_name
1973                                 || ': '
1974                                 || SQLERRM);
1975          END IF;
1976          x_return_status := fnd_api.g_ret_sts_unexp_error;
1977   END get_converted_qty;
1978 
1979 
1980 END gme_incremental_backflush_pvt;