DBA Data[Home] [Help]

PACKAGE BODY: APPS.CN_NOTIFY_ORDERS

Source


1 PACKAGE BODY CN_NOTIFY_ORDERS AS
2 -- $Header: cnnooeb.pls 120.10 2005/12/19 22:27:01 apink ship $
3 
4 
5 G_PKG_NAME          CONSTANT VARCHAR2(30) := 'CN_NOTIFY_ORDERS';
6 G_SOURCE_DOC_TYPE   CONSTANT VARCHAR2(2) := 'OC';
7 
8 --*********************************************
9 -- Private Procedures
10 --*********************************************
11 
12 ------------------------------------------------------------------+
13 
14 -- Function Name
15 --   check_header_exists
16 -- Purpose
17 --   This function will check whether a particular header exsits in
18 --   cn_not_trx.  It returns true if yes, otherwise return false.
19 -- History
20 
21 	FUNCTION check_header_exists(hid	NUMBER,
22 								 p_org_id NUMBER)
23 	RETURN 	varchar2
24 	IS
25 
26 	exist       varchar2(1) := 'N';
27 
28 	BEGIN
29 
30 		SELECT	'Y'
31 		INTO 	exist
32 		FROM 	sys.dual
33 		WHERE 	EXISTS
34 			(SELECT 1
35 			 FROM 	cn_not_trx
36 			 WHERE 	source_trx_id = hid
37 			 AND 	org_id = p_org_id);
38 
39 		RETURN exist;
40 
41 	EXCEPTION
42 
43 		WHEN NO_DATA_FOUND
44 		THEN
45 		RETURN exist;
46 
47 	END check_header_exists;
48 ---------------------------------------------------------------------------+
49 -- Procedure Name
50 --   unequal
51 -- Purpose
52 --   Overlayed procedures to check for inequality, allowing for the
53 --   possibility of NULL values
54 ---------------------------------------------------------------------------+
55 FUNCTION unequal(
56          p_lhs VARCHAR2,
57 	    p_rhs VARCHAR2) RETURN BOOLEAN IS
58 BEGIN
59     IF p_lhs <> p_rhs
60        OR (p_lhs IS NULL AND p_rhs IS NOT NULL)
61        OR (p_lhs IS NOT NULL AND p_rhs IS NULL) THEN
62         RETURN TRUE;
63     ELSE
64         RETURN FALSE;
65     END IF;
66 END unequal;
67 
68 FUNCTION unequal(
69          p_lhs NUMBER,
70 	    p_rhs NUMBER) RETURN BOOLEAN IS
71 BEGIN
72     IF p_lhs <> p_rhs
73        OR (p_lhs IS NULL AND p_rhs IS NOT NULL)
74        OR (p_lhs IS NOT NULL AND p_rhs IS NULL) THEN
75         RETURN TRUE;
76     ELSE
77         RETURN FALSE;
78     END IF;
79 END unequal;
80 
81 
82 -----------------------------------------------------------------------+
83 -- Function Name
84 --   check_last_entry
85 -- Purpose
86 --   This function will check the last entry of a particular line in
87 --   cn_not_trx.  It returns the status of its collected_flag.
88 -- History
89 
90 	FUNCTION check_last_entry(hid NUMBER,
91 				      		  lid NUMBER,
92 							  x_org_id IN NUMBER)
93 	RETURN VARCHAR2
94 	IS
95  		col_flag       VARCHAR2(1) := 'Y';
96 	BEGIN
97 
98 -- We need to use CN_NOT_TRX_ALL instead of CN_NOT_TRX because this
99 -- procedure is being called by Adjust_Order, which processes orders
100 -- from all orgs. This should be OK because we are selecting based on
101 -- header_id, which for Orders are unique identifiers across all orgs.
102 
103     SELECT collected_flag
104       INTO col_flag
105       FROM cn_not_trx_all a
106      WHERE a.source_trx_id = hid
107        AND a.source_trx_line_id = lid
108        AND a.org_id = x_org_id
109        AND a.not_trx_id = (	SELECT max(b.not_trx_id)
110 				  FROM cn_not_trx_all b
111 				 WHERE b.source_trx_id = hid
112 				   AND b.source_trx_line_id = lid
113 				   AND b.org_id = a.org_id );
114 
115     RETURN col_flag;
116 
117   EXCEPTION
118 
119     WHEN NO_DATA_FOUND THEN
120       RETURN col_flag;
121 
122   END check_last_entry;
123 
124 
125 ---------------------------------------------------------------------------+
126 -- Procedure Name
127 --   notify_line
128 -- Purpose
129 --   This procedure collects order line identifiers into cn_not_trx
130 --   as part of order update notification.
131 --
132 --   Note. Whereas Regular_Col_Notify is run for each Org, Notify_Line
133 --   is part of the Update Notification process, of which there is only
134 --   one instance for the installation - because we only have one
135 --   Notification  Queue which passes us updates to orders from any Org.
136 --   This means that new rows inserted into CN_NOT_TRX_ALL must get the
137 --   Org_Id of the updated order rather than just defaulting to the
138 --   client Org-Id. (The defaulting is OK in regular_col_notify because
139 --   that procedure only selects orders for the Client Org anyway). For
140 --   this reason, we use CN_NOT_TRX_ALL here, rather than just CN_NOT_TRX
141 --   and we explicitly set the Org_Id during our insert.
142 
143 -- History
144 --
145   PROCEDURE notify_line (
146 	p_header_id	NUMBER,
147 	p_line_id		NUMBER,
148 	p_adj_flag	VARCHAR2 := 'Y',
149 	x_org_id NUMBER ) IS
150 
151     l_trx_count 	NUMBER;
152     l_proc_audit_id	NUMBER;
153     l_rowid		ROWID;
154      l_sys_batch_size NUMBER;
155      CURSOR batch_size IS SELECT system_batch_size FROM cn_repositories WHERE org_id = x_org_id;
156 
157   BEGIN
158 
159     cn_message_pkg.debug('notify: adjust: entering notify_line (lid = '||p_line_id||') ');
160     fnd_file.put_line(fnd_file.Log, 'notify: adjust: entering notify_line (lid = '||p_line_id||') ');
161 
162     cn_process_audits_pkg.insert_row
163 	( l_rowid, l_proc_audit_id, NULL, 'NOT', 'Notification run',
164 	  NULL, NULL, NULL, NULL, NULL, SYSDATE, NULL, x_org_id);
165 
166 	  --Added as per MOAC OE Mandate
167 	  MO_GLOBAL.SET_POLICY_CONTEXT ('S', x_org_id);
168     OPEN batch_size;
169     FETCH batch_size INTO l_sys_batch_size;
170     CLOSE batch_size;
171 
172     -- Call to Check_Last_Entry makes sure that there is not
173     -- already a 'to-be-collected' record for the line in CN_NOT_TRX_ALL.
174     IF Check_Last_Entry
175                      (p_header_id,
176                       p_line_id,
177                       x_org_id) = 'Y' THEN
178       INSERT INTO cn_not_trx_all (
179         org_id,
180         not_trx_id,
181         batch_id,
182         notified_date,
183         processed_date,
184         notification_run_id,
185         collected_flag,
186         row_id,
187         source_trx_id,
188         source_trx_line_id,
189 	   source_doc_type,
190         adjusted_flag,
191         event_id)
192       SELECT
193         asoh.org_id,
194         cn_not_trx_s.NEXTVAL,
195         FLOOR(cn_not_trx_s.CURRVAL/NVL(l_sys_batch_size,200)),
196         SYSDATE,
197         asoh.booked_date,
198         l_proc_audit_id,
199         'N',
200         asoh.rowid,
201         asoh.header_id,
202         asol.line_id,
203 	   g_source_doc_type,
204         p_adj_flag,
205         cn_global.ord_event_id
206       FROM
207         aso_i_oe_order_headers_v asoh,
208         aso_i_oe_order_lines_v asol
209       WHERE
210         asoh.header_id = p_header_id
211         AND asoh.booked_flag = 'Y'              -- only interested in status of booked
212 	   -- NOTE: asoh.header_id is a primary key, so no need to
213 	   -- have an org filter for the join to asol
214         AND asol.header_id = asoh.header_id
215         AND asol.line_id = p_line_id
216         AND asol.org_id = x_org_id -- R12 MOAC Changes
217         AND asoh.org_id = asol.org_id -- R12 MOAC Changes
218 -- also collect 'RETURN's        AND asol.line_category_code = 'ORDER'   -- only collect 'Order' lines
219         AND EXISTS
220 		  (SELECT 1
221 		  FROM mtl_system_items mtl
222 		  WHERE
223                 --+
224                 -- Because this procedure is looking at orders for any
225                 -- org_id, we have to get the inventory organization for
226                 -- the org_id of the order, by passing that org_id into
227                 -- our call to OE_PROFILE.VALUE.
228                 --+
229 			 NVL(mtl.organization_id,NVL(oe_profile.value('OE_ORGANIZATION_ID',asoh.org_id),-99)) =
230                     NVL(oe_profile.value('OE_ORGANIZATION_ID',asoh.org_id),-99)
231                 AND mtl.inventory_item_id = asol.inventory_item_id
232                 AND mtl.invoiceable_item_flag = 'Y');     -- only want invoiceable items
233       cn_message_pkg.debug('notify: adjust: .  notified');
234       fnd_file.put_line(fnd_file.Log, 'notify: adjust: .  notified');
235     END IF;
236 
237     cn_message_pkg.debug('notify: adjust: exit from notify_line (lid = '||p_line_id||')');
238     fnd_file.put_line(fnd_file.Log, 'notify: adjust: exit from notify_line (lid = '||p_line_id||')');
239   END notify_line;
240 
241 
242 
243 ---------------------------------------------------------------------------+
244 -- Procedure Name
245 --   notify_deleted_line
246 -- Purpose
247 --   This procedure collects order line identifiers for deleted lines
248 --   into cn_not_trx as part of order update notification.
249 --
250 --   When a collected order is changed, all of the old lines are reversed
251 --   out and all current lines for the order are added in again. This
252 --   procedure is used to register the Id of a deleted line so that it
253 --   will be reversed.We cannot use notify_line for this because that procedure
254 --   is also used for new lines and therefore runs a query using line information
255 --   to see if that line is eligible. This infomration is no longer avaliable
256 --   for a deleted line.
257 --
258 -- History
259 --   11-01-99	D.Maskell  Created
260 
261   PROCEDURE notify_deleted_line (
262 	p_header_id	NUMBER,
263 	p_line_id	     NUMBER,
264 	p_org_id NUMBER) IS
265 
266 	l_proc_audit_id NUMBER;
267      l_rowid		ROWID;
268      l_org_id NUMBER;
269      l_sys_batch_size NUMBER;
270      CURSOR batch_size IS SELECT system_batch_size FROM cn_repositories WHERE org_id = p_org_id;
271 
272   BEGIN
273 
274     cn_message_pkg.debug('notify: adjust: entering notify_deleted_line (lid = '||p_line_id||')');
275     fnd_file.put_line(fnd_file.Log, 'notify: adjust: entering notify_deleted_line (lid = '||p_line_id||')');
276 
277 
278 	  l_org_id := p_org_id;
279 
280     cn_process_audits_pkg.insert_row
281 	( l_rowid, l_proc_audit_id, NULL, 'NOT', 'Notification run',
282 	  NULL, NULL, NULL, NULL, NULL, SYSDATE, NULL, p_org_id);
283     OPEN batch_size;
284     FETCH batch_size INTO l_sys_batch_size;
285     CLOSE batch_size;
286 
287     -- Call to Check_Last_Entry makes sure that there is not
288     -- already a 'to-be-collected' record for the line in CN_NOT_TRX_ALL.
289     IF Check_Last_Entry
290                      (p_header_id,
291                       p_line_id,
292                       l_org_id) = 'Y' THEN
293       INSERT INTO cn_not_trx_all (
294 		 org_id,
295 	     not_trx_id,
296 	     batch_id,
297 	     notified_date,
298 	     processed_date,
299 	     notification_run_id,
300 	     collected_flag,
301 	     row_id,
302 	     source_trx_id,
303 	     source_trx_line_id,
304 	     source_doc_type,
305 	     adjusted_flag,
306 	     event_id)
307       SELECT
308 		 asoh.org_id,
309 	     cn_not_trx_s.NEXTVAL,
310 	     FLOOR(cn_not_trx_s.CURRVAL/NVL(l_sys_batch_size,200)),
311 	     SYSDATE,
312 	     asoh.booked_date,
313 	     l_proc_audit_id,
314           'N',
315 	     asoh.rowid,
316 	     asoh.header_id,
317 	     p_line_id,
318 	     g_source_doc_type,
319 	     'Y',
320 	     cn_global.ord_event_id
321       FROM
322           aso_i_oe_order_headers_v asoh
323       WHERE
324           asoh.header_id = p_header_id
325           AND asoh.booked_flag = 'Y'
326 		  AND asoh.org_id = l_org_id;              -- only interested in status of booked
327       cn_message_pkg.debug('notify: adjust: .  notified');
328       fnd_file.put_line(fnd_file.Log, 'notify: adjust: .  notified');
329     END IF;
330 
331     cn_message_pkg.debug('exit from notify_deleted_line (lid = '||p_line_id||')');
332     fnd_file.put_line(fnd_file.Log, 'exit from notify_deleted_line (lid = '||p_line_id||')');
333   END notify_deleted_line;
334 
335 ---------------------------------------------------------------------------+
336 -- Procedure Name
337 --   notify_affected_lines
338 -- Purpose
339 --   This procedure collects order line identifiers into cn_not_trx_all
340 --   of lines affected by a change to an order sales credit.
341 --   Design Note: A Top Model Line will have its own line_id in its
342 --                top_model_line_id column.
343 --
344 -- History
345 --   02-10-00	D.Maskell  Created
346 -----------------------------------------------------------------------------+
347   PROCEDURE notify_affected_lines (
348 	p_header_id	NUMBER,
349 	p_line_id		NUMBER,
350 	p_org_id NUMBER) IS
351 
352     l_proc_audit_id	NUMBER;
353     l_rowid		ROWID;
354     l_org_id NUMBER;
355     -- cursor which gets information for a particular line
356     CURSOR c_line (cp_lid NUMBER) IS
357       SELECT top_model_line_id, service_reference_line_id
358       FROM aso_i_oe_order_lines_v
359       WHERE line_id = cp_lid
360 	  AND org_id = l_org_id;
361     l_line_rec		c_line%ROWTYPE;
362 
363   BEGIN
364   l_org_id := p_org_id;
365 
366     cn_message_pkg.debug('notify: adjust: entering notify_affected_lines (lid = '||p_line_id||')');
367     fnd_file.put_line(fnd_file.Log, 'notify: adjust: entering notify_affected_lines (lid = '||p_line_id||')');
368 
369     cn_process_audits_pkg.insert_row
370 	( l_rowid, l_proc_audit_id, NULL, 'NOT', 'Notification run',
371 	  NULL, NULL, NULL, NULL, NULL, SYSDATE, NULL, p_org_id);
372     --+
373     -- Examine the line (if any) to which the sales credit belonged
374     -- to determine which other lines need to be re-collected as well.
375     --+
376     IF p_line_id IS NULL THEN
377         --+
378         -- This is a Header Sales Credit, so recollect any Top Model Lines
379         -- and 'Standard' lines which do not have their own sales credits.
380         -- Do this using a recursive self-call, so that any children of
381         -- these lines, which do not have their own sales credits, will
382         -- also be re-collected.
383         --+
384         cn_message_pkg.debug('notify: adjust: .  Header SC change');
385         fnd_file.put_line(fnd_file.Log, 'notify: adjust: .  Header SC change');
386         FOR rec IN
387           (SELECT line_id
388            FROM   aso_i_oe_order_lines_v asol
389            WHERE  asol.header_id = p_header_id
390                   AND asol.service_reference_line_id IS NULL
391                   AND asol.org_id = l_org_id
392                   AND (asol.top_model_line_id IS NULL OR
393                       asol.top_model_line_id = asol.line_id)
394                   AND NOT EXISTS
395                     (SELECT 1
396                      FROM aso_i_oe_sales_credits_v assc
397                      WHERE assc.line_id = asol.line_id))
398         LOOP
399             notify_affected_lines(p_header_id, rec.line_id, l_org_id);
400         END LOOP;
401     ELSE
402         -- +
403         -- This is a line sales credt, so re-collect the line and
404         -- check if any child lines are affected.
405         --+
406         cn_message_pkg.debug('notify: adjust: .  Line SC change');
407         fnd_file.put_line(fnd_file.Log, 'notify: adjust: .  Line SC change');
408         notify_line(p_header_id, p_line_id,x_org_id => l_org_id);
409         --+
410         -- Get some line information
411         --+
412         OPEN c_line(p_line_id);
413         FETCH c_line INTO l_line_rec;
414         CLOSE c_line;
415         --+
416         -- If this is a Service Line or a Configured Line then
417         -- no other lines are affected
418         --+
419         IF l_line_rec.service_reference_line_id IS NOT NULL OR
420           (l_line_rec.top_model_line_id IS NOT NULL
421            AND p_line_id <> l_line_rec.top_model_line_id) THEN
422             cn_message_pkg.debug('notify: adjust: ..  Serv/Conf line');
423             fnd_file.put_line(fnd_file.Log, 'notify: adjust: ..  Serv/Conf line');
424             NULL;
425         --+
426         -- If this is a 'Standard' line then also re-collect any Service
427         -- Lines belonging to this line, which do not have their own
428         -- direct sales credits.
429         -- Note: Service Lines can be on a different order
430         --+
431         ELSIF l_line_rec.service_reference_line_id IS NULL
432               AND l_line_rec.top_model_line_id IS NULL THEN
433             cn_message_pkg.debug('notify: adjust: ..  Standard line');
434             fnd_file.put_line(fnd_file.Log, 'notify: adjust: ..  Standard line');
435             FOR rec IN
436               (SELECT header_id, line_id
437                FROM   aso_i_oe_order_lines_v asol
438                WHERE  asol.service_reference_line_id = p_line_id
439                AND    asol.org_id = p_org_id
440                       AND NOT EXISTS
441                         (SELECT 1
442                          FROM aso_i_oe_sales_credits_v assc
443                          WHERE assc.line_id = asol.line_id))
444             LOOP
445                 notify_line(rec.header_id, rec.line_id,x_org_id => l_org_id);
446             END LOOP;
447         --+
448         -- If this is a Top Model Line then also re-collect any Configured
449         -- Lines belonging to this line which do not have their own
450         -- direct sales credits.
451         -- Note: Configured Lines will be on same order
452         --+
453         ELSIF p_line_id = l_line_rec.top_model_line_id THEN
454             cn_message_pkg.debug('notify: adjust: ..  Top Model line');
455             fnd_file.put_line(fnd_file.Log, 'notify: adjust: ..  Top Model line');
456             FOR rec IN
457               (SELECT line_id
458                FROM   aso_i_oe_order_lines_v asol
459                WHERE  asol.top_model_line_id = p_line_id
460                AND asol.org_id = p_org_id
461                       AND asol.header_id = p_header_id   -- makes use of index
462                       AND NOT EXISTS
463                         (SELECT 1
464                          FROM aso_i_oe_sales_credits_v assc
465                          WHERE assc.line_id = asol.line_id)
466                       AND asol.line_id <> p_line_id)     -- don't re-collect ourself
467             LOOP
468                 notify_line(p_header_id, rec.line_id,x_org_id => l_org_id);
469             END LOOP;
470         END IF;
471     END IF;
472 
473     cn_message_pkg.debug('notify: adjust: exit from notify_affected_lines (lid = '||p_line_id||')');
474     fnd_file.put_line(fnd_file.Log, 'notify: adjust: exit from notify_affected_lines (lid = '||p_line_id||')');
475   END notify_affected_lines;
476 
477 ------------------------------------------------------------------------------+
478 -- Procedure Name
479 --   Adjust_Order
480 -- Purpose
481 --   This procedure receives the Header, Line and Sales Credit information
482 --   for an adjusted order. It searches through these entities to see whether
483 --   any changes have occured which are relevant to Sales Compensation. If
484 --   there are relevant changes, a notify_line procedure is called to apply
485 --   the appropriate adjustments to Sales Compensation.
486 --
487 -- History
488 --   11-15-99  D.Maskell Created
489 ------------------------------------------------------------------------------+
490 PROCEDURE Adjust_Order
491 (  p_api_version      IN NUMBER,
492    p_init_msg_list    IN VARCHAR2 := FND_API.G_FALSE,
493    p_commit           IN VARCHAR2 := FND_API.G_FALSE,
494    p_validation_level IN NUMBER   := FND_API.G_VALID_LEVEL_FULL,
495    x_return_status          OUT NOCOPY VARCHAR2,
496    x_msg_count              OUT NOCOPY NUMBER,
497    x_msg_data               OUT NOCOPY VARCHAR2,
498    p_header_id              IN NUMBER,
499    p_header_rec             IN OE_Order_PUB.Header_Rec_Type,
500    p_old_header_rec         IN OE_Order_PUB.Header_Rec_Type,
501    p_Header_Scredit_tbl     IN OE_Order_PUB.Header_Scredit_Tbl_Type,
502    p_old_Header_Scredit_tbl IN OE_Order_PUB.Header_Scredit_Tbl_Type,
503    p_line_tbl               IN OE_Order_PUB.Line_Tbl_Type,
504    p_old_line_tbl           IN OE_Order_PUB.Line_Tbl_Type,
505    p_Line_Scredit_tbl       IN OE_Order_PUB.Line_Scredit_Tbl_Type,
506    p_old_Line_Scredit_tbl   IN OE_Order_PUB.line_scredit_tbl_type,
507    p_parent_proc_audit_id   IN NUMBER,
508    x_org_id 				IN NUMBER) -- R12 MOAC Change
509 IS
510     l_api_name      CONSTANT VARCHAR2(30) := 'Adjust_Order';
511     l_api_version   CONSTANT NUMBER  := 1.0;
512     l_debug_pipe    VARCHAR2(30);
513     l_debug_level   NUMBER := 1 ;
514     l_process_audit_id   NUMBER;
515     l_order_changed BOOLEAN;
516     l_found         BOOLEAN;
517     i               NUMBER; --loop counter
518     k               NUMBER; --loop counter
519     l_idx           NUMBER; --remembered loop counter
520     l_org_id        NUMBER;
521     -- cursor which loops through all the lines under a
522     -- particular header
523     CURSOR c_affected_lines (cp_hid NUMBER) IS
524       SELECT header_id, line_id
525       FROM aso_i_oe_order_lines_v
526       WHERE header_id = cp_hid
527 	  AND org_id = x_org_id; -- R12 MOAC Change
528     l_affected_line_rec		c_affected_lines%ROWTYPE;
529     -- Cursor which gets all Service lines for the
530     -- input line, where the Service line resides on
531     -- another order
532     CURSOR c_affected_service_lines (cp_hid NUMBER, cp_lid NUMBER) IS
533       SELECT header_id, line_id
534       FROM aso_i_oe_order_lines_v
535       WHERE service_reference_line_id = cp_lid
536         AND header_id <> cp_hid
537 		AND org_id = x_org_id;
538     l_affected_service_line_rec		c_affected_lines%ROWTYPE;
539 BEGIN
540    --+
541    -- Create a Debug log file to track how the order was processed
542    --+
543    IF (p_parent_proc_audit_id IS NOT NULL) THEN
544       cn_message_pkg.end_batch (p_parent_proc_audit_id);
545    END IF;
546 
547    l_org_id := x_org_id;
548 
549    cn_message_pkg.begin_batch(
550         x_parent_proc_audit_id => p_parent_proc_audit_id,
551         x_process_audit_id     => l_process_audit_id,
552         x_request_id           => fnd_global.conc_request_id,
553         x_process_type         => 'ORD',
554 		p_org_id => l_org_id);
555 
556    cn_message_pkg.debug('notify: Got update information from Order Capture Feedback Queue for an adjusted order.');
557    fnd_file.put_line(fnd_file.Log, 'notify: Got update information from Order Capture Feedback Queue for an adjusted order.');
558 
559    cn_message_pkg.debug('notify: Checking see if any changes have occured which are relevant to Sales Compensation.');
560    fnd_file.put_line(fnd_file.Log, 'notify: Checking see if any changes have occured which are relevant to Sales Compensation.');
561 
562    cn_message_pkg.debug('notify: Entering adjust_order (hid = '||p_header_id||') ');
563    fnd_file.put_line(fnd_file.Log, 'notify: Entering adjust_order (hid = '||p_header_id||') ');
564 
565     -- Standard Start of API savepoint
566     SAVEPOINT	Update_Headers;
567     -- Standard call to check for call compatibility.
568     IF NOT FND_API.Compatible_API_Call (l_api_version,
569                                         p_api_version,
570                                         l_api_name,
571                                         G_PKG_NAME)
572     THEN
573         RAISE FND_API.G_EXC_UNEXPECTED_ERROR;
574     END IF;
575     -- Initialize message list if p_init_msg_list is set to TRUE.
576     IF FND_API.to_Boolean( p_init_msg_list ) THEN
577         FND_MSG_PUB.initialize;
578     END IF;
579     --  Initialize API return status to success
580     x_return_status := FND_API.G_RET_STS_SUCCESS;
581     -------------------+
582     -- API body
583     -------------------+
584     --+
585     -- Look to see if the Order has changed at all in a relevent way
586     -- and then act appropriately.
587     -- The general strategy is simply to call Notify_Line for each
588     -- existing order line which is affected by a change to an Order
589     -- Header, Line or Sales Credit.
590     -- Notify_Line then adds a new row in CN_NOT_TRX_ALL for the
591     -- order line. That strategy takes care of changes to existing
592     -- lines and addition of new lines. However for a line deletetion,
593     -- Notify_Line would not add a record for it in CN_NOT_TRX_ALL, because it
594     -- requeries the line to get more details,
595     -- which would fail. We must have this record because
596     -- the collection process will use its presence to Reverse
597     -- the existing line in CN_COMM_LINES_API. That is why we call the special
598     -- procedure Notify_Deleted_Line for every deleted line.
599     --+
600     -- DESIGN NOTE: you can't just loop from table.FIRST..table.LAST because this
601     -- leads to a 'Numeric or Value Error' if a table is empty. This is why I
602     -- wrapped the FIRST/LAST attributes in NVL statements for all table loops
603     -- This is less messy than having to wrap each loop in an IF..ENDIF test for
604     -- an empty table.
605     -- Also note, thorughout the code I have done the DELETE processing separately
606     -- from the Insert/Update processing. This is because I was told that the DELETE
607     -- operation would be registered in the Old_Tbl structures, (e.g. Old_Line_Tbl)
608     -- rather than the current ones (e.g. Line_Tbl). As it turns out they are
609     -- recording the DELETEs in the Current structures and not in the 'Olds'
610     -- However, you never know when they may change their minds...
611     --+
612     l_order_changed := FALSE;
613     --+
614     -- Have any Lines been Deleted?
615     --+
616     cn_message_pkg.debug('notify: adjust: Deleted Lines? - Line_Tbl');
617     fnd_file.put_line(fnd_file.Log, 'notify: adjust: Deleted Lines? - Line_Tbl');
618     FOR i IN NVL(p_line_tbl.FIRST,1)..NVL(p_line_tbl.LAST,0) LOOP
619         cn_message_pkg.debug('notify: adjust: .  lid = '|| p_line_tbl(i).line_id || ' operation = ' || Nvl(p_line_tbl(i).operation,'NULL'));
620         fnd_file.put_line(fnd_file.Log, 'notify: adjust: .  lid = '|| p_line_tbl(i).line_id || ' operation = ' || Nvl(p_line_tbl(i).operation,'NULL'));
621         IF p_line_tbl(i).operation = 'DELETE' THEN
622             notify_deleted_line
623 	                         (p_line_tbl(i).header_id,
624 	                          p_line_tbl(i).line_id,
625 							  p_org_id => l_org_id);
626         END IF;
627     END LOOP;
628     --+
629     -- Has the Order Header been Inserted?
630     -- Or has a relevant Header field been Updated?
631     -- If so, collect (or re-collect) the entire Order
632     --+
633     IF NOT l_order_changed THEN
634         cn_message_pkg.debug('notify: adjust: Header Insert/Update?');
635         fnd_file.put_line(fnd_file.Log, 'notify: adjust: Header Insert/Update?');
636 
637         cn_message_pkg.debug('notify: adjust: .  operation = '|| Nvl(p_header_rec.operation,'NULL'));
638         fnd_file.put_line(fnd_file.Log, 'notify: adjust: .  operation = '|| Nvl(p_header_rec.operation,'NULL'));
639 
640         IF p_header_rec.operation = 'CREATE' THEN
641             l_order_changed := TRUE;
642         ELSIF p_header_rec.operation = 'UPDATE' THEN
643             IF unequal(p_header_rec.invoice_to_org_id , p_old_header_rec.invoice_to_org_id) OR
644                unequal(p_header_rec.invoice_to_contact_id , p_old_header_rec.invoice_to_contact_id) OR
645                unequal(p_header_rec.ship_to_org_id , p_old_header_rec.ship_to_org_id) OR
646                unequal(p_header_rec.order_number , p_old_header_rec.order_number) OR
647                unequal(p_header_rec.booked_flag , p_old_header_rec.booked_flag) OR
648                unequal(p_header_rec.transactional_curr_code , p_old_header_rec.transactional_curr_code) OR
649                unequal(p_header_rec.conversion_rate , p_old_header_rec.conversion_rate)
650             THEN
651                 l_order_changed := TRUE;
652                 cn_message_pkg.debug('notify: adjust: .  update of interest');
653                 fnd_file.put_line(fnd_file.Log, 'notify: adjust: .  update of interest');
654             END IF;
655         END IF;
656         IF l_order_changed THEN
657             cn_message_pkg.debug('notify: adjust: .  Calling Notify_Line for each line');
658             fnd_file.put_line(fnd_file.Log, 'notify: adjust: .  Calling Notify_Line for each line');
659             FOR l_affected_line_rec IN c_affected_lines(p_header_id)
660             LOOP
661                 cn_notify_orders.notify_line
662                   (l_affected_line_rec.header_id,
663                    l_affected_line_rec.line_id,
664 				   x_org_id => l_org_id);
665                 -- Find any Service Lines for this line on other orders and
666                 -- flag them for recollection too.
667                 FOR l_affected_service_line_rec IN c_affected_service_lines(
668                                                    l_affected_line_rec.header_id,
669                                                    l_affected_line_rec.line_id)
670                 LOOP
671                     cn_notify_orders.notify_line
672                       (l_affected_service_line_rec.header_id,
673                        l_affected_service_line_rec.line_id, x_org_id => l_org_id);
674                 END LOOP;
675             END LOOP;
676         END IF;
677     END IF;
678     --+
679     -- Have any Order Lines been Inserted?
680     -- Or has a relevant Line field been Updated?
681     --+
682     IF NOT l_order_changed THEN
683         cn_message_pkg.debug('notify: adjust: Line Insert/Update? - Line_Tbl');
684         fnd_file.put_line(fnd_file.Log, 'notify: adjust: Line Insert/Update? - Line_Tbl');
685 
686         -- Loop thru the 'new' table
687         <<new_line_tbl_loop>>
688         FOR i IN NVL(p_line_tbl.FIRST,1)..NVL(p_line_tbl.LAST,0) LOOP
689             cn_message_pkg.debug('notify: adjust: .  lid = '||p_line_tbl(i).line_id||' operation = '|| Nvl(p_line_tbl(i).operation,'NULL'));
690             fnd_file.put_line(fnd_file.Log, 'notify: adjust: .  lid = '||p_line_tbl(i).line_id||' operation = '|| Nvl(p_line_tbl(i).operation,'NULL'));
691             --+
692             -- If operation CREATE, add notification for the line
693             --+
694             IF p_line_tbl(i).operation = 'CREATE' THEN
695                 cn_notify_orders.notify_line
696                       (p_line_tbl(i).header_id,
697                        p_line_tbl(i).line_id, x_org_id => l_org_id);
698             --+
699             -- If we find an UPDATE, and any significant field has changed,
700             -- add notification for the line
701             --+
702             ELSIF p_line_tbl(i).operation = 'UPDATE' THEN
703                 --+
704                 -- Locate the Before Image of the line
705                 --+
706                 l_found := FALSE;
707                 <<old_tbl_loop>>
708                 FOR k IN NVL(p_old_line_tbl.FIRST,1)..NVL(p_old_line_tbl.LAST,0) LOOP
709                     IF p_old_line_tbl(k).line_id = p_line_tbl(i).line_id THEN
710                         l_found := TRUE;
711                         l_idx := k;  --need to remember the index of the record
712                         EXIT old_tbl_loop;
713                     END IF;
714                 END LOOP old_tbl_loop;
715                 --+
716                 -- If there is no Before Image it is a fatal error
717                 --+
718                 IF NOT l_found THEN
719                     RAISE FND_API.G_EXC_UNEXPECTED_ERROR;
720                 END IF;
721                 --+
722                 -- Compare the significant fields, checking for changes
723                 --+
724                 IF unequal(p_line_tbl(i).sold_to_org_id , p_old_line_tbl(l_idx).sold_to_org_id) OR
725                    unequal(p_line_tbl(i).unit_selling_price , p_old_line_tbl(l_idx).unit_selling_price) OR
726                    unequal(p_line_tbl(i).unit_list_price , p_old_line_tbl(l_idx).unit_list_price) OR
727                    unequal(p_line_tbl(i).inventory_item_id , p_old_line_tbl(l_idx).inventory_item_id) OR
728                    unequal(p_line_tbl(i).header_id , p_old_line_tbl(l_idx).header_id) OR
729                    unequal(p_line_tbl(i).top_model_line_id , p_old_line_tbl(l_idx).top_model_line_id) OR
730                    unequal(p_line_tbl(i).service_reference_line_id , p_old_line_tbl(l_idx).service_reference_line_id) OR
731                    unequal(p_line_tbl(i).ordered_quantity , p_old_line_tbl(l_idx).ordered_quantity) OR
732                    unequal(p_line_tbl(i).ship_to_contact_id , p_old_line_tbl(l_idx).ship_to_contact_id) OR
733                    unequal(p_line_tbl(i).line_category_code , p_old_line_tbl(l_idx).line_category_code) OR
734                    (p_line_tbl(i).operation='UPDATE' AND p_old_line_tbl(l_idx).operation ='CREATE') -- Added for Main Line Placeholder Bug 4665116
735                 THEN
736                     cn_message_pkg.debug('notify: adjust: .  update of interest');
737                     fnd_file.put_line(fnd_file.Log, 'notify: adjust: .  update of interest');
738                     cn_notify_orders.notify_line
739                           (p_header_id,  --p_line_tbl(i).header_id
740                            p_line_tbl(i).line_id,x_org_id => l_org_id);
741                 END IF;
742             END IF;
743         END LOOP new_line_tbl_loop;
744     END IF;
745     --+
746     -- Have any Header Sales Credits been Deleted?
747     --+
748     IF NOT l_order_changed THEN
749         cn_message_pkg.debug('notify: adjust: Header Sales Credit Deletion? - Header_Scredit_Tbl');
750         fnd_file.put_line(fnd_file.Log, 'notify: adjust: Header Sales Credit Deletion? - Header_Scredit_Tbl');
751         FOR i IN NVL(p_header_scredit_tbl.FIRST,1)..NVL(p_header_scredit_tbl.LAST,0) LOOP
752             cn_message_pkg.debug('notify: adjust: .  scid = '||p_header_scredit_tbl(i).sales_credit_id|| ' operation = '|| Nvl(p_header_scredit_tbl(i).operation,'NULL'));
753             fnd_file.put_line(fnd_file.Log, 'notify: adjust: .  scid = '||p_header_scredit_tbl(i).sales_credit_id|| ' operation = '|| Nvl(p_header_scredit_tbl(i).operation,'NULL'));
754             IF p_header_scredit_tbl(i).operation = 'DELETE' THEN
755                 cn_notify_orders.notify_affected_lines
756                       (p_old_header_scredit_tbl(i).header_id,
757                        p_old_header_scredit_tbl(i).line_id, p_org_id => l_org_id);  -- this should be NULL
758             END IF;
759         END LOOP;
760     END IF;
761     --+
762     -- Have any Header Sales Credits been Inserted?
763     -- Or has a relevant Sales Credit field been Updated?
764     --+
765     IF NOT l_order_changed THEN
766         cn_message_pkg.debug('notify: adjust: Header Sales Credit Insert/Update? - Header_Scredit_Tbl');
767         fnd_file.put_line(fnd_file.Log, 'notify: adjust: Header Sales Credit Insert/Update? - Header_Scredit_Tbl');
768         -- Loop thru the 'new' table
769         <<new_hsc_tbl_loop>>
770         FOR i IN NVL(p_header_scredit_tbl.FIRST,1)..NVL(p_header_scredit_tbl.LAST,0) LOOP
771             cn_message_pkg.debug('notify: adjust: .  scid = '||p_header_scredit_tbl(i).sales_credit_id|| ' operation = '||Nvl(p_header_scredit_tbl(i).operation,'NULL'));
772             fnd_file.put_line(fnd_file.Log, 'notify: adjust: .  scid = '||p_header_scredit_tbl(i).sales_credit_id|| ' operation = '||Nvl(p_header_scredit_tbl(i).operation,'NULL'));
773             --+
774             -- If we find an INSERT, flag the order changed and quit loop
775             --+
776             IF p_header_scredit_tbl(i).operation = 'CREATE' THEN
777                 cn_notify_orders.notify_affected_lines
778                       (p_header_scredit_tbl(i).header_id,
779                        p_header_scredit_tbl(i).line_id,p_org_id => l_org_id);  -- this should be NULL
780             --+
781             -- If we find an UPDATE, and any significant field has changed,
782             -- flag the order changed and quit loop
783             --+
784             ELSIF p_header_scredit_tbl(i).operation = 'UPDATE' THEN
785                 --+
786                 -- Locate the Before Image of the header_scredit
787                 --+
788                 l_found := FALSE;
789                 <<old_tbl_loop>>
790                 FOR k IN NVL(p_old_header_scredit_tbl.FIRST,1)..NVL(p_old_header_scredit_tbl.LAST,0) LOOP
791                     IF p_old_header_scredit_tbl(k).sales_credit_id = p_header_scredit_tbl(i).sales_credit_id THEN
792                         l_found := TRUE;
793                         l_idx := k;  --need to remember the index of the record
794                         EXIT old_tbl_loop;
795                     END IF;
796                 END LOOP old_tbl_loop;
797                 --+
798                 -- If there is no Before Image it is a fatal error
799                 --+
800                 IF NOT l_found THEN
801                     RAISE FND_API.G_EXC_UNEXPECTED_ERROR;
802                 END IF;
803                 --+
804                 -- Compare the significant fields, checking for changes
805                 --+
806                 IF unequal(p_header_scredit_tbl(i).header_id , p_old_header_scredit_tbl(l_idx).header_id) OR
807                    unequal(p_header_scredit_tbl(i).line_id , p_old_header_scredit_tbl(l_idx).line_id) OR
808                    unequal(p_header_scredit_tbl(i).salesrep_id , p_old_header_scredit_tbl(l_idx).salesrep_id) OR
809                    unequal(p_header_scredit_tbl(i).percent , p_old_header_scredit_tbl(l_idx).percent)
810                 THEN
811                     cn_message_pkg.debug('notify: adjust: .  update of interest');
812                     fnd_file.put_line(fnd_file.Log, 'notify: adjust: .  update of interest');
813                     cn_notify_orders.notify_affected_lines
814                           (p_header_scredit_tbl(i).header_id,
815                            p_header_scredit_tbl(i).line_id,p_org_id => l_org_id);  -- this should be NULL
816                 END IF;
817             END IF;
818         END LOOP new_hsc_tbl_loop;
819     END IF;
820     --+
821     -- Have any Line Sales Credits been Deleted?
822     --+
823     IF NOT l_order_changed THEN
824         cn_message_pkg.debug('notify: adjust: Line Sales Credit Deletion? - Line_Scredit_Tbl');
825         fnd_file.put_line(fnd_file.Log, 'notify: adjust: Line Sales Credit Deletion? - Line_Scredit_Tbl');
826         FOR i IN NVL(p_line_scredit_tbl.FIRST,1)..NVL(p_line_scredit_tbl.LAST,0) LOOP
827             cn_message_pkg.debug('notify: adjust: .  scid = '||p_line_scredit_tbl(i).sales_credit_id||' operation = '||Nvl(p_line_scredit_tbl(i).operation,'NULL'));
828             fnd_file.put_line(fnd_file.Log, 'notify: adjust: .  scid = '||p_line_scredit_tbl(i).sales_credit_id||' operation = '||Nvl(p_line_scredit_tbl(i).operation,'NULL'));
829             IF p_line_scredit_tbl(i).operation = 'DELETE' THEN
830                 cn_notify_orders.notify_affected_lines
831                       (p_old_line_scredit_tbl(i).header_id,
832                        p_old_line_scredit_tbl(i).line_id,p_org_id => l_org_id);
833             END IF;
834         END LOOP;
835     END IF;
836     --+
837     -- Have any Line Sales Credits been Inserted?
838     -- Or has a relevant Sales Credit field been Updated?
839     --+
840     IF NOT l_order_changed THEN
841         cn_message_pkg.debug('notify: adjust: Line Sales Credit Insert/Update? - Line_Scredit_Tbl');
842         fnd_file.put_line(fnd_file.Log, 'notify: adjust: Line Sales Credit Insert/Update? - Line_Scredit_Tbl');
843         -- Loop thru the 'new' table
844         <<new_lsc_tbl_loop>>
845         FOR i IN NVL(p_line_scredit_tbl.FIRST,1)..NVL(p_line_scredit_tbl.LAST,0) LOOP
846             cn_message_pkg.debug('notify: adjust: .  scid = '||p_line_scredit_tbl(i).sales_credit_id||' operation = '||Nvl(p_line_scredit_tbl(i).operation,'NULL'));
847             fnd_file.put_line(fnd_file.Log, 'notify: adjust: .  scid = '||p_line_scredit_tbl(i).sales_credit_id||' operation = '||Nvl(p_line_scredit_tbl(i).operation,'NULL'));
848             --+
849             -- If we find an INSERT, flag the order changed and quit loop
850             --+
851             IF p_line_scredit_tbl(i).operation = 'CREATE' THEN
852                 cn_notify_orders.notify_affected_lines
853                       (p_line_scredit_tbl(i).header_id,
854                        p_line_scredit_tbl(i).line_id,p_org_id => l_org_id);
855             --+
856             -- If we find an UPDATE, and any significant field has changed,
857             -- flag the order changed and quit loop
858             --+
859             ELSIF p_line_scredit_tbl(i).operation = 'UPDATE' THEN
860                 --+
861                 -- Locate the Before Image of the line_scredit
862                 --+
863                 l_found := FALSE;
864                 <<old_tbl_loop>>
865                 FOR k IN NVL(p_old_line_scredit_tbl.FIRST,1)..NVL(p_old_line_scredit_tbl.LAST,0) LOOP
866                     IF p_old_line_scredit_tbl(k).sales_credit_id = p_line_scredit_tbl(i).sales_credit_id THEN
867                         l_found := TRUE;
868                         l_idx := k;  --need to remember the index of the record
869                         EXIT old_tbl_loop;
870                     END IF;
871                 END LOOP old_tbl_loop;
872                 --+
873                 -- If there is no Before Image it is a fatal error
874                 --+
875                 IF NOT l_found THEN
876                     RAISE FND_API.G_EXC_UNEXPECTED_ERROR;
877                 END IF;
878                 --+
879                 -- Compare the significant fields, checking for changes
880                 --+
881                 IF unequal(p_line_scredit_tbl(i).header_id , p_old_line_scredit_tbl(l_idx).header_id) OR
882                    unequal(p_line_scredit_tbl(i).line_id , p_old_line_scredit_tbl(l_idx).line_id) OR
883                    unequal(p_line_scredit_tbl(i).salesrep_id , p_old_line_scredit_tbl(l_idx).salesrep_id) OR
884                    unequal(p_line_scredit_tbl(i).percent , p_old_line_scredit_tbl(l_idx).percent)
885                 THEN
886                     cn_message_pkg.debug('notify: adjust: .  update of interest');
887                     fnd_file.put_line(fnd_file.Log, 'notify: adjust: .  update of interest');
888                     cn_notify_orders.notify_affected_lines
889                           (p_line_scredit_tbl(i).header_id,
890                            p_line_scredit_tbl(i).line_id,p_org_id => l_org_id);
891                 END IF;
892             END IF;
893         END LOOP new_lsc_tbl_loop;
894     END IF;
895     cn_message_pkg.debug('notify: Exit from adjust_order (hid = '||p_header_id||') ');
896     fnd_file.put_line(fnd_file.Log, 'notify: Exit from adjust_order (hid = '||p_header_id||') ');
897 
898     cn_message_pkg.end_batch(l_process_audit_id);
899     -------------------+
900     -- End of API body.
901     -------------------+
902     -- Standard check of p_commit.
903     IF FND_API.To_Boolean( p_commit ) THEN
904         COMMIT WORK;
905     END IF;
906     -- Standard call to get message count and if count is 1, get message info.
907     FND_MSG_PUB.Count_And_Get
908                         (p_count   =>  x_msg_count ,
909                          p_data    =>  x_msg_data  ,
910                          p_encoded => FND_API.G_FALSE);
911 EXCEPTION
912    WHEN FND_API.G_EXC_ERROR THEN
913       cn_message_pkg.end_batch(l_process_audit_id);
914       ROLLBACK TO Update_Headers;
915       x_return_status := FND_API.G_RET_STS_ERROR ;
916       FND_MSG_PUB.Count_And_Get
917 	(p_count   => x_msg_count,
918 	 p_data    => x_msg_data,
919 	 p_encoded => FND_API.G_FALSE);
920 
921    WHEN FND_API.G_EXC_UNEXPECTED_ERROR THEN
922       cn_message_pkg.end_batch(l_process_audit_id);
923       ROLLBACK TO Update_Headers;
924       x_return_status := FND_API.G_RET_STS_UNEXP_ERROR ;
925       FND_MSG_PUB.Count_And_Get
926 	(p_count   => x_msg_count,
927 	 p_data    => x_msg_data,
928 	 p_encoded => FND_API.G_FALSE);
929 
930    WHEN OTHERS THEN
931       cn_message_pkg.end_batch(l_process_audit_id);
932       ROLLBACK TO Update_Headers;
933       x_return_status := FND_API.G_RET_STS_UNEXP_ERROR ;
934       IF FND_MSG_PUB.Check_Msg_Level
935 	(FND_MSG_PUB.G_MSG_LVL_UNEXP_ERROR) THEN
936 	 FND_MSG_PUB.Add_Exc_Msg
937 	   (G_PKG_NAME,
938 	    l_api_name );
939       END IF;
940       FND_MSG_PUB.Count_And_Get
941 	(p_count   => x_msg_count,
942 	 p_data    => x_msg_data,
943 	 p_encoded => FND_API.G_FALSE);
944 END Adjust_Order;
945 
946 
947 --*********************************************
948 -- Public Procedures
949 --*********************************************
950 ------------------------------------------------------------------------------+
951 -- Procedure Name
952 --   Get_Notice_Conc
953 -- Purpose
954 --   Concurrent Program "Order Update Notification" wrapper
955 --   on top of Get_Notice
956 ------------------------------------------------------------------------------+
957 PROCEDURE Get_notice_conc
958   (x_errbuf               OUT NOCOPY VARCHAR2,
959    x_retcode              OUT NOCOPY NUMBER,
960    p_org_id IN  NUMBER )
961   IS
962 
963 BEGIN
964 
965    get_notice(p_parent_proc_audit_id => NULL, x_org_id => p_org_id );
966 
967 END get_notice_conc;
968 ------------------------------------------------------------------------------+
969 -- Procedure Name
970 --   Get_Notice
971 -- Purpose
972 --   This procedure collects order updates from the Order Capture Notification
973 --   API.  It is a loop which
974 --   gets the latest notification off of the queue. If the order is Booked,
975 --   this procedure initiates processing of the adjustments to the
976 --   order for OSC.
977 --
978 -- History
979 --   11-15-99  D.Maskell Created
980 ------------------------------------------------------------------------------+
981 PROCEDURE Get_notice
982   (
983    p_parent_proc_audit_id IN  NUMBER,
984    x_org_id IN NUMBER)
985  IS
986     l_return_status             VARCHAR2(2000);
987     l_process_audit_id          NUMBER;
988     l_msg_count                 NUMBER;
989     l_msg_data                  VARCHAR2(2000);
990     l_no_more_messages          VARCHAR2(2000);
991     l_header_id                 NUMBER;
992     l_booked_flag               VARCHAR2(1);
993     l_header_rec                OE_Order_PUB.Header_Rec_Type;
994     l_old_header_rec            OE_Order_PUB.Header_Rec_Type;
995     l_Header_Adj_tbl            OE_Order_PUB.Header_Adj_Tbl_Type;
996     l_old_Header_Adj_tbl        OE_Order_PUB.Header_Adj_Tbl_Type;
997     l_Header_price_Att_tbl      OE_Order_PUB.Header_Price_Att_Tbl_Type;
998     l_old_Header_Price_Att_tbl  OE_Order_PUB.Header_Price_Att_Tbl_Type;
999     l_Header_Adj_Att_tbl        OE_Order_PUB.Header_Adj_Att_Tbl_Type;
1000     l_old_Header_Adj_Att_tbl    OE_Order_PUB.Header_Adj_Att_Tbl_Type;
1001     l_Header_Adj_Assoc_tbl      OE_Order_PUB.Header_Adj_Assoc_Tbl_Type;
1002     l_old_Header_Adj_Assoc_tbl  OE_Order_PUB.Header_Adj_Assoc_Tbl_Type;
1003     l_Header_Scredit_tbl        OE_Order_PUB.Header_Scredit_Tbl_Type;
1004     l_old_Header_Scredit_tbl    OE_Order_PUB.Header_Scredit_Tbl_Type;
1005     l_line_tbl                  OE_Order_PUB.Line_Tbl_Type;
1006     l_old_line_tbl              OE_Order_PUB.Line_Tbl_Type;
1007     l_Line_Adj_tbl              OE_Order_PUB.Line_Adj_Tbl_Type;
1008     l_old_Line_Adj_tbl          OE_Order_PUB.Line_Adj_Tbl_Type;
1009     l_Line_Price_Att_tbl        OE_Order_PUB.Line_Price_Att_Tbl_Type;
1010     l_old_Line_Price_Att_tbl    OE_Order_PUB.Line_Price_Att_Tbl_Type;
1011     l_Line_Adj_Att_tbl          OE_Order_PUB.Line_Adj_Att_Tbl_Type;
1012     l_old_Line_Adj_Att_tbl      OE_Order_PUB.Line_Adj_Att_Tbl_Type;
1013     l_Line_Adj_Assoc_tbl        OE_Order_PUB.Line_Adj_Assoc_Tbl_Type;
1014     l_old_Line_Adj_Assoc_tbl    OE_Order_PUB.Line_Adj_Assoc_Tbl_Type;
1015     l_Line_Scredit_tbl          OE_Order_PUB.Line_Scredit_Tbl_Type;
1016     l_old_Line_Scredit_tbl      OE_Order_PUB.Line_Scredit_Tbl_Type;
1017     l_Lot_Serial_tbl            OE_Order_PUB.Lot_Serial_Tbl_Type;
1018     l_old_Lot_Serial_tbl        OE_Order_PUB.Lot_Serial_Tbl_Type;
1019     l_action_request_tbl        OE_Order_PUB.Request_Tbl_Type;
1020 
1021     CURSOR c_booked_flag (cp_hid NUMBER) IS
1022       SELECT booked_flag
1023       FROM aso_i_oe_order_lines_v
1024 	WHERE header_id = cp_hid
1025 	AND org_id = x_org_id; -- R12 MOAC Change
1026 
1027 	l_org_id NUMBER;
1028 
1029 BEGIN
1030    -- Standard Start of process savepoint
1031    SAVEPOINT	Update_Headers_Savepoint;
1032 
1033    l_org_id := x_org_id;
1034 
1035     --+
1036     -- Start looping to check for messages in the queue
1037     --+
1038     LOOP
1039         -- Queue savepoint for standard advanced queue error handling
1040         SAVEPOINT	Get_Notice_Loop_Savepoint;
1041         --+
1042         -- Invoke Get_Notice to dequeue queue payload and return Order data
1043         --+
1044         aso_order_feedback_pub.Get_Notice
1045               (p_api_version               => 1.0,
1046                x_return_status             => l_return_status,
1047                x_msg_count                 => l_msg_count,
1048                x_msg_data                  => l_msg_data,
1049                p_app_short_name            => 'CN',
1050                x_no_more_messages          => l_no_more_messages,
1051                x_header_rec                => l_header_rec,
1052                x_old_header_rec            => l_old_header_rec,
1053                x_Header_Adj_tbl            => l_header_adj_tbl,
1054                x_old_Header_Adj_tbl        => l_old_header_adj_tbl,
1055                x_Header_price_Att_tbl      => l_header_price_att_tbl,
1056                x_old_Header_Price_Att_tbl  => l_old_header_price_att_tbl,
1057                x_Header_Adj_Att_tbl        => l_header_adj_att_tbl,
1058                x_old_Header_Adj_Att_tbl    => l_old_header_adj_att_tbl,
1059                x_Header_Adj_Assoc_tbl      => l_header_adj_assoc_tbl,
1060                x_old_Header_Adj_Assoc_tbl  => l_old_header_adj_assoc_tbl,
1061                x_Header_Scredit_tbl        => l_header_scredit_tbl,
1062                x_old_Header_Scredit_tbl    => l_old_header_scredit_tbl,
1063                x_line_tbl                  => l_line_tbl,
1064                x_old_line_tbl              => l_old_line_tbl,
1065                x_Line_Adj_tbl              => l_line_adj_tbl,
1066                x_old_Line_Adj_tbl          => l_old_line_adj_tbl,
1067                x_Line_Price_Att_tbl        => l_line_price_att_tbl,
1068                x_old_Line_Price_Att_tbl    => l_old_line_price_att_tbl,
1069                x_Line_Adj_Att_tbl          => l_line_adj_att_tbl,
1070                x_old_Line_Adj_Att_tbl      => l_old_line_adj_att_tbl,
1071                x_Line_Adj_Assoc_tbl        => l_line_adj_assoc_tbl,
1072                x_old_Line_Adj_Assoc_tbl    => l_old_line_adj_assoc_tbl,
1073                x_Line_Scredit_tbl          => l_line_scredit_tbl,
1074                x_old_Line_Scredit_tbl      => l_old_line_scredit_tbl,
1075                x_Lot_Serial_tbl            => l_lot_serial_tbl,
1076                x_old_Lot_Serial_tbl        => l_old_lot_serial_tbl,
1077                x_action_request_tbl        => l_action_request_tbl
1078                );
1079         -- +
1080         -- Check return status
1081         --+
1082         IF NOT (l_return_status = FND_API.G_RET_STS_SUCCESS) THEN
1083 	    -- This rollback causes an error message sometimes and is anyway not
1084 	    --  necessary (no changes since COMMIT at end of loop
1085 	    --            ROLLBACK TO Update_Headers_Savepoint;
1086 
1087 	    --  hithanki:23-04-03:Changes for Enhancement#2778521:Start
1088         --  Enqueue the failed message into the Order Feedback Exception Queue
1089         fnd_file.put_line(fnd_file.Log, 'l_return_status = FND_API.G_RET_STS_SUCCESS.');
1090 
1091            aso_order_feedback_pub.handle_exception(
1092 	               p_api_version 			=> 1.0
1093 	              ,p_init_msg_list 			=> fnd_api.g_false
1094 	              ,p_commit 			=> fnd_api.g_false
1095 	              ,x_return_status 			=> l_return_status
1096 	              ,x_msg_count 			=> l_msg_count
1097 	              ,x_msg_data 			=> l_msg_data
1098 	              ,p_app_short_name 		=> 'CN'
1099 	              ,p_header_rec 			=> l_header_rec
1100 	              ,p_old_header_rec 		=> l_old_header_rec
1101 	              ,p_header_adj_tbl 		=> l_header_adj_tbl
1102 	              ,p_old_header_adj_tbl 		=> l_old_header_adj_tbl
1103 	              ,p_header_price_att_tbl 		=> l_header_price_att_tbl
1104 	              ,p_old_header_price_att_tbl 	=> l_old_header_price_att_tbl
1105 	              ,p_header_adj_att_tbl 		=> l_header_adj_att_tbl
1106 	              ,p_old_header_adj_att_tbl 	=> l_old_header_adj_att_tbl
1107 	              ,p_header_adj_assoc_tbl 		=> l_header_adj_assoc_tbl
1108 	              ,p_old_header_adj_assoc_tbl 	=> l_old_header_adj_assoc_tbl
1109 	              ,p_header_scredit_tbl 		=> l_header_scredit_tbl
1110 	              ,p_old_header_scredit_tbl 	=> l_old_header_scredit_tbl
1111 	              ,p_line_tbl 			=> l_line_tbl
1112 	              ,p_old_line_tbl 			=> l_old_line_tbl
1113 	              ,p_line_adj_tbl 			=> l_line_adj_tbl
1114 	              ,p_old_line_adj_tbl 		=> l_old_line_adj_tbl
1115 	              ,p_line_price_att_tbl 		=> l_line_price_att_tbl
1116 	              ,p_old_line_price_att_tbl 	=> l_old_line_price_att_tbl
1117 	              ,p_line_adj_att_tbl 		=> l_line_adj_att_tbl
1118 	              ,p_old_line_adj_att_tbl 		=> l_old_line_adj_att_tbl
1119 	              ,p_line_adj_assoc_tbl 		=> l_line_adj_assoc_tbl
1120 	              ,p_old_line_adj_assoc_tbl 	=> l_old_line_adj_assoc_tbl
1121 	              ,p_line_scredit_tbl 		=> l_line_scredit_tbl
1122 	              ,p_old_line_scredit_tbl 		=> l_old_line_scredit_tbl
1123 	              ,p_lot_serial_tbl 		=> l_lot_serial_tbl
1124 	              ,p_old_lot_serial_tbl 		=> l_old_lot_serial_tbl
1125            	      ,p_action_request_tbl 		=> l_action_request_tbl);
1126 
1127            -- Quit the procedure IF the queue is empty
1128 
1129            EXIT WHEN l_no_more_messages = FND_API.G_TRUE;
1130 
1131            IF l_return_status = fnd_api.g_ret_sts_success THEN
1132               COMMIT;
1133            END IF;
1134 
1135            --  hithanki:23-04-03:Changes for Enhancement#2778521:Done
1136 
1137 	   --+
1138 	   -- Create a debug log file and dump out the error message list
1139 	   --+
1140 	   IF (p_parent_proc_audit_id IS NOT NULL) THEN
1141 	      cn_message_pkg.end_batch (p_parent_proc_audit_id);
1142 	   END IF;
1143 	   cn_message_pkg.begin_batch
1144 	     (x_parent_proc_audit_id => p_parent_proc_audit_id,
1145 	      x_process_audit_id     => l_process_audit_id,
1146 	      x_request_id           => fnd_global.conc_request_id,
1147 	      x_process_type         => 'ORD',
1148 		  p_org_id => x_org_id);
1149 
1150 	   cn_message_pkg.debug('<<CN_NOTIFY_ORDERS.Get_Notice exited - error message list>>');
1151 	   fnd_file.put_line(fnd_file.Log, '<<CN_NOTIFY_ORDERS.Get_Notice exited - error message list>>');
1152 
1153 	   cn_api.get_fnd_message(NULL,NULL);
1154 	   cn_message_pkg.end_batch (l_process_audit_id);
1155 
1156 	   RETURN;
1157 
1158         END IF;
1159         --+
1160         -- Get the Booked_Flag for the order. Unfortunately, we have no idea
1161 
1162         -- which entities of the order will have data in them. We therefore
1163         -- either get the Booked_Flag direct from our Header entity , or if
1164         -- that's empty, get Header_Id from another entity and then use that to
1165         -- to call Get_Booked_Status, which will query the current Header in
1166         -- the database. The proper solution would be for the OM/OC data
1167         -- structure to include a "curr_header_rec" entity which is
1168         -- always populated.
1169         --+
1170 
1171         l_booked_flag := 'N';
1172         IF  l_header_rec.header_id <> FND_API.G_MISS_NUM THEN
1173             fnd_file.put_line(fnd_file.Log, 'l_header_rec.header_id <> FND_API.G_MISS_NUM'||l_header_rec.header_id);
1174             l_booked_flag := l_header_rec.booked_flag;
1175             l_header_id := l_header_rec.header_id;
1176         ELSE
1177             l_header_id := FND_API.G_MISS_NUM;
1178             fnd_file.put_line(fnd_file.Log, 'l_header_rec.header_id == FND_API.G_MISS_NUM'||l_header_rec.header_id);
1179             IF l_line_tbl.COUNT >0 THEN
1180                 l_header_id := l_line_tbl(l_line_tbl.FIRST).header_id;
1181             ELSIF l_old_line_tbl.COUNT >0 THEN
1182                 l_header_id := l_old_line_tbl(l_old_line_tbl.FIRST).header_id;
1183             ELSIF l_line_scredit_tbl.COUNT >0 THEN
1184                 l_header_id := l_line_scredit_tbl(l_line_scredit_tbl.FIRST).header_id;
1185             ELSIF l_old_line_scredit_tbl.COUNT >0 THEN
1186                 l_header_id := l_old_line_scredit_tbl(l_old_line_scredit_tbl.FIRST).header_id;
1187             ELSIF l_header_scredit_tbl.COUNT >0 THEN
1188                 l_header_id := l_header_scredit_tbl(l_header_scredit_tbl.FIRST).header_id;
1189             ELSIF l_old_header_scredit_tbl.COUNT >0 THEN
1190                 l_header_id := l_old_header_scredit_tbl(l_old_header_scredit_tbl.FIRST).header_id;
1191             END IF;
1192             IF l_header_id <> FND_API.G_MISS_NUM THEN
1193                 OPEN c_booked_flag(l_header_id);
1194                 FETCH c_booked_flag INTO l_booked_flag;
1195                 CLOSE c_booked_flag;
1196             END IF;
1197         END IF;
1198  --dbms_output.put_line('Get_Notice - processing header_id '||NVL(TO_CHAR(l_header_id),'null')||' Booked = '||l_booked_flag);
1199         --+
1200         -- If the order is booked, call Update_Headers to process my structure
1201         --+
1202         fnd_file.put_line(fnd_file.Log, 'Booked Flag value...'||l_booked_flag);
1203         fnd_file.put_line(fnd_file.Log, 'l_line_tbl.header_id...'||l_line_tbl.COUNT);
1204         fnd_file.put_line(fnd_file.Log, 'l_old_line_tbl.header_id...'||l_old_line_tbl.COUNT);
1205         fnd_file.put_line(fnd_file.Log, 'l_line_scredit_tbl.header_id...'||l_line_scredit_tbl.COUNT);
1206         fnd_file.put_line(fnd_file.Log, 'l_old_line_scredit_tbl.header_id...'||l_old_line_scredit_tbl.COUNT);
1207         fnd_file.put_line(fnd_file.Log, 'l_header_scredit_tbl.header_id...'||l_header_scredit_tbl.COUNT);
1208         fnd_file.put_line(fnd_file.Log, 'l_old_header_scredit_tbl.header_id...'||l_old_header_scredit_tbl.COUNT);
1209 
1210         IF l_booked_flag = 'Y' THEN
1211             Adjust_Order
1212                 (p_api_version		  => 1.0,
1213                  x_return_status	  => l_return_status,
1214                  x_msg_count		  => l_msg_count,
1215                  x_msg_data		  => l_msg_data,
1216                  p_header_id		  => l_header_id,
1217                  p_header_rec		  => l_header_rec,
1218                  p_old_header_rec	  => l_old_header_rec,
1219                  p_line_tbl		  => l_line_tbl,
1220                  p_old_line_tbl		  => l_old_line_tbl,
1221                  p_line_scredit_tbl	  => l_line_scredit_tbl,
1222                  p_old_line_scredit_tbl	  => l_old_line_scredit_tbl,
1223                  p_header_scredit_tbl	  => l_header_scredit_tbl,
1224                  p_old_header_scredit_tbl => l_old_header_scredit_tbl,
1225 		 p_parent_proc_audit_id   => p_parent_proc_audit_id,
1226 		 x_org_id => l_org_id );
1227             --+
1228             -- Check return status of functional process, rollback to undo processing
1229             -- and increment retry_count of queue
1230             --+
1231             IF NOT (l_return_status = FND_API.G_RET_STS_SUCCESS) THEN
1232                 ROLLBACK TO Get_Notice_Loop_Savepoint;
1233             END IF;
1234             COMMIT;
1235         END IF;
1236         --+
1237         -- Quit the procedure if the queue is empty
1238         --+
1239         IF l_no_more_messages = 'T' THEN
1240 	   RETURN;
1241         END IF;
1242     END LOOP;
1243 
1244 END Get_Notice;
1245 
1246 
1247 ------------------------------------------------------------------------+
1248 -- Procedure Name
1249 --   regular_col_notify
1250 -- Purpose
1251 --   This procedure collects order line identifiers into cn_not_trx
1252 --   as part of the collection process for new orders.
1253 --
1254 --   It is called from CN_COLLECT_ORDERS and is passed a
1255 --   start-period-id and end-period-id.
1256 --
1257 --   Note. The ASO views contain Org_Ids but ARE NOT ORG-PARTITIONED.
1258 --   The purpose of this procedure is to collect new orders for the
1259 --   current Org only, so we have to add an Org filter to the WHERE
1260 --   clause of the query.
1261 --   This is why there is a line in the WHERE clause to restrict
1262 --   the selection from ASO_I_OE_ORDER_HEADERS_V to only the
1263 --   current Org_Id. We only need to do this on the ...HEADERS_V
1264 --   view, because we then join from ...HEADERS_V to ...LINES_V using
1265 --   ASO_I_OE_ORDER_HEADERS_V.Header_Id, which is Primary Key.
1266 
1267 
1268 -- History
1269 --   04-16-98	J.Cheng    Created
1270 --   11-01-99	D.Maskell	 Interface to Order Capture instead
1271 --                        of Order Entry tables
1272 --   12-08-99	D.Maskell	 New processing because ASO views are
1273 --                        no longer org-partitioned.
1274 --   12-24-99  D.Maskell  Call Get_Notice to get any pending
1275 --                        order updates off of the queue
1276 
1277 PROCEDURE regular_col_notify
1278   (
1279    x_start_period	 cn_periods.period_id%TYPE,
1280    x_end_period	         cn_periods.period_id%TYPE,
1281    x_adj_flag	         VARCHAR2,
1282    parent_proc_audit_id  NUMBER,
1283    debug_pipe	         VARCHAR2 DEFAULT NULL,
1284    debug_level	         NUMBER	  DEFAULT NULL,
1285    x_org_id 			 NUMBER ) -- R12 MOAC Changes
1286      IS
1287     l_retcode       NUMBER;
1288     l_errbuf        VARCHAR2(2000);
1289     l_trx_count 	NUMBER;
1290     l_proc_audit_id	NUMBER;
1291     l_start_date	DATE;
1292     l_end_date		DATE;
1293     l_rowid		ROWID;
1294     --+
1295     -- Because this procedure is only looking at orders for
1296     -- the client org_id, we can get the right inventory
1297     -- organization for that org by a simple call to oe_profile.value
1298     --+
1299     l_so_org_id 	NUMBER;
1300     l_sys_batch_size NUMBER;
1301     l_client_org_id NUMBER;
1302 
1303     CURSOR batch_size IS SELECT system_batch_size FROM cn_repositories WHERE org_id = x_org_id;
1304 
1305   BEGIN
1306     IF (debug_pipe IS NOT NULL) THEN
1307 		cn_debug.init_pipe(debug_pipe, debug_level);
1308     END IF;
1309 
1310     cn_debug.print_msg('>>cn_notify_orders.regular_col_notify', 1);
1311 
1312     cn_message_pkg.debug('notify: cn_notify_orders.regular_col_notify>>');
1313     fnd_file.put_line(fnd_file.Log, 'notify: cn_notify_orders.regular_col_notify>>');
1314 
1315     --Added as per OM MOAC Mandate
1316     MO_GLOBAL.SET_POLICY_CONTEXT ('S', x_org_id);
1317     l_so_org_id := NVL(oe_profile.value('OE_ORGANIZATION_ID'),-99);
1318 
1319     --+
1320     -- Call Get_Notice to get any pending order updates off of the queue
1321     --+
1322     cn_message_pkg.debug('notify: Get_Notice>>');
1323     fnd_file.put_line(fnd_file.Log, 'notify: Get_Notice>>');
1324 
1325     cn_message_pkg.debug('notify: Getting any pending order updates off of the Order Capture Feedback Queue');
1326     fnd_file.put_line(fnd_file.Log, 'notify: Getting any pending order updates off of the Order Capture Feedback Queue');
1327 
1328 	l_client_org_id := x_org_id;
1329 
1330     Get_Notice(p_parent_proc_audit_id => parent_proc_audit_id, x_org_id => l_client_org_id);
1331 
1332     cn_message_pkg.debug('notify: Get_Notice<<');
1333     fnd_file.put_line(fnd_file.Log, 'notify: Get_Notice<<');
1334 
1335     l_proc_audit_id := NULL;	-- Gets a value in the call below
1336 
1337     cn_process_audits_pkg.insert_row
1338 	( l_rowid, l_proc_audit_id, NULL, 'NOT', 'Notification run',
1339 	  NULL, NULL, NULL, NULL, NULL, SYSDATE, NULL, x_org_id);
1340 
1341     cn_periods_api.set_dates(x_start_period, x_end_period, x_org_id,
1342 			     l_start_date, l_end_date);
1343 
1344     cn_message_pkg.debug
1345 	( 'notify: Inserting records into CN_NOT_TRX from period '
1346 	   || l_start_date ||' to period '|| l_end_date ||'.');
1347 
1348     fnd_file.put_line(fnd_file.Log, 'notify: Inserting records into CN_NOT_TRX from period '
1349 	   || l_start_date ||' to period '|| l_end_date ||'.');
1350 
1351     OPEN batch_size;
1352     FETCH batch_size INTO l_sys_batch_size;
1353     CLOSE batch_size;
1354 
1355     INSERT INTO cn_not_trx (
1356 	   not_trx_id,
1357 	   batch_id,
1358 	   notified_date,
1359 	   processed_date,
1360 	   notification_run_id,
1361 	   collected_flag,
1362 	   row_id,
1363 	   source_trx_id,
1364 	   source_trx_line_id,
1365 	   source_doc_type,
1366 	   adjusted_flag,
1367 	   event_id,
1368 	   org_id)
1369     SELECT
1370 	   cn_not_trx_s.NEXTVAL,
1371 	   FLOOR(cn_not_trx_s.CURRVAL/l_sys_batch_size),
1372 	   SYSDATE,
1373 	   asoh.booked_date,
1374 	   l_proc_audit_id,
1375 	   'N',
1376 	   asoh.rowid,
1377 	   asoh.header_id,
1378 	   asol.line_id,
1379 	   g_source_doc_type,
1380 	   x_adj_flag,
1381 	   cn_global.ord_event_id,
1382 	   l_client_org_id
1383     FROM
1384         aso_i_oe_order_headers_v asoh,
1385 	    aso_i_oe_order_lines_v asol
1386     WHERE
1387         -- Multi_org filter, see comment in procedure header
1388 	   -- NOTE: asoh.header_id is a primary key, so no need to
1389 	   -- have an org filter for the join to asol
1390 	   --+
1391         NVL(asoh.org_id,l_client_org_id) = l_client_org_id
1392         AND asol.org_id = asoh.org_id
1393         --+
1394         AND asoh.booked_flag = 'Y'              -- only interested in status of booked
1395         AND asol.header_id = asoh.header_id
1396 -- also collect 'RETURN's        AND asol.line_category_code = 'ORDER'   -- only collect 'Order' lines
1397         AND TRUNC(asoh.booked_date)
1398             BETWEEN TRUNC(nvl(l_start_date,asoh.booked_date))
1399                 AND TRUNC(nvl(l_end_date,asoh.booked_date))
1400         AND EXISTS
1401 		  (SELECT 1
1402 		  FROM mtl_system_items mtl
1403 		  WHERE NVL(mtl.organization_id,l_so_org_id) = l_so_org_id
1404                   AND mtl.inventory_item_id = asol.inventory_item_id
1405                   AND mtl.invoiceable_item_flag = 'Y')     -- only want invoiceable items
1406         AND NOT EXISTS
1407                        (SELECT 1
1408                        FROM cn_not_trx
1409                        WHERE source_trx_id = asoh.header_id
1410                              AND source_trx_line_id = asol.line_id
1411                              AND event_id= cn_global.ord_event_id
1412 							 AND org_id = l_client_org_id) ;
1413 
1414     l_trx_count := SQL%ROWCOUNT;
1415 
1416     --dbms_output.put_line(' In CN_NOTIFY_ORDERS REGULAR_COL_NOTIFY ');
1417     --dbms_output.put_line(' l_trx_count '||l_trx_count);
1418 
1419 
1420     cn_process_audits_pkg.update_row(l_proc_audit_id, NULL, SYSDATE, 0,
1421       'Finished notification run: Notified ' || l_trx_count || ' orders.');
1422 
1423     --DBMS_OUTPUT.put_line('parent_proc_audit_id '||parent_proc_audit_id);
1424 
1425     IF  ( l_trx_count = 0 ) THEN
1426 
1427       cn_message_pkg.debug('notify: No rows inserted into CN_NOT_TRX. Possible reason: Order transactions may have already been collected.');
1428       fnd_file.put_line(fnd_file.Log, 'notify: No rows inserted into CN_NOT_TRX. Possible reason: Order transactions may have already been collected.');
1429 
1430     END IF;
1431 
1432 --    COMMIT; -- Commit now done by Order Capture notification process or by CN_COLLECT_ORDERS
1433 
1434     cn_message_pkg.debug('notify: Finished notification run: Notified ' || l_trx_count || ' orders.');
1435     fnd_file.put_line(fnd_file.Log, 'notify: Finished notification run: Notified ' || l_trx_count || ' orders.');
1436 
1437     cn_debug.print_msg('cn_notify_orders.regular_col_notify<<', 1);
1438 
1439     cn_message_pkg.debug('notify: cn_notify_orders.regular_col_notify<<');
1440     fnd_file.put_line(fnd_file.Log, 'notify: cn_notify_orders.regular_col_notify<<');
1441 
1442     cn_message_pkg.end_batch (l_proc_audit_id);
1443 
1444 
1445   EXCEPTION
1446     WHEN OTHERS THEN ROLLBACK;
1447 
1448     cn_message_pkg.debug('notify_orders: in exception handler');
1449     fnd_file.put_line(fnd_file.Log, 'notify_orders: in exception handler');
1450 
1451     cn_message_pkg.debug(SQLCODE||' '||SQLERRM);
1452     fnd_file.put_line(fnd_file.Log, SQLCODE||' '||SQLERRM);
1453 
1454     cn_debug.print_msg('notify_orders: in exception handler', 1);
1455     cn_process_audits_pkg.update_row(l_proc_audit_id, NULL, SYSDATE, SQLCODE,
1456       SQLERRM);
1457     cn_message_pkg.end_batch (l_proc_audit_id);
1458 
1459     app_exception.raise_exception;
1460 
1461 
1462   END regular_col_notify;
1463 
1464 
1465 END CN_NOTIFY_ORDERS;
1466 
1467 
1468