DBA Data[Home] [Help]

PACKAGE BODY: APPS.RCV_ROI_PREPROCESSOR

Source


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