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