DBA Data[Home] [Help]

PACKAGE BODY: APPS.WMS_RULE_EXTN_PVT

Source


1 PACKAGE BODY wms_rule_extn_pvt AS
2   /* $Header: WMSVRXTB.pls 120.14.12020000.3 2013/01/23 05:45:27 abasheer ship $ */
3   --
4   -- File        : WMSVPPTB.pls
5   -- Content     : WMS_Test_Pub package body
6   -- Description : wms rules engine private API's
7   -- Notes       :
8   -- Modified    : 05/18/05 rambrose created orginal file
9   --
10   g_pkg_name    CONSTANT VARCHAR2(30) := 'WMS_rule_extn_PVT';
11   g_debug       NUMBER;
12 
13 
14   TYPE numtbltype IS TABLE OF NUMBER
15     INDEX BY BINARY_INTEGER;
16 
17   --Procedures for logging messages
18   PROCEDURE log_event(p_api_name VARCHAR2, p_label VARCHAR2, p_message VARCHAR2) IS
19     l_module VARCHAR2(255);
20   BEGIN
21     l_module  := 'wms.plsql.' || g_pkg_name || '.' || p_api_name || '.' || p_label;
22     inv_log_util.trace(p_message, l_module, 9);
23   END log_event;
24 
25   PROCEDURE log_error(p_api_name VARCHAR2, p_label VARCHAR2, p_message VARCHAR2) IS
26     l_module VARCHAR2(255);
27   BEGIN
28     l_module  := 'wms.plsql.' || g_pkg_name || '.' || p_api_name || '.' || p_label;
29     inv_log_util.trace(p_message, l_module, 9);
30   END log_error;
31 
32   PROCEDURE log_error_msg(p_api_name VARCHAR2, p_label VARCHAR2) IS
33     l_module VARCHAR2(255);
34   BEGIN
35     l_module  := 'wms.plsql.' || g_pkg_name || '.' || p_api_name || '.' || p_label;
36     inv_log_util.trace('err:', l_module, 9);
37   END log_error_msg;
38 
39   PROCEDURE log_procedure(p_api_name VARCHAR2, p_label VARCHAR2, p_message VARCHAR2) IS
40     l_module VARCHAR2(255);
41   BEGIN
42     l_module  := 'wms.plsql.' || g_pkg_name || '.' || p_api_name || '.' || p_label;
43     inv_log_util.trace(p_message, l_module, 9);
44   END log_procedure;
45 
46   PROCEDURE log_statement(p_api_name VARCHAR2, p_label VARCHAR2, p_message VARCHAR2) IS
47     l_module VARCHAR2(255);
48   BEGIN
49     l_module  := 'wms.plsql.' || g_pkg_name || '.' || p_api_name || '.' || p_label;
50     inv_log_util.trace(p_message, l_module, 9);
51   END log_statement;
52 
53   -- Start of comments
54   -- Name        : InitQtyTree
55   -- Function    : Initializes quantity tree for picking and returns tree id.
56   -- Pre-reqs    : none
57   -- Parameters  :
58   --  x_return_status              out varchar2(1)
59   --  x_msg_count                  out number
60   --  x_msg_data                   out varchar2(2000)
61   --  p_organization_id            in  number   required
62   --  p_inventory_item_id          in  number   required
63   --  p_transaction_source_type_id in  number   required
64   --  p_transaction_source_id      in  number   required
65   --  p_trx_source_line_id         in  number   required
66   --  p_trx_source_delivery_id     in  number   required
67   --  p_transaction_source_name    in  varchar2 required
68   --  p_tree_mode                  in  number   required
69   --  x_tree_id                    out number
70   -- Notes       : privat procedure for internal use only
71   -- End of comments
72 
73   procedure InitQtyTree (
74             x_return_status                out nocopy  varchar2
75            ,x_msg_count                    out nocopy  number
76            ,x_msg_data                     out nocopy  varchar2
77            ,p_organization_id              in   number
78            ,p_inventory_item_id            in   number
79            ,p_transaction_source_type_id   in   number
80            ,p_transaction_source_id        in   number
81            ,p_trx_source_line_id           in   number
82            ,p_trx_source_delivery_id       in   number
83            ,p_transaction_source_name      in   varchar2
84            ,p_tree_mode                    in   number
85            ,x_tree_id                      out nocopy  number
86                         ) is
87 
88     l_api_name            VARCHAR2(30) := 'InitQtyTree';
89     l_rev_control_code    MTL_SYSTEM_ITEMS.REVISION_QTY_CONTROL_CODE%type;
90     l_lot_control_code    MTL_SYSTEM_ITEMS.LOT_CONTROL_CODE%type;
91     l_ser_control_code    MTL_SYSTEM_ITEMS.SERIAL_NUMBER_CONTROL_CODE%type;
92     l_is_revision_control boolean;
93     l_is_lot_control      boolean;
94     l_is_serial_control   boolean;
95     l_msg_data VARCHAR2(240);
96     l_transaction_source_id NUMBER;
97     l_trx_source_line_id NUMBER;
98     l_debug              NUMBER;
99     cursor iteminfo is
100     select nvl(msi.REVISION_QTY_CONTROL_CODE,1)
101           ,nvl(msi.LOT_CONTROL_CODE,1)
102           ,nvl(msi.SERIAL_NUMBER_CONTROL_CODE,1)
103       from MTL_SYSTEM_ITEMS msi
104      where ORGANIZATION_ID   = p_organization_id
105        and INVENTORY_ITEM_ID = p_inventory_item_id
106     ;
107   begin
108 
109     IF (g_debug IS   NULL) THEN
110         g_debug := NVL(FND_PROFILE.VALUE('INV_DEBUG_TRACE'),0);
111     END IF;
112     l_debug := g_debug;
113     If (l_debug = 1) then
114       log_procedure(l_api_name, 'start', 'Start InitQtyTree');
115     End if;
116     /*--
117     -- debugging portion
118     -- can be commented ut for final code
119     IF inv_pp_debug.is_debug_mode THEN
120        inv_pp_debug.send_message_to_pipe('enter '||g_pkg_name||'.'||l_api_name);
121     END IF;
122     -- end of debugging section
123     -- */
124     open iteminfo;
125     fetch iteminfo into l_rev_control_code
126                        ,l_lot_control_code
127                        ,l_ser_control_code;
128     if iteminfo%notfound then
129       close iteminfo;
130       raise no_data_found;
131     end if;
132     close iteminfo;
133 
134     if l_rev_control_code = 1 then
135       l_is_revision_control := false;
136     else
137       l_is_revision_control := true;
138     end if;
139     if l_lot_control_code = 1 then
140       l_is_lot_control := false;
141     else
142       l_is_lot_control := true;
143     end if;
144     if l_ser_control_code = 1 then
145       l_is_serial_control := false;
146     else
147       l_is_serial_control := true;
148     end if;
149 
150     -- bug 2398927
151     --if source type id is 13 (inventory), don't pass in the demand
152     --source line and header info.  This info was causing LPN putaway
153     -- to fall for unit effective items.
154     IF p_transaction_source_type_id IN (4,13) THEN
155       l_transaction_source_id := -9999;
156       l_trx_source_line_id := -9999;
157     ELSE      l_transaction_source_id := p_transaction_source_id;
158       l_trx_source_line_id := p_trx_source_line_id;
159     END IF;
160 
161     If (l_debug = 1) then
162       log_event(l_api_name, 'create_tree',
163                 'Trying to create quantity tree in exclusive mode');
164     End if;
165 
166     INV_Quantity_Tree_PVT.Create_Tree
167         (
168           p_api_version_number              => 1.0
169           --,p_init_msg_list                => fnd_api.g_false
170           ,x_return_status                  => x_return_status
171           ,x_msg_count                      => x_msg_count
172           ,x_msg_data                       => x_msg_data
173           ,p_organization_id                => p_organization_id
174           ,p_inventory_item_id              => p_inventory_item_id
175           ,p_tree_mode                      => p_tree_mode
176           ,p_is_revision_control            => l_is_revision_control
177           ,p_is_lot_control                 => l_is_lot_control
178           ,p_is_serial_control              => l_is_serial_control
179           ,p_asset_sub_only                 => FALSE
180           ,p_include_suggestion             => TRUE
181           ,p_demand_source_type_id          => p_transaction_source_type_id
182           ,p_demand_source_header_id        => l_transaction_source_id
183           ,p_demand_source_line_id          => l_trx_source_line_id
184           ,p_demand_source_name             => p_transaction_source_name
185           ,p_demand_source_delivery         => p_trx_source_delivery_id
186           ,p_lot_expiration_date            => sysdate
187           ,p_onhand_source                  => inv_quantity_tree_pvt.g_all_subs
188           ,p_exclusive                      => inv_quantity_tree_pvt.g_exclusive
189           ,p_pick_release                   => inv_quantity_tree_pvt.g_pick_release_yes
190           ,x_tree_id                        => x_tree_id
191         );
192     --
193     If (l_debug = 1) then
194       log_event(l_api_name, 'create_tree_finished',
195                 'Created quantity tree in exclusive mode');
196     End if;
197    /* -- debugging portion
198     -- can be commented ut for final code
199     IF inv_pp_debug.is_debug_mode THEN
200        inv_pp_debug.send_message_to_pipe('exit '||g_pkg_name||'.'||l_api_name);
201     END IF;
202     -- end of debugging section */
203     If (l_debug = 1) then
204       log_procedure(l_api_name, 'end', 'End InitQtyTree');
205     End if;
206     --
207 exception
208     when others then
209       if iteminfo%isopen then
210         close iteminfo;
211       end if;
212       x_return_status := fnd_api.g_ret_sts_unexp_error;
213       if fnd_msg_pub.check_msg_level(fnd_msg_pub.g_msg_lvl_unexp_error) then
214         fnd_msg_pub.add_exc_msg(g_pkg_name, l_api_name);
215       end if;
216       fnd_msg_pub.count_and_get( p_count => x_msg_count
217                                 ,p_data  => x_msg_data );
218       If (l_debug = 1) then
219         log_error(l_api_name, 'error', 'Error in InitQtyTree - ' || x_msg_data);
220       End if;
221 end InitQtyTree;
222 
223 
224 PROCEDURE suggest_reservations(
225     p_api_version         IN            NUMBER
226   , p_init_msg_list       IN            VARCHAR2
227   , p_commit              IN            VARCHAR2
228   , p_validation_level    IN            NUMBER
229   , x_return_status       OUT NOCOPY    VARCHAR2
230   , x_msg_count           OUT NOCOPY    NUMBER
231   , x_msg_data            OUT NOCOPY    VARCHAR2
232   , p_transaction_temp_id IN            NUMBER
233   , p_allow_partial_pick  IN            VARCHAR2
234   , p_suggest_serial      IN            VARCHAR2
235   , p_mo_line_rec         IN OUT NOCOPY inv_move_order_pub.trolin_rec_type -- bug 12314831
236   , p_demand_source_type  IN            NUMBER
237   , p_demand_source_header_id  IN       NUMBER
238   , p_demand_source_line_id    IN       NUMBER
239   , p_demand_source_detail     IN       NUMBER DEFAULT NULL
240   , p_demand_source_name  IN            VARCHAR2 DEFAULT NULL
241   , p_requirement_date    IN            DATE  DEFAULT  NULL
242   , p_suggestions         OUT NOCOPY g_suggestion_list_rec_type
243   ) IS
244     l_api_version       CONSTANT NUMBER                                         := 1.0;
245     l_api_name             VARCHAR2(30)   :=    'Suggest_Reservations';
246     l_qry_rsv_rec            inv_reservation_global.mtl_reservation_rec_type;
247     l_new_reservation        inv_reservation_global.mtl_reservation_rec_type;
248     l_orig_reservation       inv_reservation_global.mtl_reservation_rec_type;
249     l_last_reservation       inv_reservation_global.mtl_reservation_rec_type;
250     -- Record for querying up matching reservations for the move order line
251     l_demand_rsvs_ordered     inv_reservation_global.mtl_reservation_tbl_type;
252     l_demand_reservations     inv_reservation_global.mtl_reservation_tbl_type;
253     l_rsv_qty_available       NUMBER;
254 
255      l_rsv_qty2_available      NUMBER; --BUG#7377744 Added a secondary quantity available to reserve to make it consistent with process_reservations call
256     l_new_reservation_id      NUMBER;
257     l_qty_succ_reserved       NUMBER;
258     l_rsv_index               NUMTBLTYPE;
259     l_demand_info             wsh_inv_delivery_details_v%ROWTYPE;
260     l_dummy_sn                inv_reservation_global.serial_number_tbl_type;
261     l_reserved_serials       inv_reservation_global.serial_number_tbl_type;
262     l_suggested_serials       inv_reservation_global.serial_number_tbl_type;
263     l_reservation_count_by_id NUMBER;
264     l_requirement_date        DATE;
265     l_primary_uom_code        VARCHAR2(10) ;
266     l_simulation_mode         NUMBER;
267     l_simulation_id           NUMBER;
268     l_api_error_code          VARCHAR2(10);
269     l_return_value          BOOLEAN;
270     l_message                  VARCHAR2(200);
271     l_reservable_type          NUMBER;
272     i NUMBER;
273 
274     first_pass                BOOLEAN;
275     l_tree_id                       NUMBER;
276     l_qoh                       NUMBER;
277     l_rqoh                      NUMBER;
278     l_qr                        NUMBER;
279     l_qs                        NUMBER;
280     l_att                       NUMBER;
281     l_atr                       NUMBER;
282     l_allocation_quantity       NUMBER;
283     l_sqoh                      NUMBER;
284     l_srqoh                     NUMBER;
285     l_sqr                       NUMBER;
286     l_sqs                       NUMBER;
287     l_satt                      NUMBER;
288     l_satr                      NUMBER;
289 
290     l_debug NUMBER := NVL(FND_PROFILE.VALUE('INV_DEBUG_TRACE'),0);
291 
292     l_last_sugg_str    VARCHAR2(120);
293 
294     --bug 12314831
295     l_reservable_qty            NUMBER := 0; -- Changed the initialization for Bug 13910013
296     l_reservable_mol_uom_qty    NUMBER := 0;
297     l_reservable_primary_qty    NUMBER := 0;
298     l_reservable_sec_qty        NUMBER := 0;
299     l_update_mol                BOOLEAN;
300 
301     l_rsv_pri_qty               NUMBER;
302 
303     l_return_status           VARCHAR2 (1);
304     l_msg_count               NUMBER;
305     l_msg_data                VARCHAR2 (400);
306     l_rsv_rec                 inv_reservation_global.mtl_reservation_rec_type;
307     l_original_serial_number  inv_reservation_global.serial_number_tbl_type;
308     del_resvn_error           EXCEPTION;
309     l_lot_divisible_flag      VARCHAR2(1):='Y'; -- Added for Bug 13910013
310 	l_lot_control_code        NUMBER; -- Added for Bug 16203819
311 
312   CURSOR c_sugg_grp IS
313      SELECT from_organization_id
314           , lot_number
315           , revision
316           , from_subinventory_code
317           , from_locator_id
318           , lpn_id
319           , reservation_id
320           , sum(primary_quantity) primary_quantity
321           , sum(transaction_quantity) transaction_quantity
322           , sum(secondary_quantity) secondary_quantity
323           , revision || ' - ' || lot_number || ' - ' || from_subinventory_code || ' - ' || from_locator_id || ' - ' || lpn_id as sugg_str
324      FROM wms_transactions_temp
325      WHERE line_type_code = 2
326      GROUP BY from_organization_id,
327               lot_number, from_subinventory_code, revision,
328              from_locator_id, lpn_id, reservation_id
329      ORDER BY sugg_str, reservation_id;
330 
331    CURSOR c_high_level_res_csr IS
332         SELECT  mr.organization_id org_id,
333                 mr.reservation_id res_id
334         FROM mtl_reservations mr
335         WHERE mr.organization_id = p_mo_line_rec.organization_id
336           AND mr.demand_source_type_id = INV_GLOBALS.G_SOURCETYPE_WIP
337           AND mr.demand_source_header_id = p_demand_source_header_id
338           AND mr.demand_source_line_id = p_demand_source_line_id
339           AND NVL(mr.lot_number,'@@@') = '@@@'
340           AND NVL(mr.subinventory_code, '@@@') = '@@@'
341           AND NVL(mr.locator_id, '-999') = '-999'
342           AND NVL(mr.lpn_id, '-999') = '-999'
343           AND NVL(mr.revision, '@@@') = '@@@'
344           AND NOT EXISTS (SELECT 1
345                             FROM mtl_material_transactions_temp
346                             WHERE reservation_id = mr.reservation_id)
347           ORDER BY mr.requirement_date, mr.reservation_id;
348 
349 
350   CURSOR c_sugg_serials(lc_from_org   NUMBER
351                       , lc_from_sub   VARCHAR2
352                       , lc_from_loc   NUMBER
353                       , lc_from_rev   VARCHAR2
354                       , lc_lot_num    VARCHAR2
355                       , lc_lpn_id     NUMBER
356                       , lc_res_id     NUMBER) IS
357      SELECT serial_number
358      FROM   wms_transactions_temp
359      WHERE line_type_code = 2
360        AND from_organization_id = lc_from_org
361        AND from_subinventory_code = lc_from_sub
362        AND nvl(from_locator_id,-888)      = nvl(lc_from_loc,-888)
363        AND nvl(revision,'@@@')      = nvl(lc_from_rev,'@@@')
364        AND nvl(lot_number,'@@@')          = nvl(lc_lot_num,'@@@')
365        AND nvl(lpn_id,-888)     = nvl(lc_lpn_id, -888)
366        AND nvl(reservation_id,-888) = nvl(lc_res_id, -888);
367 
368 
369   CURSOR c_suggestions IS
370      SELECT from_organization_id
371           , to_organization_id
372           , revision
373           , lot_number
374           , lot_expiration_date
375           , from_subinventory_code
376           , to_subinventory_code
377           , from_locator_id
378           , to_locator_id
379           , lpn_id
380           , reservation_id
381           , serial_number
382           , grade_code
383           , from_cost_group_id
384           , to_cost_group_id
385           , sum(primary_quantity) primary_quantity
386           , sum(transaction_quantity) transaction_quantity
387           , sum(secondary_quantity) secondary_quantity
388      FROM wms_transactions_temp
389      WHERE line_type_code = 2
390      GROUP BY from_organization_id, to_organization_id, revision,
391               lot_number, lot_expiration_date, from_subinventory_code,
392               to_subinventory_code, from_locator_id, to_locator_id, lpn_id, reservation_id,
393               serial_number, grade_code, from_cost_group_id, to_cost_group_id;
394 
395   CURSOR c_rsv_primary_qty(p_rsv_id  NUMBER) IS
396      SELECT mr.primary_reservation_quantity
397      FROM   mtl_reservations  mr
398      WHERE  mr.reservation_id = p_rsv_id;
399 
400 BEGIN
401 
402   g_debug := l_debug;
403 
404   If l_debug = 1  THEN
405      log_procedure(l_api_name, 'start', 'Start suggest_reservations');
406      log_event( l_api_name
407               , 'start_detail'
408               , 'Starting the WMS Rules engine Extention to create Rules Based reservations: '
409                 || p_transaction_temp_id
410               );
411   End if;
412 
413   -- Standard start of API savepoint
414   SAVEPOINT suggest_reservations_sa;
415 
416   --
417   -- Standard Call to check for call compatibility
418   IF NOT fnd_api.compatible_api_call(l_api_version, p_api_version, l_api_name, g_pkg_name) THEN
419      RAISE fnd_api.g_exc_unexpected_error;
420   END IF;
421 
422   --
423   -- Initialize message list if p_init_msg_list is set to true
424   IF fnd_api.to_boolean(p_init_msg_list) THEN
425      fnd_msg_pub.initialize;
426   END IF;
427 
428   log_procedure(l_api_name, 'start', 'Start suggest_reservations');
429   --
430   -- Initialisize API return status to access
431   x_return_status          := fnd_api.g_ret_sts_success;
432   --
433 
434   l_return_value := INV_CACHE.set_item_rec(p_mo_line_rec.organization_id,
435                                              p_mo_line_rec.inventory_item_id);
436   l_reservable_type:= INV_CACHE.item_rec.reservable_type;
437   l_lot_divisible_flag:= INV_CACHE.item_rec.lot_divisible_flag; -- Added for Bug 13910013
438   l_lot_control_code := INV_CACHE.item_rec.lot_control_code; -- Added for Bug 16203819
439 
440   IF l_reservable_type = 2 THEN
441      IF (l_debug = 1) THEN
442          log_error(l_api_name, 'Suggest_Reservations','Error - Item is not reservable');
443      END IF;
444 
445      RAISE fnd_api.g_exc_error;
446   END IF;
447 
448   /* Set Demand Info Record */
449   l_demand_info.oe_line_id := p_demand_source_line_id;
450 
451   /* Call Process Reservations */
452   -- Bug#7377744: included secondary quantity available to reserve in the parameters
453   inv_pick_release_pvt.process_reservations(
454      x_return_status => x_return_status
455    , x_msg_count => x_msg_count
456    , x_msg_data => x_msg_data
457    , p_demand_info => l_demand_info
458    , p_mo_line_rec => p_mo_line_rec
459    , p_mso_line_id => p_demand_source_header_id
460    , p_demand_source_type => p_demand_source_type
461    , p_demand_source_name => p_demand_source_name
462    , p_allow_partial_pick => p_allow_partial_pick
463    , x_demand_rsvs_ordered => l_demand_rsvs_ordered
464    , x_rsv_qty_available => l_rsv_qty_available
465     ,x_rsv_qty2_available  => l_rsv_qty2_available);
466 
467 
468   -- Return an error if the query reservations call failed
469   IF x_return_status <> fnd_api.g_ret_sts_success THEN
470      IF ( l_debug = 1 ) THEN
471         log_error(l_api_name, 'Suggest_Reservations', 'l_return_status = '|| x_return_status);
472         log_error(l_api_name, 'Suggest_Reservations', 'Process Reservations Failed ' || x_msg_data);
473      END IF;
474      RAISE fnd_api.g_exc_unexpected_error;
475   END IF;
476 
477   /* Place reservation IDs into a table for easy access when creating new reservations */
478   IF l_demand_rsvs_ordered.count > 0 THEN
479      log_event(l_api_name, 'Suggest_Reservations','# Reservations returned from Process Reservation : ' || l_demand_rsvs_ordered.count);
480      FOR i in l_demand_rsvs_ordered.First..l_demand_rsvs_ordered.Last LOOP
481           inv_reservation_pvt.print_rsv_rec(l_demand_rsvs_ordered (i));
482         l_rsv_index(l_demand_rsvs_ordered(i).reservation_id) := i;
483 
484         -- bug 12314831 start
485         IF ( l_debug = 1 ) THEN
486           log_event(l_api_name, 'Suggest_Reservations','l_demand_rsvs_ordered(i).secondary_reservation_quantity :  ' || l_demand_rsvs_ordered(i).secondary_reservation_quantity );
487         END IF;
488 
489         l_reservable_sec_qty := l_reservable_sec_qty + l_demand_rsvs_ordered(i).secondary_reservation_quantity ;
490 
491         IF ( l_debug = 1 ) THEN
492            log_event(l_api_name, 'Suggest_Reservations','Check if the MOL UOM code is different than reservation UOM code ');
493            log_event(l_api_name, 'Suggest_Reservations','l_demand_rsvs_ordered(i).reservation_uom_code: ' || l_demand_rsvs_ordered(i).reservation_uom_code);
494            log_event(l_api_name, 'Suggest_Reservations','p_mo_line_rec.uom_code: ' || p_mo_line_rec.uom_code);
495         END IF;
496 
497 
498         IF l_demand_rsvs_ordered(i).reservation_uom_code <> p_mo_line_rec.uom_code THEN
499            -- perform UOM conversion
500            l_reservable_mol_uom_qty := inv_convert.inv_um_convert ( l_demand_rsvs_ordered(i).inventory_item_id,
501                                                         5,
502                                                         l_demand_rsvs_ordered(i).reservation_quantity,
503                                                         l_demand_rsvs_ordered(i).reservation_uom_code,
504                                                         p_mo_line_rec.uom_code,
505                                                         NULL,
506                                                         NULL);
507            IF ( l_debug = 1 ) THEN
508               log_event(l_api_name, 'Suggest_Reservations','Converted reservable qty (in MOLs UOM): ' || l_reservable_mol_uom_qty);
509            END IF;
510 
511            l_reservable_qty := l_reservable_qty + l_reservable_mol_uom_qty;
512 
513            IF ( l_debug = 1 ) THEN
514               log_event(l_api_name, 'Suggest_Reservations','Converted reservable qty: ' || l_reservable_qty);
515            END IF;
516         ELSE
517            l_reservable_qty := l_reservable_qty + l_demand_rsvs_ordered(i).reservation_quantity;
518         END IF;
519 
520         IF ( l_debug = 1 ) THEN
521            log_event(l_api_name, 'Suggest_Reservations','Check if the MOLs primary UOM code is different than reservation UOM code ');
522            log_event(l_api_name, 'Suggest_Reservations','l_demand_rsvs_ordered(i).reservation_uom_code: ' || l_demand_rsvs_ordered(i).reservation_uom_code);
523            log_event(l_api_name, 'Suggest_Reservations','MOLs primary UOM code ' || INV_CACHE.item_rec.primary_uom_code);
524         END IF;
525 
526         IF l_demand_rsvs_ordered(i).reservation_uom_code <> INV_CACHE.item_rec.primary_uom_code THEN
527            IF ( l_debug = 1 ) THEN
528               log_event(l_api_name, 'Suggest_Reservations','l_reservable_primary_qty: ' || l_reservable_primary_qty);
529            END IF;
530            l_reservable_primary_qty := l_reservable_primary_qty + inv_convert.inv_um_convert ( l_demand_rsvs_ordered(i).inventory_item_id,
531                                                                                     5,
532                                                                                     l_demand_rsvs_ordered(i).reservation_quantity,
533                                                                                     l_demand_rsvs_ordered(i).reservation_uom_code,
534                                                                                     INV_CACHE.item_rec.primary_uom_code,
535                                                                                     NULL,
536                                                                                     NULL);
537         -- Added the else part for Bug 13910013
538         ELSE
539            l_reservable_primary_qty := l_reservable_primary_qty + l_demand_rsvs_ordered(i).primary_reservation_quantity;
540         END IF;
541 
542            IF ( l_debug = 1 ) THEN
543               log_event(l_api_name, 'Suggest_Reservations','converted l_reservable_primary_qty: ' || l_reservable_primary_qty);
544            END IF;
545 
546         -- bug 12314831 end
547      END LOOP;
548   END IF;
549 
550   -- bug 12314831 start
551   IF ( l_debug = 1 ) THEN
552      log_event(l_api_name, 'Suggest_Reservations','Reservable Qty: ' || l_reservable_qty);
553      log_event(l_api_name, 'Suggest_Reservations','Passed p_mo_line_rec.quantity: ' || p_mo_line_rec.quantity);
554   END IF;
555 
556   IF (l_lot_divisible_flag <> 'N') THEN -- Added for Bug 13910013
557 	update mtl_txn_request_lines
558 		 set quantity = l_reservable_qty,
559 		 primary_quantity = l_reservable_primary_qty,
560 		 secondary_quantity = l_reservable_sec_qty
561 	 where line_id = p_mo_line_rec.line_id;
562   END IF; -- End of Bug 13910013
563 
564   IF ( l_debug = 1 ) THEN
565      log_event(l_api_name, 'Suggest_Reservations','Updated number of rows: ' || SQL%ROWCOUNT);
566      log_event(l_api_name, 'Suggest_Reservations','Update the INV Cache');
567   END IF;
568 
569   l_update_mol := INV_CACHE.set_mol_rec(p_mo_line_rec.line_id);
570 
571   IF ( l_debug = 1 ) THEN
572      log_event(l_api_name, 'Suggest_Reservations','Update the p_mo_line_rec');
573   END IF;
574 
575   p_mo_line_rec := inv_trolin_util.query_row(p_mo_line_rec.line_id);
576   -- bug 12314831 end
577 
578   DELETE FROM WMS_TRANSACTIONS_TEMP WHERE line_type_code = 2;
579 
580   /* Call create suggestions */
581   wms_engine_pvt.create_suggestions(
582      p_api_version         => 1.0
583    , p_init_msg_list       => fnd_api.g_true
584    , p_commit              => fnd_api.g_false
585    , p_validation_level    => NULL
586    , x_return_status       => x_return_status
587    , x_msg_count           => x_msg_count
588    , x_msg_data            => x_msg_data
589    , p_transaction_temp_id => p_mo_line_rec.line_id
590    , p_reservations        => l_demand_rsvs_ordered
591    , p_suggest_serial      => p_suggest_serial
592    , p_simulation_mode     => wms_engine_pvt.g_pick_full_mode
593    , p_simulation_id       => NULL
594    , p_plan_tasks          => FALSE
595    , p_quick_pick_flag     => 'N'
596    );
597 
598   IF x_return_status <> fnd_api.g_ret_sts_success THEN
599      IF ( l_debug = 1 ) THEN
600         log_error(l_api_name, 'Suggest_Reservations', 'l_return_status = '|| x_return_status);
601         log_error(l_api_name, 'Suggest_Reservations', 'Detailing Failed ');
602      END IF;
603      fnd_msg_pub.count_and_get(p_count => x_msg_count, p_data => l_message, p_encoded => 'F');
604 
605      IF (x_msg_count = 0) THEN
606         IF ( l_debug = 1) THEN
607            log_error(l_api_name, 'Suggest_Reservations', 'no message from detailing engine');
608         END IF;
609      ELSIF (x_msg_count = 1) THEN
610         IF ( l_debug = 1 ) THEN
611            log_error(l_api_name, 'Suggest_Reservations', l_message);
612         END IF;
613      ELSE
614         FOR i IN 1 .. x_msg_count LOOP
615             l_message  := fnd_msg_pub.get(i, 'F');
616             IF ( l_debug = 1) THEN
617                log_error(l_api_name, 'Suggest_Reservations', l_message);
618             END IF;
619         END LOOP;
620 
621         fnd_msg_pub.delete_msg();
622      END IF;
623 
624      ROLLBACK TO suggest_reservations_sa;
625 
626      fnd_message.set_name('INV', 'INV_DETAILING_FAILED');
627      fnd_message.set_token('LINE_NUM', TO_CHAR(p_mo_line_rec.line_number));
628      fnd_msg_pub.ADD;
629      x_msg_count := 1;
630      RAISE fnd_api.g_exc_unexpected_error;
631   END IF;
632 
633   l_suggested_serials := l_dummy_sn;
634   l_requirement_date := nvl(p_requirement_date, sysdate);
635 
636   first_pass := TRUE;
637   FOR l_grp_sugg_rec in c_sugg_grp LOOP --{
638       IF first_pass THEN
639          InitQtyTree ( x_return_status
640                       ,x_msg_count
641                       ,x_msg_data
642                       ,p_mo_line_rec.organization_id
643                       ,p_mo_line_rec.inventory_item_id
644                       ,p_demand_source_type
645                       ,p_demand_source_header_id
646                       ,p_demand_source_line_id
647                       ,p_demand_source_detail
648                       ,p_demand_source_name
649                       ,INV_Quantity_Tree_PVT.g_transaction_mode
650                       ,l_tree_id
651                       );
652          if x_return_status = fnd_api.g_ret_sts_unexp_error then
653             raise fnd_api.g_exc_unexpected_error;
654          elsif x_return_status = fnd_api.g_ret_sts_error then
655             raise fnd_api.g_exc_error;
656          end if;
657          first_pass := FALSE;
658       END IF;
659 
660       -- Update quantity tree for this suggested quantity
661       IF l_debug = 1 THEN
662          log_statement(l_api_name, 'update_tree', 'Updating qty tree');
663       END IF;
664 
665       inv_quantity_tree_pvt.update_quantities
666           ( p_api_version_number         => 1.0
667           , p_init_msg_lst               => fnd_api.g_false
668           , x_return_status              => x_return_status
669           , x_msg_count                  => x_msg_count
670           , x_msg_data                   => x_msg_data
671           , p_tree_id                    => l_tree_id
672           , p_revision                   => l_grp_sugg_rec.revision
673           , p_lot_number                 => l_grp_sugg_rec.lot_number
674           , p_subinventory_code          => l_grp_sugg_rec.from_subinventory_code
675           , p_locator_id                 => l_grp_sugg_rec.from_locator_id
676           , p_primary_quantity           => -1 * l_grp_sugg_rec.primary_quantity
677           , p_secondary_quantity         => -1 * l_grp_sugg_rec.secondary_quantity             -- INVCONV
678           , p_quantity_type              => inv_quantity_tree_pvt.g_qs_txn
679           , x_qoh                        => l_qoh
680           , x_rqoh                       => l_rqoh
681           , x_qr                         => l_qr
682           , x_qs                         => l_qs
683           , x_att                        => l_att
684           , x_atr                        => l_atr
685           , x_sqoh                       => l_sqoh                                             -- INVCONV
686           , x_srqoh                      => l_srqoh                                            -- INVCONV
687           , x_sqr                        => l_sqr                                              -- INVCONV
688           , x_sqs                        => l_sqs                                              -- INVCONV
689           , x_satt                       => l_satt                                             -- INVCONV
690           , x_satr                       => l_satr                                             -- INVCONV
691           , p_transfer_subinventory_code => null
692           , p_cost_group_id              => null
693           , p_lpn_id                     => l_grp_sugg_rec.lpn_id
694           );
695 
696       IF x_return_status = fnd_api.g_ret_sts_unexp_error THEN
697          IF l_debug = 1 THEN
698             log_statement(l_api_name, 'uerr_update_qty', 'Unexpected error in inv_quantity_tree_pvt.update_quantities');
699          END IF;
700 
701          RAISE fnd_api.g_exc_unexpected_error;
702       ELSIF x_return_status = fnd_api.g_ret_sts_error THEN
703          IF l_debug = 1 THEN
704             log_statement(l_api_name, 'err_update_qty', 'Error in inv_quantity_tree_pvt.update_quantities');
705          END IF;
706          RAISE fnd_api.g_exc_error;
707       END IF;
708 
709       /* Get Original reservation for which these grouped suggestions were created */
710        -- {{ Test Case #  UTK- REALLOC
711        --  Description : API called with either a) No existing Reservation or
712        --  b) A single existing Reservation or c) Multiple existing Reservations }}
713       IF l_grp_sugg_rec.reservation_id IS NOT NULL
714       THEN
715          IF l_debug = 1 THEN
716             log_event(l_api_name, 'Suggest_Reservations','Sugg Res : ' || l_grp_sugg_rec.reservation_id);
717          END IF;
718 
719          l_orig_reservation := l_demand_rsvs_ordered(l_rsv_index(l_grp_sugg_rec.reservation_id));
720          l_primary_uom_code := l_orig_reservation.primary_uom_code;
721          l_new_reservation := l_orig_reservation;
722 
723          OPEN c_rsv_primary_qty(l_orig_reservation.reservation_id);
724          FETCH c_rsv_primary_qty INTO l_rsv_pri_qty;
725          CLOSE c_rsv_primary_qty;
726       END IF;
727 
728       IF l_debug = 1 THEN
729          log_event(l_api_name, 'Suggest_Reservations', 'Suggested lot_number : ' || l_grp_sugg_rec.lot_number);
730          log_event(l_api_name, 'Suggest_Reservations', 'Suggested subinventory_code : ' || l_grp_sugg_rec.from_subinventory_code);
731          log_event(l_api_name, 'Suggest_Reservations', 'Suggested locator id : ' || l_grp_sugg_rec.from_locator_id);
732          log_event(l_api_name, 'Suggest_Reservations', 'Suggested lpn_id  : ' || l_grp_sugg_rec.lpn_id);
733          log_event(l_api_name, 'Suggest_Reservations', 'Suggested pri quantity  : ' || l_grp_sugg_rec.primary_quantity);
734          log_event(l_api_name, 'Suggest_Reservations', 'Suggested sec quantity  : ' || l_grp_sugg_rec.secondary_quantity);
735 		 log_event(l_api_name, 'Suggest_Reservations', 'l_lot_control_code  : ' || l_lot_control_code);  -- Added for Bug 16203819
736       END IF;
737 
738 	  /* Start changes for Bug 16203819 */
739 	  IF l_lot_control_code <> 1 AND l_grp_sugg_rec.lot_number IS NULL THEN
740 	    INV_FLEX_LOT_ALLOCATION_PUB.G_LOT_VALIDATION := 'N';
741 	  ELSE
742 	    INV_FLEX_LOT_ALLOCATION_PUB.G_LOT_VALIDATION := 'Y';
743 	  END IF;
744 
745       IF l_debug = 1 THEN
746          log_event(l_api_name, 'Suggest_Reservations', 'INV_FLEX_LOT_ALLOCATION_PUB.G_LOT_VALIDATION : ' || INV_FLEX_LOT_ALLOCATION_PUB.G_LOT_VALIDATION);
747       END IF;
748 
749 	  /* End changes for Bug 16203819 */
750 
751       /* Set new_rsv record from the grouped suggestion record */
752       l_new_reservation.organization_id       := p_mo_line_rec.organization_id;
753       l_new_reservation.inventory_item_id     := p_mo_line_rec.inventory_item_id;
754       l_new_reservation.supply_source_type_id := inv_reservation_global.g_source_type_inv;
755       l_new_reservation.revision              := l_grp_sugg_rec.revision;
756       l_new_reservation.lot_number            := l_grp_sugg_rec.lot_number;
757       l_new_reservation.subinventory_code     := l_grp_sugg_rec.from_subinventory_code;
758       l_new_reservation.locator_id            := l_grp_sugg_rec.from_locator_id;
759       l_new_reservation.lpn_id                := l_grp_sugg_rec.lpn_id;
760 
761       l_new_reservation.primary_uom_code      := l_primary_uom_code;
762       l_new_reservation.reservation_uom_code  := p_mo_line_rec.uom_code;
763       l_new_reservation.secondary_uom_code    := p_mo_line_rec.secondary_uom;
764 
765       l_new_reservation.primary_reservation_quantity   := l_grp_sugg_rec.primary_quantity;
766       l_new_reservation.secondary_reservation_quantity := l_grp_sugg_rec.secondary_quantity;
767       l_new_reservation.demand_source_type_id          := p_demand_source_type;
768       l_new_reservation.demand_source_header_id        := p_demand_source_header_id;
769       l_new_reservation.demand_source_line_id          := p_demand_source_line_id;
770       l_new_reservation.demand_source_name             := p_demand_source_name;
771       l_new_reservation.requirement_date               := l_requirement_date;
772 
773       IF p_suggest_serial = 'Y' THEN
774          l_suggested_serials := l_dummy_sn;
775          IF ( l_debug = 1 ) THEN
776             log_event(l_api_name,'Suggest_Reservations','Get Serials Suggested for this Reservation');
777          END IF;
778          FOR l_ser_rec in c_sugg_serials(l_new_reservation.organization_id, l_new_reservation.subinventory_code,
779                                          l_new_reservation.locator_id, l_new_reservation.revision, l_new_reservation.lot_number,
780                                          l_new_reservation.lpn_id, l_grp_sugg_rec.reservation_id
781                                         ) LOOP
782              l_suggested_serials(i).inventory_item_id := p_mo_line_rec.inventory_item_id;
783              l_suggested_serials(i).serial_number := l_ser_rec.serial_number;
784          END LOOP;
785       END IF;
786 
787       IF l_grp_sugg_rec.reservation_id IS NOT NULL THEN
788          IF l_debug = 1 THEN
789             log_event(l_api_name, 'Suggest_Reservations', 'Original revision : ' || l_orig_reservation.revision);
790             log_event(l_api_name, 'Suggest_Reservations', 'Original lot_number : ' || l_orig_reservation.lot_number);
791             log_event(l_api_name, 'Suggest_Reservations', 'Original subinventory_code : ' || l_orig_reservation.subinventory_code);
792             log_event(l_api_name, 'Suggest_Reservations', 'Original locator id : ' || l_orig_reservation.locator_id);
793             log_event(l_api_name, 'Suggest_Reservations', 'Original lpn_id  : ' || l_orig_reservation.lpn_id);
794             log_event(l_api_name, 'Suggest_Reservations', 'Original pri quantity  : ' || l_orig_reservation.primary_reservation_quantity);
795             log_event(l_api_name, 'Suggest_Reservations', 'Original sec quantity  : ' || l_orig_reservation.secondary_reservation_quantity);
796          END IF;
797 
798          l_last_sugg_str := l_grp_sugg_rec.sugg_str;
799          l_last_reservation := l_new_reservation;
800 
801          /* Check whether original reservation is equal to the allocated record */
802          /* If not equal to the original reservation the transfer the allocated quantity to the new reservation */
803          IF ((nvl(l_orig_reservation.lot_number,'-999') <> nvl(l_new_reservation.lot_number, '-999')) OR
804              (nvl(l_orig_reservation.revision,'-999') <> nvl(l_new_reservation.revision, '-999')) OR
805              (nvl(l_orig_reservation.subinventory_code,'-999') <> nvl(l_new_reservation.subinventory_code, '-999')) OR
806              (nvl(l_orig_reservation.locator_id,'-999') <> nvl(l_new_reservation.locator_id, '-999')) OR
807              (nvl(l_orig_reservation.lpn_id,'-999') <> nvl(l_new_reservation.lpn_id, '-999')))
808          THEN
809             IF NVL(l_rsv_pri_qty,0) >= l_new_reservation.primary_reservation_quantity THEN --{
810                -- Setting this to null will allow the reservation to be added to other reservations
811                -- with the same controls that may have been created during this process
812                l_new_reservation.reservation_id := NULL;
813 
814                inv_reservation_pvt.Transfer_Reservation (
815                    p_api_version_number     => 1.0
816                  , p_init_msg_lst           => fnd_api.g_false
817                  , x_return_status          => x_return_status
818                  , x_msg_count              => x_msg_count
819                  , x_msg_data               => x_msg_data
820                  , p_original_rsv_rec       => l_orig_reservation
821                  , p_to_rsv_rec             => l_new_reservation
822                  , p_original_serial_number => l_dummy_sn
823                  , p_validation_flag        => fnd_api.g_false
824                  , x_reservation_id         => l_new_reservation_id
825                  );
826 
827                -- Bug 6719290 Return an error if the transfer reservation call failed
828                IF x_return_status = fnd_api.g_ret_sts_error THEN
829                   IF (l_debug = 1) THEN
830                       log_error(l_api_name, 'Suggest_Reservations','expected error in transfer reservation');
831                   END IF;
832                   fnd_message.set_name('INV', 'INV_TRANSFER_RSV_FAILED');
833                   fnd_msg_pub.ADD;
834                   RAISE fnd_api.g_exc_error;
835                END IF;
836 
837                -- Return an error if the transfer reservation call failed
838                IF x_return_status <> fnd_api.g_ret_sts_success THEN
839                   IF (l_debug = 1) THEN
840                      log_error(l_api_name, 'Suggest_Reservations','error in transfer reservation');
841                   END IF;
842                   fnd_message.set_name('INV', 'INV_TRANSFER_RSV_FAILED');
843                   fnd_msg_pub.ADD;
844                   RAISE fnd_api.g_exc_unexpected_error;
845                END IF;
846                IF l_debug = 1 THEN
847                   log_event(l_api_name, 'Suggest_Reservations', 'After calling transfer from ' || l_orig_reservation.reservation_id || ' to ' || l_new_reservation_id);
848                END IF;
849              --}
850             ELSE --{ Remaining high level reservation quantity < suggested quantity
851 
852                inv_reservation_pvt.update_reservation(
853                  p_api_version_number        => 1.0
854                , p_init_msg_lst              => fnd_api.g_false
855                , x_return_status             => x_return_status
856                , x_msg_count                 => x_msg_count
857                , x_msg_data                  => x_msg_data
858                , p_original_rsv_rec          => l_orig_reservation
859                , p_to_rsv_rec                => l_new_reservation
860                , p_original_serial_number    => l_dummy_sn
861                , p_to_serial_number          => l_reserved_serials
862                , p_validation_flag           => fnd_api.g_false
863                , p_check_availability        => fnd_api.g_false
864                );
865 
866                -- Return an error if the update reservation call failed
867                IF x_return_status <> fnd_api.g_ret_sts_success THEN
868                   IF (l_debug = 1) THEN
869                      log_error(l_api_name, 'Suggest_Reservations','error in update reservation');
870                   END IF;
871                   fnd_message.set_name('INV', 'INV_UPDATE_RSV_FAILED');
872                   fnd_msg_pub.ADD;
873                   RAISE fnd_api.g_exc_unexpected_error;
874                END IF;
875 
876             END IF; --}
877          ELSE
878             IF l_debug = 1 THEN
879                log_event(l_api_name, 'Suggest_Reservations', 'Reservation already Exists and is Detailed: ID = ' || l_grp_sugg_rec.reservation_id);
880             END IF;
881          END IF;
882       -- ELSE reservation ID is null AND not the same inventory controls
883       ELSIF l_grp_sugg_rec.sugg_str = nvl(l_last_sugg_str,'@@@') THEN
884          /* Update the current reservation with the quantities from the new reservation */
885          l_new_reservation.primary_reservation_quantity := l_last_reservation.primary_reservation_quantity + l_new_reservation.primary_reservation_quantity;
886          l_new_reservation.secondary_reservation_quantity := l_last_reservation.secondary_reservation_quantity + l_new_reservation.secondary_reservation_quantity;
887 
888          inv_reservation_pvt.update_reservation(
889                  p_api_version_number        => 1.0
890                , p_init_msg_lst              => fnd_api.g_false
891                , x_return_status             => x_return_status
892                , x_msg_count                 => x_msg_count
893                , x_msg_data                  => x_msg_data
894                , p_original_rsv_rec          => l_last_reservation
895                , p_to_rsv_rec                => l_new_reservation
896                , p_original_serial_number    => l_dummy_sn
897                , p_to_serial_number          => l_reserved_serials
898                , p_validation_flag           => 'Q'
899                , p_check_availability        => fnd_api.g_false
900                );
901 
902          -- Return an error if the update reservation call failed
903          IF x_return_status <> fnd_api.g_ret_sts_success THEN
904             IF (l_debug = 1) THEN
905                log_error(l_api_name, 'Suggest_Reservations','error in update reservation');
906             END IF;
907             fnd_message.set_name('INV', 'INV_UPDATE_RSV_FAILED');
908             fnd_msg_pub.ADD;
909             RAISE fnd_api.g_exc_unexpected_error;
910          END IF;
911 
912       ELSE -- reservtion ID is null
913          /* Create new reservation and set as current reservation */
914          IF l_debug = 1 THEN
915             log_event(l_api_name, 'Suggest_Reservations', 'Defaulting vales to create the reservations');
916          END IF;
917 
918          l_new_reservation.reservation_id             := NULL; -- cannot know
919          l_new_reservation.demand_source_delivery        := NULL;
920          l_new_reservation.primary_uom_id                := NULL;
921          l_new_reservation.secondary_uom_id              := NULL;
922          l_new_reservation.reservation_uom_code          := NULL;
923          l_new_reservation.reservation_uom_id            := NULL;
924          l_new_reservation.reservation_quantity          := NULL;
925          l_new_reservation.autodetail_group_id           := NULL;
926          l_new_reservation.external_source_code          := NULL;
927          l_new_reservation.external_source_line_id       := NULL;
928          l_new_reservation.supply_source_header_id       := NULL;
929          l_new_reservation.supply_source_line_id         := NULL;
930          l_new_reservation.supply_source_name            := NULL;
931          l_new_reservation.supply_source_line_detail     := NULL;
932          l_new_reservation.subinventory_id               := NULL;
933          l_new_reservation.lot_number_id                 := NULL;
934          l_new_reservation.pick_slip_number              := NULL;
935          l_new_reservation.attribute_category            := NULL;
936          l_new_reservation.attribute1                    := NULL;
937          l_new_reservation.attribute2                    := NULL;
938          l_new_reservation.attribute3                    := NULL;
939          l_new_reservation.attribute4                    := NULL;
940          l_new_reservation.attribute5                    := NULL;
941          l_new_reservation.attribute6                    := NULL;
942          l_new_reservation.attribute7                    := NULL;
943          l_new_reservation.attribute8                    := NULL;
944          l_new_reservation.attribute9                    := NULL;
945          l_new_reservation.attribute10                   := NULL;
946          l_new_reservation.attribute11                   := NULL;
947          l_new_reservation.attribute12                   := NULL;
948          l_new_reservation.attribute13                   := NULL;
949          l_new_reservation.attribute14                   := NULL;
950          l_new_reservation.attribute15                   := NULL;
951          l_new_reservation.ship_ready_flag               := NULL;
952          l_new_reservation.detailed_quantity             := 0;
953 
954          inv_reservation_pub.create_reservation(
955              p_api_version_number         => 1.0
956            , p_init_msg_lst               => fnd_api.g_false
957            , x_return_status              => x_return_status
958            , x_msg_count                  => x_msg_count
959            , x_msg_data                   => x_msg_data
960            , p_rsv_rec                    => l_new_reservation
961            , p_serial_number              => l_suggested_serials
962            , x_serial_number              => l_reserved_serials
963            , p_partial_reservation_flag   => fnd_api.g_true
964            , p_force_reservation_flag     => fnd_api.g_false
965            , p_validation_flag            => 'Q'
966            , x_quantity_reserved          => l_qty_succ_reserved
967            , x_reservation_id             => l_new_reservation_id
968            );
969 
970          IF l_debug = 1 THEN
971             log_event(l_api_name, 'Suggest_Reservations', 'After creating the reservations: status =' || x_return_status);
972             log_event(l_api_name, 'Suggest_Reservations', 'After creating the reservations: Reservation ID =' || l_new_reservation_id);
973          END IF;
974          -- Return an error if the create reservation call failed
975          IF x_return_status <> fnd_api.g_ret_sts_success THEN
976             IF (l_debug = 1) THEN
977                log_error(l_api_name, 'Suggest_Reservations','error in create reservation');
978             END IF;
979             fnd_message.set_name('INV', 'INV_CREATE_RSV_FAILED');
980             fnd_msg_pub.ADD;
981             RAISE fnd_api.g_exc_unexpected_error;
982          END IF;
983       END IF;
984   END LOOP; --}
985 
986   IF wms_engine_pvt.g_sec_qty_round_mode IS NOT NULL THEN --{
987      FOR l_res_rec in c_high_level_res_csr LOOP
988          IF l_debug = 1 THEN
989             log_event(l_api_name, 'Suggest_Reservations', 'Removing High Level Reservation res_id: ' || l_res_rec.res_id);
990          END IF;
991 
992          x_return_status := fnd_api.g_ret_sts_success;
993          l_rsv_rec.reservation_id := l_res_rec.res_id;
994 
995          inv_reservation_pvt.delete_reservation (
996               p_api_version_number => 1.0
997             , p_init_msg_lst       => fnd_api.g_false
998             , x_return_status      => l_return_status
999             , x_msg_count          => l_msg_count
1000             , x_msg_data           => l_msg_data
1001             , p_rsv_rec            => l_rsv_rec
1002             , p_original_serial_number => l_original_serial_number
1003             , p_validation_flag    => NULL
1004             );
1005 
1006           IF l_debug = 1 THEN
1007              log_event(l_api_name, 'Suggest_Reservations', 'Done removing High Level Reservation res_id: ' || l_res_rec.res_id);
1008           END IF;
1009 
1010           IF (l_return_status <> fnd_api.g_ret_sts_success) THEN
1011              RAISE del_resvn_error;
1012           END IF;
1013      END LOOP;
1014   END IF; --}
1015 
1016   -- Return the suggestions
1017   OPEN c_suggestions;
1018   FETCH c_suggestions BULK COLLECT INTO
1019       p_suggestions.from_organization_id
1020     , p_suggestions.to_organization_id
1021     , p_suggestions.revision
1022     , p_suggestions.lot_number
1023     , p_suggestions.lot_expiration_date
1024     , p_suggestions.from_subinventory_code
1025     , p_suggestions.to_subinventory_code
1026     , p_suggestions.from_locator_id
1027     , p_suggestions.to_locator_id
1028     , p_suggestions.lpn_id
1029     , p_suggestions.reservation_id
1030     , p_suggestions.serial_number
1031     , p_suggestions.grade_code
1032     , p_suggestions.from_cost_group_id
1033     , p_suggestions.to_cost_group_id
1034     , p_suggestions.primary_quantity
1035     , p_suggestions.transaction_quantity
1036     , p_suggestions.secondary_quantity;
1037   CLOSE c_suggestions;
1038 
1039 EXCEPTION
1040    WHEN del_resvn_error THEN
1041       IF (l_debug = 1) THEN
1042          log_event(l_api_name, 'Deleting Reservations', 'When deleting high level reservation inv_reservation_pub.delete_reservation returned ' || l_return_status);
1043       END IF;
1044 
1045    WHEN fnd_api.g_exc_error THEN
1046       --ROLLBACK TO suggest_reservations_sa;
1047       x_return_status  := fnd_api.g_ret_sts_error;
1048       fnd_msg_pub.count_and_get(p_count => x_msg_count, p_data => x_msg_data);
1049       IF l_debug = 1 THEN
1050          log_error(l_api_name, 'error', 'Error in suggest_reservations - ' || x_msg_data);
1051       END IF ;
1052    --
1053    WHEN fnd_api.g_exc_unexpected_error THEN
1054       --ROLLBACK TO suggest_reservations_sa;
1055       x_return_status  := fnd_api.g_ret_sts_unexp_error;
1056       fnd_msg_pub.count_and_get(p_count => x_msg_count, p_data => x_msg_data);
1057       IF l_debug = 1 THEN
1058       log_error(l_api_name, 'unexp_error', 'Unexpected error ' || 'in suggest_reservations - ' || x_msg_data);
1059       END IF;
1060    --
1061    WHEN OTHERS THEN
1062       ROLLBACK TO suggest_reservations_sa;
1063       x_return_status  := fnd_api.g_ret_sts_unexp_error;
1064 
1065       IF fnd_msg_pub.check_msg_level(fnd_msg_pub.g_msg_lvl_unexp_error) THEN
1066          fnd_msg_pub.add_exc_msg(g_pkg_name, l_api_name);
1067       END IF;
1068       fnd_msg_pub.count_and_get(p_count => x_msg_count, p_data => x_msg_data);
1069       IF l_debug = 1 THEN
1070          log_error(l_api_name, 'other_error', 'Other error ' || 'in suggest_reservations - ' || x_msg_data);
1071          log_error(l_api_name, 'other_error', 'SQL Error ' || SQLERRM);
1072       END IF;
1073 END suggest_reservations;
1074 
1075 END wms_rule_extn_pvt;