DBA Data[Home] [Help]

PACKAGE BODY: APPS.RCV_ROI_PREPROCESSOR

Source


1 PACKAGE BODY rcv_roi_preprocessor AS
2 /* $Header: RCVPREPB.pls 120.19.12010000.4 2009/01/22 12:54:23 smididud ship $*/
3 -- Read the profile option that enables/disables the debug log
4     g_asn_debug      VARCHAR2(1)  := NVL(fnd_profile.VALUE('RCV_DEBUG_MODE'), 'N');
5     x_interface_type VARCHAR2(25) := 'RCV-856';
6 
7    /* Shikyu Project This helping function is needed for cursor*/
8    FUNCTION get_oe_osa_flag(
9       p_oe_order_line_id NUMBER
10    )
11       RETURN NUMBER IS
12       x_return_status VARCHAR2(1);
13       x_msg_count     NUMBER;
14       x_msg_data      VARCHAR2(2000);
15       x_is_enabled    VARCHAR2(1);
16    BEGIN
17       IF (p_oe_order_line_id IS NULL) THEN
18          RETURN 2;
19       ELSE
20          jmf_shikyu_grp.is_so_line_shikyu_enabled(1,
21                                                   fnd_api.g_false,
22                                                   x_return_status,
23                                                   x_msg_count,
24                                                   x_msg_data,
25                                                   p_oe_order_line_id,
26                                                   x_is_enabled
27                                                  );
28 
29          IF x_is_enabled = 'Y' THEN
30             RETURN 1;
31          ELSE
32             RETURN 2;
33          END IF;
34       END IF;
35    EXCEPTION
36       WHEN OTHERS THEN
37          RETURN 2;
38    END get_oe_osa_flag;
39 
40     /* Checking if the transaction type is supported by ROI
41      * */
42     FUNCTION is_valid_txn_type(
43                  p_txn_type rcv_transactions_interface.transaction_type%TYPE
44     ) RETURN BOOLEAN IS
45         TYPE txn_type_table IS TABLE OF rcv_transactions_interface.transaction_type%TYPE;
46         -- define supported transaction types
47         l_txn_type_tbl txn_type_table := txn_type_table ('SHIP'
48                                                         ,'RECEIVE'
49                                                         ,'DELIVER'
50                                                         ,'TRANSFER'
51                                                         ,'ACCEPT'
52                                                         ,'REJECT'
53                                                         ,'CORRECT'
54                                                         ,'CANCEL'
55                                                         ,'RETURN TO VENDOR'
56                                                         ,'RETURN TO RECEIVING'
57                                                         ,'RETURN TO CUSTOMER'
58                                                         );
59         i NUMBER;
60      BEGIN
61         FOR i in 1..l_txn_type_tbl.COUNT LOOP
62             IF p_txn_type = l_txn_type_tbl(i) THEN
63                 RETURN TRUE;
64             END IF;
65         END LOOP;
66         RETURN FALSE;
67     EXCEPTION
68         WHEN OTHERS THEN
69             RETURN FALSE;
70     END is_valid_txn_type;
71 
72 /*    FUNCTION get_header_record(
73                   p_header_id rcv_transactions_interface.interface_header_id%TYPE
74     ) RETURN header_record_type IS
75 
76     END get_header_record;
77 */
78     /* Preprocess replaces rcv_shipment_object_sv.create_object with a cleaner structure. */
79     PROCEDURE preprocessor(
80         x_request_id NUMBER,
81         x_group_id   NUMBER
82     ) IS
83         x_error_record           rcv_roi_preprocessor.error_rec_type;
84         x_header_record          rcv_roi_preprocessor.header_rec_type;
85         x_cascaded_table         rcv_roi_preprocessor.cascaded_trans_tab_type;
86         x_progress               VARCHAR2(3)                                                := '000';
87         x_fail_all_lines         VARCHAR2(1)                                                := 'N';
88         x_fail_if_one_line_fails BOOLEAN                                                    := FALSE;
89         n                        BINARY_INTEGER                                             := 0;
90         x_empty_header_record    rcv_roi_preprocessor.header_rec_type;
91 --added for lpn support
92         l_lpn_grp_id             rcv_transactions_interface.lpn_group_id%TYPE;
93         l_proc_status_code       rcv_transactions_interface.processing_status_code%TYPE;
94         l_group_id               rcv_transactions_interface.GROUP_ID%TYPE; -- used in local query
95         p_group_id               rcv_transactions_interface.GROUP_ID%TYPE; -- matches the passed in value
96         p_request_id             rcv_transactions_interface.processing_request_id%TYPE;
97         l_update_lpn_group       BOOLEAN                                                    := FALSE;
98         l_failed_rows_exist      NUMBER                                                     := 0;
99         l_txn_code               VARCHAR2(10);
100         l_lpn_group_id           NUMBER;
101         l_ship_header_id         NUMBER;
102         l_ret_status             VARCHAR2(20);
103         l_msg_count              NUMBER;
104         l_msg_data               VARCHAR2(100);
105         l_temp                   NUMBER;
106         l_group_count            NUMBER;
107         l_return_status1         VARCHAR2(1);
108         l_msg_count1             NUMBER;
109         l_msg_data1              fnd_new_messages.MESSAGE_TEXT%TYPE;
110         l_to_org_id              rcv_transactions_interface.to_organization_id%TYPE;
111         l_drop_ship_exists       NUMBER; /* Bug3705658 */
112         l_auto_deliver           VARCHAR2(1) := 'N'; /* Bug3705658 */
113         x_site_id_count          NUMBER := 0; -- Bug 4355172
114         l_count                  NUMBER;  --Bug 4881909
115         l_fsc_enabled            VARCHAR2(1)    := NVL(fnd_profile.VALUE('RCV_FSC_ENABLED'), 'N');
116         l_prev_org_id MO_GLOB_ORG_ACCESS_TMP.ORGANIZATION_ID%TYPE;  --<R12 MOAC>
117 
118         TYPE group_id_pool IS TABLE OF NUMBER
119             INDEX BY BINARY_INTEGER;
120 
121         l_exception_group_id     group_id_pool;
122 	l_return_status          VARCHAR2(1);
123 	l_check_dcp                  NUMBER;
124 	x_empty_error_record           rcv_roi_preprocessor.error_rec_type;
125 
126 /*        TYPE header_record_cache IS TABLE OF rcv_roi_preprocessor.header_rec_type
127             INDEX BY BINARY_INTEGER;
128 
129         l_header_record_cache    header_record_cache;
130 */
131         CURSOR distinct_groups(
132             p_request_id NUMBER
133         ) IS
134             SELECT DISTINCT (GROUP_ID)
135             FROM            rcv_transactions_interface
136             WHERE           processing_request_id = p_request_id
137             AND             processing_status_code = 'RUNNING';
138 
139 /* Bug 3434460.
140  * We need to set transfer_lpn_ids for all deliver transactions
141  * for non-wms orgs. Get all the org_ids that belong to this group.
142 */
143         CURSOR distinct_org_id(
144             p_request_id NUMBER,
145             p_group_id   NUMBER
146         ) IS
147             SELECT DISTINCT (to_organization_id)
148             FROM            rcv_transactions_interface
149             WHERE           processing_request_id = p_request_id
150             AND             (group_id = p_group_id or p_group_id = 0)
151             AND             processing_status_code = 'RUNNING'
152             AND             to_organization_id IS NOT NULL;
153 
154         CURSOR get_bad_asbn_shikyu IS --Shikyu project
155            SELECT   header_interface_id
156            FROM     (SELECT rsh.header_interface_id,
157                             DECODE(NVL(poll.outsourced_assembly, get_oe_osa_flag(rti.oe_order_line_id)),
158                                    1, 1,
159                                    NULL
160                                   ) osa_flag
161                      FROM   rcv_headers_interface rsh,
162                             rcv_transactions_interface rti,
163                             po_line_locations_all poll
164                      WHERE  rsh.asn_type = 'ASBN'
165                      AND    rsh.header_interface_id = rti.header_interface_id
166                      AND    poll.line_location_id (+) = rti.po_line_location_id
167                      AND    rti.processing_status_code = 'RUNNING')
168            GROUP BY header_interface_id
169            HAVING   COUNT(*) > COUNT(osa_flag)
170            AND      COUNT(osa_flag) > 0;
171 
172 	/*Added for the RCV DCP. This cursors is used to loop through the
173 	 * * records in RHI*/
174 /* Moved this cursor as well as its for loop to the rcv_dcp_pvt package */
175 /*	CURSOR headers_cur_dcp(x_request_id NUMBER, x_group_id NUMBER) IS
176 		SELECT *
177 		FROM rcv_headers_interface
178 		WHERE NVL(asn_type, 'STD') IN('ASN', 'ASBN', 'STD', 'WC')
179 			AND processing_status_code IN('RUNNING', 'SUCCESS','ERROR','PENDING')
180 			AND(NVL(validation_flag, 'N') = 'Y'
181 				OR processing_status_code = 'SUCCESS') -- include success row for multi-line asn
182 			AND(processing_request_id IS NULL
183 				OR processing_request_id = x_request_id)
184 			AND GROUP_ID = DECODE(x_group_id, 0, GROUP_ID, x_group_id); */
185 
186     BEGIN
187          <<dcp_pre_processor_start>>
188 	 g_asn_debug := NVL(fnd_profile.VALUE('RCV_DEBUG_MODE'), 'N');
189 
190 
191         /* For online mode, we send request_id as null. Consider it as -999 if
192          * it is null.
193         */
194         p_request_id := NVL(x_request_id, 0);
195         p_group_id   := NVL(x_group_id, 0);
196 
197         IF (g_asn_debug = 'Y') THEN
198             asn_debug.put_line('Entering preprocessor. Request_id = ' || p_request_id || ',Group_id=' || p_group_id);
199         END IF;
200 
201 	SAVEPOINT dcp_preprocessor_start;
202 	l_check_dcp := rcv_dcp_pvt.g_check_dcp;
203 
204 	IF l_check_dcp IS NULL THEN
205 		l_check_dcp := rcv_dcp_pvt.is_dcp_enabled;
206 	END IF;
207 
208         -- Cache basic configuration options
209         IF (g_is_edi_installed IS NULL) THEN
210             g_is_edi_installed  := po_core_s.get_product_install_status('EC');
211         END IF;
212 
213         /* get the profile option */
214         fnd_profile.get('RCV_FAIL_IF_LINE_FAILS', x_fail_all_lines);
215 
216         IF x_fail_all_lines = 'Y' THEN
217             x_fail_if_one_line_fails  := TRUE;
218         END IF;
219 
220         IF (g_asn_debug = 'Y') THEN
221             asn_debug.put_line('RCV_FAIL_IF_LINE_FAILS profile option =' || x_fail_all_lines);
222         END IF;
223 
224         /* the garbage collector is no longer needed by essential character of the normalization package.
225            if a row belongs to an org, run it, else fail it (or leave it pending).
226            LPN explosion has to happen before defaulting so it was moved into the normalization package.
227            The order_transaction_id is set by the default package
228         */
229 
230 
231         l_prev_org_id := -999;  --<R12 MOAC>
232 
233         /* 3434460.
234          * We need to set transfer_lpn_ids to null for all Deliver type
235          * of transactions (Deliver/Direct Delivery). This needs to
236          * be done for all non-wms orgs.
237         */
238 
239 /* Bug#6862487: Performance issue fix.
240    1) The following update statement performs badly in ONLINE mode,
241       as the processing_request_id of RTI will be null.
242       This update statement is required only in case of BATCH mode
243       to clear off the lpn references for Non-WMS organizations in case
244       user populated the lpn references by mistake.
245       ONLINE mode is used programatically by the application code, so it is
246       not possible to get lpn references for Non wms orgn.
247       So, we can safely skip the following code in case of ONLINE mode.
248       For ONLINE mode, request_id will be null and ProC treats null value as
249       zero. So,if p_request_id is zero, then it is ONLINE mode.
250   2)  Removed the group_id condition added as part of this bug fix.
251       If RTP is launched without group_id, then p_group_id of preprocessor()
252       would be null. So, removed that condition.
253   3)  Added close distinct_org_id, as there is no close cursor statement.
254  */
255       if p_request_id <> 0 then --Bug#6862487
256         OPEN distinct_org_id(p_request_id, p_group_id);
257 
258         LOOP
259             FETCH distinct_org_id INTO l_to_org_id;
260             EXIT WHEN distinct_org_id%NOTFOUND;
261 
262             IF (    NOT wms_install.check_install(l_return_status1,
263                                                   l_msg_count1,
264                                                   l_msg_data1,
265                                                   l_to_org_id
266                                                  )
267                 AND l_return_status1 = fnd_api.g_ret_sts_success) THEN
268                 UPDATE rcv_transactions_interface
269                    SET transfer_lpn_id = NULL,
270                        transfer_license_plate_number = NULL
271                  WHERE processing_request_id = p_request_id
272                 AND    to_organization_id = l_to_org_id
273                 AND    (   (transaction_type = 'DELIVER')
274                         OR (    transaction_type = 'RECEIVE'
275                             AND auto_transact_code = 'DELIVER'));
276 
277                 IF (g_asn_debug = 'Y') THEN
278                     asn_debug.put_line('Set transfer_lpn_id and transfer_license_plate_number to null for deliver transactions for the non-wms org ' || l_to_org_id);
279                 END IF;
280             END IF;
281         END LOOP;
282         CLOSE distinct_org_id;--Bug#6862487
283       else--Online mode transaction
284          if (g_asn_debug = 'Y') then
285             asn_debug.put_line('Skipped Set transfer_lpn_id and transfer_license_plate_number to null for ONLINE mode txn '||p_request_id);
286          end if;
287       end if;--Bug#6862487
288         /* End of 3434460. */
289         IF (g_asn_debug = 'Y') THEN
290             asn_debug.put_line('After update to order_transaction_id');
291         END IF;
292 
293         /* this belongs before the transaction looping */
294         FOR bad_shikyu IN get_bad_asbn_shikyu LOOP --Shikyu project
295            BEGIN
296               rcv_error_pkg.set_error_message('RCV_BAD_ASBN_SHIKYU');
297               rcv_error_pkg.set_token('HEADER_INTERFACE_ID', bad_shikyu.header_interface_id);
298               rcv_error_pkg.log_interface_error('RCV_HEADERS_INTERFACE',
299                                                 'HEADER_INTERFACE_ID',
300                                                 x_group_id,
301                                                 bad_shikyu.header_interface_id,
302                                                 NULL,
303                                                 FALSE
304                                                );
305 
306               UPDATE rcv_headers_interface
307                  SET processing_status_code = 'ERROR'
308                WHERE header_interface_id = bad_shikyu.header_interface_id;
309 
310               UPDATE rcv_transactions_interface
311                  SET processing_status_code = 'ERROR'
312                WHERE header_interface_id = bad_shikyu.header_interface_id;
313            EXCEPTION
314               WHEN OTHERS THEN
315                  NULL;
316            END;
317         END LOOP;
318 
319         OPEN rcv_roi_preprocessor.txns_cur(p_request_id, p_group_id);
320 
321         IF (g_asn_debug = 'Y') THEN
322             asn_debug.put_line('Opened transactions cursor.');
323         END IF;
324 
325         x_progress  := '010';
326         n           := 0;
327         x_cascaded_table.DELETE;
328 
329         -- Loop through the entries in rcv_transactions_interface.
330         LOOP --{
331             asn_debug.put_line('enter loop');
332             n                                   := n + 1;
333             FETCH rcv_roi_preprocessor.txns_cur INTO x_cascaded_table(n);
334             EXIT WHEN rcv_roi_preprocessor.txns_cur%NOTFOUND;
335             x_cascaded_table(n).error_status    := 'S';
336             x_cascaded_table(n).error_message   := NULL;
337             x_cascaded_table(n).derive          := 'N';
338             x_cascaded_table(n).matching_basis  := 'QUANTITY';
339             x_cascaded_table(n).purchase_basis  := 'GOODS';
340             x_cascaded_table(n).derive_index    := 0;
341             l_proc_status_code                  := 'SUCCESS';
342             l_update_lpn_group                  := FALSE;
343 
344             IF (g_asn_debug = 'Y') THEN
345                 asn_debug.put_line('Current counter is ' || TO_CHAR(n));
346                 asn_debug.put_line('No of records in cascaded table ' || TO_CHAR(x_cascaded_table.COUNT));
347                 asn_debug.put_line('header interface id is ' || TO_CHAR(x_cascaded_table(n).header_interface_id));
348             END IF;
349 
350             x_progress                          := '040';
351             rcv_error_pkg.initialize(x_cascaded_table(n).GROUP_ID,
352                                      x_cascaded_table(n).header_interface_id,
353                                      x_cascaded_table(n).interface_transaction_id
354                                     );
355 
356 
357             -- Check if it's a valid transaction type
358             IF NOT is_valid_txn_type(x_cascaded_table(n).transaction_type) THEN
359                 x_cascaded_table(n).error_status  := 'E';
360                 x_cascaded_table(n).error_message := 'RCV_ROI_INVALID_TXN_TYPE';
361                 rcv_error_pkg.set_error_message('RCV_ROI_INVALID_TXN_TYPE');
362                 rcv_error_pkg.set_token('TXN_TYPE', x_cascaded_table(n).transaction_type);
363                 rcv_error_pkg.log_interface_error('TRANSACTION_TYPE', FALSE);
364                 -- mark it's a line error
365                 l_update_lpn_group := TRUE;
366             END IF ;
367 
368             --<R12 MOAC START>
369 
370             IF ( (l_prev_org_id = -999) OR (l_prev_org_id <>  x_cascaded_table(n).org_id )
371              AND ( x_cascaded_table(n).org_id is NOT NULL ) ) THEN
372 
373                MO_GLOBAL.set_policy_context('S',TO_NUMBER(x_cascaded_table(n).org_id));
374 
375                IF (g_asn_debug = 'Y') THEN
376                    asn_debug.put_line('Setting Operating unit context to ' ||x_cascaded_table(n).org_id);
377                END IF;
378 
379                l_prev_org_id := x_cascaded_table(n).org_id;
380 
381             END IF;
382 
383            --<R12 MOAC END>
384 
385             -- added for parent child support
386             BEGIN
387                 IF x_cascaded_table(n).parent_interface_txn_id IS NOT NULL THEN --{
388                     BEGIN
389                         SELECT processing_status_code
390                         INTO   l_proc_status_code
391                         FROM   rcv_transactions_interface
392                         WHERE  interface_transaction_id = x_cascaded_table(n).parent_interface_txn_id;
393                     EXCEPTION
394                         WHEN NO_DATA_FOUND THEN
395                             rcv_error_pkg.set_error_message('RCV_NO_PARENT_TRANSACTION');
396                             rcv_error_pkg.log_interface_error('PARENT_INTERFACE_TXN_ID');
397                     END;
398 
399                     IF l_proc_status_code = 'ERROR' THEN
400                         RAISE rcv_error_pkg.e_fatal_error;
401                     END IF;
402                 END IF; --}
403 
404                 IF x_cascaded_table(n).parent_source_transaction_num IS NOT NULL THEN
405                     BEGIN --{
406                         SELECT processing_status_code
407                         INTO   l_proc_status_code
408                         FROM   rcv_transactions_interface
409                         WHERE  source_transaction_num = x_cascaded_table(n).parent_source_transaction_num;
410                     EXCEPTION
411                         WHEN NO_DATA_FOUND THEN
412                             rcv_error_pkg.set_error_message('RCV_NO_PARENT_TRANSACTION');
413                             rcv_error_pkg.log_interface_error('PARENT_SOURCE_TRANSACTION_NUM');
414                     END;
415                     IF l_proc_status_code = 'ERROR' THEN
416                         RAISE rcv_error_pkg.e_fatal_error;
417                     END IF;
418                 END IF; --}
419                 -- end added for parent child support(*)
420 
421                 -- if parent not errored out, see if this row is already errored out in rti because of something else
422                 BEGIN
423                     SELECT processing_status_code
424                     INTO   l_proc_status_code
425                     FROM   rcv_transactions_interface
426                     WHERE  interface_transaction_id = x_cascaded_table(n).interface_transaction_id;
427 
428                 EXCEPTION
429                     WHEN NO_DATA_FOUND THEN
430                         rcv_error_pkg.set_error_message('RCV_INVALID_TRANSACTION_TYPE');
431                         rcv_error_pkg.log_interface_error('INTERFACE_TRANSACTION_ID');
432                 END;
433 
434                 IF l_proc_status_code = 'ERROR' THEN
435                     RAISE rcv_error_pkg.e_fatal_error;
436                 END IF;
437 
438             EXCEPTION
439                 WHEN rcv_error_pkg.e_fatal_error THEN
440                     x_cascaded_table(n).error_status            := 'E';
441                     x_cascaded_table(n).error_message           := rcv_error_pkg.get_last_message;
442                     x_cascaded_table(n).processing_status_code  := 'ERROR';
443             END;
444 
445             IF (g_asn_debug = 'Y') THEN
446                 asn_debug.put_line('l_proc_status_code ' || l_proc_status_code);
447             END IF;
448 
449             -- begin processing of the header
450             -- does the row have a header
451             IF (    (x_cascaded_table(n).header_interface_id IS NOT NULL)
452                 AND (x_cascaded_table(n).error_status NOT IN ('P', 'E'))) THEN --{
453                 -- find out if failed lines exist for this header in rti
454                 SELECT COUNT(*)
455                 INTO   l_failed_rows_exist
456                 FROM   rcv_transactions_interface
457                 WHERE  processing_status_code = 'ERROR'
458                 AND    header_interface_id = x_cascaded_table(n).header_interface_id;
459 
460                 -- if this is an asn which has failed lines and
461                 IF     l_failed_rows_exist >= 1
462                    AND x_fail_if_one_line_fails
463                    AND x_cascaded_table(n).transaction_type = 'SHIP'
464                    AND x_cascaded_table(n).auto_transact_code = 'SHIP' THEN
465                     x_error_record.error_status   := 'E';
466                     x_error_record.error_message  := NULL;
467                 ELSE
468                     x_error_record.error_status   := 'S';
469                     x_error_record.error_message  := NULL;
470                 END IF;
471 
472                 IF (g_asn_debug = 'Y') THEN
473                     asn_debug.put_line('x_error_record.error_status: '|| x_error_record.error_status);
474                     asn_debug.put_line('transaction_type: '||x_cascaded_table(n).transaction_type);
475                     asn_debug.put_line('header_record.header_id: '||x_header_record.header_record.header_interface_id);
476                     asn_debug.put_line('x_cascaded_table(n).header_interface_id: '||x_cascaded_table(n).header_interface_id);
477                 END IF;
478 
479                 /* If rhi is success and all the other processed rti rows
480                  * in the same header id is also successful.
481                 */
482 
483                 IF (x_error_record.error_status IN('S', 'W')) THEN --{
484                     IF x_cascaded_table(n).header_interface_id <>
485                             nvl(x_header_record.header_record.header_interface_id, -1) THEN
486                     --{ exclude the case where the current trxn shares header with the previous trxn.
487                            IF (g_asn_debug = 'Y') THEN
488                                asn_debug.put_line('Initialize header record for RTI id: '||
489                                                    to_char(x_cascaded_table(n).interface_transaction_id));
490                            END IF;
491                            x_header_record  := x_empty_header_record;
492                            -- initialize error_record
493                            x_header_record.error_record  := x_error_record;
494 
495                         OPEN rcv_roi_preprocessor.headers_cur(p_request_id,
496                                                               p_group_id,
497                                                               x_cascaded_table(n).header_interface_id
498                                                              );
499                         IF (g_asn_debug = 'Y') THEN
500                             asn_debug.put_line('Before processing header');
501                         END IF;
502 
503                         FETCH rcv_roi_preprocessor.headers_cur INTO x_header_record.header_record;
504                             -- there should be 1 header record for this transaction
505                         asn_debug.put_line('Processing header for interface txn id =' ||
506                                             TO_CHAR(x_cascaded_table(n).interface_transaction_id));
507                         -- header cursor found, header is not processed yet : process the header
508                         IF RCV_ROI_PREPROCESSOR.headers_cur%FOUND THEN --{
509                           IF x_header_record.header_record.processing_status_code = 'RUNNING' THEN --{
510                             IF (x_cascaded_table(n).transaction_type IN ('SHIP', 'RECEIVE')) THEN --{
511 
512                                 IF x_header_record.header_record.transaction_type = 'NEW' THEN --{
513                                     -- Second, switch on the header receipt source code
514                                     IF x_header_record.header_record.receipt_source_code = 'VENDOR' THEN
515                                         -- This is either a PO, ASN, or ASBN RECEIVE or SHIP
516                                         rcv_roi_header.process_vendor_header(x_header_record);
517                                     ELSIF x_header_record.header_record.receipt_source_code = 'CUSTOMER' THEN
518                                         -- This is an RMA RECEIVE
519                                         rcv_roi_header.process_customer_header(x_header_record);
520                                     /* Bug 3314675.
521                                      * Change the receipt_source_code to INVENTORY from INTERNAL and
522                                      * Call process_internal_order_header to process inter-org shipment
523                                      * receipts.
524                                     */
525                                     ELSIF x_header_record.header_record.receipt_source_code = 'INVENTORY' THEN
526                                         -- This is an Inter-Org Transfer RECEIVE
527                                         rcv_roi_header.process_internal_order_header(x_header_record);
528                                     ELSIF x_header_record.header_record.receipt_source_code = 'INTERNAL ORDER' THEN
529                                         -- This is an Internal Order RECEIVE
530                                         rcv_roi_header.process_internal_order_header(x_header_record);
531                                     END IF; -- Switch on receipt source code
532                                 ELSE --}{ txn not new
533                                     IF (x_header_record.header_record.transaction_type = 'CANCEL') THEN --{
534                                     -- Cancelling an ASN or ASBN
535                                         rcv_roi_header.process_cancellation(x_header_record);
536 
537                                         IF (x_header_record.error_record.error_status NOT IN('S', 'W')) THEN --{
538                                             -- the cancellation failed
539                                             IF (g_asn_debug = 'Y') THEN
540                                                 asn_debug.put_line('RCV_ASN_NOT_ACCEPT');
541                                                 asn_debug.put_line('The header has failed ' || TO_CHAR(x_header_record.header_record.header_interface_id));
542                                                 asn_debug.put_line('ASN could not be cancelled');
543                                             END IF;
544 
545                                             rcv_error_pkg.set_error_message('RCV_ASN_NOT_ACCEPT');
546                                             rcv_error_pkg.set_token('SHIPMENT', x_header_record.header_record.shipment_num);
547                                             rcv_error_pkg.log_interface_error('SHIPMENT_NUM', FALSE);
548                                         END IF; --}
549                                     END IF; -- }
550                                 END IF; -- } switch on transaction type (supporting new/cancel)
551                             ELSE --}{ if transaction_type is receive or ship
552                                 -- Any other trxns here would be a transaction with fault header record
553                                 -- Keep the header_interface_id so that if the txn fails the header can be errored.
554                                 -- x_cascaded_table(n).header_interface_id := NULL;
555                                 x_header_record  := x_empty_header_record;
556                                 x_header_record.error_record.error_status := 'W';
557                                 rcv_error_pkg.set_error_message('RCV_ROI_FAULT_HEADER');
558                                 rcv_error_pkg.set_token('TXN_TYPE', x_cascaded_table(n).transaction_type);
559                                 rcv_error_pkg.log_interface_error('TRANSACTION_HEADER_ID', FALSE);
560 
561                             END IF; --}
562                           END IF; --} if processing_status_code is running
563                         ELSE   -- } { no header row is picked up by header cursor
564                             -- header record is missing. need to error out this trxn.
565                             IF (g_asn_debug = 'Y') THEN
566                                  asn_debug.put_line('Header missing for trxn '||
567                                                      to_char(x_cascaded_table(n).interface_transaction_id) ||', set error_status to E');
568                             END IF;
569                             x_header_record.error_record.error_status := 'E';
570                             -- need to insert po_inerface_errors
571                             rcv_error_pkg.set_error_message('RCV_ROI_HEADER_MISSING');
572                             rcv_error_pkg.set_token('TXN_TYPE', x_cascaded_table(n).transaction_type);
573                             rcv_error_pkg.log_interface_error('HEADER_INTERFACE_ID', FALSE);
574                         END IF; --} this is the check for whether header is processed
575 
576                         asn_debug.put_line('closing the header cursor for txn = ' || TO_CHAR(x_cascaded_table(n).interface_transaction_id));
577                         CLOSE rcv_roi_preprocessor.headers_cur;
578                     END IF; --} matches excluding shared header.
579 
580                     -- after processing header update rhi/rti
581                     -- IF (x_header_record.error_record.error_status = 'E') THEN -- Bugfix 5592848
582                     IF (x_header_record.error_record.error_status NOT IN ('S', 'W', 'P') ) THEN --{ -- Bugfix 5592848
583                                                                               -- header errored out
584                                                                               -- 1) update rhi
585                         -- x_header_record.header_record might still be null in this case
586                         -- if no row found in RHI, a no_data_found exception will be raised
587                         UPDATE rcv_headers_interface
588                            SET processing_status_code = 'ERROR'
589                         WHERE header_interface_id = x_cascaded_table(n).header_interface_id;
590 
591                         x_header_record.header_record.processing_status_code  := 'ERROR';
592                         x_header_record.error_record.error_status             := 'E';
593 
594                         /* Bug 4344351: Log a message indicating an error in RCV_HEADERS_INTERFACE table.*/
595                         rcv_error_pkg.log_interface_error('RCV_HEADERS_INTERFACE','',FALSE);
596 
597                         -- 2) update rti
598                         IF (g_asn_debug = 'Y') THEN
599                             asn_debug.put_line('update_rti_error after rhi error ');
600                         END IF;
601 
602                         update_rti_error(p_group_id                => x_cascaded_table(n).GROUP_ID,
603                                          p_interface_id            => NULL,
604                                          p_header_interface_id     => x_header_record.header_record.header_interface_id,
605                                          p_lpn_group_id            => NULL
606                                         );
607                         -- 3) should update the error status for this row
608                         x_cascaded_table(n).error_status                      := 'E';
609                     /* Bug 3359613.
610                      * Set error_Status to P in x_cascaded_table so that
611                      * we dont process the rti row which belongs to a
612                      * different OU.
613                     */
614                     ELSIF (x_header_record.error_record.error_status = 'P') THEN --}{
615                         IF (g_asn_debug = 'Y') THEN
616                             asn_debug.put_line('Set x_cascaded_table.error_status to P');
617                         END IF;
618 
619                         x_cascaded_table(n).error_status            := 'P';
620                         x_cascaded_table(n).processing_status_code  := 'PENDING';
621                     ELSE -- }{ the header was processed successfully
622                         UPDATE rcv_headers_interface
623                            SET processing_status_code = 'SUCCESS',
624                                validation_flag = 'N',
625                                receipt_header_id = x_header_record.header_record.receipt_header_id
626                          WHERE header_interface_id = x_header_record.header_record.header_interface_id
627                            AND processing_status_code <> 'SUCCESS';
628 
629                         IF (g_asn_debug = 'Y') THEN
630                             asn_debug.put_line('RCV_ASN_ACCEPT_NO_ERR');
631                         END IF;
632                     END IF; --} header errored out
633                 END IF; --}  matches with x_error_record.error_record <> E
634             ELSE --}{
635                 IF (g_asn_debug = 'Y') THEN
636                     asn_debug.put_line('reset header record to empty for headerless trxns or errored out trxns '||
637                                         to_char(x_cascaded_table(n).interface_transaction_id) );
638                 END IF;
639                 x_header_record  := x_empty_header_record;
640             END IF;         --} matches with whether transaction has header
641                     -- end processing of the header
642 
643                     -- if this row is still not error => if it is later in status error => it failed because of process line
644 
645             IF x_cascaded_table(n).error_status IN('S', 'W') THEN
646                 l_update_lpn_group  := TRUE;
647             END IF;
648 
649             IF (g_asn_debug = 'Y') THEN
650                 asn_debug.put_line('After processing header for this transaction:');
651                 asn_debug.put_line('X_cascaded_table(n).header_interface_id=' || x_cascaded_table(n).header_interface_id);
652                 asn_debug.put_line('X_header_record.error_record.error_status=' || x_header_record.error_record.error_status);
653                 asn_debug.put_line('x_cascaded_table(n).error_status=' || x_cascaded_table(n).error_status);
654                 asn_debug.put_line('x_cascaded_table(n).error_message=' || x_cascaded_table(n).error_message);
655             END IF;
656 
657           /* bug 4368726, for asn cancel's the call rcv_roi_header.process_cancellation(x_header_record)
658              will delete all the pending RTI rows and insert new RTI rows ready for the processor.
659              Processing these deleted rows causes an unhandled exception when deleting the ROWID later on
660              which will produce the invalid transaction error and then will cause all the subsequent transactions
661              in the group to fail. What's the point of even having transactions to a cancel because it's entirely
662              determined by the header. The only thing a transaction is needed for it to produce an entry in the
663              looping cursor.
664           */
665           IF (NVL(x_header_record.header_record.transaction_type,'NEW') <> 'CANCEL') THEN --{
666             BEGIN --{ processing lines
667                 IF (    x_cascaded_table(n).header_interface_id IS NOT NULL
668                     AND x_header_record.error_record.error_status IN('S', 'W')
669                     AND x_cascaded_table(n).error_status IN('S', 'W')) THEN                                                          --{
670                                                                             -- header has been processed and is valid
671                                                                             -- process the line
672                     /* Receipt_source_code is mandatory for
673                      * rhi. Get the value and default it if it is null
674                      * in x_Cascaded_table.
675                    */
676                     IF (x_cascaded_table(n).receipt_source_code IS NULL) THEN
677                         x_cascaded_table(n).receipt_source_code  := x_header_record.header_record.receipt_source_code;
678                     END IF;
679 
680                     process_line(x_cascaded_table,
681                                  n,
682                                  x_header_record.header_record.header_interface_id,
683                                  x_header_record.header_record.asn_type,
684                                  x_header_record
685                                 );
686                 END IF; --} end for a valid processed header
687 
688                         -- this is the case for a headerless transaction
689 
690                 IF (    x_cascaded_table(n).header_interface_id IS NULL
691                     AND x_cascaded_table(n).error_status IN('S', 'W')) THEN                                                         --{
692                                                                             -- 1) process the childless transaction
693                                                                             -- process the line
694                     /* Error out if receipt_source_code is null. We need it
695                      * to process rti row.
696                     */
697                     rcv_error_pkg.test_is_null(x_cascaded_table(n).receipt_source_code,
698                                                'RECEIPT_SOURCE_CODE',
699                                                'RCV_RECEIPT_SOURCE_CODE_REQ'
700                                               );
701                     process_line(x_cascaded_table,
702                                  n,
703                                  x_header_record.header_record.header_interface_id,
704                                  x_header_record.header_record.asn_type,
705                                  x_header_record
706                                 );
707                 END IF; --} end of processing a headerless transaction
708 
709                 -- R12: Freight and Special Charges
710                 -- Preprocess charges for receipt or ASN if charges coresponding
711                 -- to this transaction exist in RCI.
712                  IF (x_cascaded_table(n).transaction_type IN ('SHIP', 'RECEIVE')
713                      AND x_header_record.error_record.error_status IN('S', 'W')
714 	             AND rcv_table_functions.is_lcm_shipment(x_cascaded_table(n).po_line_location_id) = 'N'  -- lcm changes
715                      AND x_cascaded_table(n).error_status IN('S', 'W')) THEN --{
716 
717                       /* Bug 7830436: Code changes to Freight and Special Charges flow */
718 		      if nvl(l_fsc_enabled,'N') = 'N' then
719 		         asn_debug.put_line('Freight and Special Charges is disabled, so charges are not processed');
720 		      else
721 		      RCV_CHARGES_GRP.preprocess_charges
722                            ( p_api_version        => 1.0
723                            , p_init_msg_list      => 'Y'
724                            , x_return_status      => x_cascaded_table(n).error_status
725                            , x_msg_count          => l_msg_count
726                            , x_msg_data           => l_msg_data
727                            , p_header_record      => x_header_record.header_record
728                            , p_transaction_record => x_cascaded_table(n)
729                            );
730 		      end if;
731 
732                  END IF; --}
733 
734             EXCEPTION
735                 WHEN rcv_error_pkg.e_fatal_error THEN
736                     x_cascaded_table(n).error_status   := 'E';
737                     x_cascaded_table(n).error_message  := rcv_error_pkg.get_last_message;
738             END; --} processing lines
739                  -- update the rti row to error
740 
741             IF (    x_cascaded_table(n).error_status NOT IN('S', 'W')
742                 AND l_update_lpn_group) THEN
743                 -- write to po_interface_errors for all shipments
744                 IF ( --(X_cascaded_table(n).header_interface_id is not null) and
745                          (    x_fail_if_one_line_fails
746                           AND x_cascaded_table(n).transaction_type = 'SHIP')
747                       OR (   x_cascaded_table(n).error_message = 'RCV_REJECT_ASBN_CONSIGNED_PO'
748                           OR x_cascaded_table(n).error_message = 'RCV_REJECT_CONSUMPTION_PO'
749                           OR x_cascaded_table(n).error_message = 'RCV_REJECT_CONSUMPTION_RELEASE')
750                    ) THEN
751                     rcv_error_pkg.set_error_message('RCV_ASN_NOT_ACCEPT');
752                     rcv_error_pkg.set_token('SHIPMENT', x_header_record.header_record.shipment_num);
753                     rcv_error_pkg.log_interface_error('SHIPMENT_NUM', FALSE);
754                 END IF;
755             END IF;
756 
757             -- insert the split rti rows back into rti
758             -- also call the wms api to split their lot serial info
759 
760             /* Bug 4881909 : Call handle_rcv_asn_transactions() only if the
761             **               error_status is 'S' or 'W'
762             */
763             IF (x_cascaded_table(n).error_status NOT IN('S', 'W')) THEN
764 
765                 IF (g_asn_debug = 'Y') THEN
766                     asn_debug.put_line('Skipping call to handle_rcv_asn_txn ');
767                 END IF;
768                 x_cascaded_table(n).processing_status_code  := 'ERROR';
769                 l_proc_status_code                          := 'ERROR';
770             ELSE
771 
772                 /* If the txn is successful, set rsh.asn_status to null if it is marked as a 'NEW_SHIP'
773                  * so that the rsh record will not be deleted later on.
774                  *
775                  * rsh.asn_status will remain as 'NEW_SHIP' until one line goes through. If all the
776                  * lines have failed, the asn_status will remain as 'NEW_SHIP' and the rsh will be deleted.
777                 **/
778                 UPDATE rcv_shipment_headers
779                    SET asn_status = null
780                  WHERE (shipment_header_id = x_cascaded_table(n).shipment_header_id
781                         OR shipment_num = (select shipment_num
782                                              from rcv_headers_interface
783                                             where header_interface_id =
784                                                   x_cascaded_table(n).header_interface_id)
785                         OR shipment_header_id =  (select receipt_header_id
786                                                     from rcv_headers_interface
787                                                    where header_interface_id =
788                                                          x_cascaded_table(n).header_interface_id))
789                    AND asn_status = 'NEW_SHIP';
790 
791                 IF (g_asn_debug = 'Y') THEN
792                     asn_debug.put_line(sql%rowcount || ' new_ship RSH updated');
793                     asn_debug.put_line('Before handle_rcv_asn_txn ');
794                 END IF;
795                 rcv_roi_transaction.handle_rcv_asn_transactions(x_cascaded_table, x_header_record);
796             END IF;
797 
798 
799             /* Bug3705658 - START */
800 
801 	    /* Receipt Number should be generated for Drop Ship ASN's and ASBN's
802 	    ** with profile option 'PO: Automatically Deliver Drop Ship ASNs' set to
803             ** 'Y'. This is because at header level when default_receipt_num is called the
804 	    ** transaction_type and auto_transact_code in RTI would be 'SHIP' and hence
805 	    ** receipt_num would not have been created. So we need to create the
806 	    ** receipt_num over here.
807 	    */
808             IF ((x_header_record.header_record.asn_type in ('ASN','ASBN')) AND
809 	        (x_header_record.header_record.receipt_num is NULL) AND
810 		(x_header_record.error_record.error_status IN('S', 'W'))
811                ) THEN --{
812                 IF (g_asn_debug = 'Y') THEN
813                     asn_debug.put_line('ASN or ASBN Transaction');
814                 END IF;
815 
816 		SELECT count(*)
817                 INTO   l_drop_ship_exists
818                 FROM   po_line_locations_all plla,
819                        rcv_transactions_interface rti
820                 WHERE  rti.header_interface_id = x_header_record.header_record.header_interface_id
821                 and    rti.po_line_location_id = plla.line_location_id
822                 and    plla.drop_ship_flag = 'Y';
823 
824                 IF (g_asn_debug = 'Y') THEN
825                     asn_debug.put_line('Number of Drop Ship Lines:' || l_drop_ship_exists);
826                 END IF;
827                 IF l_drop_ship_exists > 0 THEN --{
828                     FND_PROFILE.GET('PO_AUTO_DELIVER_DROPSHIP_ASN', l_auto_deliver);
829                     IF (g_asn_debug = 'Y') THEN
830                         asn_debug.put_line('Profile Option PO_AUTO_DELIVER_DROPSHIP_ASN:' || l_auto_deliver);
831                     END IF;
832                     IF l_auto_deliver = 'Y' THEN --{
833                         IF (g_asn_debug = 'Y') THEN
834                             asn_debug.put_line('Generate Receipt Number');
835                         END IF;
836 
837 			RCV_ROI_HEADER_COMMON.default_receipt_info(x_header_record);
838 
839                         IF (g_asn_debug = 'Y') THEN
840                             asn_debug.put_line('Generated Receipt Number:' || x_header_record.header_record.receipt_num);
841                         END IF;
842 
843                         UPDATE RCV_SHIPMENT_HEADERS
844 			SET RECEIPT_NUM = x_header_record.header_record.receipt_num
845 			WHERE SHIPMENT_HEADER_ID = x_header_record.header_record.receipt_header_id;
846 
847                     END IF; --}
848     	        END IF;--}
849              END IF; --}
850 
851 	     /* Bug3705658 - END */
852             -- Erroring out RHI/RTI when line processing failed
853             -- Deleting RSH rows that are created for the errored out txn.
854             IF (    l_proc_status_code = 'ERROR'
855                 AND l_update_lpn_group) THEN --{ line processing failed
856 
857                 l_ship_header_id := nvl(x_cascaded_table(n).shipment_header_id,
858                                         x_header_record.header_record.receipt_header_id);
859 
860                 IF (g_asn_debug = 'Y') THEN
861                      asn_debug.put_line('Erroring out RHI/RTI');
862                      asn_debug.put_line('shipment_header_id : '|| l_ship_header_id);
863                 END IF;
864                 /* Bug 4779020. A line is ASN/Non ASN is decided by transaction tye */
865                 /* need to check auto_transact_code as well to exclude inv shipments */
866                 IF (    x_fail_if_one_line_fails
867                     AND x_cascaded_table(n).transaction_type = 'SHIP'
868                     AND x_cascaded_table(n).auto_transact_code = 'SHIP') THEN --{ asn case
869                     -- delete rsh and rsl
870                     DELETE FROM rcv_shipment_headers
871                      WHERE shipment_header_id = l_ship_header_id;
872 
873                     IF (g_asn_debug = 'Y') THEN
874                         asn_debug.put_line(sql%rowcount || ' RSH record deleted');
875                     END IF;
876 
877                     DELETE FROM rcv_shipment_lines
878                      WHERE shipment_header_id = l_ship_header_id;
879 
880                     IF (g_asn_debug = 'Y') THEN
881                         asn_debug.put_line(sql%rowcount || ' RSL record deleted');
882                     END IF;
883 
884                     -- update rti
885                     IF (g_asn_debug = 'Y') THEN
886                         asn_debug.put_line('update_rti_error for a fail all ASN transaction ');
887                     END IF;
888 
889                     update_rti_error(p_group_id                => x_cascaded_table(n).group_id,
890                                      p_interface_id            => NULL,
891                                      p_header_interface_id     => x_header_record.header_record.header_interface_id,
892                                      p_lpn_group_id            => NULL
893                                     );
894 
895                      /* Bug 4779020 .Update the RHI to error.Exit the Loop to prevent processing the line */
896                     IF (g_asn_debug = 'Y') THEN
897                         asn_debug.put_line('error out rhi for a fail all ASN transaction ');
898                     END IF;
899 
900                     UPDATE rcv_headers_interface
901                        SET processing_status_code = 'ERROR',
902                            validation_flag = 'Y',
903                            receipt_header_id = NULL
904                      WHERE header_interface_id = x_header_record.header_record.header_interface_id;
905 
906                     x_header_record.error_record.error_status := 'E';
907 
908                     /* Bug 4779020 End */
909                 ELSE --}{ not an asn with fail all option turned on
910                     IF (g_asn_debug = 'Y') THEN
911                         asn_debug.put_line('update_rti_error for an non fail all ASN transaction ');
912                     END IF;
913 
914                     update_rti_error(p_group_id                => x_cascaded_table(n).group_id,
915                                      p_interface_id            => x_cascaded_table(n).interface_transaction_id,
916                                      p_header_interface_id     => NULL,
917                                      p_lpn_group_id            => x_cascaded_table(n).lpn_group_id
918                                     );
919 
920                     -- update the rhi to error if all of its line processing failed
921                     IF (g_asn_debug = 'Y') THEN
922                         asn_debug.put_line('update rhi for non fail-all-ASN transaction ');
923                     END IF;
924 
925                     IF x_cascaded_table(n).header_interface_id IS NOT NULL THEN --{
926                        UPDATE rcv_headers_interface rhi
927                           SET rhi.processing_status_code = 'ERROR',
928                               rhi.validation_flag = 'Y',
929                               rhi.receipt_header_id = NULL
930                           WHERE header_interface_id = x_cascaded_table(n).header_interface_id
931                           AND NOT EXISTS ( SELECT  rti.interface_transaction_id
932                                              FROM  rcv_transactions_interface rti
933                                             WHERE  rhi.header_interface_id = rti.header_interface_id
934                                               AND  rti.processing_status_code in ('RUNNING', 'PENDING'));
935 
936                        IF (g_asn_debug = 'Y') THEN
937                           asn_debug.put_line(sql%rowcount || ' RHI record updated to error. ');
938                        END IF;
939 
940                     END IF; --}
941 
942                     /* Bug 4191118: Need to remove the rsh row if line transaction fails.
943                      * Only delete the shipment header that was created in this trxn loop
944                      * for PO/RMA receipt or ASN import.
945                      *
946                      * Bug 5024414: Only delete shipment headers where there is no running
947                      * or pending interface line under the interface header, so that we only
948                      * delete rsh after all rti lines have failed.
949                      * */
950                     DELETE FROM rcv_shipment_headers
951                      WHERE shipment_header_id = l_ship_header_id
952                       AND  asn_status = 'NEW_SHIP'
953                       AND NOT EXISTS ( SELECT  rti.interface_transaction_id
954                                          FROM  rcv_transactions_interface rti,
955                                                rcv_headers_interface rhi
956                                         WHERE  rhi.header_interface_id = rti.header_interface_id
957                                           AND  rti.processing_status_code in ('RUNNING', 'PENDING')
958                                           AND  rhi.receipt_header_id = l_ship_header_id );
959 
960                     IF (g_asn_debug = 'Y') THEN
961                         asn_debug.put_line(sql%rowcount || ' rsh record deleted');
962                     END IF;
963 
964                 END IF; --} not asn and fail all case
965 
966             END IF; --} line processing failed
967 
968           END IF; --} header_record.transaction_type <> 'CANCEL'  --bug 4368726
969 
970             -- set n back to 0
971             n                                   := 0;
972 
973             /* Bug#3890439
974             * Need to call 824 Interface to insert records into ECE_ADVO_HEADERS
975             * and ECE_ADVO_DETAILS for errored out transactions if it was an ASN
976             * import and EDI is installed. Data in these 2 tables will be extracted
977             * to generate outbound 824 Application Advice.
978             */
979 
980             /* Bug 4881909 Start :
981             **   Call 824 interface only when RHI or RTI row is in error.
982             */
983               IF (x_header_record.header_record.asn_type IN('ASN', 'ASBN')) THEN
984                 IF g_is_edi_installed = 'I' THEN
985 
986                   begin
987                     select 1
988                     into l_count
989                     from dual where exists (select 'Errored RHI'
990                                             from    rcv_headers_interface
991                                             where   asn_type in ('ASN','ASBN')
992                                               and   processing_status_code = 'ERROR'
993                                               and   header_interface_id = x_header_record.header_record.header_interface_id);
994                   exception
995                     when NO_DATA_FOUND then
996 
997                       begin
998                         select 1
999                         into l_count
1000                         from dual
1001                         where exists (select 'Errored RTIs'
1002                                       from    rcv_transactions_interface
1003                                       where   processing_status_code = 'ERROR'
1004                                         and   header_interface_id = x_header_record.header_record.header_interface_id);
1005 
1006                       exception
1007                         when NO_DATA_FOUND then
1008                           l_count := 0;
1009                       end;
1010                   end;
1011 
1012                    if (l_count = 1) then
1013                      rcv_824_sv.rcv_824_insert(x_header_record, 'ASN');
1014                    end if;
1015 
1016                 END IF;
1017               END IF;  -- end of asn_type IN('ASN', 'ASBN')
1018            /* Bug 4881909 End */
1019 
1020         END LOOP; --} end loop of transaction rows in rti
1021 
1022         /* Forward port for Bug 4355172 vendor_site_id was not getting defaulted to rcv_shipment_headers.
1023            As a result skip_lot if setup against a supplier site will not work.
1024            since vendor_site_id is derived and populated into RTI get the same and update
1025            RSH */
1026                 if (x_header_record.header_record.transaction_type <> 'CANCEL') and
1027                    (x_header_record.header_record.vendor_site_id is null) and
1028                    (x_header_record.header_record.header_interface_id is not null) and
1029                       (x_header_record.error_record.error_status IN('S', 'W')) then
1030                    if (x_header_record.header_record.receipt_source_code='VENDOR') then
1031 
1032                        select count(count(vendor_site_id))
1033                        into x_site_id_count
1034                        from rcv_transactions_interface
1035                        where shipment_header_id=x_header_record.header_record.receipt_header_id
1036                        and vendor_site_id is not null
1037                        group by vendor_site_id;
1038                                               -- Update only if all shipments have same vendor site id
1039                        if (x_site_id_count = 1) then
1040                        Begin
1041                           update rcv_shipment_headers
1042                           set vendor_site_id=(select distinct vendor_site_id
1043                                               from rcv_transactions_interface
1044                                               where shipment_header_id=x_header_record.header_record.receipt_header_id
1045                                               and vendor_site_id is not null)
1046                           where shipment_header_id=x_header_record.header_record.receipt_header_id;
1047                        Exception
1048                        when others then null;
1049                        end;
1050                        end if;
1051                     end if;
1052                  end if;
1053 
1054          /* End 4355172 */
1055 
1056 
1057         CLOSE rcv_roi_preprocessor.txns_cur;
1058         asn_debug.put_line('after loop');
1059 
1060 	--DCP call
1061 	BEGIN
1062 		IF (g_asn_debug = 'Y') THEN
1063 			asn_debug.put_line('l_check_dcp ' || l_check_dcp);
1064 			asn_debug.put_line('g_check_dcp ' || rcv_dcp_pvt.g_check_dcp);
1065 		END IF;
1066 
1067 		IF l_check_dcp  > 0 THEN
1068 			-- Moved the driving cursor to the DCP package itself
1069 			-- FOR header_cur_rec IN headers_cur_dcp(x_request_id, x_group_id) LOOP
1070 			rcv_dcp_pvt.validate_data(p_dcp_event => 'PREPROCESSOR', p_request_id => x_request_id, p_group_id => x_group_id, p_raise_exception => 'Y', x_return_status => l_return_status);
1071 			--END LOOP;
1072 		END IF;
1073 	EXCEPTION
1074 		WHEN rcv_dcp_pvt.data_inconsistency_exception THEN
1075 			IF (g_asn_debug = 'Y') THEN
1076 				asn_debug.put_line('Data Inconsistency Exception');
1077 			END IF;
1078 			IF  distinct_org_id%ISOPEN THEN
1079 				CLOSE  distinct_org_id;
1080 			END IF;
1081 			x_error_record := x_empty_error_record;
1082 			x_header_record  := x_empty_header_record;
1083 			-- initialize error_record
1084 			x_header_record.error_record  := x_error_record;
1085 
1086 			ROLLBACK TO dcp_preprocessor_start;
1087 			GOTO dcp_pre_processor_start;
1088 		WHEN OTHERS THEN
1089 			IF (g_asn_debug = 'Y') THEN
1090 				asn_debug.put_line('When Others ' || SQLERRM);
1091 			END IF;
1092 			NULL;
1093 	END;
1094 	--End DCP call
1095 
1096         IF (g_asn_debug = 'Y') THEN
1097             asn_debug.put_line('Exit preprocessor');
1098         END IF;
1099     EXCEPTION
1100         WHEN NO_DATA_FOUND THEN
1101             rcv_error_pkg.set_sql_error_message('RCV_ROI_PREPROCESSOR.preprocessor','sqlcode');
1102             rcv_error_pkg.log_interface_error('PARENT_SOURCE_TRANSACTION_NUM', FALSE);
1103 
1104             IF rcv_roi_preprocessor.txns_cur%ISOPEN THEN
1105                 CLOSE rcv_roi_preprocessor.txns_cur;
1106             END IF;
1107 
1108             --pjiang, close header cursor explicitly
1109             IF rcv_roi_preprocessor.headers_cur%ISOPEN THEN
1110                 CLOSE rcv_roi_preprocessor.headers_cur;
1111             END IF;
1112         WHEN rcv_error_pkg.e_fatal_error THEN --we didn't catch an error that we should have caught
1113             asn_debug.put_line('uncaught e_fatal_error in rcv_roi_preprocess.preprocessor - abnormal execution');
1114             asn_debug.put_line('last error message = ' || rcv_error_pkg.get_last_message);
1115         WHEN OTHERS THEN
1116             IF (g_asn_debug = 'Y') THEN
1117                 asn_debug.put_line('Exception in preprocessor:');
1118                 asn_debug.put_line('sqlerrm: ' || SQLERRM);
1119                 asn_debug.put_line('l_msg_count: ' || l_msg_count);
1120                 asn_debug.put_line('l_msg_data: ' || l_msg_data);
1121                 asn_debug.put_line('Set rti rows to error for this and call txn complete');
1122             END IF;
1123 
1124             IF rcv_roi_preprocessor.txns_cur%ISOPEN THEN
1125                 CLOSE rcv_roi_preprocessor.txns_cur;
1126             END IF;
1127 
1128             --pjiang, close header cursor explicitly
1129             IF rcv_roi_preprocessor.headers_cur%ISOPEN THEN
1130                 CLOSE rcv_roi_preprocessor.headers_cur;
1131             END IF;
1132 
1133             /*We default p_group_id to 0 */
1134             IF (    p_group_id IS NOT NULL
1135                 AND p_group_id <> 0) THEN
1136                 IF (g_asn_debug = 'Y') THEN
1137                     asn_debug.put_line('update_rti_error in exception with group_id ');
1138                 END IF;
1139 
1140                 update_rti_error(p_group_id                => p_group_id,
1141                                  p_interface_id            => NULL,
1142                                  p_header_interface_id     => NULL,
1143                                  p_lpn_group_id            => NULL
1144                                 );
1145             ELSIF(p_request_id IS NOT NULL) THEN
1146                 OPEN distinct_groups(p_request_id);
1147                 l_group_count  := 1;
1148 
1149                 LOOP
1150                     FETCH distinct_groups INTO l_exception_group_id(n);
1151                     EXIT WHEN distinct_groups%NOTFOUND;
1152 
1153                     IF (g_asn_debug = 'Y') THEN
1154                         asn_debug.put_line('update_rti_error in exception with request_id ');
1155                     END IF;
1156 
1157                     update_rti_error(p_group_id                => l_exception_group_id(n),
1158                                      p_interface_id            => NULL,
1159                                      p_header_interface_id     => NULL,
1160                                      p_lpn_group_id            => NULL
1161                                     );
1162                     l_group_count  := l_group_count + 1;
1163                 END LOOP;
1164 
1165                 CLOSE distinct_groups;
1166             END IF;
1167     END preprocessor;
1168 
1169     PROCEDURE default_from_parent_trx(
1170         x_cascaded_table IN OUT NOCOPY rcv_roi_preprocessor.cascaded_trans_tab_type,
1171         n                IN OUT NOCOPY BINARY_INTEGER
1172     ) IS
1173         CURSOR get_parent_row_from_rt(
1174             p_transaction_id rcv_transactions.transaction_id%TYPE
1175         ) IS
1176             SELECT --mandatory matching values
1177                     rt.shipment_header_id,
1178                     rt.shipment_line_id,
1179                     rt.source_document_code,
1180                     rt.po_header_id,
1181                     rt.po_release_id,
1182                     rt.po_line_id,
1183                     rt.po_line_location_id,
1184                     rt.po_distribution_id,
1185                     rt.po_revision_num,
1186                     rt.requisition_line_id,
1187                     rt.po_unit_price,
1188                     rt.currency_code,
1189                     rt.currency_conversion_type,
1190                     rt.vendor_id,
1191                     rt.vendor_site_id,
1192                     rt.source_doc_unit_of_measure,
1193                     rt.oe_order_header_id,
1194                     rt.oe_order_line_id,
1195                     rt.customer_id,
1196                     rt.customer_site_id,
1197                     rt.job_id,
1198                     rt.timecard_id,
1199                     rt.timecard_ovn,
1200                     rt.project_id,
1201                     rt.task_id,
1202                     rsl.category_id,
1203                     rsl.item_description,
1204                     rsl.item_id,
1205                     rsl.item_revision,
1206                     rsl.vendor_item_num,
1207                     rsl.vendor_lot_num,
1208                     rsl.from_organization_id,
1209                     rsl.to_organization_id,
1210                     --defaulting values
1211                     rt.unit_of_measure,
1212                     rt.primary_unit_of_measure,
1213                     rt.uom_code,
1214                     rt.employee_id,
1215                     rt.currency_conversion_rate,
1216                     rt.currency_conversion_date,
1217                     rt.deliver_to_person_id,
1218                     rt.deliver_to_location_id,
1219                     rt.secondary_unit_of_measure,
1220                     rt.secondary_uom_code
1221             FROM   rcv_transactions rt,
1222                    rcv_shipment_lines rsl
1223             WHERE  transaction_id = p_transaction_id
1224             AND    rt.shipment_line_id = rsl.shipment_line_id(+);
1225 
1226         CURSOR get_parent_row_from_rti(
1227             p_transaction_id rcv_transactions.transaction_id%TYPE
1228         ) IS
1229             SELECT --mandatory matching values
1230                     shipment_header_id,
1231                     shipment_line_id,
1232                     source_document_code,
1233                     po_header_id,
1234                     po_release_id,
1235                     po_line_id,
1236                     po_line_location_id,
1237                     po_distribution_id,
1238                     po_revision_num,
1239                     requisition_line_id,
1240                     po_unit_price,
1241                     currency_code,
1242                     currency_conversion_type,
1243                     vendor_id,
1244                     vendor_site_id,
1245                     source_doc_unit_of_measure,
1246                     oe_order_header_id,
1247                     oe_order_line_id,
1248                     customer_id,
1249                     customer_site_id,
1250                     job_id,
1251                     timecard_id,
1252                     timecard_ovn,
1253                     project_id,
1254                     task_id,
1255                     category_id,
1256                     item_description,
1257                     item_id,
1258                     item_revision,
1259                     vendor_item_num,
1260                     vendor_lot_num,
1261                     from_organization_id,
1262                     to_organization_id,
1263                     --defaulting values
1264                     unit_of_measure,
1265                     primary_unit_of_measure,
1266                     uom_code,
1267                     employee_id,
1268                     currency_conversion_rate,
1269                     currency_conversion_date,
1270                     deliver_to_person_id,
1271                     deliver_to_location_id,
1272                     secondary_unit_of_measure,
1273                     secondary_uom_code
1274             FROM   rcv_transactions_interface
1275             WHERE  interface_transaction_id = p_transaction_id;
1276 
1277         CURSOR get_parent_row_from_cascade(
1278             p_parent_index NUMBER
1279         ) IS
1280             SELECT --mandatory matching values
1281                     x_cascaded_table(p_parent_index).shipment_header_id shipment_header_id,
1282                     x_cascaded_table(p_parent_index).shipment_line_id shipment_line_id,
1283                     x_cascaded_table(p_parent_index).source_document_code source_document_code,
1284                     x_cascaded_table(p_parent_index).po_header_id po_header_id,
1285                     x_cascaded_table(p_parent_index).po_release_id po_release_id,
1286                     x_cascaded_table(p_parent_index).po_line_id po_line_id,
1287                     x_cascaded_table(p_parent_index).po_line_location_id po_line_location_id,
1288                     x_cascaded_table(p_parent_index).po_distribution_id po_distribution_id,
1289                     x_cascaded_table(p_parent_index).po_revision_num po_revision_num,
1290                     x_cascaded_table(p_parent_index).requisition_line_id requisition_line_id,
1291                     x_cascaded_table(p_parent_index).po_unit_price po_unit_price,
1292                     x_cascaded_table(p_parent_index).currency_code currency_code,
1293                     x_cascaded_table(p_parent_index).currency_conversion_type currency_conversion_type,
1294                     x_cascaded_table(p_parent_index).vendor_id vendor_id,
1295                     x_cascaded_table(p_parent_index).vendor_site_id vendor_site_id,
1296                     x_cascaded_table(p_parent_index).source_doc_unit_of_measure source_doc_unit_of_measure,
1297                     x_cascaded_table(p_parent_index).oe_order_header_id oe_order_header_id,
1298                     x_cascaded_table(p_parent_index).oe_order_line_id oe_order_line_id,
1299                     x_cascaded_table(p_parent_index).customer_id customer_id,
1300                     x_cascaded_table(p_parent_index).customer_site_id customer_site_id,
1301                     x_cascaded_table(p_parent_index).job_id job_id,
1302                     x_cascaded_table(p_parent_index).timecard_id timecard_id,
1303                     x_cascaded_table(p_parent_index).timecard_ovn timecard_ovn,
1304                     x_cascaded_table(p_parent_index).project_id project_id,
1305                     x_cascaded_table(p_parent_index).task_id task_id,
1306                     x_cascaded_table(p_parent_index).category_id category_id,
1307                     x_cascaded_table(p_parent_index).item_description item_description,
1308                     x_cascaded_table(p_parent_index).item_id item_id,
1309                     x_cascaded_table(p_parent_index).item_revision item_revision,
1310                     x_cascaded_table(p_parent_index).vendor_item_num vendor_item_num,
1311                     x_cascaded_table(p_parent_index).vendor_lot_num vendor_lot_num,
1312                     x_cascaded_table(p_parent_index).from_organization_id from_organization_id,
1313                     x_cascaded_table(p_parent_index).to_organization_id to_organization_id,
1314                     --defaulting values
1315                     x_cascaded_table(p_parent_index).unit_of_measure unit_of_measure,
1316                     x_cascaded_table(p_parent_index).primary_unit_of_measure primary_unit_of_measure,
1317                     x_cascaded_table(p_parent_index).uom_code uom_code,
1318                     x_cascaded_table(p_parent_index).employee_id employee_id,
1319                     x_cascaded_table(p_parent_index).currency_conversion_rate currency_conversion_rate,
1320                     x_cascaded_table(p_parent_index).currency_conversion_date currency_conversion_date,
1321                     x_cascaded_table(p_parent_index).deliver_to_person_id deliver_to_person_id,
1322                     x_cascaded_table(p_parent_index).deliver_to_location_id deliver_to_location_id,
1323                     x_cascaded_table(p_parent_index).secondary_unit_of_measure secondary_unit_of_measure,
1324                     x_cascaded_table(p_parent_index).secondary_uom_code secondary_uom_code
1325             FROM   DUAL;
1326 
1327         x_parent_row get_parent_row_from_rt%ROWTYPE;
1328 
1329         PROCEDURE default_no_check(
1330             p_src_value IN            VARCHAR2,
1331             p_dst_value IN OUT NOCOPY VARCHAR2
1332         ) IS
1333         BEGIN
1334             IF     p_dst_value IS NULL
1335                AND p_src_value IS NOT NULL THEN
1336                 p_dst_value  := p_src_value;
1337             END IF;
1338         END default_no_check;
1339 
1340         PROCEDURE default_no_check(
1341             p_src_value IN            NUMBER,
1342             p_dst_value IN OUT NOCOPY NUMBER
1343         ) IS
1344         BEGIN
1345             IF     p_dst_value IS NULL
1346                AND p_src_value IS NOT NULL THEN
1347                 p_dst_value  := p_src_value;
1348             END IF;
1349         END default_no_check;
1350     BEGIN
1351         IF (x_cascaded_table(n).derive = 'Y') THEN --{
1352             IF (x_cascaded_table(n).derive_index <> 0) THEN --{
1353                 OPEN get_parent_row_from_cascade(x_cascaded_table(n).derive_index);
1354                 FETCH get_parent_row_from_cascade INTO x_parent_row;
1355 
1356                 IF (get_parent_row_from_cascade%NOTFOUND) THEN
1357                     CLOSE get_parent_row_from_cascade;
1358                     RETURN;
1359                 END IF;
1360 
1361                 CLOSE get_parent_row_from_cascade;
1362             ELSIF (x_cascaded_table(n).parent_interface_txn_id IS NOT NULL) THEN
1363                 OPEN get_parent_row_from_rti(x_cascaded_table(n).parent_interface_txn_id);
1364                 FETCH get_parent_row_from_rti INTO x_parent_row;
1365 
1366                 IF (get_parent_row_from_rti%NOTFOUND) THEN
1367                     CLOSE get_parent_row_from_rti;
1368                     RETURN;
1369                 END IF;
1370 
1371                 CLOSE get_parent_row_from_rti;
1372             ELSE
1373                 RETURN;
1374             END IF;
1375         ELSIF (x_cascaded_table(n).parent_transaction_id IS NOT NULL) THEN
1376             OPEN get_parent_row_from_rt(x_cascaded_table(n).parent_transaction_id);
1377             FETCH get_parent_row_from_rt INTO x_parent_row;
1378 
1379             IF (get_parent_row_from_rt%NOTFOUND) THEN
1380                 CLOSE get_parent_row_from_rt;
1381                 RETURN;
1382             END IF;
1383 
1384             CLOSE get_parent_row_from_rt;
1385         ELSE
1386             RETURN;
1387         END IF;
1388 
1389         --mandatory matching values
1390         rcv_error_pkg.default_and_check(x_parent_row.shipment_header_id,
1391                                         x_cascaded_table(n).shipment_header_id,
1392                                         'SHIPMENT_HEADER_ID'
1393                                        );
1394         rcv_error_pkg.default_and_check(x_parent_row.shipment_line_id,
1395                                         x_cascaded_table(n).shipment_line_id,
1396                                         'SHIPMENT_LINE_ID'
1397                                        );
1398         rcv_error_pkg.default_and_check(x_parent_row.source_document_code,
1399                                         x_cascaded_table(n).source_document_code,
1400                                         'SOURCE_DOCUMENT_CODE'
1401                                        );
1402         rcv_error_pkg.default_and_check(x_parent_row.po_header_id,
1403                                         x_cascaded_table(n).po_header_id,
1404                                         'PO_HEADER_ID'
1405                                        );
1406         rcv_error_pkg.default_and_check(x_parent_row.po_release_id,
1407                                         x_cascaded_table(n).po_release_id,
1408                                         'PO_RELEASE_ID'
1409                                        );
1410         rcv_error_pkg.default_and_check(x_parent_row.po_line_id,
1411                                         x_cascaded_table(n).po_line_id,
1412                                         'PO_LINE_ID'
1413                                        );
1414         rcv_error_pkg.default_and_check(x_parent_row.po_line_location_id,
1415                                         x_cascaded_table(n).po_line_location_id,
1416                                         'PO_LINE_LOCATION_ID'
1417                                        );
1418         rcv_error_pkg.default_and_check(x_parent_row.po_distribution_id,
1419                                         x_cascaded_table(n).po_distribution_id,
1420                                         'PO_DISTRIBUTION_ID'
1421                                        );
1422         rcv_error_pkg.default_and_check(x_parent_row.po_revision_num,
1423                                         x_cascaded_table(n).po_revision_num,
1424                                         'PO_REVISION_NUM'
1425                                        );
1426         rcv_error_pkg.default_and_check(x_parent_row.requisition_line_id,
1427                                         x_cascaded_table(n).requisition_line_id,
1428                                         'REQUISITION_LINE_ID'
1429                                        );
1430         rcv_error_pkg.default_and_check(x_parent_row.po_unit_price,
1431                                         x_cascaded_table(n).po_unit_price,
1432                                         'PO_UNIT_PRICE'
1433                                        );
1434         rcv_error_pkg.default_and_check(x_parent_row.currency_code,
1435                                         x_cascaded_table(n).currency_code,
1436                                         'CURRENCY_CODE'
1437                                        );
1438         rcv_error_pkg.default_and_check(x_parent_row.currency_conversion_type,
1439                                         x_cascaded_table(n).currency_conversion_type,
1440                                         'CURRENCY_CONVERSION_TYPE'
1441                                        );
1442         rcv_error_pkg.default_and_check(x_parent_row.vendor_id,
1443                                         x_cascaded_table(n).vendor_id,
1444                                         'VENDOR_ID'
1445                                        );
1446         rcv_error_pkg.default_and_check(x_parent_row.vendor_site_id,
1447                                         x_cascaded_table(n).vendor_site_id,
1448                                         'VENDOR_SITE_ID'
1449                                        );
1450         rcv_error_pkg.default_and_check(x_parent_row.source_doc_unit_of_measure,
1451                                         x_cascaded_table(n).source_doc_unit_of_measure,
1452                                         'SOURCE_DOC_UNIT_OF_MEASURE'
1453                                        );
1454         rcv_error_pkg.default_and_check(x_parent_row.oe_order_header_id,
1455                                         x_cascaded_table(n).oe_order_header_id,
1456                                         'OE_ORDER_HEADER_ID'
1457                                        );
1458         rcv_error_pkg.default_and_check(x_parent_row.oe_order_line_id,
1459                                         x_cascaded_table(n).oe_order_line_id,
1460                                         'OE_ORDER_LINE_ID'
1461                                        );
1462         rcv_error_pkg.default_and_check(x_parent_row.customer_id,
1463                                         x_cascaded_table(n).customer_id,
1464                                         'CUSTOMER_ID'
1465                                        );
1466         rcv_error_pkg.default_and_check(x_parent_row.customer_site_id,
1467                                         x_cascaded_table(n).customer_site_id,
1468                                         'CUSTOMER_SITE_ID'
1469                                        );
1470         rcv_error_pkg.default_and_check(x_parent_row.job_id,
1471                                         x_cascaded_table(n).job_id,
1472                                         'JOB_ID'
1473                                        );
1474         rcv_error_pkg.default_and_check(x_parent_row.timecard_id,
1475                                         x_cascaded_table(n).timecard_id,
1476                                         'TIMECARD_ID'
1477                                        );
1478         rcv_error_pkg.default_and_check(x_parent_row.timecard_ovn,
1479                                         x_cascaded_table(n).timecard_ovn,
1480                                         'TIMECARD_OVN'
1481                                        );
1482         rcv_error_pkg.default_and_check(x_parent_row.project_id,
1483                                         x_cascaded_table(n).project_id,
1484                                         'PROJECT_ID'
1485                                        );
1486         rcv_error_pkg.default_and_check(x_parent_row.task_id,
1487                                         x_cascaded_table(n).task_id,
1488                                         'TASK_ID'
1489                                        );
1490         rcv_error_pkg.default_and_check(x_parent_row.category_id,
1491                                         x_cascaded_table(n).category_id,
1492                                         'CATEGORY_ID'
1493                                        );
1494         rcv_error_pkg.default_and_check(x_parent_row.item_description,
1495                                         x_cascaded_table(n).item_description,
1496                                         'ITEM_DESCRIPTION'
1497                                        );
1498         rcv_error_pkg.default_and_check(x_parent_row.item_id,
1499                                         x_cascaded_table(n).item_id,
1500                                         'ITEM_ID'
1501                                        );
1502         rcv_error_pkg.default_and_check(x_parent_row.item_revision,
1503                                         x_cascaded_table(n).item_revision,
1504                                         'ITEM_REVISION'
1505                                        );
1506         rcv_error_pkg.default_and_check(x_parent_row.vendor_item_num,
1507                                         x_cascaded_table(n).vendor_item_num,
1508                                         'VENDOR_ITEM_NUM'
1509                                        );
1510         rcv_error_pkg.default_and_check(x_parent_row.vendor_lot_num,
1511                                         x_cascaded_table(n).vendor_lot_num,
1512                                         'VENDOR_LOT_NUM'
1513                                        );
1514         rcv_error_pkg.default_and_check(x_parent_row.from_organization_id,
1515                                         x_cascaded_table(n).from_organization_id,
1516                                         'FROM_ORGANIZATION_ID'
1517                                        );
1518         rcv_error_pkg.default_and_check(x_parent_row.to_organization_id,
1519                                         x_cascaded_table(n).to_organization_id,
1520                                         'TO_ORGANIZATION_ID'
1521                                        );
1522         --defaulting values
1523         default_no_check(x_parent_row.unit_of_measure, x_cascaded_table(n).unit_of_measure);
1524         default_no_check(x_parent_row.primary_unit_of_measure, x_cascaded_table(n).primary_unit_of_measure);
1525         default_no_check(x_parent_row.uom_code, x_cascaded_table(n).uom_code);
1526         default_no_check(x_parent_row.employee_id, x_cascaded_table(n).employee_id);
1527         default_no_check(x_parent_row.currency_conversion_rate, x_cascaded_table(n).currency_conversion_rate);
1528         default_no_check(x_parent_row.currency_conversion_date, x_cascaded_table(n).currency_conversion_date);
1529         default_no_check(x_parent_row.deliver_to_person_id, x_cascaded_table(n).deliver_to_person_id);
1530         default_no_check(x_parent_row.deliver_to_location_id, x_cascaded_table(n).deliver_to_location_id);
1531         default_no_check(x_parent_row.secondary_unit_of_measure, x_cascaded_table(n).secondary_unit_of_measure);
1532         default_no_check(x_parent_row.secondary_uom_code, x_cascaded_table(n).secondary_uom_code);
1533     EXCEPTION
1534         WHEN rcv_error_pkg.e_fatal_error THEN
1535             x_cascaded_table(n).error_status  := rcv_error_pkg.g_ret_sts_error;
1536             x_cascaded_table(n).error_message := rcv_error_pkg.get_last_message;
1537     END default_from_parent_trx;
1538 
1539     PROCEDURE process_line(
1540         x_cascaded_table IN OUT NOCOPY rcv_roi_preprocessor.cascaded_trans_tab_type,
1541         n                IN OUT NOCOPY BINARY_INTEGER,
1542         x_header_id      IN            rcv_headers_interface.header_interface_id%TYPE,
1543         x_asn_type       IN            rcv_headers_interface.asn_type%TYPE,
1544         v_header_record  IN OUT NOCOPY rcv_roi_preprocessor.header_rec_type
1545     ) IS
1546         x_parent_id            NUMBER;
1547         x_progress             VARCHAR2(3);
1548         x_error_record         rcv_shipment_object_sv.errorrectype;
1549         x_start_indice         BINARY_INTEGER                                       := NULL;
1550         i                      BINARY_INTEGER                                       := NULL;
1551         used_for_cascaded_rows rcv_roi_preprocessor.cascaded_trans_tab_type;
1552         /* Bug 3434460 */
1553         l_return_status        VARCHAR2(1);
1554         l_msg_count            NUMBER;
1555         l_msg_data             fnd_new_messages.MESSAGE_TEXT%TYPE;
1556         l_to_org_id            rcv_transactions_interface.to_organization_id%TYPE;
1557     BEGIN
1558         IF (g_asn_debug = 'Y') THEN
1559             asn_debug.put_line('Enter create shipment line');
1560         END IF;
1561 
1562         IF (g_asn_debug = 'Y') THEN
1563             asn_debug.put_line('Initialize the table structure used for storing the cascaded rows' || x_cascaded_table(n).transaction_type);
1564             asn_debug.put_line('receipt source code' || x_cascaded_table(n).receipt_source_code);
1565         END IF;
1566 
1567         -- delete all records from used_for_cascaded_rows
1568         used_for_cascaded_rows.DELETE;
1569         x_progress      := '000';
1570         x_start_indice  := n;
1571 
1572         -- default information from the parent trx
1573         default_from_parent_trx(x_cascaded_table,n);
1574 
1575         -- derive the shipment line information
1576         IF (x_cascaded_table(n).error_status IN ('S','W') ) THEN --Bug: 5586062
1577             IF (x_cascaded_table(n).receipt_source_code = 'VENDOR') THEN --{
1578                 IF (x_cascaded_table(n).transaction_type IN('SHIP', 'RECEIVE')) THEN
1579                     rcv_roi_transaction.derive_vendor_rcv_line(x_cascaded_table,
1580                                                                n,
1581                                                                used_for_cascaded_rows,
1582                                                                v_header_record
1583                                                               );
1584                 ELSIF(x_cascaded_table(n).transaction_type IN('TRANSFER', 'ACCEPT', 'REJECT', 'DELIVER')) THEN
1585                     asn_debug.put_line('calling derive routine for transaction ' || x_cascaded_table(n).transaction_type);
1586                     rcv_roi_transaction.derive_vendor_trans_del(x_cascaded_table,
1587                                                                 n,
1588                                                                 used_for_cascaded_rows,
1589                                                                 v_header_record
1590                                                                );
1591                 ELSIF(x_cascaded_table(n).transaction_type =('CORRECT')) THEN
1592                     asn_debug.put_line('calling derive routine for transaction ' || x_cascaded_table(n).transaction_type);
1593                     rcv_roi_transaction.derive_correction_line(x_cascaded_table,
1594                                                                n,
1595                                                                used_for_cascaded_rows,
1596                                                                v_header_record
1597                                                               );
1598                 ELSIF(x_cascaded_table(n).transaction_type = 'RETURN TO VENDOR') THEN
1599                     asn_debug.put_line('calling derive routine for transaction ' || x_cascaded_table(n).transaction_type);
1600                     rcv_roi_return.derive_return_line(x_cascaded_table,
1601                                                       n,
1602                                                       used_for_cascaded_rows,
1603                                                       v_header_record
1604                                                      );
1605                 ELSIF(x_cascaded_table(n).transaction_type = 'RETURN TO RECEIVING') THEN
1606                     asn_debug.put_line('calling derive routine for transaction ' || x_cascaded_table(n).transaction_type);
1607                     rcv_roi_return.derive_return_line(x_cascaded_table,
1608                                                       n,
1609                                                       used_for_cascaded_rows,
1610                                                       v_header_record
1611                                                      );
1612                 ELSE
1613                     asn_debug.put_line('We do not support transaction type ' || x_cascaded_table(n).transaction_type);
1614                     rcv_error_pkg.set_error_message('RCV_INVALID_TRANSACTION_TYPE');
1615                     rcv_error_pkg.log_interface_error('TRANSACTION_TYPE');
1616                 END IF;
1617             ELSIF(x_cascaded_table(n).receipt_source_code = 'INTERNAL ORDER') THEN
1618                 IF (x_cascaded_table(n).transaction_type = 'RECEIVE') THEN
1619                     asn_debug.put_line('calling derive routine for transaction ' || x_cascaded_table(n).transaction_type);
1620                     rcv_int_order_pp_pvt.derive_io_receive_line(x_cascaded_table,
1621                                                                 n,
1622                                                                 used_for_cascaded_rows,
1623                                                                 v_header_record
1624                                                                );
1625                 ELSIF(x_cascaded_table(n).transaction_type IN('TRANSFER', 'ACCEPT', 'REJECT', 'DELIVER')) THEN
1626                     asn_debug.put_line('calling derive routine for transaction ' || x_cascaded_table(n).transaction_type);
1627                     rcv_int_order_pp_pvt.derive_io_trans_line(x_cascaded_table,
1628                                                               n,
1629                                                               used_for_cascaded_rows,
1630                                                               v_header_record
1631                                                              );
1632                 ELSIF(x_cascaded_table(n).transaction_type =('CORRECT')) THEN
1633                     asn_debug.put_line('calling derive routine for transaction ' || x_cascaded_table(n).transaction_type);
1634                     rcv_int_order_pp_pvt.derive_io_correct_line(x_cascaded_table,
1635                                                                 n,
1636                                                                 used_for_cascaded_rows,
1637                                                                 v_header_record
1638                                                                );
1639                 ELSE
1640                     asn_debug.put_line('We do not support transaction type ' || x_cascaded_table(n).transaction_type);
1641                     rcv_error_pkg.set_error_message('RCV_INVALID_TRANSACTION_TYPE');
1642                     rcv_error_pkg.log_interface_error('TRANSACTION_TYPE');
1643                 END IF; -- IF INTERNAL ORDER
1644             ELSIF(x_cascaded_table(n).receipt_source_code = 'INVENTORY') THEN --} {
1645                 IF (x_cascaded_table(n).transaction_type = 'RECEIVE') THEN
1646                     rcv_int_org_transfer.derive_int_org_rcv_line(x_cascaded_table,
1647                                                                  n,
1648                                                                  used_for_cascaded_rows,
1649                                                                  v_header_record
1650                                                                 );
1651                 ELSIF(x_cascaded_table(n).transaction_type IN('TRANSFER', 'ACCEPT', 'REJECT', 'DELIVER')) THEN
1652                     asn_debug.put_line('calling derive routine for transaction ' || x_cascaded_table(n).transaction_type);
1653                     rcv_int_org_transfer.derive_int_org_trans_del(x_cascaded_table,
1654                                                                   n,
1655                                                                   used_for_cascaded_rows,
1656                                                                   v_header_record
1657                                                                  );
1658                 ELSIF(x_cascaded_table(n).transaction_type =('CORRECT')) THEN
1659                     asn_debug.put_line('calling derive routine for transaction ' || x_cascaded_table(n).transaction_type);
1660                     rcv_int_org_transfer.derive_int_org_cor_line(x_cascaded_table,
1661                                                                  n,
1662                                                                  used_for_cascaded_rows,
1663                                                                  v_header_record
1664                                                                 );
1665                 ELSE
1666                     asn_debug.put_line('We do not support transaction type ' || x_cascaded_table(n).transaction_type);
1667                     rcv_error_pkg.set_error_message('RCV_INVALID_TRANSACTION_TYPE');
1668                     rcv_error_pkg.log_interface_error('TRANSACTION_TYPE');
1669                 END IF;
1670             ELSIF(x_cascaded_table(n).receipt_source_code = 'CUSTOMER') THEN --} {
1671                 asn_debug.put_line('calling derive routine for RMA transaction ' || x_cascaded_table(n).transaction_type);
1672 
1673                 IF (x_cascaded_table(n).transaction_type = 'RECEIVE') THEN --{
1674                     rcv_rma_transactions.derive_rma_line(x_cascaded_table,
1675                                                          n,
1676                                                          used_for_cascaded_rows,
1677                                                          v_header_record
1678                                                         );
1679                 ELSIF(x_cascaded_table(n).transaction_type IN('TRANSFER', 'ACCEPT', 'REJECT', 'DELIVER')) THEN
1680                     rcv_rma_transactions.derive_rma_trans_del(x_cascaded_table,
1681                                                               n,
1682                                                               used_for_cascaded_rows,
1683                                                               v_header_record
1684                                                              );
1685                 ELSIF(x_cascaded_table(n).transaction_type = 'RETURN TO CUSTOMER') THEN
1686                     rcv_roi_return.derive_return_line(x_cascaded_table,
1687                                                       n,
1688                                                       used_for_cascaded_rows,
1689                                                       v_header_record
1690                                                      );
1691                 ELSIF(x_cascaded_table(n).transaction_type = 'CORRECT') THEN
1692                     rcv_rma_transactions.derive_rma_correction_line(x_cascaded_table,
1693                                                                     n,
1694                                                                     used_for_cascaded_rows,
1695                                                                     v_header_record
1696                                                                    );
1697                 ELSE
1698                     asn_debug.put_line('We do not support transaction type ' || x_cascaded_table(n).transaction_type);
1699                     rcv_error_pkg.set_error_message('RCV_INVALID_TRANSACTION_TYPE');
1700                     rcv_error_pkg.log_interface_error('TRANSACTION_TYPE');
1701                 END IF; --}
1702             ELSE --}{
1703                 asn_debug.put_line('We do not support receipt_source_code ' || x_cascaded_table(n).receipt_source_code);
1704                 rcv_error_pkg.set_error_message('RCV_INVALID_TRANSACTION_TYPE');
1705                 rcv_error_pkg.log_interface_error('TRANSACTION_TYPE');
1706             END IF; --}
1707         END IF;
1708         IF (g_asn_debug = 'Y') THEN
1709             asn_debug.put_line('Back from derive routine with ' || TO_CHAR(used_for_cascaded_rows.COUNT) || ' rows');
1710             asn_debug.put_line('Error Status ' || x_cascaded_table(n).error_status);
1711             asn_debug.put_line('Error Message ' || x_cascaded_table(n).error_message);
1712         END IF;
1713 
1714         x_progress      := '010';
1715 
1716         IF     (x_cascaded_table(n).error_status IN('S', 'W'))
1717            AND used_for_cascaded_rows.COUNT > 0 THEN --{ we have returned with a cascaded table
1718             FOR i IN 1 .. used_for_cascaded_rows.COUNT LOOP --{
1719                 IF (g_asn_debug = 'Y') THEN
1720                     asn_debug.put_line('Defaulting for cascaded row ' || TO_CHAR(i));
1721                 END IF;
1722 
1723                 -- default shipment line information
1724                 IF (x_cascaded_table(n).receipt_source_code = 'VENDOR') THEN --{
1725                     IF (x_cascaded_table(n).transaction_type IN('SHIP', 'RECEIVE')) THEN --{
1726                         rcv_roi_transaction.default_vendor_rcv_line(used_for_cascaded_rows,
1727                                                                     i,
1728                                                                     x_header_id,
1729                                                                     v_header_record
1730                                                                    );
1731                     ELSIF(x_cascaded_table(n).transaction_type IN('TRANSFER', 'ACCEPT', 'REJECT', 'DELIVER')) THEN --}{
1732                         asn_debug.put_line('Defaulting for cascaded row ' || TO_CHAR(i));
1733                         asn_debug.put_line('Defaulting for cascaded row ' || x_cascaded_table(n).transaction_type);
1734                         rcv_roi_transaction.default_vendor_trans_del(used_for_cascaded_rows, i);
1735                     ELSIF(x_cascaded_table(n).transaction_type = 'CORRECT') THEN --}{
1736                         asn_debug.put_line('Defaulting for cascaded row ' || TO_CHAR(i));
1737                         asn_debug.put_line('Defaulting for cascaded row ' || x_cascaded_table(n).transaction_type);
1738                         rcv_roi_transaction.default_vendor_correct(used_for_cascaded_rows, i);
1739                     ELSIF(x_cascaded_table(n).transaction_type = 'RETURN TO VENDOR') THEN --}{
1740                         asn_debug.put_line('Defaulting for cascaded row ' || TO_CHAR(i));
1741                         asn_debug.put_line('Defaulting for cascaded row ' || x_cascaded_table(n).transaction_type);
1742                         rcv_roi_return.default_return_line(used_for_cascaded_rows, i);
1743                     ELSIF(x_cascaded_table(n).transaction_type = 'RETURN TO RECEIVING') THEN --}{
1744                         asn_debug.put_line('Defaulting for cascaded row ' || TO_CHAR(i));
1745                         rcv_roi_return.default_return_line(used_for_cascaded_rows, i);
1746                     END IF; --}
1747                 ELSIF(x_cascaded_table(n).receipt_source_code = 'INTERNAL ORDER') THEN
1748                     IF (x_cascaded_table(n).transaction_type = 'RECEIVE') THEN
1749                         rcv_int_order_pp_pvt.default_io_receive_line(used_for_cascaded_rows, i);
1750                     ELSIF(x_cascaded_table(n).transaction_type IN('TRANSFER', 'ACCEPT', 'REJECT', 'DELIVER')) THEN
1751                         asn_debug.put_line('Defaulting for cascaded row ' || TO_CHAR(i) || ' TYPE: ' || x_cascaded_table(n).transaction_type);
1752                         rcv_int_order_pp_pvt.default_io_trans_line(used_for_cascaded_rows, i);
1753                     ELSIF(x_cascaded_table(n).transaction_type = 'CORRECT') THEN
1754                         asn_debug.put_line('Defaulting for cascaded row ' || TO_CHAR(i) || ' TYPE: ' || x_cascaded_table(n).transaction_type);
1755                         rcv_int_order_pp_pvt.default_io_correct_line(used_for_cascaded_rows, i);
1756                     ELSIF(x_cascaded_table(n).transaction_type IN('RETURN TO VENDOR', 'RETURN TO RECEIVING')) THEN
1757                         asn_debug.put_line('Defaulting for cascaded row ' || TO_CHAR(i) || ' TYPE: ' || x_cascaded_table(n).transaction_type);
1758                         rcv_roi_return.default_return_line(used_for_cascaded_rows, i);
1759                     END IF; -- FOR default INTERNAL ORDER
1760                 ELSIF(x_cascaded_table(n).receipt_source_code = 'INVENTORY') THEN -- } {
1761                     IF (x_cascaded_table(n).transaction_type = 'RECEIVE') THEN --{
1762                         rcv_int_org_transfer.default_int_org_rcv_line(used_for_cascaded_rows, i);
1763                     ELSIF(x_cascaded_table(n).transaction_type IN('TRANSFER', 'ACCEPT', 'REJECT', 'DELIVER')) THEN --}{
1764                         asn_debug.put_line('Defaulting for cascaded row ' || TO_CHAR(i));
1765                         asn_debug.put_line('Defaulting for cascaded row ' || x_cascaded_table(n).transaction_type);
1766                         rcv_int_org_transfer.default_int_org_trans_del(used_for_cascaded_rows, i);
1767                     ELSIF(x_cascaded_table(n).transaction_type IN('CORRECT')) THEN --}{
1768                         asn_debug.put_line('Defaulting for cascaded row ' || TO_CHAR(i));
1769                         rcv_int_org_transfer.default_int_org_cor_line(used_for_cascaded_rows, i);
1770                     ELSIF(x_cascaded_table(n).transaction_type = 'RETURN TO VENDOR') THEN --}{
1771                         asn_debug.put_line('Defaulting for cascaded row ' || TO_CHAR(i));
1772                         asn_debug.put_line('Defaulting for cascaded row ' || x_cascaded_table(n).transaction_type);
1773                         rcv_roi_return.default_return_line(used_for_cascaded_rows, i);
1774                     ELSIF(x_cascaded_table(n).transaction_type = 'RETURN TO RECEIVING') THEN --}{
1775                         asn_debug.put_line('Defaulting for cascaded row ' || TO_CHAR(i));
1776                         rcv_roi_return.default_return_line(used_for_cascaded_rows, i);
1777                     END IF; --}
1778                 ELSIF(x_cascaded_table(n).receipt_source_code = 'CUSTOMER') THEN -- } {
1779                     asn_debug.put_line('Defaulting for cascaded row ' || TO_CHAR(i));
1780 
1781                     IF (x_cascaded_table(n).transaction_type = 'RECEIVE') THEN --{
1782                         rcv_rma_transactions.default_rma_line(used_for_cascaded_rows,
1783                                                               i,
1784                                                               x_header_id,
1785                                                               v_header_record
1786                                                              );
1787                     ELSIF(x_cascaded_table(n).transaction_type = 'RETURN TO CUSTOMER') THEN --}{
1788                         rcv_roi_return.default_return_line(used_for_cascaded_rows, i);
1789                     ELSIF(x_cascaded_table(n).transaction_type IN('TRANSFER', 'ACCEPT', 'REJECT', 'DELIVER')) THEN
1790                         rcv_roi_transaction.default_vendor_trans_del(used_for_cascaded_rows, i);
1791                     ELSIF(x_cascaded_table(n).transaction_type = 'CORRECT') THEN
1792                         rcv_roi_transaction.default_vendor_correct(used_for_cascaded_rows, i);
1793                     END IF; --}
1794                 END IF; --}
1795 
1796                 /* 3434460.
1797                  * We need to set transfer_lpn_ids to null for all Deliver type
1798                  * of transactions (Deliver/Direct Delivery). This needs to
1799                  * be done for all non-wms orgs. If to_org_id was given by
1800                  * the user, then this would have been done already after
1801                  * explode_lpn. So check for transfer_lpn_id not null.
1802                 */
1803                 IF (    (   (    used_for_cascaded_rows(i).transaction_type = 'RECEIVE'
1804                              AND used_for_cascaded_rows(i).auto_transact_code = 'DELIVER')
1805                          OR (used_for_cascaded_rows(i).transaction_type = 'DELIVER'))
1806                     AND (   used_for_cascaded_rows(i).transfer_lpn_id IS NOT NULL
1807                          OR used_for_cascaded_rows(i).transfer_license_plate_number IS NOT NULL)
1808                    ) THEN
1809                     IF (    NOT wms_install.check_install(l_return_status,
1810                                                           l_msg_count,
1811                                                           l_msg_data,
1812                                                           used_for_cascaded_rows(i).to_organization_id
1813                                                          )
1814                         AND l_return_status = fnd_api.g_ret_sts_success) THEN
1815                         used_for_cascaded_rows(i).transfer_lpn_id                := NULL;
1816                         used_for_cascaded_rows(i).transfer_license_plate_number  := NULL;
1817 
1818                         IF (g_asn_debug = 'Y') THEN
1819                             asn_debug.put_line('Set transfer_lpn_id and transfer_licese_plate_number to null for a deliver transaction in an non-WMS org for interface_trx_id ' || used_for_cascaded_rows(i).order_transaction_id);
1820                         END IF;
1821                     END IF;
1822                 END IF;
1823 
1824                 /* Bug 3434460 */
1825                 x_progress                               := '020';
1826                 used_for_cascaded_rows(i).error_status   := 'S';
1827                 used_for_cascaded_rows(i).error_message  := NULL;
1828 
1829                 -- validate shipment line information
1830                 --if(X_cascaded_table(n).receipt_source_code = 'VENDOR' and X_cascaded_table(n).transaction_type = 'RECEIVE') then
1831                 IF (x_cascaded_table(n).receipt_source_code = 'VENDOR') THEN
1832                     rcv_roi_transaction.validate_vendor_rcv_line(used_for_cascaded_rows,
1833                                                                  i,
1834                                                                  x_asn_type,
1835                                                                  v_header_record
1836                                                                 );
1837                 ELSIF(x_cascaded_table(n).receipt_source_code = 'INTERNAL ORDER') THEN
1838                     rcv_int_order_pp_pvt.validate_io_receive_line(used_for_cascaded_rows,
1839                                                                   i,
1840                                                                   v_header_record
1841                                                                  );
1842                 ELSIF(x_cascaded_table(n).receipt_source_code = 'INVENTORY') THEN
1843                     -- and X_cascaded_table(n).transaction_type = 'RECEIVE') then
1844                     rcv_int_org_transfer.validate_int_org_rcv_line(used_for_cascaded_rows,
1845                                                                    i,
1846                                                                    v_header_record
1847                                                                   );
1848                 ELSIF(x_cascaded_table(n).receipt_source_code = 'CUSTOMER') THEN
1849                     rcv_rma_transactions.validate_rma_line(used_for_cascaded_rows,
1850                                                            i,
1851                                                            v_header_record
1852                                                           );
1853                 END IF;
1854 
1855                 x_progress                               := '030';
1856 
1857                 IF (used_for_cascaded_rows(i).error_status NOT IN('S', 'W')) THEN --{
1858                     used_for_cascaded_rows(i).processing_status_code  := 'ERROR';
1859                     x_cascaded_table(n).processing_status_code        := 'ERROR';
1860                     x_cascaded_table(n).error_status                  := used_for_cascaded_rows(i).error_status;
1861                     x_cascaded_table(n).error_message                 := used_for_cascaded_rows(i).error_message;
1862 
1863                     IF (g_asn_debug = 'Y') THEN
1864                         asn_debug.put_line('Have hit error condition in validation');
1865                         asn_debug.put_line('Mark needed flags and error message');
1866                         asn_debug.put_line('Delete the cascaded rows');
1867                     END IF;
1868 
1869                     used_for_cascaded_rows.DELETE;
1870                     EXIT;
1871                 ELSIF(used_for_cascaded_rows(i).error_status IN('S', 'W')) THEN --}{
1872                     /* update interface_available_qty in rti .We now will look at
1873                      * this column to get the available qty if the current row
1874                      * is a child of another row in rti.
1875                     */
1876                     IF used_for_cascaded_rows(i).matching_basis = 'AMOUNT' THEN
1877                         asn_debug.put_line('calling update interface amt ');
1878                         rcv_roi_transaction.update_interface_available_amt(used_for_cascaded_rows, i);
1879                     ELSE
1880                         asn_debug.put_line('calling update interface qty ');
1881                         rcv_roi_transaction.update_interface_available_qty(used_for_cascaded_rows, i);
1882                     END IF;
1883                 END IF; --}
1884             END LOOP; --}
1885 
1886             IF x_cascaded_table(n).processing_status_code = 'ERROR' THEN --{
1887                 IF (g_asn_debug = 'Y') THEN
1888                     asn_debug.put_line('Have hit error condition in validation');
1889                     asn_debug.put_line('Mark needed flags and error message');
1890                     asn_debug.put_line('Delete the cascaded rows');
1891                 END IF;
1892 
1893                 used_for_cascaded_rows.DELETE;
1894             ELSE --} {
1895                 IF (g_asn_debug = 'Y') THEN
1896                     asn_debug.put_line('Have finished default and validation');
1897                     asn_debug.put_line('Process has encountered no fatal errors');
1898                     asn_debug.put_line('Will write the cascaded rows into actual table');
1899                     asn_debug.put_line('Count of cascaded rows ' || TO_CHAR(used_for_cascaded_rows.COUNT));
1900                 END IF;
1901 
1902                 FOR j IN 1 .. used_for_cascaded_rows.COUNT LOOP --{
1903                     IF (g_asn_debug = 'Y') THEN
1904                         asn_debug.put_line('Current counter in actual table is at ' || TO_CHAR(n));
1905                     END IF;
1906 
1907                     x_cascaded_table(n)  := used_for_cascaded_rows(j);
1908                     used_for_cascaded_rows.DELETE(j);
1909                     n                    := n + 1;
1910                 END LOOP; --}
1911 
1912                 IF (g_asn_debug = 'Y') THEN
1913                     asn_debug.put_line('Current counter before decrementing in actual table is at ' || TO_CHAR(n));
1914                 END IF;
1915 
1916                 n  := n - 1; -- Get the counter in sync
1917 
1918                 IF (g_asn_debug = 'Y') THEN
1919                     asn_debug.put_line('Current counter in actual table is at ' || TO_CHAR(n));
1920                 END IF;
1921             END IF; --}
1922         ELSE --} {
1923             x_cascaded_table(n).processing_status_code  := 'ERROR'; --  changed (i) -> (n)
1924             RETURN;
1925         END IF; --}
1926 
1927         IF (g_asn_debug = 'Y') THEN
1928             asn_debug.put_line('Exit create shipment line');
1929         END IF;
1930     EXCEPTION
1931         WHEN rcv_error_pkg.e_fatal_error THEN
1932             x_cascaded_table(n).error_status   := 'E';
1933             x_cascaded_table(n).error_message  := rcv_error_pkg.get_last_message;
1934         WHEN OTHERS THEN
1935             IF (g_asn_debug = 'Y') THEN
1936                 asn_debug.put_line('Exception in process_line');
1937             END IF;
1938     END process_line;
1939 
1940     PROCEDURE explode_lpn_failed(
1941         x_interface_txn_id IN OUT NOCOPY rcv_transactions_interface.interface_transaction_id%TYPE,
1942         x_group_id                       NUMBER,
1943         x_lpn_group_id                   NUMBER
1944     ) IS
1945     BEGIN
1946         IF (g_asn_debug = 'Y') THEN
1947             asn_debug.put_line('update_rti_error in explode_lpn_failed   ');
1948         END IF;
1949 
1950         update_rti_error(p_group_id                => x_group_id,
1951                          p_interface_id            => x_interface_txn_id,
1952                          p_header_interface_id     => NULL,
1953                          p_lpn_group_id            => x_lpn_group_id
1954                         );
1955         rcv_error_pkg.set_error_message('RCV_LPN_EXPLOSION_FAILED');
1956         rcv_error_pkg.set_token('LPN_GROUP_ID', x_lpn_group_id);
1957         rcv_error_pkg.log_interface_warning('LPN_GROUP_ID');
1958     EXCEPTION
1959         WHEN OTHERS THEN
1960             IF (g_asn_debug = 'Y') THEN
1961                 asn_debug.put_line('Exception in explode_lpn_failed');
1962             END IF;
1963     END explode_lpn_failed;
1964 
1965     PROCEDURE update_rti_error(
1966         p_group_id            IN rcv_transactions_interface.GROUP_ID%TYPE,
1967         p_interface_id        IN rcv_transactions_interface.interface_transaction_id%TYPE,
1968         p_header_interface_id IN rcv_transactions_interface.header_interface_id%TYPE,
1969         p_lpn_group_id        IN rcv_transactions_interface.lpn_group_id%TYPE
1970     ) IS
1971         l_return_status        VARCHAR2(1);
1972         l_msg_data             VARCHAR2(2000);
1973         l_msg_count            NUMBER;
1974         l_inventory_id         NUMBER;
1975         l_txn_mode             VARCHAR2(25);
1976         l_processing_mode_code rcv_transactions_interface.processing_mode_code%TYPE;
1977     BEGIN
1978         IF (g_asn_debug = 'Y') THEN
1979             asn_debug.put_line('Set rti row to error');
1980             asn_debug.put_line('p_group_id ' || p_group_id);
1981             asn_debug.put_line('p_interface_id ' || p_interface_id);
1982             asn_debug.put_line('p_header_interface_id ' || p_header_interface_id);
1983             asn_debug.put_line('p_lpn_group_id ' || p_lpn_group_id);
1984         END IF;
1985 
1986         -- bug 3676436, if there is a pending error message than we log it
1987         rcv_error_pkg.log_interface_error('INTERFACE_TRANSACTION_ID',FALSE);
1988 
1989         IF (p_header_interface_id IS NOT NULL) THEN
1990             SELECT DISTINCT (processing_mode_code)
1991             INTO            l_processing_mode_code
1992             FROM            rcv_transactions_interface
1993             WHERE           header_interface_id = p_header_interface_id;
1994         ELSIF(p_interface_id IS NOT NULL) THEN
1995             SELECT processing_mode_code
1996             INTO   l_processing_mode_code
1997             FROM   rcv_transactions_interface
1998             WHERE  interface_transaction_id = p_interface_id;
1999         ELSIF(p_group_id IS NOT NULL) THEN
2000             /* Bug 3361395.
2001              * When there is an when others exception in the
2002              * pre-processor we should not process any of the
2003              * Get the processing_mode here to use it later in
2004              * in this procedure.
2005             */
2006             SELECT DISTINCT (processing_mode_code)
2007             INTO            l_processing_mode_code
2008             FROM            rcv_transactions_interface
2009             WHERE           GROUP_ID = p_group_id;
2010         END IF;
2011 
2012         IF (g_asn_debug = 'Y') THEN
2013             asn_debug.put_line('Processing_mode_code ' || l_processing_mode_code);
2014         END IF;
2015 
2016         IF (l_processing_mode_code = 'ONLINE') THEN
2017             IF (g_asn_debug = 'Y') THEN
2018                 asn_debug.put_line('online error ');
2019             END IF;
2020 
2021             UPDATE rcv_transactions_interface
2022                SET processing_status_code = 'ERROR'
2023              WHERE GROUP_ID = p_group_id;
2024 
2025             inv_receiving_transaction.txn_complete(p_group_id          => p_group_id,
2026                                                    p_txn_status        => 'FALSE',
2027                                                    p_txn_mode          => 'ONLINE',
2028                                                    x_return_status     => l_return_status,
2029                                                    x_msg_data          => l_msg_data,
2030                                                    x_msg_count         => l_msg_count
2031                                                   );
2032         ELSE   /* For Batch and immediate */
2033             IF (p_header_interface_id IS NOT NULL) THEN
2034                 IF (g_asn_debug = 'Y') THEN
2035                     asn_debug.put_line('header_interface_id not null ');
2036                 END IF;
2037 
2038                 UPDATE rcv_transactions_interface
2039                    SET processing_status_code = 'ERROR'
2040                  WHERE header_interface_id = p_header_interface_id;
2041 
2042                 l_inventory_id  := p_header_interface_id;
2043                 l_txn_mode      := 'HEADER';
2044             ELSIF(p_lpn_group_id IS NOT NULL) THEN
2045                 IF (g_asn_debug = 'Y') THEN
2046                     asn_debug.put_line('lpn_group_id not null ');
2047                 END IF;
2048 
2049                 UPDATE rcv_transactions_interface
2050                    SET processing_status_code = 'ERROR'
2051                  WHERE lpn_group_id = p_lpn_group_id;
2052 
2053                 l_inventory_id  := p_lpn_group_id;
2054                 l_txn_mode      := 'LPN_GROUP';
2055             ELSIF(p_interface_id IS NOT NULL) THEN
2056                 IF (g_asn_debug = 'Y') THEN
2057                     asn_debug.put_line('interface_id not null ');
2058                 END IF;
2059 
2060                 UPDATE rcv_transactions_interface
2061                    SET processing_status_code = 'ERROR'
2062                  WHERE interface_transaction_id = p_interface_id;
2063 
2064                 l_inventory_id  := p_interface_id;
2065                 l_txn_mode      := 'PREPROCESSOR';
2066             ELSIF(p_group_id IS NOT NULL) THEN
2067                 /* Bug 3361395.
2068                  * When there is an when others exception in the
2069                  * pre-processor we should not process any of the
2070                  * the rti or rhi rows. Call txn_complete with
2071                  * group_id and txn_mode as the processing mode.
2072                  * WMS assumes that when we call them with
2073                  * ONLINE/BATCH/IMMEDIATE then we call them with
2074                  * only group_id.
2075                 */
2076                 IF (g_asn_debug = 'Y') THEN
2077                     asn_debug.put_line('update all rti rows to error');
2078                 END IF;
2079 
2080                 UPDATE rcv_headers_interface
2081                    SET processing_status_code = 'ERROR'
2082                  WHERE GROUP_ID = p_group_id;
2083 
2084                 UPDATE rcv_transactions_interface
2085                    SET processing_status_code = 'ERROR'
2086                  WHERE GROUP_ID = p_group_id;
2087 
2088                 l_inventory_id  := p_group_id;
2089                 l_txn_mode      := l_processing_mode_code;
2090             END IF;
2091 
2092             IF (g_asn_debug = 'Y') THEN
2093                 asn_debug.put_line('Before call to txn_complete');
2094             END IF;
2095 
2096             inv_receiving_transaction.txn_complete(p_group_id          => l_inventory_id,
2097                                                    p_txn_status        => 'FALSE',
2098                                                    p_txn_mode          => l_txn_mode,
2099                                                    x_return_status     => l_return_status,
2100                                                    x_msg_data          => l_msg_data,
2101                                                    x_msg_count         => l_msg_count
2102                                                   );
2103 
2104             IF (g_asn_debug = 'Y') THEN
2105                 asn_debug.put_line('After call to txn_complete');
2106             END IF;
2107         END IF;
2108     EXCEPTION
2109         WHEN OTHERS THEN
2110             IF (g_asn_debug = 'Y') THEN
2111                 asn_debug.put_line('Exception in update_rti_error');
2112             END IF;
2113     END update_rti_error;
2114 END rcv_roi_preprocessor;