DBA Data[Home] [Help]

PACKAGE BODY: APPS.CN_SCA_CREDITS_BATCH_PUB

Source


1 PACKAGE BODY cn_sca_credits_batch_pub AS
2   -- $Header: cnpscabb.pls 120.27 2010/10/29 06:22:47 ppillai ship $
3   -- +======================================================================+
4   -- |                Copyright (c) 1994 Oracle Corporation                 |
5   -- |                   Redwood Shores, California, USA                    |
6   -- |                        All rights reserved.                          |
7   -- +======================================================================+
8   --
9   -- Package Name
10   --   CN_SCA_CREDITS_BATCH_PUB
11   -- Purpose
12   --   Package Body to process the Sales Credit Allocations
13   --   Add the flow diagram here.
14   -- History
15     --   06/26/03   Rao.Chenna         Created
16     -- Nov 17, 2005    vensrini        Added org_id to insert into
17     --                                 CN_SCA_PROCESS_BATCHES stmt
18     --
19     --                                 Added fnd_request.set_org_id
20     --                                 call in conc_submit proc
21     --
22   g_pkg_name    CONSTANT VARCHAR2(30)                 := 'CN_SCA_CREDITS_BATCH_PUB';
23   g_file_name   CONSTANT VARCHAR2(12)                 := 'cnpscabb.pls';
24   no_trx                 EXCEPTION;
25   conc_fail              EXCEPTION;
26   api_call_failed        EXCEPTION;
27   g_cn_debug             VARCHAR2(1)                  := fnd_profile.VALUE('CN_DEBUG');
28   g_login_id             NUMBER                       := fnd_global.conc_login_id;
29   g_sysdate              DATE                         := SYSDATE;
30   g_program_id           NUMBER                       := fnd_global.conc_program_id;
31   g_user_id              NUMBER                       := fnd_global.user_id;
32   g_request_id           NUMBER                       := fnd_global.conc_request_id;
33   g_fetch_limit          NUMBER                       := 10000;
34 
35 
36   TYPE g_rowid_tbl_type IS TABLE OF ROWID;
37 
38   TYPE g_comm_lines_api_id_tbl_type IS TABLE OF cn_comm_lines_api_all.comm_lines_api_id%TYPE;
39 
40   TYPE g_trans_object_id_tbl_type IS TABLE OF jtf_tae_1001_sc_winners.trans_object_id%TYPE;
41 
42   TYPE g_terr_id_tbl_type IS TABLE OF jtf_tae_1001_sc_winners.terr_id%TYPE;
43 
44   TYPE g_salesrep_id_tbl_type IS TABLE OF cn_salesreps.salesrep_id%TYPE;
45 
46   TYPE g_emp_no_tbl_type IS TABLE OF cn_salesreps.employee_number%TYPE;
47 
48   TYPE g_role_id_tbl_type IS TABLE OF jtf_tae_1001_sc_winners.role_id%TYPE;
49 
50   TYPE g_split_pctg_tbl_type IS TABLE OF jtf_terr_rsc_all.attribute1%TYPE;
51 
52   TYPE g_rev_type_tbl_type IS TABLE OF jtf_terr_rsc_all.attribute1%TYPE;
53 
54   TYPE g_terr_name_tbl_type IS TABLE OF jtf_terr_all.NAME%TYPE;
55 
56   TYPE g_del_flag_tbl_type IS TABLE OF VARCHAR2(1);
57 
58   g_unloaded_txn_tbl     g_rowid_tbl_type;
59   g_loaded_txn_rowid_tbl g_rowid_tbl_type;
60   g_loaded_txn_comid_tbl g_comm_lines_api_id_tbl_type;
61   g_sca_insert_tbl_type  cn_sca_insert_tbl_type;
62 
63   --
64   PROCEDURE debugmsg(msg VARCHAR2) IS
65   BEGIN
66     IF g_cn_debug = 'Y' THEN
67       cn_message_pkg.DEBUG(SUBSTR(msg, 1, 254));
68       fnd_file.put_line(fnd_file.LOG, msg);
69     END IF;
70   END debugmsg;
71 
72   PROCEDURE parent_conc_wait(
73          l_child_program_id_tbl IN  OUT NOCOPY    sub_program_id_type
74        , retcode                OUT     NOCOPY    VARCHAR2
75        , errbuf                 OUT     NOCOPY    VARCHAR2
76 
77                     )
78 IS
79 
80     call_status                  BOOLEAN;
81 
82     l_req_id                     NUMBER;
83 
84     l_phase                      VARCHAR2(100);
85     l_status                     VARCHAR2(100);
86     l_dev_phase                  VARCHAR2(100);
87     l_dev_status                 VARCHAR2(100);
88     l_message                    VARCHAR2(2000);
89 
90     child_proc_fail_exception    EXCEPTION;
91 BEGIN
92      debugmsg('SCA : CN_SCATM_TAE_PUB.Parent Process starts Waiting For Child
93      Processes to complete');
94 
95      FOR l_child_program_id IN l_child_program_id_tbl.FIRST..l_child_program_id_tbl.LAST
96      LOOP
97 
98             call_status :=
99             FND_CONCURRENT.get_request_status(
100             l_child_program_id_tbl(l_child_program_id), '', '',
101  			    l_phase, l_status, l_dev_phase,
102                             l_dev_status, l_message);
103 
104            debugmsg('SCA : CN_SCATM_TAE_PUB. Request '||l_child_program_id_tbl(l_child_program_id)
105            ||' l_dev_phase '||l_dev_phase||' l_dev_status ');
106 
107            WHILE l_dev_phase <> 'COMPLETE'
108            LOOP
109 
110             call_status :=
111             FND_CONCURRENT.get_request_status(
112             l_child_program_id_tbl(l_child_program_id), '', '',
113  			    l_phase, l_status, l_dev_phase,
114                             l_dev_status, l_message);
115 
116            debugmsg('SCA : CN_SCATM_TAE_PUB. Request '||l_child_program_id_tbl(l_child_program_id)
117            ||' l_dev_phase '||l_dev_phase||' l_dev_status. Parent Process going to sleep for 10 seconds. ');
118 
119                dbms_lock.sleep(10);
120 
121            END LOOP;
122 
123 
124             IF l_dev_status = 'ERROR'
125             THEN
126                retcode := 2;
127                errbuf := l_message;
128                raise child_proc_fail_exception;
129             END IF;
130 
131      END LOOP;
132 EXCEPTION
133 WHEN child_proc_fail_exception
134 THEN
135 retcode := 2;
136 debugmsg('SCA : CN_SCATM_TAE_PUB.get_credited_txns.Child Proc Failed exception');
137 debugmsg('SCA : SQLCODE : ' || SQLCODE);
138 debugmsg('SCA : SQLERRM : ' || SQLERRM);
139 WHEN OTHERS THEN
140 debugmsg('SCA : Unexpected exception in get_credited_txns');
141 debugmsg('SCA : SQLCODE : ' || SQLCODE);
142 debugmsg('SCA : SQLERRM : ' || SQLERRM);
143 retcode  := 2;
144 errbuf   := 'CN_SCATM_TAE_PUB.get_credited_txns.others';
145 
146 END parent_conc_wait;
147 
148   --
149   PROCEDURE conc_submit(
150     x_conc_program         IN            VARCHAR2
151   , x_parent_proc_audit_id IN            NUMBER
152   , x_physical_batch_id    IN            NUMBER
153   , x_start_date           IN            DATE
154   , x_end_date             IN            DATE
155   , p_transaction_source   IN            VARCHAR2
156   , p_org_id               IN            NUMBER
157   , x_request_id           IN OUT NOCOPY NUMBER
158   ) IS
159   BEGIN
160     debugmsg('Conc_Submit : p_transaction_source = ' || p_transaction_source);
161     debugmsg('Conc_Submit : x_start_date = ' || x_start_date);
162     debugmsg('Conc_Submit : x_end_date = ' || x_end_date);
163     debugmsg('Conc_Submit : x_physical_batch_id = ' || x_physical_batch_id);
164     fnd_request.set_org_id(p_org_id);   -- vensrini Nov 17, 2005
165     x_request_id  :=
166       fnd_request.submit_request(
167         application                  => 'CN'
168       , program                      => x_conc_program
169       , argument1                    => x_parent_proc_audit_id
170       , argument2                    => x_physical_batch_id
171       , argument3                    => p_transaction_source
172       , argument4                    => x_start_date
173       , argument5                    => x_end_date
174       , argument6                    => p_org_id
175       );
176     debugmsg('Conc_Submit : x_request_id = ' || x_request_id);
177 
178     IF x_request_id = 0 THEN
179       debugmsg('Loader : Conc_Submit : Submit failure for phys batch ' || x_physical_batch_id);
180       debugmsg('Loader : Conc_Submit: ' || fnd_message.get);
181       debugmsg('Loader : Conc_Submit : Submit failure for phys batch ' || x_physical_batch_id);
182     ELSE
183       cn_message_pkg.FLUSH;
184       COMMIT;   -- Commit for each concurrent program i.e. runner
185     END IF;
186 
187     debugmsg('Conc_Submit : End Procedure');
188   END conc_submit;
189 
190   --
191   PROCEDURE conc_dispatch(
192     x_parent_proc_audit_id IN NUMBER
193   , x_start_date           IN DATE
194   , x_end_date             IN DATE
195   , x_logical_batch_id     IN NUMBER
196   , x_transaction_source   IN VARCHAR2
197   , p_org_id               IN NUMBER
198   ) IS
199     TYPE requests IS TABLE OF NUMBER(15)
200       INDEX BY BINARY_INTEGER;
201 
202     TYPE batches IS TABLE OF NUMBER(15)
203       INDEX BY BINARY_INTEGER;
204 
205     l_primary_request_stack requests;
206     l_primary_batch_stack   batches;
207     l_empty_request_stack   requests;
208     l_empty_batch_stack     batches;
209     x_batch_total           NUMBER                     := 0;
210     l_temp_id               NUMBER                     := 0;
211     l_temp_phys_batch_id    NUMBER;
212     primary_ptr             NUMBER                     := 1;   -- Must start at 1
213     l_dev_phase             VARCHAR2(80);
214     l_dev_status            VARCHAR2(80);
215     l_request_id            NUMBER;
216     l_completed_batch_count NUMBER                     := 0;
217     l_call_status           BOOLEAN;
218     l_next_process          VARCHAR2(30);
219     l_dummy                 VARCHAR2(500);
220     unfinished              BOOLEAN                    := TRUE;
221     l_user_id               NUMBER(15)                 := fnd_global.user_id;
222     l_resp_id               NUMBER(15)                 := fnd_global.resp_id;
223     l_login_id              NUMBER(15)                 := fnd_global.login_id;
224     l_conc_prog_id          NUMBER(15)                 := fnd_global.conc_program_id;
225     l_conc_request_id       NUMBER(15)                 := fnd_global.conc_request_id;
226     l_prog_appl_id          NUMBER(15)                 := fnd_global.prog_appl_id;
227     x_debug                 NUMBER;
228     debug_v                 NUMBER;
229     conc_status             BOOLEAN;
230     l_sleep_time            NUMBER                     := 180;
231     l_sleep_time_char       VARCHAR2(30);
232     l_errbuf                VARCHAR2(1000);
233     l_retcode               NUMBER;
234 
235     -- Get individual physical batch id's for the entire logical batch
236     CURSOR physical_batches IS
237       SELECT DISTINCT sca_process_batch_id
238                  FROM cn_sca_process_batches
239                 WHERE logical_batch_id = x_logical_batch_id;
240 
241     physical_rec            physical_batches%ROWTYPE;
242   BEGIN
243     debugmsg('SCA : Conc_Dispatch : Start of Conc_Dispatch');
244     debugmsg('SCA : Conc_Dispatch : Logical Batch ID = ' || x_logical_batch_id);
245 
246     WHILE unfinished LOOP
247       l_primary_request_stack  := l_empty_request_stack;
248       l_primary_batch_stack    := l_empty_batch_stack;
249       primary_ptr              := 1;   -- Start at element one not element zero
250       l_completed_batch_count  := 0;
251       x_batch_total            := 0;
252 
253       FOR physical_rec IN physical_batches LOOP
254         debugmsg(
255              'Conc_Dispatch : Calling conc_submit. '
256           || 'physical_rec.sca_process_batch_id = '
257           || physical_rec.sca_process_batch_id
258         );
259         debugmsg('SCA : Conc_Dispatch : call SCA_BATCH_RUNNER');
260         cn_sca_credits_batch_pub.conc_submit
261                                           (
262           x_conc_program               => 'CN_SCA_PROCESS_BATCH_RULES'
263         , x_parent_proc_audit_id       => x_parent_proc_audit_id
264         , x_physical_batch_id          => physical_rec.sca_process_batch_id
265         , x_start_date                 => x_start_date
266         , x_end_date                   => x_end_date
267         , p_transaction_source         => x_transaction_source
268         , p_org_id                     => p_org_id
269         , x_request_id                 => l_temp_id
270         );
271         debugmsg('SCA : Conc_Dispatch : done SCA_BATCH_RUNNER');
272         x_batch_total                           := x_batch_total + 1;
273         l_primary_request_stack(x_batch_total)  := l_temp_id;
274         l_primary_batch_stack(x_batch_total)    := physical_rec.sca_process_batch_id;
275 
276         -- If submission failed update the batch record and bail
277         IF l_temp_id = 0 THEN
278           --cn_debug.print_msg('conc disp submit failed',1);
279           l_temp_phys_batch_id  := physical_rec.sca_process_batch_id;
280           RAISE conc_fail;
281         END IF;
282       END LOOP;
283 
284       debugmsg('SCA : Conc_Dispatch : Total conc requests submitted : ' || x_batch_total);
285       debugmsg('Total conc requests submitted : ' || x_batch_total);
286       --cn_message_pkg.flush;
287       debug_v                  := l_primary_request_stack(primary_ptr);
288       l_sleep_time_char        := fnd_profile.VALUE('CN_SLEEP_TIME');
289 
290       IF l_sleep_time_char IS NOT NULL THEN
291         l_sleep_time  := TO_NUMBER(l_sleep_time_char);
292       END IF;
293 
294       DBMS_LOCK.sleep(l_sleep_time);
295 
296       WHILE l_completed_batch_count <= x_batch_total LOOP
297         IF l_primary_request_stack(primary_ptr) IS NOT NULL THEN
298           l_call_status  :=
299             fnd_concurrent.get_request_status(
300               request_id                   => l_primary_request_stack(primary_ptr)
301             , phase                        => l_dummy
302             , status                       => l_dummy
303             , dev_phase                    => l_dev_phase
304             , dev_status                   => l_dev_status
305             , MESSAGE                      => l_dummy
306             );
307 
308           IF (NOT l_call_status) THEN
309             debugmsg('SCA : Conc_Dispatch : request_id is ' || l_primary_request_stack(primary_ptr));
310             RAISE conc_fail;
311           END IF;
312 
313           IF (l_dev_phase = 'COMPLETE') THEN
314             debug_v                               := l_primary_request_stack(primary_ptr);
315             l_temp_phys_batch_id                  := l_primary_batch_stack(primary_ptr);
316             l_primary_batch_stack(primary_ptr)    := NULL;
317             l_primary_request_stack(primary_ptr)  := NULL;
318             l_completed_batch_count               := l_completed_batch_count + 1;
319 
320             IF (l_dev_status = 'ERROR') THEN
321               debugmsg('SCA : Conc_Dispatch : ' || 'Request completed with error for ' || debug_v);
322               RAISE conc_fail;
323             ELSIF l_dev_status = 'NORMAL' THEN
324               x_debug  := l_primary_batch_stack(primary_ptr);
325             END IF;   -- If error
326           END IF;   -- If complete
327         END IF;   -- If null ptr
328 
329         primary_ptr  := primary_ptr + 1;
330 
331         IF (l_completed_batch_count = x_batch_total) THEN
332           debugmsg(
333                'SCA : Conc_Dispatch :  All requests complete for physical '
334             || 'transaction_source : '
335             || x_transaction_source
336           );
337           -- Get out of the loop by adding 1
338           l_completed_batch_count  := l_completed_batch_count + 1;
339           debugmsg(
340                'SCA : Conc_Dispatch :  All requests complete for '
341             || 'logical process : '
342             || x_transaction_source
343           );
344           unfinished               := FALSE;
345         ELSE
346           -- Made a complete pass through the srp_periods in this physical
347           -- batch and some conc requests have not completed.
348           -- Give the conc requests a few minutes to run before
349           -- checking their status
350           IF (primary_ptr > x_batch_total) THEN
351             DBMS_LOCK.sleep(l_sleep_time);
352             primary_ptr  := 1;
353           END IF;
354         END IF;
355       END LOOP;
356     END LOOP;
357   EXCEPTION
358     WHEN NO_DATA_FOUND THEN
359       debugmsg('SCA : Conc_Dispatch : no rows for process ' || x_transaction_source);
360     WHEN conc_fail THEN
361       debugmsg('SCA : Conc_Dispatch : Exception conc_fail');
362       conc_status  := fnd_concurrent.set_completion_status(status => 'ERROR', MESSAGE => '');
363       RAISE;
364     WHEN OTHERS THEN
365       debugmsg('SCA : Conc_Dispatch : Unexpected Exception');
366       RAISE;
367   END conc_dispatch;
368 
369   --
370   PROCEDURE split_batches(
371     p_logical_batch_id   IN            NUMBER
372   , p_start_date         IN            DATE
373   , p_end_date           IN            DATE
374   , p_transaction_source IN            VARCHAR2
375   , p_org_id             IN            NUMBER
376   , x_size               OUT NOCOPY    NUMBER
377   ) IS
378     l_sql_stmt             VARCHAR2(10000);
379     l_sql_stmt_count       VARCHAR2(10000);
380     l_sql_stmt_id          VARCHAR2(10000);
381     l_sql_stmt_divider     VARCHAR2(10000);
382     l_sql_stmt_resource    VARCHAR2(10000);
383     l_no_trx               BOOLEAN;
384     l_sca_process_batch_id cn_sca_process_batches.sca_process_batch_id%TYPE;
385 
386     TYPE rc IS REF CURSOR;
387 
388     TYPE divider_type IS TABLE OF NUMBER;
389 
390     query_cur              rc;
391     i                      NUMBER;
392     l_header_rec           cn_comm_lines_api%ROWTYPE;
393     l_lines_output_id      cn_sca_lines_output.sca_lines_output_id%TYPE;
394     l_header_interface_id  cn_sca_headers_interface.sca_headers_interface_id%TYPE;
395     l_comm_lines_api_id    cn_comm_lines_api.comm_lines_api_id%TYPE;
396     l_source_id            cn_sca_headers_interface.source_id%TYPE;
397     l_order_number         cn_comm_lines_api.order_number%TYPE;
398     l_invoice_number       cn_comm_lines_api.invoice_number%TYPE;
399     l_id                   NUMBER;
400     l_logical_batch_size   NUMBER;
401     l_worker_num           NUMBER;
402     l_physical_batch_size  NUMBER;
403     l_divider_size         NUMBER;
404     divider                divider_type                                           := divider_type
405                                                                                                  ();
406     loop_count             NUMBER;
407     l_start_id             cn_sca_process_batches.start_id%TYPE;
408     l_end_id               cn_sca_process_batches.end_id%TYPE;
409     l_user_id              NUMBER(15)                                         := fnd_global.user_id;
410     l_login_id             NUMBER(15)                                        := fnd_global.login_id;
411   BEGIN
412     debugmsg('Allocation Process : Split Batches Start ');
413     debugmsg('Allocation Process : p_start_date = ' || p_start_date);
414     debugmsg('Allocation Process : p_end_date = ' || p_end_date);
415     -- Get the number of transactions that needs to be processed,
416     -- i.e. the logical batch size
417     l_sql_stmt_count  := 'SELECT count(1) FROM cn_sca_headers_interface cshi ';
418     l_sql_stmt        :=
419          'WHERE cshi.processed_date BETWEEN :p_start_date AND :p_end_date '
420       || 'AND cshi.transaction_source = :p_transaction_source '
421       || 'AND cshi.process_status = ''SCA_UNPROCESSED'' '
422       || 'AND cshi.org_id = :p_org_id '
423       || 'ORDER BY cshi.sca_headers_interface_id ';
424     l_sql_stmt_count  := l_sql_stmt_count || l_sql_stmt;
425 
426     OPEN query_cur
427      FOR l_sql_stmt_count USING p_start_date, p_end_date, p_transaction_source, p_org_id;
428 
429     FETCH query_cur
430      INTO l_logical_batch_size;
431 
432     x_size            := l_logical_batch_size;
433     l_worker_num      := NVL(fnd_profile.VALUE('CN_NUMBER_OF_WORKERS'), 1);
434 
435     IF (l_worker_num < 1) THEN
436       l_worker_num  := 1;
437     END IF;
438 
439     debugmsg(p_transaction_source || ': Assign : Logical Batch Size = '
440       || TO_CHAR(l_logical_batch_size));
441     debugmsg(p_transaction_source || ': Assign : Number of Workers = ' || TO_CHAR(l_worker_num));
442 
443     -- calculate the minimas and maximas of the physical batches
444     IF (l_logical_batch_size > l_worker_num) THEN
445       l_physical_batch_size    := FLOOR(l_logical_batch_size / l_worker_num);
446       l_divider_size           := l_worker_num * 2;
447       divider.EXTEND;
448       divider(1)               := 1;
449       divider.EXTEND;
450       divider(2)               := divider(1) + l_physical_batch_size - 1;
451 
452       FOR counter IN 2 .. l_worker_num LOOP
453         divider.EXTEND;
454         divider(2 * counter - 1)  := divider(2 * counter - 2) + 1;
455         divider.EXTEND;
456         divider(2 * counter)      := divider(2 * counter - 1) + l_physical_batch_size - 1;
457 
458         IF (counter <> l_worker_num) THEN
459           debugmsg(
460                p_transaction_source
461             || ': Assign : Maxima'
462             || counter
463             || ' = '
464             || TO_CHAR(divider(2 * counter))
465           );
466         END IF;
467       END LOOP;
468 
469       divider(l_divider_size)  := l_logical_batch_size;
470     ELSE
471       l_physical_batch_size  := 0;
472 
473       FOR counter IN 1 .. l_logical_batch_size LOOP
474         divider.EXTEND;
475         divider(2 * counter - 1)  := counter;
476         divider.EXTEND;
477         divider(2 * counter)      := counter;
478       END LOOP;
479     END IF;
480 
481     --
482     IF (divider.COUNT = 0) THEN
483       l_no_trx  := TRUE;
484       RAISE no_trx;
485     ELSE
486       l_no_trx            := FALSE;
487       l_sql_stmt_divider  := '(''' || divider(divider.FIRST) || '''';
488       i                   := divider.NEXT(divider.FIRST);
489 
490       WHILE i IS NOT NULL LOOP
491         l_sql_stmt_divider  := l_sql_stmt_divider || ', ''' || divider(i) || '''';
492         i                   := divider.NEXT(i);
493       END LOOP;
494 
495       l_sql_stmt_divider  := l_sql_stmt_divider || ')';
496     END IF;
497 
498     IF (NOT l_no_trx) THEN
499       l_sql_stmt_id  :=
500                    'SELECT cshi.sca_headers_interface_id ' || 'FROM cn_sca_headers_interface CSHI ';
501       l_sql_stmt_id  := l_sql_stmt_id || l_sql_stmt;
502       l_sql_stmt_id  :=
503            'SELECT sca_headers_interface_id FROM '
504         || '(SELECT rownum row_number, sca_headers_interface_id FROM '
505         || '('
506         || l_sql_stmt_id
507         || ')) sca_headers_table '
508         || 'WHERE sca_headers_table.row_number IN '
509         || l_sql_stmt_divider;
510 
511       OPEN query_cur
512        FOR l_sql_stmt_id USING p_start_date, p_end_date, p_transaction_source, p_org_id;
513 
514       loop_count     := 1;
515       debugmsg(p_transaction_source || ': Assign : Insert into CN_SCA_PROCESS_BATCHES ');
516 
517       IF (l_physical_batch_size >= 2) THEN
518         LOOP
519           FETCH query_cur
520            INTO l_id;
521 
522           EXIT WHEN query_cur%NOTFOUND;
523 
524           IF ((loop_count MOD 2) = 1) THEN
525             l_start_id  := l_id;
526           END IF;
527 
528           IF ((loop_count MOD 2) = 0) THEN
529             l_end_id  := l_id;
530 
531             SELECT cn_sca_process_batches_s.NEXTVAL
532               INTO l_sca_process_batch_id
533               FROM SYS.DUAL;
534 
535             INSERT INTO cn_sca_process_batches
536                         (
537                          sca_process_batch_id
538                        , start_id
539                        , end_id
540                        , TYPE
541                        , logical_batch_id
542                        , creation_date
543                        , created_by
544                        , last_update_date
545                        , last_updated_by
546                        , last_update_login
547                        , org_id
548                         )
549                  VALUES (
550                          l_sca_process_batch_id
551                        , l_start_id
552                        , l_end_id
553                        , p_transaction_source
554                        , p_logical_batch_id
555                        , SYSDATE
556                        , l_user_id
557                        , SYSDATE
558                        , l_user_id
559                        , l_login_id
560                        , p_org_id
561                         );
562 
563             debugmsg(
564                  p_transaction_source
565               || ': Assign : sca_process_batch_id = '
566               || TO_CHAR(l_sca_process_batch_id)
567             );
568             debugmsg(p_transaction_source || ': Assign : start_id = ' || l_start_id);
569             debugmsg(p_transaction_source || ': Assign : end_id = ' || l_end_id);
570             debugmsg(
571               p_transaction_source || ': Assign : logical_batch_id = '
572               || TO_CHAR(p_logical_batch_id)
573             );
574             debugmsg(p_transaction_source || ': Assign : batch_type = ' || p_transaction_source);
575           END IF;
576 
577           loop_count  := loop_count + 1;
578         END LOOP;
579       ELSE
580         LOOP
581           FETCH query_cur
582            INTO l_id;
583 
584           EXIT WHEN query_cur%NOTFOUND;
585 
586           IF (loop_count = l_worker_num AND l_physical_batch_size = 1) THEN
587             l_start_id  := l_id;
588           END IF;
589 
590           IF (loop_count > l_worker_num AND l_physical_batch_size = 1) THEN
591             l_end_id  := l_id;
592 
593             SELECT cn_sca_process_batches_s.NEXTVAL
594               INTO l_sca_process_batch_id
595               FROM SYS.DUAL;
596 
597             INSERT INTO cn_sca_process_batches
598                         (
599                          sca_process_batch_id
600                        , start_id
601                        , end_id
602                        , TYPE
603                        , logical_batch_id
604                        , creation_date
605                        , created_by
606                        , last_update_date
607                        , last_updated_by
608                        , last_update_login
609                        , org_id
610                         )
611                  VALUES (
612                          l_sca_process_batch_id
613                        , l_start_id
614                        , l_end_id
615                        , p_transaction_source
616                        , p_logical_batch_id
617                        , SYSDATE
618                        , l_user_id
619                        , SYSDATE
620                        , l_user_id
621                        , l_login_id
622                        , p_org_id
623                         );
624 
625             debugmsg(
626                  p_transaction_source
627               || ': Assign : sca_process_batch_id = '
628               || TO_CHAR(l_sca_process_batch_id)
629             );
630             debugmsg(p_transaction_source || ': Assign : start_id = ' || l_start_id);
631             debugmsg(p_transaction_source || ': Assign : end_id = ' || l_end_id);
632             debugmsg(
633               p_transaction_source || ': Assign : logical_batch_id = '
634               || TO_CHAR(p_logical_batch_id)
635             );
636             debugmsg(p_transaction_source || ': Assign : batch_type = ' || p_transaction_source);
637           END IF;
638 
639           IF (
640               loop_count < l_worker_num OR(loop_count = l_worker_num AND l_physical_batch_size < 1)
641              ) THEN
642             SELECT cn_sca_process_batches_s.NEXTVAL
643               INTO l_sca_process_batch_id
644               FROM SYS.DUAL;
645 
646             INSERT INTO cn_sca_process_batches
647                         (
648                          sca_process_batch_id
649                        , start_id
650                        , end_id
651                        , TYPE
652                        , logical_batch_id
653                        , creation_date
654                        , created_by
655                        , last_update_date
656                        , last_updated_by
657                        , last_update_login
658                        , org_id
659                         )
660                  VALUES (
661                          l_sca_process_batch_id
662                        , l_id
663                        , l_id
664                        , p_transaction_source
665                        , p_logical_batch_id
666                        , SYSDATE
667                        , l_user_id
668                        , SYSDATE
669                        , l_user_id
670                        , l_login_id
671                        , p_org_id
672                         );
673 
674             debugmsg(
675                  p_transaction_source
676               || ': Assign : sca_process_batch_id = '
677               || TO_CHAR(l_sca_process_batch_id)
678             );
679             debugmsg(p_transaction_source || ': Assign : start_id = ' || l_id);
680             debugmsg(p_transaction_source || ': Assign : end_id = ' || l_id);
681             debugmsg(
682               p_transaction_source || ': Assign : logical_batch_id = '
683               || TO_CHAR(p_logical_batch_id)
684             );
685             debugmsg(p_transaction_source || ': Assign : batch_type = ' || p_transaction_source);
686           END IF;
687 
688           loop_count  := loop_count + 1;
689         END LOOP;
690       END IF;
691     END IF;
692   EXCEPTION
693     WHEN no_trx THEN
694       debugmsg(p_transaction_source || ': Assign : No transactions to process ');
695     WHEN OTHERS THEN
696       debugmsg(p_transaction_source || ': Assign : Unexpected Error');
697       RAISE;
698   END split_batches;
699 
700   --
701   PROCEDURE get_sales_credits(
702     errbuf               OUT NOCOPY    VARCHAR2
703   , retcode              OUT NOCOPY    NUMBER
704   , p_transaction_source IN            VARCHAR2
705   , p_start_date         IN            VARCHAR2
706   , p_end_date           IN            VARCHAR2
707   ) IS
708     --+
709     --+ Variable Declaration
710     --+
711     l_start_date       DATE;
712     l_end_date         DATE;
713     l_process_audit_id NUMBER;
714     l_logical_batch_id NUMBER;
715     x_size_inv         NUMBER;
716     x_size_ord         NUMBER;
717     x_size             NUMBER;
718     conc_status        BOOLEAN;
719     l_wf_item_key      VARCHAR2(240);
720     l_return_status    VARCHAR2(1);
721     l_rule_count       NUMBER        := 0;
722     l_status           VARCHAR2(1);
723     l_industry         VARCHAR2(1);
724     l_oracle_schema    VARCHAR2(30);
725     l_return           BOOLEAN;
726     p_org_id           NUMBER;
727     --+
728     --+ Exceptions Declaration
729     --+
730     index_ex           EXCEPTION;
731     no_rule_ex         EXCEPTION;
732   BEGIN
733     p_org_id      := mo_global.get_current_org_id();
734     cn_message_pkg.begin_batch(
735       x_process_type               => 'ALLOCATION_PROCESS'
736     , x_parent_proc_audit_id       => NULL
737     , x_process_audit_id           => l_process_audit_id
738     , x_request_id                 => fnd_global.conc_request_id
739     , p_org_id                     => p_org_id
740     );
741     -- Convert the dates for the varchar2 parameters passed in from
742     -- concurrent program
743     l_start_date  := fnd_date.canonical_to_date(p_start_date);
744     l_end_date    := fnd_date.canonical_to_date(p_end_date);
745 
746     --+
747     --+ Call begin_batch to get process_audit_id for debug log file
748     --+
749     SELECT cn_sca_logical_batches_s.NEXTVAL
750       INTO l_logical_batch_id
751       FROM SYS.DUAL;
752 
753     debugmsg('Allocation Process : Start of Transfer');
754     debugmsg('Allocation Process : process_audit_id is ' || l_process_audit_id);
755     --dbms_output.put_line('Allocation Process : process_audit_id is ' || l_process_audit_id );
756     debugmsg('Allocation Process : logical_batch_id is ' || l_logical_batch_id);
757     debugmsg('Allocation Process : p_start_date is ' || p_start_date);
758     debugmsg('Allocation Process : p_end_date is ' || p_end_date);
759     debugmsg('Allocation Process : mo_global.get_current_org_id is - ' || p_org_id);
760 
761     --+
762     --+ Check whether credit rules existing for a given transaction source and
763     --+ operating unit
764     --+
765     SELECT COUNT(1)
766       INTO l_rule_count
767       FROM cn_sca_denorm_rules a
768      WHERE a.transaction_source = p_transaction_source AND a.org_id = p_org_id;
769 
770     IF (l_rule_count = 0) THEN
771       RAISE no_rule_ex;
772     END IF;
773 
774     --+
775     --+ Call this procedure to to find out the number of records and split
776     --+ them into multiple physical batches.
777     --+
778     cn_sca_credits_batch_pub.split_batches(l_logical_batch_id, l_start_date, l_end_date
779     , p_transaction_source, p_org_id, x_size);
780     COMMIT;
781 
782     IF (x_size = 0) THEN
783       RAISE no_trx;
784     END IF;
785 
786     --+
787     --+ Getting the schema name and use it as a parameter in DDL statements.
788     --+ to fix bug# 3537330 (04/23/04)
789     --+
790     l_return      :=
791       fnd_installation.get_app_info(
792         application_short_name       => 'CN'
793       , status                       => l_status
794       , industry                     => l_industry
795       , oracle_schema                => l_oracle_schema
796       );
797     debugmsg('Allocation Process : Schema Name: ' || l_oracle_schema);
798     --+
799     --+ Removing data from intermediate tables
800     --+
801     debugmsg('Allocation Process : Removing data from intermediate tables');
802 
803     BEGIN
804       EXECUTE IMMEDIATE 'TRUNCATE TABLE ' || l_oracle_schema || '.cn_sca_matches_all REUSE STORAGE';
805     EXCEPTION
806       WHEN OTHERS THEN
807         debugmsg('Allocation Process : Unable to trancate cn_sca_matches' || SQLERRM);
808         RAISE;
809     END;
810 
811     BEGIN
812       EXECUTE IMMEDIATE 'TRUNCATE TABLE ' || l_oracle_schema || '.cn_sca_winners_all REUSE STORAGE';
813     EXCEPTION
814       WHEN OTHERS THEN
815         debugmsg('Allocation Process : Unable to trancate cn_sca_winners' || SQLERRM);
816         RAISE;
817     END;
818 
819     COMMIT;
820     --+
821     --+ Setting the tables in NOLOGGING mode
822     --+
823     debugmsg('Allocation Process : Set the tables to NOLOGGING Mode');
824 
825     BEGIN
826       EXECUTE IMMEDIATE 'ALTER TABLE ' || l_oracle_schema || '.cn_sca_matches_all NOLOGGING';
827     EXCEPTION
828       WHEN OTHERS THEN
829         debugmsg('Allocation Process : Unable to set NOLOGGING for cn_sca_matches' || SQLERRM);
830         RAISE;
831     END;
832 
833     BEGIN
834       EXECUTE IMMEDIATE 'ALTER TABLE ' || l_oracle_schema || '.cn_sca_winners_all NOLOGGING';
835     EXCEPTION
836       WHEN OTHERS THEN
837         debugmsg('Allocation Process : Unable to set NOLOGGING for cn_sca_winners' || SQLERRM);
838         RAISE;
839     END;
840 
841     --+
842     --+ Delete existing indexes and create indexes on ATTRIBUTE columns of
843     --+ input interface table.
844     --+
845     cn_sca_utl_pvt.manage_indexes(
846       p_transaction_source         => p_transaction_source
847     , p_org_id                     => p_org_id
848     , x_return_status              => l_return_status
849     );
850 
851     IF (l_return_status <> fnd_api.g_ret_sts_success) THEN
852       RAISE index_ex;
853     END IF;
854 
855     COMMIT;
856     --+
857     --+ Once physical batches are created, this procedure assign each physical
858     --+ batch as a concurrent program
859     --+
860     cn_sca_credits_batch_pub.conc_dispatch(
861       x_parent_proc_audit_id       => l_process_audit_id
862     , x_start_date                 => l_start_date
863     , x_end_date                   => l_end_date
864     , x_transaction_source         => p_transaction_source
865     , p_org_id                     => p_org_id
866     , x_logical_batch_id           => l_logical_batch_id
867     );
868     --+
869     --+ Once processing is done, call workflow process to execute the calling
870     --+ module's procedure to populate data from SCA tables to their tables.
871     --+
872     debugmsg('Allocation Process : Calling WF to execute Calling Module Procedure');
873 
874     BEGIN
875       cn_sca_wf_pkg.start_process(
876         p_start_date                 => l_start_date
877       , p_end_date                   => l_end_date
878       , p_trx_source                 => p_transaction_source
879       , p_org_id                     => p_org_id
880       , p_wf_process                 => 'CN_SCA_TRX_LOAD_PR'
881       , p_wf_item_type               => 'CNSCARPR'
882       , x_wf_item_key                => l_wf_item_key
883       );
884       debugmsg('Allocation Process : Executed Calling Module Procedure');
885     EXCEPTION
886       WHEN OTHERS THEN
887         debugmsg('Allocation Process : Error while processing Calling Module Procedure');
888     END;
889 
890     COMMIT WORK;
891     debugmsg('Allocation Process : Ending: get_sales_credits ');
892     cn_message_pkg.end_batch(l_process_audit_id);
893   EXCEPTION
894     WHEN no_trx THEN
895       debugmsg('Get Sales Credits : No input transactions found for Rules Engine Processing');
896       debugmsg('Get Sales Credits : Rules Engine Processing ended with errors');
897       conc_status  := fnd_concurrent.set_completion_status(status => 'ERROR', MESSAGE => '');
898       cn_message_pkg.end_batch(l_process_audit_id);
899     WHEN no_rule_ex THEN
900       debugmsg('Get Sales Credits : No Credit Rules found for Rules Engine Processing');
901       debugmsg('Get Sales Credits : Rules Engine Processing ended with errors');
902       conc_status  := fnd_concurrent.set_completion_status(status => 'ERROR', MESSAGE => '');
903       cn_message_pkg.end_batch(l_process_audit_id);
904     WHEN index_ex THEN
905       debugmsg('Get Sales Credits : Error occured while creating indexes dynamically');
906       debugmsg('Get Sales Credits : Rules Engine Processing ended with errors');
907       conc_status  := fnd_concurrent.set_completion_status(status => 'ERROR', MESSAGE => '');
908       cn_message_pkg.end_batch(l_process_audit_id);
909     WHEN OTHERS THEN
910       debugmsg('Get Sales Credits : Unexpected exception');
911       debugmsg('Get Sales Credits : Oracle Error: ' || SQLERRM);
912       debugmsg('Get Sales Credits : Rules Engine Processing ended with errors');
913       conc_status  := fnd_concurrent.set_completion_status(status => 'ERROR', MESSAGE => '');
914       cn_message_pkg.end_batch(l_process_audit_id);
915   END get_sales_credits;
916 
917   --
918 
919   /**************************************/
920   /* Start of the new crediting process */
921   /**************************************/
922 
923   /* This procedure returns the appropiate where clause to select    */
924   /* data from the table cn_comm_lines_api_all depending on run mode */
925   PROCEDURE get_where_clause(
926     p_start_date   IN            DATE
927   , p_end_date     IN            DATE
928   , p_org_id       IN            NUMBER
929   , p_run_mode     IN            VARCHAR2
930   , x_where_clause OUT NOCOPY    VARCHAR2
931   , errbuf         IN OUT NOCOPY VARCHAR2
932   , retcode        IN OUT NOCOPY VARCHAR2
933   ) IS
934   BEGIN
935     debugmsg('SCA : Start of get_where_clause');
936     errbuf          := NULL;
937     retcode         := 0;
938     x_where_clause  := 'WHERE org_id = ' || p_org_id || ' ';
939     x_where_clause  :=
940          x_where_clause
941       || 'AND txn_date between '
942       || 'to_date('''
943       || TO_CHAR(p_start_date, 'dd/mm/yyyy')
944       || ''',''dd/mm/yyyy:hh24:mi:ss'')'
945       || ' and to_date('''
946       || TO_CHAR(p_end_date, 'dd/mm/yyyy')||':23:59:59'
947       || ''',''dd/mm/yyyy:hh24:mi:ss'')'
948       || ' ';
949     /* only the collected txns are selected and not the ones generated by this process */
950     x_where_clause  := x_where_clause || 'AND terr_id IS NULL ';
951 
952   	 IF (p_run_mode <> 'ALL' AND p_run_mode <> 'INCREMENTAL' ) THEN
953         /* loaded txns are not considered for crediting in NEW mode */
954         /* commented this code and changed code to consider only the not credited transactions */
955         x_where_clause  := x_where_clause || 'AND load_status NOT IN ( ''CREDITED'' ) ';
956      END IF;
957 
958      IF( p_run_mode = 'INCREMENTAL' ) THEN
959         x_where_clause  := x_where_clause || ' AND  trans_object_id IN (
960                                         SELECT comm_lines_api_id
961                                           FROM cn_comm_lines_api_all
962                                          WHERE load_status NOT IN(''OBSOLETE'', ''FILTERED'')
963                                            AND adjust_status NOT IN(''FROZEN'', ''REVERSAL'')
964                                            START WITH COMM_LINES_API_ID IN (SELECT adj_comm_lines_api_id from cn_comm_lines_api_all
965                                                                            WHERE terr_id IN (
966                                                                                       SELECT jcdt.terr_id
967                                                                                         FROM jty_conc_req_summ jcrs, jty_changed_dea_terrs jcdt
968                                                                                         WHERE jcrs.program_name = ''JTY_STAR''
969                                                                                           AND jcrs.retcode   = 0
970                                                                                           AND jcrs.param1   = -1001
971                                                                                           AND jcrs.param2   = ''DEA INCREMENTAL''
972                                                                                           AND jcrs.request_id = jcdt.star_request_id)
973                                                                             AND processed_date BETWEEN  '
974                                                                                           || 'to_date('''
975                                                                                           || TO_CHAR(p_start_date, 'dd/mm/yyyy')
976                                                                                           || ''',''dd/mm/yyyy:hh24:mi:ss'')'
977                                                                                           || ' and to_date('''
978                                                                                           || TO_CHAR(p_end_date, 'dd/mm/yyyy')||':23:59:59'
979                                                                                           || ''',''dd/mm/yyyy:hh24:mi:ss''))'
980                                            ||'CONNECT BY PRIOR ADJ_COMM_LINES_API_ID = COMM_LINES_API_ID )';
981      END IF;
982 
983      x_where_clause  :=  x_where_clause || 'AND (adjust_status NOT IN (''FROZEN'', ''REVERSAL'')) ';
984      /* donot select txns for which user has checked the "preserve credit override flag" to bypass crediting process */
985      x_where_clause  :=  x_where_clause || 'AND (preserve_credit_override_flag = ''N'') ';
986 
987     debugmsg('SCA : where clause : ' || x_where_clause);
988     debugmsg('SCA : End of get_where_clause');
989   EXCEPTION
990     WHEN OTHERS THEN
991       debugmsg('SCA : Unexpected exception in get_where_clause');
992       debugmsg('SCA : SQLCODE : ' || SQLCODE);
993       debugmsg('SCA : SQLERRM : ' || SQLERRM);
994       retcode  := 2;
995       errbuf   := 'CN_SCATM_TAE_PUB.get_where_clause.others';
996   END get_where_clause;
997 
998   /* This procedure returns the flex field names that are used */
999   /* in TM to store the split percentage and revenue type      */
1000   PROCEDURE get_flex_field_names(
1001     p_ffname_split_pctg OUT NOCOPY    VARCHAR2
1002   , p_ffname_rev_type   OUT NOCOPY    VARCHAR2
1003   , errbuf              IN OUT NOCOPY VARCHAR2
1004   , retcode             IN OUT NOCOPY VARCHAR2
1005   ) IS
1006     l_invalid_ffnames EXCEPTION;
1007   BEGIN
1008     debugmsg('SCA : Start of get_flex_field_names');
1009     errbuf   := NULL;
1010     retcode  := 0;
1011 
1012     /* Get the flex field name corresponding to split percentage */
1013     IF (fnd_profile.defined('CN_FFNAME_SPLIT_PCTG')) THEN
1014       p_ffname_split_pctg  := fnd_profile.VALUE('CN_FFNAME_SPLIT_PCTG');
1015     END IF;
1016 
1017     /* Get the flex field name corresponding to revenue type */
1018     IF (fnd_profile.defined('CN_FFNAME_REV_TYPE')) THEN
1019       p_ffname_rev_type  := fnd_profile.VALUE('CN_FFNAME_REV_TYPE');
1020     END IF;
1021 
1022     /* the two flex field names should not be same and they should one of the fields attribute1 .. 15 */
1023     IF (
1024            (
1025             p_ffname_split_pctg NOT IN
1026               (
1027                'ATTRIBUTE1'
1028              , 'ATTRIBUTE2'
1029              , 'ATTRIBUTE3'
1030              , 'ATTRIBUTE4'
1031              , 'ATTRIBUTE5'
1032              , 'ATTRIBUTE6'
1033              , 'ATTRIBUTE7'
1034              , 'ATTRIBUTE8'
1035              , 'ATTRIBUTE9'
1036              , 'ATTRIBUTE10'
1037              , 'ATTRIBUTE11'
1038              , 'ATTRIBUTE12'
1039              , 'ATTRIBUTE13'
1040              , 'ATTRIBUTE14'
1041              , 'ATTRIBUTE15'
1042               )
1043            )
1044         OR (
1045             p_ffname_rev_type NOT IN
1046               (
1047                'ATTRIBUTE1'
1048              , 'ATTRIBUTE2'
1049              , 'ATTRIBUTE3'
1050              , 'ATTRIBUTE4'
1051              , 'ATTRIBUTE5'
1052              , 'ATTRIBUTE6'
1053              , 'ATTRIBUTE7'
1054              , 'ATTRIBUTE8'
1055              , 'ATTRIBUTE9'
1056              , 'ATTRIBUTE10'
1057              , 'ATTRIBUTE11'
1058              , 'ATTRIBUTE12'
1059              , 'ATTRIBUTE13'
1060              , 'ATTRIBUTE14'
1061              , 'ATTRIBUTE15'
1062               )
1063            )
1064         OR (p_ffname_split_pctg = p_ffname_rev_type)
1065        ) THEN
1066       RAISE l_invalid_ffnames;
1067     END IF;
1068 
1069     debugmsg('SCA : Flex field name for split pctg : ' || p_ffname_split_pctg);
1070     debugmsg('SCA : Flex field name for revenue type : ' || p_ffname_rev_type);
1071     debugmsg('SCA : End of get_flex_field_names');
1072   EXCEPTION
1073     WHEN l_invalid_ffnames THEN
1074       debugmsg('SCA : Invalid flex field name specification');
1075       retcode  := 2;
1076       errbuf   := 'Invalid flex field name specification';
1077     WHEN OTHERS THEN
1078       debugmsg('SCA : Unexpected exception in get_flex_field_names');
1079       debugmsg('SCA : SQLCODE : ' || SQLCODE);
1080       debugmsg('SCA : SQLERRM : ' || SQLERRM);
1081       retcode  := 2;
1082       errbuf   := 'CN_SCATM_TAE_PUB.get_flex_field_names.others';
1083   END get_flex_field_names;
1084 
1085   /* This procedure marks the txns processed as CREDITED */
1086   PROCEDURE update_txns_processed(errbuf IN OUT NOCOPY VARCHAR2, retcode IN OUT NOCOPY VARCHAR2
1087   , p_worker_id IN NUMBER) IS
1088     l_no_of_records NUMBER;
1089   BEGIN
1090     debugmsg('SCA : Start of update_txns_processed');
1091     errbuf   := NULL;
1092     retcode  := 0;
1093 
1094     /* mark the transactions in the api table as CREDITED            */
1095     /* for which territory manager has returned a valid credited txn */
1096 
1097     UPDATE CN_COMM_LINES_API_ALL CLA
1098     SET LOAD_STATUS = 'CREDITED', ADJUST_STATUS = 'SCA_ALLOCATED'
1099     WHERE COMM_LINES_API_ID IN
1100      ( SELECT /*+ cardinality(a,1) */ TRANS_OBJECT_ID
1101        FROM   (
1102                select /*+ no_merge */ DISTINCT TRANS_OBJECT_ID
1103                from   JTF_TAE_1001_SC_WINNERS A
1104                where  A.WORKER_ID = p_worker_id
1105               ) A
1106        WHERE  EXISTS
1107              (
1108                select /*+ no_unest */ 1
1109                from   CN_COMM_LINES_API_ALL B
1110                where  B.ADJ_COMM_LINES_API_ID = A.TRANS_OBJECT_ID
1111                AND    B.TERR_ID IS NOT NULL
1112               )
1113      );
1114 
1115 
1116     debugmsg('SCA : End of update_txns_processed');
1117   EXCEPTION
1118     WHEN OTHERS THEN
1119       debugmsg('SCA : Unexpected exception in update_txns_processed');
1120       debugmsg('SCA : SQLCODE : ' || SQLCODE);
1121       debugmsg('SCA : SQLERRM : ' || SQLERRM);
1122       retcode  := 2;
1123       errbuf   := 'CN_SCATM_TAE_PUB.update_txns_processed.others';
1124   END update_txns_processed;
1125 
1126   /* This procedure inserts credited txns into api table */
1127   PROCEDURE insert_api_txns(
1128     p_org_id              IN            NUMBER
1129   , p_trans_object_id_tbl IN OUT NOCOPY g_trans_object_id_tbl_type
1130   , p_salesrep_id_tbl     IN OUT NOCOPY g_salesrep_id_tbl_type
1131   , p_emp_no_tbl          IN OUT NOCOPY g_emp_no_tbl_type
1132   , p_role_id_tbl         IN OUT NOCOPY g_role_id_tbl_type
1133   , p_split_pctg_tbl      IN OUT NOCOPY g_split_pctg_tbl_type
1134   , p_rev_type_tbl        IN OUT NOCOPY g_rev_type_tbl_type
1135   , p_terr_id_tbl         IN OUT NOCOPY g_terr_id_tbl_type
1136   , p_terr_name_tbl       IN OUT NOCOPY g_terr_name_tbl_type
1137   , p_del_flag_tbl        IN OUT NOCOPY g_del_flag_tbl_type
1138   , errbuf                IN OUT NOCOPY VARCHAR2
1139   , retcode               IN OUT NOCOPY VARCHAR2
1140   ) IS
1141     l_no_of_records NUMBER;
1142     l_error_index   NUMBER;
1143     ERRORS          NUMBER;
1144     dml_errors      EXCEPTION;
1145     PRAGMA EXCEPTION_INIT(dml_errors, -24381);
1146   BEGIN
1147     debugmsg('SCA : Start of insert_api_txns');
1148     errbuf           := NULL;
1149     retcode          := 0;
1150     l_no_of_records  := p_trans_object_id_tbl.COUNT;
1151 
1152     debugmsg('SCA : Number of rows to be inserted : ' || l_no_of_records);
1153     debugmsg('SCA : Start of insert_api_txns '||to_char(sysdate,'dd-mm-rrrr hh24:mi:ss'));
1154     IF (l_no_of_records > 0) THEN
1155       /* insert the credited transactions into api table */
1156       /* process all the rows even if some of them fail  */
1157 
1158     --     g_sca_insert_tbl_type := cn_sca_insert_tbl_type(cn_sca_insert_rec_type(1,1,1,1,1,1,1,1,1));
1159     --      FOR i IN p_trans_object_id_tbl.FIRST .. p_trans_object_id_tbl.LAST
1160     --      LOOP
1161     --         g_sca_insert_tbl_type.EXTEND;
1162     --         g_sca_insert_tbl_type(i) := cn_sca_insert_rec_type(p_trans_object_id_tbl(i)
1163     --                                                     , p_salesrep_id_tbl(i)
1164     --                                                     , p_emp_no_tbl(i)
1165     --                                                     , p_role_id_tbl(i)
1166     --                                                     , p_split_pctg_tbl(i)
1167     --                                                     , p_rev_type_tbl(i)
1168     --                                                     , p_terr_id_tbl(i)
1169     --                                                     , p_terr_name_tbl(i)
1170     --                                                     , p_del_flag_tbl(i));
1171     --      END LOOP;
1172 
1173         FORALL i IN p_trans_object_id_tbl.FIRST .. p_trans_object_id_tbl.LAST SAVE EXCEPTIONS
1174         INSERT INTO cn_comm_lines_api_all
1175                     (
1176                      salesrep_id
1177                    , processed_date
1178                    , processed_period_id
1179                    , transaction_amount
1180                    , trx_type
1181                    , revenue_class_id
1182                    , load_status
1183                    , attribute_category
1184                    , attribute1
1185                    , attribute2
1186                    , attribute3
1187                    , attribute4
1188                    , attribute5
1189                    , attribute6
1190                    , attribute7
1191                    , attribute8
1192                    , attribute9
1193                    , attribute10
1194                    , attribute11
1195                    , attribute12
1196                    , attribute13
1197                    , attribute14
1198                    , attribute15
1199                    , attribute16
1200                    , attribute17
1201                    , attribute18
1202                    , attribute19
1203                    , attribute20
1204                    , attribute21
1205                    , attribute22
1206                    , attribute23
1207                    , attribute24
1208                    , attribute25
1209                    , attribute26
1210                    , attribute27
1211                    , attribute28
1212                    , attribute29
1213                    , attribute30
1214                    , attribute31
1215                    , attribute32
1216                    , attribute33
1217                    , attribute34
1218                    , attribute35
1219                    , attribute36
1220                    , attribute37
1221                    , attribute38
1222                    , attribute39
1223                    , attribute40
1224                    , attribute41
1225                    , attribute42
1226                    , attribute43
1227                    , attribute44
1228                    , attribute45
1229                    , attribute46
1230                    , attribute47
1231                    , attribute48
1232                    , attribute49
1233                    , attribute50
1234                    , attribute51
1235                    , attribute52
1236                    , attribute53
1237                    , attribute54
1238                    , attribute55
1239                    , attribute56
1240                    , attribute57
1241                    , attribute58
1242                    , attribute59
1243                    , attribute60
1244                    , attribute61
1245                    , attribute62
1246                    , attribute63
1247                    , attribute64
1248                    , attribute65
1249                    , attribute66
1250                    , attribute67
1251                    , attribute68
1252                    , attribute69
1253                    , attribute70
1254                    , attribute71
1255                    , attribute72
1256                    , attribute73
1257                    , attribute74
1258                    , attribute75
1259                    , attribute76
1260                    , attribute77
1261                    , attribute78
1262                    , attribute79
1263                    , attribute80
1264                    , attribute81
1265                    , attribute82
1266                    , attribute83
1267                    , attribute84
1268                    , attribute85
1269                    , attribute86
1270                    , attribute87
1271                    , attribute88
1272                    , attribute89
1273                    , attribute90
1274                    , attribute91
1275                    , attribute92
1276                    , attribute93
1277                    , attribute94
1278                    , attribute95
1279                    , attribute96
1280                    , attribute97
1281                    , attribute98
1282                    , attribute99
1283                    , attribute100
1284                    , comm_lines_api_id
1285                    , conc_batch_id
1286                    , process_batch_id
1287                    , salesrep_number
1288                    , rollup_date
1289                    , source_doc_id
1290                    , source_doc_type
1291                    , created_by
1292                    , creation_date
1293                    , last_updated_by
1294                    , last_update_date
1295                    , last_update_login
1296                    , transaction_currency_code
1297                    , exchange_rate
1298                    , acctd_transaction_amount
1299                    , trx_id
1300                    , trx_line_id
1301                    , trx_sales_line_id
1302                    , quantity
1303                    , source_trx_number
1304                    , discount_percentage
1305                    , margin_percentage
1306                    , source_trx_id
1307                    , source_trx_line_id
1308                    , source_trx_sales_line_id
1309                    , negated_flag
1310                    , customer_id
1311                    , inventory_item_id
1312                    , order_number
1313                    , booked_date
1314                    , invoice_number
1315                    , invoice_date
1316                    , adjust_date
1317                    , adjusted_by
1318                    , revenue_type
1319                    , adjust_rollup_flag
1320                    , adjust_comments
1321                    , adjust_status
1322                    , line_number
1323                    , bill_to_address_id
1324                    , ship_to_address_id
1325                    , bill_to_contact_id
1326                    , ship_to_contact_id
1327                    , adj_comm_lines_api_id
1328                    , pre_defined_rc_flag
1329                    , rollup_flag
1330                    , forecast_id
1331                    , upside_quantity
1332                    , upside_amount
1333                    , uom_code
1334                    , reason_code
1335                    , TYPE
1336                    , pre_processed_code
1337                    , quota_id
1338                    , srp_plan_assign_id
1339                    , role_id
1340                    , comp_group_id
1341                    , commission_amount
1342                    , employee_number
1343                    , reversal_flag
1344                    , reversal_header_id
1345                    , sales_channel
1346                    , object_version_number
1347                    , split_pct
1348                    , split_status
1349                    , org_id
1350                    , terr_id
1351                    , terr_name
1352                    , preserve_credit_override_flag -- to ensure this is not null
1353                     )
1354           SELECT p_salesrep_id_tbl(i) -- parent.salesrep_id
1355                , ccla.processed_date
1356                , ccla.processed_period_id
1357                , ROUND(NVL((ccla.transaction_amount * p_split_pctg_tbl(i)) / 100, 0), 2)  -- parent.split_percentage
1358                , ccla.trx_type
1359                , ccla.revenue_class_id
1360                , 'UNLOADED'
1361                , ccla.attribute_category
1362                , ccla.attribute1
1363                , ccla.attribute2
1364                , ccla.attribute3
1365                , ccla.attribute4
1366                , ccla.attribute5
1367                , ccla.attribute6
1368                , ccla.attribute7
1369                , ccla.attribute8
1370                , ccla.attribute9
1371                , ccla.attribute10
1372                , ccla.attribute11
1373                , ccla.attribute12
1374                , ccla.attribute13
1375                , ccla.attribute14
1376                , ccla.attribute15
1377                , ccla.attribute16
1378                , ccla.attribute17
1379                , ccla.attribute18
1380                , ccla.attribute19
1381                , ccla.attribute20
1382                , ccla.attribute21
1383                , ccla.attribute22
1384                , ccla.attribute23
1385                , ccla.attribute24
1386                , ccla.attribute25
1387                , ccla.attribute26
1388                , ccla.attribute27
1389                , ccla.attribute28
1390                , ccla.attribute29
1391                , ccla.attribute30
1392                , ccla.attribute31
1393                , ccla.attribute32
1394                , ccla.attribute33
1395                , ccla.attribute34
1396                , ccla.attribute35
1397                , ccla.attribute36
1398                , ccla.attribute37
1399                , ccla.attribute38
1400                , ccla.attribute39
1401                , ccla.attribute40
1402                , ccla.attribute41
1403                , ccla.attribute42
1404                , ccla.attribute43
1405                , ccla.attribute44
1406                , ccla.attribute45
1407                , ccla.attribute46
1408                , ccla.attribute47
1409                , ccla.attribute48
1410                , ccla.attribute49
1411                , ccla.attribute50
1412                , ccla.attribute51
1413                , ccla.attribute52
1414                , ccla.attribute53
1415                , ccla.attribute54
1416                , ccla.attribute55
1417                , ccla.attribute56
1418                , ccla.attribute57
1419                , ccla.attribute58
1420                , ccla.attribute59
1421                , ccla.attribute60
1422                , ccla.attribute61
1423                , ccla.attribute62
1424                , ccla.attribute63
1425                , ccla.attribute64
1426                , ccla.attribute65
1427                , ccla.attribute66
1428                , ccla.attribute67
1429                , ccla.attribute68
1430                , ccla.attribute69
1431                , ccla.attribute70
1432                , ccla.attribute71
1433                , ccla.attribute72
1434                , ccla.attribute73
1435                , ccla.attribute74
1436                , ccla.attribute75
1437                , ccla.attribute76
1438                , ccla.attribute77
1439                , ccla.attribute78
1440                , ccla.attribute79
1441                , ccla.attribute80
1442                , ccla.attribute81
1443                , ccla.attribute82
1444                , ccla.attribute83
1445                , ccla.attribute84
1446                , ccla.attribute85
1447                , ccla.attribute86
1448                , ccla.attribute87
1449                , ccla.attribute88
1450                , ccla.attribute89
1451                , ccla.attribute90
1452                , ccla.attribute91
1453                , ccla.attribute92
1454                , ccla.attribute93
1455                , ccla.attribute94
1456                , ccla.attribute95
1457                , ccla.attribute96
1458                , ccla.attribute97
1459                , ccla.attribute98
1460                , ccla.attribute99
1461                , ccla.attribute100
1462                , cn_comm_lines_api_s.NEXTVAL
1463                , ccla.conc_batch_id
1464                , ccla.process_batch_id
1465                , NULL
1466                , ccla.rollup_date
1467                , ccla.source_doc_id
1468                , ccla.source_doc_type
1469                , g_user_id
1470                , g_sysdate
1471                , g_user_id
1472                , g_sysdate
1473                , g_login_id
1474                , ccla.transaction_currency_code
1475                , ccla.exchange_rate
1476                , NULL
1477                , ccla.trx_id
1478                , ccla.trx_line_id
1479                , ccla.trx_sales_line_id
1480                , ccla.quantity
1481                , ccla.source_trx_number
1482                , ccla.discount_percentage
1483                , ccla.margin_percentage
1484                , ccla.source_trx_id
1485                , ccla.source_trx_line_id
1486                , ccla.source_trx_sales_line_id
1487                , ccla.negated_flag
1488                , ccla.customer_id
1489                , ccla.inventory_item_id
1490                , ccla.order_number
1491                , ccla.booked_date
1492                , ccla.invoice_number
1493                , ccla.invoice_date
1494                , g_sysdate
1495                , g_user_id
1496                , p_rev_type_tbl(i)  -- parent.revenue_type
1497                , ccla.adjust_rollup_flag
1498                , 'Created by TAE'
1499                , ccla.adjust_status
1500                , ccla.line_number
1501                , ccla.bill_to_address_id
1502                , ccla.ship_to_address_id
1503                , ccla.bill_to_contact_id
1504                , ccla.ship_to_contact_id
1505                , ccla.comm_lines_api_id
1506                , ccla.pre_defined_rc_flag
1507                , ccla.rollup_flag
1508                , ccla.forecast_id
1509                , ccla.upside_quantity
1510                , ccla.upside_amount
1511                , ccla.uom_code
1512                , ccla.reason_code
1513                , ccla.TYPE
1514                , ccla.pre_processed_code
1515                , ccla.quota_id
1516                , ccla.srp_plan_assign_id
1517                , p_role_id_tbl(i)  -- parent.role_id
1518                , ccla.comp_group_id
1519                , ccla.commission_amount
1520                , p_emp_no_tbl(i) -- parent.employee_number
1521                , ccla.reversal_flag
1522                , ccla.reversal_header_id
1523                , ccla.sales_channel
1524                , ccla.object_version_number
1525                , p_split_pctg_tbl(i) -- parent.split_percentage
1526                , ccla.split_status
1527                , ccla.org_id
1528                , p_terr_id_tbl(i) -- parent.terr_id
1529                , p_terr_name_tbl(i) -- parent.terr_name
1530                , 'N'  -- to ensure preserve_credit_override_flag is not null
1531             FROM cn_comm_lines_api_all ccla
1532            WHERE ccla.comm_lines_api_id = p_trans_object_id_tbl(i)
1533              AND ccla.org_id = p_org_id
1534              AND p_del_flag_tbl(i) <> 'Y';
1535 
1536  --, table ( cast ( cn_sca_credits_batch_pub.convert_to_table()
1537 --                                                            as cn_sca_insert_tbl_type)) parent
1538   --         WHERE ccla.comm_lines_api_id = parent.trans_object_id
1539     --         AND ccla.org_id = p_org_id
1540       --       AND parent.del_flag <> 'Y';
1541 
1542     END IF;
1543     debugmsg('SCA : End of insert_api_txns '||to_char(sysdate,'dd-mm-rrrr hh24:mi:ss'));
1544     debugmsg('SCA : End of insert_api_txns');
1545   EXCEPTION
1546     WHEN dml_errors THEN
1547       ERRORS  := SQL%BULK_EXCEPTIONS.COUNT;
1548       debugmsg('SCA : Number of transactions that failed : ' || ERRORS);
1549 
1550       /* Log the erroneous txns to log file */
1551       FOR i IN 1 .. ERRORS LOOP
1552         l_error_index  := SQL%BULK_EXCEPTIONS(i).ERROR_INDEX;
1553         debugmsg(
1554              'SCA : Error #'
1555           || i
1556           || ' occurred during comm_lines_api_id : '
1557           || p_trans_object_id_tbl(l_error_index)
1558         );
1559         debugmsg('SCA : Error message is ' || SQLERRM(-SQL%BULK_EXCEPTIONS(i).ERROR_CODE));
1560       END LOOP;
1561     WHEN OTHERS THEN
1562       debugmsg('SCA : Unexpected exception in insert_api_txns');
1563       debugmsg('SCA : SQLCODE : ' || SQLCODE);
1564       debugmsg('SCA : SQLERRM : ' || SQLERRM);
1565       retcode  := 2;
1566       errbuf   := 'CN_SCATM_TAE_PUB.insert_api_txns.others';
1567   END insert_api_txns;
1568 
1569   /* This procedure calls the territory APIs and get the winning */
1570   /* salesreps and split percentages for each transaction        */
1571   PROCEDURE get_credited_txns(
1572     p_where_clause IN            VARCHAR2
1573   , p_request_id   IN            NUMBER
1574   , errbuf         IN OUT NOCOPY VARCHAR2
1575   , retcode        IN OUT NOCOPY VARCHAR2
1576   , p_start_date   IN            DATE
1577   , p_end_date     IN            DATE
1578   , p_org_id       IN            NUMBER
1579   , p_run_mode     IN            VARCHAR2
1580   , p_terr_id      IN            NUMBER
1581   ) IS
1582     l_return_status              VARCHAR2(30);
1583     l_msg_count                  NUMBER;
1584     l_msg_data                   VARCHAR2(3000);
1585     lp_start_date                DATE;
1586     lp_end_date                  DATE;
1587     l_child_program_id_tbl       sub_program_id_type;
1588     l_collect_txn_num_workers    NUMBER;
1589     l_num_of_days                NUMBER;
1590     l_date_span                  NUMBER;
1591     l_where_clause               VARCHAR2(2000);
1592     child_proc_fail_exception    EXCEPTION;
1593 
1594     l_req_id                     NUMBER;
1595     l_count                      NUMBER;
1596   BEGIN
1597     debugmsg('SCA : Start of get_credited_txns');
1598     errbuf   := NULL;
1599     retcode  := 0;
1600     l_collect_txn_num_workers := 0;
1601 
1602     debugmsg('SCA : Populating data to TRANS table');
1603     --Validate STAR DEA INCREMENTAL mode was run or not.
1604 
1605     IF( p_run_mode = 'INCREMENTAL' ) THEN
1606       SELECT count(*)
1607         INTO l_count
1608         FROM   jty_conc_req_summ a
1609        WHERE  a.program_name = 'JTY_STAR'
1610        AND    a.param1       = -1001
1611        AND    a.param2       = 'DEA INCREMENTAL'
1612        AND    a.retcode      = 0;
1613 
1614       IF (l_count = 0) THEN
1615         -- debug message
1616          retcode := 2;
1617          errbuf := 'STAR should be run at least once in DAE INCREMENTAL mode before running Sales Credit Allocation in INCREMENTAL MODE.';
1618          debugmsg(errbuf);
1619          RAISE FND_API.G_EXC_ERROR;
1620       END IF;
1621 
1622       l_count := 0;
1623 
1624       SELECT count(*)
1625       INTO   l_count
1626       FROM   jty_conc_req_summ a
1627       WHERE  a.program_name = 'JTY_STAR'
1628       AND    a.param1       = -1001
1629       AND    a.retcode      = 0
1630       AND a.param2   = 'DATE EFFECTIVE'
1631       AND request_date  >  (  SELECT MAX(request_date)
1632                               FROM jty_conc_req_summ a
1633                               WHERE a.program_name = 'JTY_STAR'
1634                               AND a.retcode          = 0
1635                               AND a.param1   = -1001
1636                               AND a.param2   = 'DEA INCREMENTAL' );
1637 
1638       IF (l_count > 0) THEN
1639         -- debug message
1640         retcode := 2;
1641         errbuf  := 'Last run mode of STAR is DEA TOTAL. SCA can''t be run in incremental mode';
1642         debugmsg(errbuf);
1643         RAISE    FND_API.G_EXC_ERROR;
1644       END IF;
1645     END IF;
1646 
1647     get_where_clause(
1648       p_start_date                 => p_start_date
1649     , p_end_date                   => p_end_date
1650     , p_org_id                     => p_org_id
1651     , p_run_mode                   => p_run_mode
1652     , x_where_clause               => l_where_clause
1653     , errbuf                       => errbuf
1654     , retcode                      => retcode
1655     );
1656 
1657     /* insert the selected transactions from cn_comm_lines_api_all table */
1658     /* to the interface table jtf_tae_1001_sc_dea_trans                  */
1659     jty_assign_bulk_pub.collect_trans_data(
1660       p_api_version_number         => 1.0
1661     , p_init_msg_list              => fnd_api.g_false
1662     , p_source_id                  => -1001
1663     , p_trans_id                   => -1002
1664     , p_program_name               => 'SALES/INCENTIVE COMPENSATION PROGRAM'
1665     , p_mode                       => 'DATE EFFECTIVE'
1666     , p_where                      => l_where_clause
1667     , p_no_of_workers              => g_num_workers
1668     , p_percent_analyzed           => 20
1669     ,   -- this value can be either a profile option or a parameter to conc program
1670       p_request_id                 => p_request_id
1671     ,   -- request id of the concurrent program
1672       x_return_status              => l_return_status
1673     , x_msg_count                  => l_msg_count
1674     , x_msg_data                   => l_msg_data
1675     , errbuf                       => errbuf
1676     , retcode                      => retcode
1677     , p_oic_mode                   => 'CLEAR'
1678     );
1679 
1680     IF (retcode <> 0) THEN
1681       debugmsg('SCA : jty_assign_bulk_pub.collect_trans_data has failed');
1682       RAISE fnd_api.g_exc_error;
1683     END IF;
1684 
1685     debugmsg('SCA : jty_assign_bulk_pub.collect_trans_data with mode CLEAR completed successfully. ');
1686 
1687     lp_start_date := p_start_date;
1688     lp_end_date   := p_end_date;
1689 
1690     l_child_program_id_tbl := sub_program_id_type();
1691     l_date_span   :=   (p_end_date - p_start_date);
1692 
1693     IF(l_date_span <=  g_num_workers) THEN
1694         l_num_of_days := 1;
1695     ELSE
1696         l_num_of_days :=  round(l_date_span/g_num_workers);
1697     END IF;
1698 
1699     WHILE trunc(lp_start_date) < ( p_end_date + 1)
1700     LOOP
1701        l_collect_txn_num_workers := l_collect_txn_num_workers +1;
1702 
1703        IF (l_collect_txn_num_workers > g_num_workers) THEN
1704          EXIT;
1705        END IF;
1706 
1707        lp_end_date := trunc(lp_start_date) + (l_num_of_days-1);
1708 
1709        IF ((lp_end_date > p_end_date) or (l_collect_txn_num_workers = g_num_workers))
1710        THEN
1711           lp_end_date :=p_end_date;
1712        END IF;
1713 
1714        IF g_num_workers = 1
1715        THEN
1716           lp_end_date :=p_end_date;
1717        END IF;
1718 
1719        debugmsg('SCA:lp_start_date  ' || to_char(lp_start_date, 'DD-MON-YY:hh:mm:ss'));
1720        debugmsg('SCA:lp_end_date ' || to_char(lp_end_date, 'DD-MON-YY:hh:mm:ss'));
1721        debugmsg('SCA : Submitting Child Request '|| l_collect_txn_num_workers ||
1722                  ' for start date = '||lp_start_date ||' and end_date = '||lp_end_date);
1723 
1724 
1725        l_req_id := FND_REQUEST.SUBMIT_REQUEST('CN', -- Application
1726                                        'CN_SCATM_COLLECT_TRANS_BATCH'	  , -- Concurrent Program
1727                                        '', -- description
1728                                        '', -- start time
1729                                        FALSE -- sub request flag
1730                                       ,lp_start_date
1731                                       ,lp_end_date
1732                                       , p_org_id
1733                                       , p_run_mode
1734                                       ,g_num_workers
1735                                       ,p_request_id
1736                                         );
1737        COMMIT;
1738 
1739        lp_start_date := lp_end_date  + 1;
1740 
1741        IF  l_req_id = 0 THEN
1742           retcode := 2;
1743           errbuf := fnd_message.get;
1744           raise child_proc_fail_exception;
1745        ELSE
1746           -- storing the request ids in an array
1747           l_child_program_id_tbl.EXTEND;
1748           l_child_program_id_tbl(l_child_program_id_tbl.LAST):=l_req_id;
1749        END IF;
1750      END LOOP;
1751 
1752      debugmsg('SCA : CN_SCATM_TAE_PUB.Parent Process starts Waiting For Collect Transaction
1753      Child Processes to complete');
1754 
1755      parent_conc_wait(l_child_program_id_tbl,retcode,errbuf);
1756 
1757      COMMIT;
1758 
1759      IF retcode = 2
1760      THEN
1761         raise fnd_api.g_exc_error;
1762      END IF;
1763 
1764     /* insert the selected transactions from cn_comm_lines_api_all table */
1765     /* to the interface table jtf_tae_1001_sc_dea_trans                  */
1766     jty_assign_bulk_pub.collect_trans_data(
1767       p_api_version_number         => 1.0
1768     , p_init_msg_list              => fnd_api.g_false
1769     , p_source_id                  => -1001
1770     , p_trans_id                   => -1002
1771     , p_program_name               => 'SALES/INCENTIVE COMPENSATION PROGRAM'
1772     , p_mode                       => 'DATE EFFECTIVE'
1773     , p_where                      => l_where_clause
1774     , p_no_of_workers              => g_num_workers
1775     , p_percent_analyzed           => 20
1776     ,   -- this value can be either a profile option or a parameter to conc program
1777       p_request_id                 => p_request_id
1778     ,   -- request id of the concurrent program
1779       x_return_status              => l_return_status
1780     , x_msg_count                  => l_msg_count
1781     , x_msg_data                   => l_msg_data
1782     , errbuf                       => errbuf
1783     , retcode                      => retcode
1784     , p_oic_mode                   => 'POST'
1785     );
1786 
1787     IF (retcode <> 0) THEN
1788       debugmsg('SCA : jty_assign_bulk_pub.collect_trans_data has failed');
1789       RAISE fnd_api.g_exc_error;
1790     END IF;
1791 
1792     debugmsg('SCA : jty_assign_bulk_pub.collect_trans_data with oic_mode '||
1793     'POST completed successfully');
1794     debugmsg('SCA : Populating data to WINNERS table');
1795     /* this api will apply the rules to the transactions present in jtf_tae_1001_sc_dea_trans       */
1796     /* and populate the winning salesreps for each transaction in the table jtf_tae_1001_sc_winners */
1797     FOR l_worker_id IN 1..g_num_workers
1798     LOOP
1799 
1800        debugmsg('SCA : Submitting Child Request for worker id '|| l_worker_id
1801        ||' with p_oic_mode as MATCH/POPULATE' );
1802 
1803        l_req_id := FND_REQUEST.SUBMIT_REQUEST('CN', -- Application
1804                                        'CN_SCATM_PROCESS_WINNERS_BATCH'	  , -- Concurrent Program
1805                                        '', -- description
1806                                        '', -- start time
1807                                        FALSE -- sub request flag
1808                                       , l_worker_id
1809                                       , 'MATCH/POPULATE' -- p_oic_mode
1810 									  , p_terr_id);
1811 
1812        COMMIT;
1813 
1814        IF  l_req_id = 0 THEN
1815           retcode := 2;
1816           errbuf := fnd_message.get;
1817           raise child_proc_fail_exception;
1818        ELSE
1819           -- storing the request ids in an array
1820           l_child_program_id_tbl.EXTEND;
1821           l_child_program_id_tbl(l_child_program_id_tbl.LAST):=l_req_id;
1822        END IF;
1823 
1824     debugmsg('SCA : CN_SCATM_TAE_PUB.Parent Process starts Waiting For Child Get Winners
1825     Processes to complete');
1826 
1827     END LOOP;
1828 
1829     parent_conc_wait(l_child_program_id_tbl,retcode,errbuf);
1830     COMMIT;
1831 
1832     IF retcode = 2
1833     THEN
1834        raise fnd_api.g_exc_error;
1835     END IF;
1836 
1837    debugmsg('SCA : CN_SCATM_TAE_PUB. Process_Match successful, now will generate stats ');
1838 
1839     batch_process_winners(
1840      errbuf       => errbuf
1841    , retcode      => retcode
1842    , p_worker_id  =>  0
1843    , p_oic_mode   => 'MATCH/POST'
1844    , p_terr_id    => p_terr_id
1845    );
1846 
1847    IF (retcode <> 0) THEN
1848       debugmsg('SCA : jty_assign_bulk_pub.collect_trans_data has failed while '||
1849       ' trying to generate stats on matches table ');
1850       RAISE fnd_api.g_exc_error;
1851     END IF;
1852 
1853   debugmsg('SCA : CN_SCATM_TAE_PUB. Generate stats on matches table successful');
1854 
1855     --Code added here to handle process_match and process_winners index stats
1856     -- in parallel
1857         debugmsg('SCA : Populating data to WINNERS table');
1858     /* this api will apply the rules to the transactions present in jtf_tae_1001_sc_dea_trans       */
1859     /* and populate the winning salesreps for each transaction in the table jtf_tae_1001_sc_winners */
1860     FOR l_worker_id IN 1..g_num_workers
1861     LOOP
1862 
1863        debugmsg('SCA : Submitting Child Request for worker id '|| l_worker_id);
1864 
1865        l_req_id := FND_REQUEST.SUBMIT_REQUEST('CN', -- Application
1866                                        'CN_SCATM_PROCESS_WINNERS_BATCH'	  , -- Concurrent Program
1867                                        '', -- description
1868                                        '', -- start time
1869                                        FALSE -- sub request flag
1870                                       ,l_worker_id
1871                                       , 'WINNER/POPULATE' -- p_oic_mode
1872 									  , p_terr_id);
1873        COMMIT;
1874 
1875        IF  l_req_id = 0 THEN
1876           retcode := 2;
1877           errbuf := fnd_message.get;
1878           raise child_proc_fail_exception;
1879        ELSE
1880           -- storing the request ids in an array
1881           l_child_program_id_tbl.EXTEND;
1882           l_child_program_id_tbl(l_child_program_id_tbl.LAST):=l_req_id;
1883        END IF;
1884 
1885      debugmsg('SCA : CN_SCATM_TAE_PUB.Parent Process starts Waiting For Child Get Winners Processes to complete');
1886 
1887     END LOOP;
1888 
1889     parent_conc_wait(l_child_program_id_tbl,retcode,errbuf);
1890     COMMIT;
1891 
1892     IF retcode = 2
1893     THEN
1894        raise fnd_api.g_exc_error;
1895     END IF;
1896 
1897 
1898     debugmsg('SCA : CN_SCATM_TAE_PUB. Process_winners successful, now will generate stats ');
1899 
1900     batch_process_winners(
1901      errbuf       => errbuf
1902    , retcode      => retcode
1903    , p_worker_id  =>  0
1904    , p_oic_mode   => 'WINNER/POST'
1905    , p_terr_id	  => p_terr_id
1906    );
1907 
1908 
1909    IF (retcode <> 0) THEN
1910       debugmsg('SCA : jty_assign_bulk_pub.collect_trans_data has failed while '||
1911       ' trying to generate stats on winners table ');
1912       RAISE fnd_api.g_exc_error;
1913     END IF;
1914     -- End of Addition
1915     debugmsg('SCA : jty_assign_bulk_pub.generate stats on winners successful');
1916     debugmsg('SCA : jty_assign_bulk_pub.get_winners completed successfully');
1917     debugmsg('SCA : End of get_credited_txns');
1918 
1919   EXCEPTION
1920     WHEN fnd_api.g_exc_error THEN
1921       debugmsg('SCA : CN_SCATM_TAE_PUB.get_credited_txns.g_exc_error');
1922       debugmsg('SCA : SQLCODE : ' || SQLCODE);
1923       debugmsg('SCA : SQLERRM : ' || SQLERRM);
1924     WHEN child_proc_fail_exception THEN
1925       debugmsg('SCA : CN_SCATM_TAE_PUB.get_credited_txns.Child Proc Failed exception');
1926       debugmsg('SCA : SQLCODE : ' || SQLCODE);
1927       debugmsg('SCA : SQLERRM : ' || SQLERRM);
1928     WHEN OTHERS THEN
1929       debugmsg('SCA : Unexpected exception in get_credited_txns');
1930       debugmsg('SCA : SQLCODE : ' || SQLCODE);
1931       debugmsg('SCA : SQLERRM : ' || SQLERRM);
1932       retcode  := 2;
1933       errbuf   := 'CN_SCATM_TAE_PUB.get_credited_txns.others';
1934   END get_credited_txns;
1935 
1936   /* This procedure gets the winning salesreps, split percentages and revenue types from the           */
1937   /* table jtf_tae_1001_sc_winners and create credited transactions in the table cn_comm_lines_api_all */
1938   PROCEDURE process_new_txns(
1939     p_org_id IN            NUMBER
1940   , p_worker_id IN NUMBER
1941   , errbuf   IN OUT NOCOPY VARCHAR2
1942   , retcode  IN OUT NOCOPY VARCHAR2
1943   ) IS
1944     TYPE l_credited_txn_curtyp IS REF CURSOR;
1945 
1946     c_credited_txn_cur    l_credited_txn_curtyp;
1947     l_ffname_split_pctg   VARCHAR2(15);
1948     l_ffname_rev_type     VARCHAR2(15);
1949     l_no_of_errors        NUMBER;
1950     l_trans_object_id_tbl g_trans_object_id_tbl_type;
1951     l_terr_id_tbl         g_terr_id_tbl_type;
1952     l_terr_name_tbl       g_terr_name_tbl_type;
1953     l_salesrep_id_tbl     g_salesrep_id_tbl_type;
1954     l_emp_no_tbl          g_emp_no_tbl_type;
1955     l_role_id_tbl         g_role_id_tbl_type;
1956     l_split_pctg_tbl      g_split_pctg_tbl_type;
1957     l_rev_type_tbl        g_rev_type_tbl_type;
1958     l_del_flag_tbl        g_del_flag_tbl_type;
1959   BEGIN
1960     debugmsg('SCA : Start of process_new_txns');
1961     errbuf   := NULL;
1962     retcode  := 0;
1963     /* Get name of the flex fields used in TM */
1964     /* to store split pctg and revenue type   */
1965     get_flex_field_names(
1966       p_ffname_split_pctg          => l_ffname_split_pctg
1967     , p_ffname_rev_type            => l_ffname_rev_type
1968     , errbuf                       => errbuf
1969     , retcode                      => retcode
1970     );
1971 
1972     IF (retcode <> 0) THEN
1973       debugmsg('SCA : CN_SCATM_TAE_PUB.get_flex_field_names has failed');
1974       RAISE fnd_api.g_exc_error;
1975     END IF;
1976 
1977     debugmsg('SCA :  CN_SCATM_TAE_PUB.get_flex_field_names completed successfully');
1978 
1979     /* Cursor definition to select all winning resources from winners table */
1980     OPEN c_credited_txn_cur
1981      FOR    'SELECT /*+ leading(a) cardinality(a,100) */ a.trans_object_id, '
1982          || '       a.terr_id,         '
1983          || '       c.name,            '
1984          || '       d.salesrep_id,     '
1985          || '       d.employee_number, '
1986          || '       a.role_id,         '
1987          || '       ''N'',             '
1988          || '       b.'
1989          || l_ffname_split_pctg
1990          || ', '
1991          || '       b.'
1992          || l_ffname_rev_type
1993          || ' '
1994          || 'FROM   jtf_tae_1001_sc_winners a, '
1995          || '       jtf_terr_rsc_all        b, '
1996          || '       jtf_terr_all            c, '
1997          || '       cn_salesreps            d  '
1998          || 'WHERE  a.terr_rsc_id = b.terr_rsc_id '
1999          || 'AND    a.terr_id     = c.terr_id '
2000          || 'AND    a.resource_id = d.resource_id '
2001          || 'AND    a.worker_id = '||p_worker_id;
2002 
2003     /* loop through the winning resources in batches , "g_fetch_limit" records per batch, */
2004     /* and insert the records in the table cn_comm_lines_api_all                          */
2005     LOOP
2006       FETCH c_credited_txn_cur
2007       BULK COLLECT INTO l_trans_object_id_tbl
2008            , l_terr_id_tbl
2009            , l_terr_name_tbl
2010            , l_salesrep_id_tbl
2011            , l_emp_no_tbl
2012            , l_role_id_tbl
2013            , l_del_flag_tbl
2014            , l_split_pctg_tbl
2015            , l_rev_type_tbl LIMIT g_fetch_limit;
2016 
2017       EXIT WHEN l_trans_object_id_tbl.COUNT <= 0;
2018       debugmsg('SCA : Number of winning rows returned : ' || l_trans_object_id_tbl.COUNT);
2019       /* insert the credited txns into api table */
2020       insert_api_txns(
2021         p_org_id                     => p_org_id
2022       , p_trans_object_id_tbl        => l_trans_object_id_tbl
2023       , p_salesrep_id_tbl            => l_salesrep_id_tbl
2024       , p_emp_no_tbl                 => l_emp_no_tbl
2025       , p_role_id_tbl                => l_role_id_tbl
2026       , p_split_pctg_tbl             => l_split_pctg_tbl
2027       , p_rev_type_tbl               => l_rev_type_tbl
2028       , p_terr_id_tbl                => l_terr_id_tbl
2029       , p_terr_name_tbl              => l_terr_name_tbl
2030       , p_del_flag_tbl               => l_del_flag_tbl
2031       , errbuf                       => errbuf
2032       , retcode                      => retcode
2033       );
2034 
2035       IF (retcode <> 0) THEN
2036         debugmsg('SCA : CN_SCATM_TAE_PUB.insert_api_txns has failed');
2037         RAISE fnd_api.g_exc_error;
2038       END IF;
2039 
2040       debugmsg('SCA : CN_SCATM_TAE_PUB.insert_api_txns completed successfully');
2041     END LOOP;
2042 
2043     CLOSE c_credited_txn_cur;
2044 
2045     debugmsg('SCA : End of process_new_txns');
2046   EXCEPTION
2047     WHEN fnd_api.g_exc_error THEN
2048       IF c_credited_txn_cur%ISOPEN THEN
2049         CLOSE c_credited_txn_cur;
2050       END IF;
2051 
2052       debugmsg('SCA : CN_SCATM_TAE_PUB.process_new_txns.g_exc_error');
2053       debugmsg('SCA : SQLCODE : ' || SQLCODE);
2054       debugmsg('SCA : SQLERRM : ' || SQLERRM);
2055     WHEN OTHERS THEN
2056       IF c_credited_txn_cur%ISOPEN THEN
2057         CLOSE c_credited_txn_cur;
2058       END IF;
2059 
2060       debugmsg('SCA : Unexpected exception in process_new_txns');
2061       debugmsg('SCA : SQLCODE : ' || SQLCODE);
2062       debugmsg('SCA : SQLERRM : ' || SQLERRM);
2063       retcode  := 2;
2064       errbuf   := 'CN_SCATM_TAE_PUB.process_new_txns.others';
2065   END process_new_txns;
2066 
2067   /* This procedure does the following for txns that have been loaded for calc */
2068   /*         -- obsolete the corresponding record in cn_commission_headers_all */
2069   /*         -- create a reversal entry in cn_comm_lines_api_all               */
2070   PROCEDURE api_negate_record(
2071     p_api_id_tbl IN OUT NOCOPY g_comm_lines_api_id_tbl_type
2072   , p_rowid_tbl  IN OUT NOCOPY g_rowid_tbl_type
2073   , errbuf       IN OUT NOCOPY VARCHAR2
2074   , retcode      IN OUT NOCOPY VARCHAR2
2075   ) IS
2076   BEGIN
2077     debugmsg('SCA : Start of api_negate_record');
2078     errbuf   := NULL;
2079     retcode  := 0;
2080 
2081     IF (p_api_id_tbl.COUNT <= 0) THEN
2082       RETURN;
2083     END IF;
2084 
2085     /* create the reversal entry in api table */
2086     FORALL i IN p_rowid_tbl.FIRST .. p_rowid_tbl.LAST
2087       INSERT INTO cn_comm_lines_api_all
2088                   (
2089                    salesrep_id
2090                  , processed_date
2091                  , processed_period_id
2092                  , transaction_amount
2093                  , trx_type
2094                  , revenue_class_id
2095                  , load_status
2096                  , attribute_category
2097                  , attribute1
2098                  , attribute2
2099                  , attribute3
2100                  , attribute4
2101                  , attribute5
2102                  , attribute6
2103                  , attribute7
2104                  , attribute8
2105                  , attribute9
2106                  , attribute10
2107                  , attribute11
2108                  , attribute12
2109                  , attribute13
2110                  , attribute14
2111                  , attribute15
2112                  , attribute16
2113                  , attribute17
2114                  , attribute18
2115                  , attribute19
2116                  , attribute20
2117                  , attribute21
2118                  , attribute22
2119                  , attribute23
2120                  , attribute24
2121                  , attribute25
2122                  , attribute26
2123                  , attribute27
2124                  , attribute28
2125                  , attribute29
2126                  , attribute30
2127                  , attribute31
2128                  , attribute32
2129                  , attribute33
2130                  , attribute34
2131                  , attribute35
2132                  , attribute36
2133                  , attribute37
2134                  , attribute38
2135                  , attribute39
2136                  , attribute40
2137                  , attribute41
2138                  , attribute42
2139                  , attribute43
2140                  , attribute44
2141                  , attribute45
2142                  , attribute46
2143                  , attribute47
2144                  , attribute48
2145                  , attribute49
2146                  , attribute50
2147                  , attribute51
2148                  , attribute52
2149                  , attribute53
2150                  , attribute54
2151                  , attribute55
2152                  , attribute56
2153                  , attribute57
2154                  , attribute58
2155                  , attribute59
2156                  , attribute60
2157                  , attribute61
2158                  , attribute62
2159                  , attribute63
2160                  , attribute64
2161                  , attribute65
2162                  , attribute66
2163                  , attribute67
2164                  , attribute68
2165                  , attribute69
2166                  , attribute70
2167                  , attribute71
2168                  , attribute72
2169                  , attribute73
2170                  , attribute74
2171                  , attribute75
2172                  , attribute76
2173                  , attribute77
2174                  , attribute78
2175                  , attribute79
2176                  , attribute80
2177                  , attribute81
2178                  , attribute82
2179                  , attribute83
2180                  , attribute84
2181                  , attribute85
2182                  , attribute86
2183                  , attribute87
2184                  , attribute88
2185                  , attribute89
2186                  , attribute90
2187                  , attribute91
2188                  , attribute92
2189                  , attribute93
2190                  , attribute94
2191                  , attribute95
2192                  , attribute96
2193                  , attribute97
2194                  , attribute98
2195                  , attribute99
2196                  , attribute100
2197                  , comm_lines_api_id
2198                  , conc_batch_id
2199                  , process_batch_id
2200                  , salesrep_number
2201                  , rollup_date
2202                  , source_doc_id
2203                  , source_doc_type
2204                  , created_by
2205                  , creation_date
2206                  , last_updated_by
2207                  , last_update_date
2208                  , last_update_login
2209                  , transaction_currency_code
2210                  , exchange_rate
2211                  , acctd_transaction_amount
2212                  , trx_id
2213                  , trx_line_id
2214                  , trx_sales_line_id
2215                  , quantity
2216                  , source_trx_number
2217                  , discount_percentage
2218                  , margin_percentage
2219                  , source_trx_id
2220                  , source_trx_line_id
2221                  , source_trx_sales_line_id
2222                  , negated_flag
2223                  , customer_id
2224                  , inventory_item_id
2225                  , order_number
2226                  , booked_date
2227                  , invoice_number
2228                  , invoice_date
2229                  , adjust_date
2230                  , adjusted_by
2231                  , revenue_type
2232                  , adjust_rollup_flag
2233                  , adjust_comments
2234                  , adjust_status
2235                  , line_number
2236                  , bill_to_address_id
2237                  , ship_to_address_id
2238                  , bill_to_contact_id
2239                  , ship_to_contact_id
2240                  , adj_comm_lines_api_id
2241                  , pre_defined_rc_flag
2242                  , rollup_flag
2243                  , forecast_id
2244                  , upside_quantity
2245                  , upside_amount
2246                  , uom_code
2247                  , reason_code
2248                  , TYPE
2249                  , pre_processed_code
2250                  , quota_id
2251                  , srp_plan_assign_id
2252                  , role_id
2253                  , comp_group_id
2254                  , commission_amount
2255                  , employee_number
2256                  , reversal_flag
2257                  , reversal_header_id
2258                  , sales_channel
2259                  , object_version_number
2260                  , split_pct
2261                  , split_status
2262                  , org_id
2263                  , terr_id
2264                  , terr_name
2265                   )
2266         SELECT ccla.salesrep_id
2267              , ccla.processed_date
2268              , ccla.processed_period_id
2269              , -1 * NVL(ccla.transaction_amount, 0)
2270              , ccla.trx_type
2271              , ccla.revenue_class_id
2272              , 'UNLOADED'
2273              , ccla.attribute_category
2274              , ccla.attribute1
2275              , ccla.attribute2
2276              , ccla.attribute3
2277              , ccla.attribute4
2278              , ccla.attribute5
2279              , ccla.attribute6
2280              , ccla.attribute7
2281              , ccla.attribute8
2282              , ccla.attribute9
2283              , ccla.attribute10
2284              , ccla.attribute11
2285              , ccla.attribute12
2286              , ccla.attribute13
2287              , ccla.attribute14
2288              , ccla.attribute15
2289              , ccla.attribute16
2290              , ccla.attribute17
2291              , ccla.attribute18
2292              , ccla.attribute19
2293              , ccla.attribute20
2294              , ccla.attribute21
2295              , ccla.attribute22
2296              , ccla.attribute23
2297              , ccla.attribute24
2298              , ccla.attribute25
2299              , ccla.attribute26
2300              , ccla.attribute27
2301              , ccla.attribute28
2302              , ccla.attribute29
2303              , ccla.attribute30
2304              , ccla.attribute31
2305              , ccla.attribute32
2306              , ccla.attribute33
2307              , ccla.attribute34
2308              , ccla.attribute35
2309              , ccla.attribute36
2310              , ccla.attribute37
2311              , ccla.attribute38
2312              , ccla.attribute39
2313              , ccla.attribute40
2314              , ccla.attribute41
2315              , ccla.attribute42
2316              , ccla.attribute43
2317              , ccla.attribute44
2318              , ccla.attribute45
2319              , ccla.attribute46
2320              , ccla.attribute47
2321              , ccla.attribute48
2322              , ccla.attribute49
2323              , ccla.attribute50
2324              , ccla.attribute51
2325              , ccla.attribute52
2326              , ccla.attribute53
2327              , ccla.attribute54
2328              , ccla.attribute55
2329              , ccla.attribute56
2330              , ccla.attribute57
2331              , ccla.attribute58
2332              , ccla.attribute59
2333              , ccla.attribute60
2334              , ccla.attribute61
2335              , ccla.attribute62
2336              , ccla.attribute63
2337              , ccla.attribute64
2338              , ccla.attribute65
2339              , ccla.attribute66
2340              , ccla.attribute67
2341              , ccla.attribute68
2342              , ccla.attribute69
2343              , ccla.attribute70
2344              , ccla.attribute71
2345              , ccla.attribute72
2346              , ccla.attribute73
2347              , ccla.attribute74
2348              , ccla.attribute75
2349              , ccla.attribute76
2350              , ccla.attribute77
2351              , ccla.attribute78
2352              , ccla.attribute79
2353              , ccla.attribute80
2354              , ccla.attribute81
2355              , ccla.attribute82
2356              , ccla.attribute83
2357              , ccla.attribute84
2358              , ccla.attribute85
2359              , ccla.attribute86
2360              , ccla.attribute87
2361              , ccla.attribute88
2362              , ccla.attribute89
2363              , ccla.attribute90
2364              , ccla.attribute91
2365              , ccla.attribute92
2366              , ccla.attribute93
2367              , ccla.attribute94
2368              , ccla.attribute95
2369              , ccla.attribute96
2370              , ccla.attribute97
2371              , ccla.attribute98
2372              , ccla.attribute99
2373              , ccla.attribute100
2374              , cn_comm_lines_api_s.NEXTVAL
2375              , NULL
2376              , NULL
2377              , NULL
2378              , ccla.rollup_date
2379              , NULL
2380              , ccla.source_doc_type
2381              , g_user_id
2382              , g_sysdate
2383              , g_user_id
2384              , g_sysdate
2385              , g_login_id
2386              , ccla.transaction_currency_code
2387              , ccla.exchange_rate
2388              , -1 * NVL(ccla.acctd_transaction_amount, 0)
2389              , NULL
2390              , NULL
2391              , NULL
2392              , -1 * ccla.quantity
2393              , ccla.source_trx_number
2394              , ccla.discount_percentage
2395              , ccla.margin_percentage
2396              , ccla.source_trx_id
2397              , ccla.source_trx_line_id
2398              , ccla.source_trx_sales_line_id
2399              , 'Y'
2400              , ccla.customer_id
2401              , ccla.inventory_item_id
2402              , ccla.order_number
2403              , ccla.booked_date
2404              , ccla.invoice_number
2405              , ccla.invoice_date
2406              , g_sysdate
2407              , g_user_id
2408              , ccla.revenue_type
2409              , ccla.adjust_rollup_flag
2410              , 'Created by TAE'
2411              , 'REVERSAL'
2412              , ccla.line_number
2413              , ccla.bill_to_address_id
2414              , ccla.ship_to_address_id
2415              , ccla.bill_to_contact_id
2416              , ccla.ship_to_contact_id
2417              , ccla.comm_lines_api_id
2418              , ccla.pre_defined_rc_flag
2419              , ccla.rollup_flag
2420              , ccla.forecast_id
2421              , ccla.upside_quantity
2422              , ccla.upside_amount
2423              , ccla.uom_code
2424              , ccla.reason_code
2425              , ccla.TYPE
2426              , ccla.pre_processed_code
2427              , ccla.quota_id
2428              , ccla.srp_plan_assign_id
2429              , ccla.role_id
2430              , ccla.comp_group_id
2431              , ccla.commission_amount
2432              , ccla.employee_number
2433              , 'Y'
2434              , ccha.commission_header_id
2435              , ccla.sales_channel
2436              , ccla.object_version_number
2437              , ccla.split_pct
2438              , ccla.split_status
2439              , ccla.org_id
2440              , ccla.terr_id
2441              , ccla.terr_name
2442           FROM cn_comm_lines_api ccla, cn_commission_headers_all ccha
2443          WHERE ccla.ROWID = p_rowid_tbl(i)
2444            AND ccha.comm_lines_api_id = ccla.comm_lines_api_id
2445            AND (ccha.adjust_status NOT IN('FROZEN', 'REVERSAL')) --OR(adjust_status IS NULL))
2446            AND ccha.trx_type NOT IN('ITD', 'GRP', 'THR');
2447     /* update the corresponding records in commission_headers */
2448     FORALL i IN p_api_id_tbl.FIRST .. p_api_id_tbl.LAST
2449       UPDATE cn_commission_headers
2450          SET adjust_status = 'FROZEN'
2451            , reversal_header_id =
2452                (SELECT commission_header_id
2453                   FROM cn_commission_headers_all
2454                  WHERE comm_lines_api_id = p_api_id_tbl(i)
2455                    AND (adjust_status NOT IN('FROZEN', 'REVERSAL'))-- OR(adjust_status IS NULL))
2456                    AND trx_type NOT IN('ITD', 'GRP', 'THR'))
2457            , reversal_flag = 'Y'
2458            , adjust_date = g_sysdate
2459            , adjusted_by = g_user_id
2460            , adjust_comments = 'Created by SCA'
2461            , last_update_date = g_sysdate
2462            , last_updated_by = g_user_id
2463            , last_update_login = g_login_id
2464        WHERE comm_lines_api_id = p_api_id_tbl(i);
2465     debugmsg('SCA : End of api_negate_record');
2466   EXCEPTION
2467     WHEN OTHERS THEN
2468       debugmsg('SCA : Unexpected exception in api_negate_record');
2469       debugmsg('SCA : SQLCODE : ' || SQLCODE);
2470       debugmsg('SCA : SQLERRM : ' || SQLERRM);
2471       retcode  := 2;
2472       errbuf   := 'CN_SCATM_TAE_PUB.api_negate_record.others';
2473   END api_negate_record;
2474 
2475   /* This procedure deletes the child transaction records      */
2476   /* from api table which have not been loaded for calculation */
2477   PROCEDURE handle_unloaded_txns(
2478     l_unloaded_txn_tbl IN OUT NOCOPY g_rowid_tbl_type
2479   , p_rowid       IN            ROWID
2480   , p_update_flag IN            BOOLEAN
2481   , errbuf        IN OUT NOCOPY VARCHAR2
2482   , retcode       IN OUT NOCOPY VARCHAR2
2483   ) IS
2484     l_no_of_records NUMBER;
2485   BEGIN
2486     debugmsg('SCA : Start of handle_unloaded_txns');
2487     errbuf           := NULL;
2488     retcode          := 0;
2489 
2490     /* Store the txn in the global pl/sql table if a valid txn is passed */
2491     IF (p_rowid IS NOT NULL) THEN
2492       l_unloaded_txn_tbl.EXTEND;
2493       l_unloaded_txn_tbl(l_unloaded_txn_tbl.LAST)  := p_rowid;
2494     END IF;
2495 
2496     l_no_of_records  := l_unloaded_txn_tbl.COUNT;
2497 
2498     /* change DB if the # of records in the pl/sql table becomes greater than        */
2499     /* "g_fetch_limit" or if the procedure is called exclusively to update the table */
2500     IF (l_no_of_records > 0) THEN
2501       IF ((l_no_of_records >= g_fetch_limit) OR(p_update_flag)) THEN
2502         FORALL i IN l_unloaded_txn_tbl.FIRST .. l_unloaded_txn_tbl.LAST
2503           DELETE      cn_comm_lines_api_all
2504                 WHERE ROWID = l_unloaded_txn_tbl(i);
2505         l_unloaded_txn_tbl.TRIM(l_no_of_records);
2506       END IF;
2507     END IF;
2508 
2509     debugmsg('SCA : End of handle_unloaded_txns');
2510   EXCEPTION
2511     WHEN OTHERS THEN
2512       debugmsg('SCA : Unexpected exception in handle_unloaded_txns');
2513       debugmsg('SCA : SQLCODE : ' || SQLCODE);
2514       debugmsg('SCA : SQLERRM : ' || SQLERRM);
2515       retcode  := 2;
2516       errbuf   := 'CN_SCATM_TAE_PUB.handle_unloaded_txns.others';
2517   END handle_unloaded_txns;
2518 
2519   /* This procedure processes the child transactions that have been loaded for calc */
2520   PROCEDURE handle_loaded_txns(
2521     l_loaded_txn_rowid_tbl IN OUT NOCOPY g_rowid_tbl_type
2522   , l_loaded_txn_comid_tbl IN OUT NOCOPY g_comm_lines_api_id_tbl_type
2523   , p_rowid       IN            ROWID
2524   , p_api_id      IN            NUMBER
2525   , p_update_flag IN            BOOLEAN
2526   , errbuf        IN OUT NOCOPY VARCHAR2
2527   , retcode       IN OUT NOCOPY VARCHAR2
2528   ) IS
2529     l_no_of_records NUMBER;
2530   BEGIN
2531     debugmsg('SCA : Start of handle_loaded_txns');
2532     errbuf           := NULL;
2533     retcode          := 0;
2534 
2535     /* Store the txn in the global pl/sql table if a valid txn is passed */
2536     IF (p_rowid IS NOT NULL) THEN
2537       l_loaded_txn_rowid_tbl.EXTEND;
2538       l_loaded_txn_rowid_tbl(l_loaded_txn_rowid_tbl.LAST)  := p_rowid;
2539       l_loaded_txn_comid_tbl.EXTEND;
2540       l_loaded_txn_comid_tbl(l_loaded_txn_comid_tbl.LAST)  := p_api_id;
2541     END IF;
2542 
2543     l_no_of_records  := l_loaded_txn_rowid_tbl.COUNT;
2544 
2545     /* change DB if the # of records in the pl/sql table becomes greater than        */
2546     /* "g_fetch_limit" or if the procedure is called exclusively to update the table */
2547     IF (l_no_of_records > 0) THEN
2548       IF ((l_no_of_records >= g_fetch_limit) OR(p_update_flag)) THEN
2549         api_negate_record(
2550           p_api_id_tbl                 => l_loaded_txn_comid_tbl
2551         , p_rowid_tbl                  => l_loaded_txn_rowid_tbl
2552         , errbuf                       => errbuf
2553         , retcode                      => retcode
2554         );
2555 
2556         IF (retcode <> 0) THEN
2557           debugmsg('SCA : CN_SCATM_TAE_PUB.api_negate_record has failed');
2558           RAISE fnd_api.g_exc_error;
2559         END IF;
2560 
2561         debugmsg('SCA : CN_SCATM_TAE_PUB.api_negate_record completed successfully');
2562         l_loaded_txn_rowid_tbl.TRIM(l_no_of_records);
2563         l_loaded_txn_comid_tbl.TRIM(l_no_of_records);
2564       END IF;
2565     END IF;
2566 
2567     debugmsg('SCA : End of handle_loaded_txns');
2568   EXCEPTION
2569     WHEN fnd_api.g_exc_error THEN
2570       debugmsg('SCA : CN_SCATM_TAE_PUB.handle_loaded_txns.g_exc_error');
2571       debugmsg('SCA : SQLCODE : ' || SQLCODE);
2572       debugmsg('SCA : SQLERRM : ' || SQLERRM);
2573     WHEN OTHERS THEN
2574       debugmsg('SCA : Unexpected exception in handle_loaded_txns');
2575       debugmsg('SCA : SQLCODE : ' || SQLCODE);
2576       debugmsg('SCA : SQLERRM : ' || SQLERRM);
2577       retcode  := 2;
2578       errbuf   := 'CN_SCATM_TAE_PUB.handle_loaded_txns.others';
2579   END handle_loaded_txns;
2580 
2581   /* This procedure gets the winning salesreps, split percentages and revenue types from the           */
2582   /* table jtf_tae_1001_sc_winners and create credited transactions in the table cn_comm_lines_api_all */
2583   PROCEDURE process_all_txns(
2584     p_org_id IN            NUMBER
2585   , p_worker_id IN NUMBER
2586   , errbuf   IN OUT NOCOPY VARCHAR2
2587   , retcode  IN OUT NOCOPY VARCHAR2
2588   ) IS
2589     TYPE l_credited_txn_curtyp IS REF CURSOR;
2590 
2591     TYPE l_txn_amt_tbl_type IS TABLE OF cn_comm_lines_api_all.transaction_amount%TYPE;
2592 
2593     TYPE l_no_of_credits_tbl_type IS TABLE OF NUMBER;
2594 
2595     TYPE l_child_load_status_tbl_type IS TABLE OF cn_comm_lines_api_all.load_status%TYPE;
2596 
2597     c_credited_txn_cur      l_credited_txn_curtyp;
2598     l_ffname_split_pctg     VARCHAR2(15);
2599     l_ffname_rev_type       VARCHAR2(15);
2600     l_error_index           NUMBER;
2601     l_table_index           NUMBER;
2602     l_no_of_credits         NUMBER;
2603     l_api_id                NUMBER;
2604     l_rows_fetched          NUMBER;
2605     l_match_found           BOOLEAN;
2606     l_txn_amt               NUMBER;
2607     l_temp_index            NUMBER;
2608     l_no_of_errors          NUMBER;
2609     l_rowid_tbl             g_rowid_tbl_type;
2610     l_api_id_tbl            g_trans_object_id_tbl_type;
2611     l_terr_id_tbl           g_terr_id_tbl_type;
2612     l_terr_name_tbl         g_terr_name_tbl_type;
2613     l_salesrep_id_tbl       g_salesrep_id_tbl_type;
2614     l_emp_no_tbl            g_emp_no_tbl_type;
2615     l_role_id_tbl           g_role_id_tbl_type;
2616     l_txn_amt_tbl           l_txn_amt_tbl_type;
2617     l_split_pctg_tbl        g_split_pctg_tbl_type;
2618     l_rev_type_tbl          g_rev_type_tbl_type;
2619     l_del_flag_tbl          g_del_flag_tbl_type;
2620     l_no_of_credits_tbl     l_no_of_credits_tbl_type;
2621     l_child_rowid_tbl       g_rowid_tbl_type;
2622     l_child_api_id_tbl      g_trans_object_id_tbl_type;
2623     l_child_salesrep_id_tbl g_salesrep_id_tbl_type;
2624     l_child_txn_amt_tbl     l_txn_amt_tbl_type;
2625     l_child_role_id_tbl     g_role_id_tbl_type;
2626     l_child_terr_id_tbl     g_terr_id_tbl_type;
2627     l_child_split_pctg_tbl  g_split_pctg_tbl_type;
2628     l_child_rev_type_tbl    g_rev_type_tbl_type;
2629     l_child_load_status_tbl l_child_load_status_tbl_type;
2630 
2631     l_unloaded_txn_tbl     g_rowid_tbl_type;
2632     l_loaded_txn_rowid_tbl  g_rowid_tbl_type;
2633     l_loaded_txn_comid_tbl g_comm_lines_api_id_tbl_type;
2634 
2635     l_count NUMBER; -- Added for bug 8538923
2636 
2637     CURSOR get_child_records (p_api_id NUMBER) IS
2638     --     SELECT     ROWID
2639     --                 , comm_lines_api_id
2640     --                 , load_status
2641     --                 , salesrep_id
2642     --                 , transaction_amount
2643     --                 , role_id
2644     --                 , terr_id
2645     --                 , split_pct
2646     --                 , revenue_type
2647     --              FROM cn_comm_lines_api_all
2648     --             WHERE load_status NOT IN('OBSOLETE', 'FILTERED')
2649     --               AND adjust_status NOT IN('FROZEN', 'REVERSAL')
2650     --               AND comm_lines_api_id = p_api_id
2651     --      UNION ALL
2652       SELECT     ROWID
2653                  , comm_lines_api_id
2654                  , load_status
2655                  , salesrep_id
2656                  , transaction_amount
2657                  , role_id
2658                  , terr_id
2659                  , split_pct
2660                  , revenue_type
2661               FROM cn_comm_lines_api_all
2662              WHERE load_status NOT IN('OBSOLETE', 'FILTERED')
2663                AND adjust_status NOT IN('FROZEN', 'REVERSAL')
2664                START WITH COMM_LINES_API_ID = p_api_id
2665                CONNECT BY PRIOR COMM_LINES_API_ID = ADJ_COMM_LINES_API_ID;
2666 
2667     --Added the cursor below for bug 	8538923
2668     CURSOR get_child_records_for_rev_txns (
2669     p_api_id NUMBER,
2670     p_revenue_type cn_comm_lines_api_all.REVENUE_TYPE%TYPE,
2671     p_split_pct  cn_comm_lines_api_all.SPLIT_PCT%TYPE,
2672     p_terr_id  cn_comm_lines_api_all.TERR_ID%TYPE,
2673     p_role_id  cn_comm_lines_api_all.ROLE_ID%TYPE,
2674     p_transaction_amount  cn_comm_lines_api_all.TRANSACTION_AMOUNT%TYPE,
2675     p_salesrep_id  cn_comm_lines_api_all.SALESREP_ID%TYPE
2676     ) IS
2677       SELECT  count(*)
2678               FROM cn_comm_lines_api_all
2679              WHERE load_status NOT IN('OBSOLETE', 'FILTERED')
2680                AND salesrep_id= p_salesrep_id
2681                AND transaction_amount = -1*p_transaction_amount
2682                AND NVL(role_id, -1) = p_role_id
2683                AND terr_id = p_terr_id
2684                AND split_pct= p_split_pct
2685                AND revenue_type =p_revenue_type
2686                START WITH COMM_LINES_API_ID = p_api_id
2687                CONNECT BY PRIOR COMM_LINES_API_ID = ADJ_COMM_LINES_API_ID;
2688 
2689   BEGIN
2690     debugmsg('SCA : Start of process_all_txns');
2691 
2692     -- initialise the tables
2693     l_unloaded_txn_tbl     := g_rowid_tbl_type();
2694     l_loaded_txn_rowid_tbl := g_rowid_tbl_type();
2695     l_loaded_txn_comid_tbl := g_comm_lines_api_id_tbl_type();
2696 
2697     errbuf   := NULL;
2698     retcode  := 0;
2699     /* Get name of the flex fields used in TM */
2700     /* to store split pctg and revenue type   */
2701     get_flex_field_names(
2702       p_ffname_split_pctg          => l_ffname_split_pctg
2703     , p_ffname_rev_type            => l_ffname_rev_type
2704     , errbuf                       => errbuf
2705     , retcode                      => retcode
2706     );
2707 
2708     IF (retcode <> 0) THEN
2709       debugmsg('SCA : CN_SCATM_TAE_PUB.get_flex_field_names has failed');
2710       RAISE fnd_api.g_exc_error;
2711     END IF;
2712 
2713     debugmsg('SCA :  CN_SCATM_TAE_PUB.get_flex_field_names completed successfully');
2714 
2715     /* Cursor definition to get all the winning resources returned by TAE */
2716     OPEN c_credited_txn_cur
2717      FOR    'SELECT /*+ leading ( a ) cardinality ( a , 100 ) use_nl(a e.s e.re.b) */  d.rowid,                                        '
2718          || '       d.comm_lines_api_id,                            '
2719          || '       a.terr_id,                                      '
2720          || '       c.name,                                         '
2721          || '       e.salesrep_id,                                  '
2722          || '       e.employee_number,                              '
2723          || '       a.role_id,                                      '
2724          || '       d.transaction_amount,                           '
2725          || '       b.'
2726          || l_ffname_split_pctg
2727          || ',                '
2728          || '       b.'
2729          || l_ffname_rev_type
2730          || ',                  '
2731          || '       ''N'',                                          '
2732          || '       count(*) over(partition by d.comm_lines_api_id) '
2733          || 'FROM   jtf_tae_1001_sc_winners a, '
2734          || '       jtf_terr_rsc_all        b, '
2735          || '       jtf_terr_all            c, '
2736          || '       cn_comm_lines_api_all   d, '
2737          || '       cn_salesreps            e  '
2738          || 'WHERE  a.terr_rsc_id = b.terr_rsc_id           '
2739          || 'AND    a.terr_id = c.terr_id                   '
2740          || 'AND    a.trans_object_id = d.comm_lines_api_id '
2741          || 'AND    a.resource_id = e.resource_id '
2742          || 'AND    a.worker_id = '||p_worker_id
2743          || 'ORDER BY d.comm_lines_api_id ';
2744 
2745     /* loop through the winning resources in batches , "g_fetch_limit" records per batch, */
2746     /* and insert the records in the table cn_comm_lines_api_all                          */
2747     LOOP
2748       FETCH c_credited_txn_cur
2749       BULK COLLECT INTO l_rowid_tbl
2750            , l_api_id_tbl
2751            , l_terr_id_tbl
2752            , l_terr_name_tbl
2753            , l_salesrep_id_tbl
2754            , l_emp_no_tbl
2755            , l_role_id_tbl
2756            , l_txn_amt_tbl
2757            , l_split_pctg_tbl
2758            , l_rev_type_tbl
2759            , l_del_flag_tbl
2760            , l_no_of_credits_tbl LIMIT g_fetch_limit;
2761 
2762       EXIT WHEN l_rowid_tbl.COUNT <= 0;
2763       debugmsg('SCA : Number of winning rows returned : ' || l_rowid_tbl.COUNT);
2764       /* Start Code to make sure that the winning records of a  */
2765       /* particular transactions are not fetched across batches */
2766       debugmsg('SCA : Start of fetching remaining winning records for last txn');
2767       l_table_index    := l_rowid_tbl.LAST;
2768       l_no_of_credits  := l_no_of_credits_tbl(l_table_index);
2769       l_api_id         := l_api_id_tbl(l_table_index);
2770       l_rows_fetched   := 0;
2771 
2772       /* Get the number of rows fetched for the last transaction */
2773       LOOP
2774         l_rows_fetched  := l_rows_fetched + 1;
2775 
2776         IF (
2777                (l_rows_fetched = l_no_of_credits)
2778             OR (l_table_index = l_rowid_tbl.FIRST)
2779             OR (l_api_id <> l_api_id_tbl(l_table_index - 1))
2780            ) THEN
2781           EXIT;
2782         END IF;
2783 
2784         /* go to previous row */
2785         l_table_index   := l_table_index - 1;
2786       END LOOP;
2787 
2788       /* fetch the remaining winning records for the last transaction */
2789       FOR i IN 1 ..(l_no_of_credits - l_rows_fetched) LOOP
2790         l_rowid_tbl.EXTEND;
2791         l_api_id_tbl.EXTEND;
2792         l_terr_id_tbl.EXTEND;
2793         l_terr_name_tbl.EXTEND;
2794         l_salesrep_id_tbl.EXTEND;
2795         l_emp_no_tbl.EXTEND;
2796         l_role_id_tbl.EXTEND;
2797         l_txn_amt_tbl.EXTEND;
2798         l_split_pctg_tbl.EXTEND;
2799         l_rev_type_tbl.EXTEND;
2800         l_del_flag_tbl.EXTEND;
2801         l_no_of_credits_tbl.EXTEND;
2802 
2803         FETCH c_credited_txn_cur
2804          INTO l_rowid_tbl(l_rowid_tbl.LAST)
2805             , l_api_id_tbl(l_api_id_tbl.LAST)
2806             , l_terr_id_tbl(l_terr_id_tbl.LAST)
2807             , l_terr_name_tbl(l_terr_name_tbl.LAST)
2808             , l_salesrep_id_tbl(l_salesrep_id_tbl.LAST)
2809             , l_emp_no_tbl(l_emp_no_tbl.LAST)
2810             , l_role_id_tbl(l_role_id_tbl.LAST)
2811             , l_txn_amt_tbl(l_txn_amt_tbl.LAST)
2812             , l_split_pctg_tbl(l_split_pctg_tbl.LAST)
2813             , l_rev_type_tbl(l_rev_type_tbl.LAST)
2814             , l_del_flag_tbl(l_del_flag_tbl.LAST)
2815             , l_no_of_credits_tbl(l_no_of_credits_tbl.LAST);
2816       END LOOP;   /* end loop for */
2817 
2818       debugmsg('SCA : End of fetching remaining winning records for last txn');
2819       /* End Code to make sure that the winning records of a  */
2820       /* particular transactions are not fetched across batches */
2821 
2822       /* Process all the winning records row by row */
2823       l_table_index    := l_rowid_tbl.FIRST;
2824 
2825       LOOP
2826         /* exit after we have processed the last row */
2827         IF (l_table_index > l_rowid_tbl.LAST) THEN
2828           EXIT;
2829         END IF;
2830 
2831         -- debugmsg('SCA : Now processing transaction with id : ' || l_api_id_tbl(l_table_index));
2832 
2833         /* Get all children of the transaction which are  */
2834         /* active and generated by this crediting process */
2835              OPEN get_child_records (l_api_id_tbl(l_table_index));
2836              FETCH get_child_records  BULK COLLECT INTO
2837                     l_child_rowid_tbl
2838                   , l_child_api_id_tbl
2839                   , l_child_load_status_tbl
2840                   , l_child_salesrep_id_tbl
2841                   , l_child_txn_amt_tbl
2842                   , l_child_role_id_tbl
2843                   , l_child_terr_id_tbl
2844                   , l_child_split_pctg_tbl
2845                   , l_child_rev_type_tbl;
2846              CLOSE get_child_records;
2847 
2848         IF (l_child_rowid_tbl.COUNT > 0) THEN
2849           FOR i IN l_child_rowid_tbl.FIRST .. l_child_rowid_tbl.LAST LOOP
2850             --debugmsg('SCA : Now processing child transaction with id : ' || l_child_api_id_tbl(i));
2851 
2852             /* if the child has not been loaded for calculation   */
2853             /* delete the child record from cn_comm_lines_api_all */
2854             IF (l_child_load_status_tbl(i) <> 'LOADED') THEN
2855               /* delete the row if it is not the same txn that we have processed */
2856               IF (
2857                       (l_child_api_id_tbl(i) <> l_api_id_tbl(l_table_index))
2858                   AND (l_child_terr_id_tbl(i) IS NOT NULL) --IS NOT NULL
2859                  ) THEN
2860 
2861 
2862 
2863                   /* start of code : logic used here is  similar to used  for loaded tansaction. Reference bug 7589796    */
2864                   l_match_found  := FALSE;
2865 
2866                   /* check to see if the child matches with any of the credited transaction              */
2867                   /* if so, donot obsolete the child instead donot insert the new credited txn generated */
2868                   FOR j IN 1 .. l_no_of_credits_tbl(l_table_index) LOOP
2869                     l_temp_index  := l_table_index +(j - 1);
2870 
2871 					IF( l_temp_index > l_rowid_tbl.LAST) THEN
2872 					 EXIT;
2873 					END IF;
2874 
2875                     /* update txn amt to -1 if user either has not specified anything for split pctg */
2876                     /* or has specified an invalid chaaracter (anything other than numbers) for it   */
2877                     BEGIN
2878                       IF (l_split_pctg_tbl(l_temp_index) IS NULL) THEN
2879                         l_txn_amt  := -1;
2880                       ELSE
2881                         l_txn_amt  :=
2882                           ROUND(
2883                             NVL((l_txn_amt_tbl(l_temp_index) * l_split_pctg_tbl(l_temp_index)) / 100, 0)
2884                           , 2
2885                           );
2886                       END IF;
2887                     EXCEPTION
2888                       WHEN VALUE_ERROR THEN
2889                         l_txn_amt  := -1;
2890                       WHEN OTHERS THEN
2891                         RAISE;
2892                     END;
2893 
2894                     IF (
2895                             (l_child_salesrep_id_tbl(i) = l_salesrep_id_tbl(l_temp_index))
2896                         AND (l_child_txn_amt_tbl(i) = l_txn_amt)
2897                        -- AND (l_child_role_id_tbl(i) = l_role_id_tbl(l_temp_index))
2898                         AND (nvl(l_child_role_id_tbl(i),-1) = nvl(l_role_id_tbl(l_temp_index),-1))  -- Fix for bug 7298004
2899                         AND (l_child_terr_id_tbl(i) = l_terr_id_tbl(l_temp_index))
2900                         AND (l_child_split_pctg_tbl(i) = l_split_pctg_tbl(l_temp_index))
2901                         AND (l_child_rev_type_tbl(i) = l_rev_type_tbl(l_temp_index))
2902                         AND (l_del_flag_tbl(l_temp_index) = 'N')
2903                        ) THEN
2904                       /* if a match is found then exit the loop after marking the newly generated */
2905                       /* credited txn not to be inserted in the api table                         */
2906 
2907                         l_del_flag_tbl(l_temp_index)  := 'Y';
2908                         l_match_found                 := TRUE;
2909                         EXIT;
2910                     END IF;
2911                   END LOOP;
2912 
2913                   IF (NOT l_match_found) THEN
2914                  /*   debugmsg
2915                       (
2916                          'SCA : Calling CN_SCATM_TAE_PUB.handle_unloaded_txns for child transaction : '
2917                       || l_child_api_id_tbl(i)
2918                     ); */
2919                     handle_unloaded_txns(
2920                      l_unloaded_txn_tbl
2921                     , p_rowid                      => l_child_rowid_tbl(i)
2922                     , p_update_flag                => FALSE
2923                     , errbuf                       => errbuf
2924                     , retcode                      => retcode
2925                     );
2926 
2927                     IF (retcode <> 0) THEN
2928                       --debugmsg('SCA : CN_SCATM_TAE_PUB.handle_unloaded_txns has failed');
2929                       RAISE fnd_api.g_exc_error;
2930                     END IF;
2931 
2932                     --debugmsg('SCA : CN_SCATM_TAE_PUB.handle_unloaded_txns completed successfully');
2933                   END IF;
2934                  /* end of code : logic used here is  similar to  used  for loaded tansactions. Reference bug 7589796    */
2935               END IF;
2936             ELSE
2937               /* if the child has been loaded for calculation */
2938               l_match_found  := FALSE;
2939 
2940               /* check to see if the child matches with any of the credited transaction              */
2941               /* if so, donot obsolete the child instead donot insert the new credited txn generated */
2942               FOR j IN 1 .. l_no_of_credits_tbl(l_table_index) LOOP
2943                 l_temp_index  := l_table_index +(j - 1);
2944 
2945 				  IF( l_temp_index > l_rowid_tbl.LAST) THEN
2946 					 EXIT;
2947 				  END IF;
2948 
2949                 /* update txn amt to -1 if user either has not specified anything for split pctg */
2950                 /* or has specified an invalid chaaracter (anything other than numbers) for it   */
2951                 BEGIN
2952                   IF (l_split_pctg_tbl(l_temp_index) IS NULL) THEN
2953                     l_txn_amt  := -1;
2954                   ELSE
2955                     l_txn_amt  :=
2956                       ROUND(
2957                         NVL((l_txn_amt_tbl(l_temp_index) * l_split_pctg_tbl(l_temp_index)) / 100, 0)
2958                       , 2
2959                       );
2960                   END IF;
2961                 EXCEPTION
2962                   WHEN VALUE_ERROR THEN
2963                     l_txn_amt  := -1;
2964                   WHEN OTHERS THEN
2965                     RAISE;
2966                 END;
2967 
2968                 IF (
2969                         (l_child_salesrep_id_tbl(i) = l_salesrep_id_tbl(l_temp_index))
2970                     AND (l_child_txn_amt_tbl(i) = l_txn_amt)
2971                    -- AND (l_child_role_id_tbl(i) = l_role_id_tbl(l_temp_index))
2972                     AND (nvl(l_child_role_id_tbl(i),-1) = nvl(l_role_id_tbl(l_temp_index),-1))  -- Fix for bug 7298004
2973                     AND (l_child_terr_id_tbl(i) = l_terr_id_tbl(l_temp_index))
2974                     AND (l_child_split_pctg_tbl(i) = l_split_pctg_tbl(l_temp_index))
2975                     AND (l_child_rev_type_tbl(i) = l_rev_type_tbl(l_temp_index))
2976                     AND (l_del_flag_tbl(l_temp_index) = 'N')
2977                    ) THEN
2978                   /* if a match is found then exit the loop after marking the newly generated */
2979                   /* credited txn not to be inserted in the api table                         */
2980 
2981                   --Modified the flow for  bug 	8538923
2982                    OPEN get_child_records_for_rev_txns (
2983                    l_child_api_id_tbl(i) ,
2984                    l_child_rev_type_tbl(i),
2985                    l_child_split_pctg_tbl(i),
2986                    l_child_terr_id_tbl(i),
2987                    nvl(l_child_role_id_tbl(i),-1),
2988                    l_child_txn_amt_tbl(i),
2989                    l_child_salesrep_id_tbl(i));
2990 
2991                    FETCH get_child_records_for_rev_txns INTO l_count;
2992 
2993                    IF l_count = 0
2994                    THEN
2995 
2996                      l_del_flag_tbl(l_temp_index)  := 'Y';
2997                      l_match_found                 := TRUE;
2998                      CLOSE get_child_records_for_rev_txns;
2999                      EXIT;
3000 
3001                    END IF;
3002 
3003                  CLOSE get_child_records_for_rev_txns;
3004 
3005                 END IF;
3006               END LOOP;
3007 
3008               IF (NOT l_match_found) THEN
3009                 /* if no match is found then create reversal entry */
3010               /*  debugmsg
3011                    (
3012                      'SCA : Calling CN_SCATM_TAE_PUB.handle_loaded_txns for child transaction : '
3013                   || l_child_api_id_tbl(i)
3014                 ); */
3015                 handle_loaded_txns(
3016                    l_loaded_txn_rowid_tbl => l_loaded_txn_rowid_tbl
3017                 , l_loaded_txn_comid_tbl => l_loaded_txn_comid_tbl
3018                 , p_rowid                      => l_child_rowid_tbl(i)
3019                 , p_api_id                     => l_child_api_id_tbl(i)
3020                 , p_update_flag                => FALSE
3021                 , errbuf                       => errbuf
3022                 , retcode                      => retcode
3023                 );
3024 
3025                 IF (retcode <> 0) THEN
3026                   debugmsg('SCA : CN_SCATM_TAE_PUB.handle_loaded_txns has failed');
3027                   RAISE fnd_api.g_exc_error;
3028                 END IF;
3029 
3030                 debugmsg('SCA : CN_SCATM_TAE_PUB.handle_loaded_txns completed successfully');
3031               END IF;
3032             END IF;   /* end if load_status <> 'LOADED' */
3033           END LOOP;   /* end processing all the children */
3034         END IF;   /* end if l_child_rowid_tbl.COUNT > 0 */
3035 
3036         /* increase the table index to point to the next transaction */
3037         l_table_index  := l_table_index + l_no_of_credits_tbl(l_table_index);
3038       END LOOP;   /* end loop processing winning records row by row */
3039 
3040       /* Make changes to DB for unloaded txns present in the PL/SQL table */
3041       debugmsg('SCA : Calling CN_SCATM_TAE_PUB.handle_unloaded_txns');
3042       handle_unloaded_txns(l_unloaded_txn_tbl => l_unloaded_txn_tbl,
3043       p_rowid   => NULL, p_update_flag => TRUE, errbuf => errbuf
3044       , retcode                      => retcode);
3045 
3046       IF (retcode <> 0) THEN
3047         debugmsg('SCA : CN_SCATM_TAE_PUB.handle_unloaded_txns has failed');
3048         RAISE fnd_api.g_exc_error;
3049       END IF;
3050 
3051       debugmsg('SCA : CN_SCATM_TAE_PUB.handle_unloaded_txns completed successfully');
3052       /* Make changes to DB for loaded txns present in the PL/SQL table */
3053       debugmsg('SCA : Calling CN_SCATM_TAE_PUB.handle_loaded_txns');
3054       handle_loaded_txns(
3055         l_loaded_txn_rowid_tbl => l_loaded_txn_rowid_tbl
3056       , l_loaded_txn_comid_tbl => l_loaded_txn_comid_tbl
3057       , p_rowid                      => NULL
3058       , p_api_id                     => NULL
3059       , p_update_flag                => TRUE
3060       , errbuf                       => errbuf
3061       , retcode                      => retcode
3062       );
3063 
3064       IF (retcode <> 0) THEN
3065         debugmsg('SCA : CN_SCATM_TAE_PUB.handle_loaded_txns has failed');
3066         RAISE fnd_api.g_exc_error;
3067       END IF;
3068 
3069       debugmsg('SCA : CN_SCATM_TAE_PUB.handle_loaded_txns completed successfully');
3070       /* insert the credited txns into api table */
3071       insert_api_txns(
3072         p_org_id                     => p_org_id
3073       , p_trans_object_id_tbl        => l_api_id_tbl
3074       , p_salesrep_id_tbl            => l_salesrep_id_tbl
3075       , p_emp_no_tbl                 => l_emp_no_tbl
3076       , p_role_id_tbl                => l_role_id_tbl
3077       , p_split_pctg_tbl             => l_split_pctg_tbl
3078       , p_rev_type_tbl               => l_rev_type_tbl
3079       , p_terr_id_tbl                => l_terr_id_tbl
3080       , p_terr_name_tbl              => l_terr_name_tbl
3081       , p_del_flag_tbl               => l_del_flag_tbl
3082       , errbuf                       => errbuf
3083       , retcode                      => retcode
3084       );
3085 
3086       IF (retcode <> 0) THEN
3087         debugmsg('SCA : CN_SCATM_TAE_PUB.insert_api_txns has failed');
3088         RAISE fnd_api.g_exc_error;
3089       END IF;
3090 
3091       debugmsg('SCA : CN_SCATM_TAE_PUB.insert_api_txns completed successfully');
3092     END LOOP;   /* end loop fetch winning records */
3093 
3094     CLOSE c_credited_txn_cur;
3095 
3096     debugmsg('SCA : End of process_all_txns');
3097   EXCEPTION
3098     WHEN fnd_api.g_exc_error THEN
3099       IF c_credited_txn_cur%ISOPEN THEN
3100         CLOSE c_credited_txn_cur;
3101       END IF;
3102 
3103       debugmsg('SCA : CN_SCATM_TAE_PUB.process_all_txns.g_exc_error');
3104       debugmsg('SCA : SQLCODE : ' || SQLCODE);
3105       debugmsg('SCA : SQLERRM : ' || SQLERRM);
3106     WHEN OTHERS THEN
3107       IF c_credited_txn_cur%ISOPEN THEN
3108         CLOSE c_credited_txn_cur;
3109       END IF;
3110 
3111       debugmsg('SCA : Unexpected exception in process_all_txns');
3112       debugmsg('SCA : SQLCODE : ' || SQLCODE);
3113       debugmsg('SCA : SQLERRM : ' || SQLERRM);
3114       retcode  := 2;
3115       errbuf   := 'CN_SCATM_TAE_PUB.process_all_txns.others';
3116   END process_all_txns;
3117 
3118   /* Entry point of credit allocation process */
3119   PROCEDURE get_assignments(
3120     errbuf       OUT NOCOPY    VARCHAR2
3121   , retcode      OUT NOCOPY    VARCHAR2
3122   , p_org_id     IN            NUMBER
3123   , p_start_date IN            VARCHAR2
3124   , p_end_date   IN            VARCHAR2
3125   , p_run_mode   IN            VARCHAR2
3126   , p_terr_id    IN            NUMBER DEFAULT NULL
3127   ) IS
3128     l_start_date         DATE;
3129     l_end_date           DATE;
3130     l_process_audit_id   NUMBER;
3131     l_where_clause       VARCHAR2(1000);
3132     l_skip_credit_flag   VARCHAR2(1);
3133     l_count              NUMBER;
3134     l_invalid_run_mode   EXCEPTION;
3135     l_skip_crediting     EXCEPTION;
3136     l_invalid_date_range EXCEPTION;
3137 
3138     l_req_id NUMBER;
3139 
3140     l_child_program_id_tbl sub_program_id_type;
3141 
3142     l_phase  VARCHAR2(100);
3143     l_status VARCHAR2(100);
3144     l_dev_phase VARCHAR2(100);
3145     l_dev_status VARCHAR2(100);
3146     l_message VARCHAR2(1000);
3147     call_status boolean;
3148 
3149     child_proc_fail_exception exception;
3150 
3151   BEGIN
3152     retcode                 := 0;
3153     errbuf                  := NULL;
3154     /* Convert the dates for the varchar2 parameters passed in from concurrent program */
3155     l_start_date            := fnd_date.canonical_to_date(p_start_date);
3156     l_end_date              := fnd_date.canonical_to_date(p_end_date);
3157     /* Call begin_batch to get process_audit_id for debug log file */
3158     cn_message_pkg.begin_batch(
3159       x_process_type               => 'SCATM'
3160     , x_parent_proc_audit_id       => NULL
3161     , x_process_audit_id           => l_process_audit_id
3162     , x_request_id                 => fnd_global.conc_request_id
3163     , p_org_id                     => p_org_id
3164     );
3165     debugmsg('SCA : Start of Credit Allocation using TM');
3166     debugmsg('SCA : process_audit_id is ' || l_process_audit_id);
3167     /* Continue only if the profile "OIC: Skip Credit Allocation" is set to No */
3168     l_skip_credit_flag      := 'Y';
3169 
3170     IF (fnd_profile.defined('CN_SKIP_CREDIT_ALLOCATION')) THEN
3171       l_skip_credit_flag  := fnd_profile.VALUE('CN_SKIP_CREDIT_ALLOCATION');
3172     END IF;
3173 
3174     IF (l_skip_credit_flag <> 'N') THEN
3175       debugmsg('SCA : Profile OIC: Skip Credit Allocation is set to Yes');
3176       retcode  := 1;
3177       errbuf   := 'SCA : Profile OIC: Skip Credit Allocation is set to Yes';
3178       RAISE l_skip_crediting;
3179     END IF;
3180 
3181     /* run mode should be either NEW or ALL */
3182     IF ((p_run_mode <> 'NEW') AND(p_run_mode <> 'ALL')
3183         AND(p_run_mode <> 'INCREMENTAL')) THEN
3184       debugmsg('SCA : Invalid Run Mode');
3185       retcode  := 2;
3186       errbuf   := 'Inavlid Run Mode parameter value';
3187       RAISE l_invalid_run_mode;
3188     END IF;
3189 
3190     /* Verify that the start date is within open period */
3191     l_count                 := 0;
3192 
3193     SELECT COUNT(*)
3194       INTO l_count
3195       FROM cn_acc_period_statuses_v acc
3196      WHERE TRUNC(l_start_date) BETWEEN TRUNC(acc.start_date) AND TRUNC(acc.end_date)
3197        AND acc.period_status = 'O'
3198        AND acc.org_id = p_org_id
3199        AND ROWNUM = 1;
3200 
3201     IF (l_count = 0) THEN
3202       debugmsg('SCA : Start Date is not within open period');
3203       retcode  := 2;
3204       errbuf   := 'Start Date is not within open period';
3205       RAISE l_invalid_date_range;
3206     END IF;
3207 
3208     /* Verify that the end date is within open period */
3209     l_count                 := 0;
3210 
3211     SELECT COUNT(*)
3212       INTO l_count
3213       FROM cn_acc_period_statuses_v acc
3214      WHERE TRUNC(l_end_date) BETWEEN TRUNC(acc.start_date) AND TRUNC(acc.end_date)
3215        AND acc.period_status = 'O'
3216        AND acc.org_id = p_org_id
3217        AND ROWNUM = 1;
3218 
3219     IF (l_count = 0) THEN
3220       debugmsg('SCA : End Date is not within open period');
3221       retcode  := 2;
3222       errbuf   := 'End Date is not within open period';
3223       RAISE l_invalid_date_range;
3224     END IF;
3225 
3226     /* Initialize global pl/sql tables */
3227     g_unloaded_txn_tbl      := g_rowid_tbl_type();
3228     g_loaded_txn_rowid_tbl  := g_rowid_tbl_type();
3229     g_loaded_txn_comid_tbl  := g_comm_lines_api_id_tbl_type();
3230 
3231     SELECT TO_NUMBER(NVL(fnd_profile.value('CN_NUMBER_OF_WORKERS'),1)) INTO g_num_workers
3232     FROM dual;
3233 
3234     IF g_num_workers < 1
3235     THEN
3236       g_num_workers := 1;
3237     END IF;
3238 
3239     debugmsg('SCA : CN_SCATM_TAE_PUB.Number of Workers '||g_num_workers);
3240     debugmsg('SCA : CN_SCATM_TAE_PUB.get_where_clause completed successfully');
3241     /* Call the territory APIs and get the winning salesreps */
3242     /* and split percentages for each transaction            */
3243     get_credited_txns(
3244       p_where_clause               => l_where_clause
3245     , p_request_id                 => g_request_id
3246     , errbuf                       => errbuf
3247     , retcode                      => retcode
3248     , p_start_date                 => l_start_date
3249     , p_end_date                   => l_end_date
3250     , p_org_id                     => p_org_id
3251     , p_run_mode                   => p_run_mode
3252 	  , p_terr_id					           => p_terr_id
3253     );
3254 
3255     IF (retcode <> 0) THEN
3256       debugmsg('SCA : CN_SCATM_TAE_PUB.get_credited_txns has failed');
3257       RAISE fnd_api.g_exc_error;
3258     END IF;
3259 
3260     debugmsg('SCA : CN_SCATM_TAE_PUB.get_credited_txns completed successfully');
3261 
3262     l_child_program_id_tbl := sub_program_id_type();
3263 
3264     FOR l_worker_id IN 1..g_num_workers
3265     LOOP
3266         l_req_id := FND_REQUEST.SUBMIT_REQUEST('CN', -- Application
3267               				     'CN_SCATM_CRED_ALLOC_TXN_BATCH'	  , -- Concurrent Program
3268               				     '', -- description
3269               				     '', -- start time
3270                            FALSE, -- sub request flag
3271                            p_org_id, -- Parameters Org Id
3272                            p_run_mode, --Parameter Run Mode
3273                            l_worker_id -- parameter worker id
3274                             );
3275        COMMIT;
3276 
3277        IF  l_req_id =0
3278        THEN
3279           retcode := 2;
3280           errbuf := fnd_message.get;
3281           raise child_proc_fail_exception;
3282        ELSE
3283           -- storing the request ids in an array
3284           l_child_program_id_tbl.EXTEND;
3285           l_child_program_id_tbl(l_child_program_id_tbl.LAST):=l_req_id;
3286        END IF;
3287      END LOOP;
3288 
3289      debugmsg('SCA : CN_SCATM_TAE_PUB.Parent Process starts Waiting For Child Processes to complete');
3290 
3291      parent_conc_wait(l_child_program_id_tbl,retcode,errbuf);
3292 
3293      COMMIT;
3294 
3295      IF retcode = 2
3296      THEN
3297         debugmsg('SCA : CN_SCATM_TAE_PUB.update_txns_processed has failed');
3298         raise fnd_api.g_exc_error;
3299      END IF;
3300 
3301     IF (retcode <> 0) THEN
3302       debugmsg('SCA : CN_SCATM_TAE_PUB.update_txns_processed has failed');
3303       RAISE fnd_api.g_exc_error;
3304     END IF;
3305 
3306     debugmsg('SCA : CN_SCATM_TAE_PUB.update_txns_processed completed successfully');
3307     -- Call end_batch to end debug log file
3308     debugmsg('SCA : CN_SCATM_TAE_PUB. Parent Process Complete Successfully at '||CURRENT_TIMESTAMP);
3309     debugmsg('SCA : End of SCATM');
3310     cn_message_pkg.end_batch(l_process_audit_id);
3311     COMMIT;
3312   EXCEPTION
3313     WHEN l_invalid_date_range THEN
3314       debugmsg('SCA : CN_SCATM_TAE_PUB.get_assignments.l_invalid_date_range');
3315       debugmsg('SCA : End of SCATM');
3316       cn_message_pkg.end_batch(l_process_audit_id);
3317     WHEN l_skip_crediting THEN
3318       debugmsg('SCA : CN_SCATM_TAE_PUB.get_assignments.l_skip_crediting');
3319       debugmsg('SCA : End of SCATM');
3320       cn_message_pkg.end_batch(l_process_audit_id);
3321     WHEN l_invalid_run_mode THEN
3322       debugmsg('SCA : CN_SCATM_TAE_PUB.get_assignments.l_invalid_run_mode');
3323       debugmsg('SCA : End of SCATM');
3324       cn_message_pkg.end_batch(l_process_audit_id);
3325     WHEN fnd_api.g_exc_error THEN
3326       debugmsg('SCA : CN_SCATM_TAE_PUB.get_assignments.g_exc_error');
3327       debugmsg('SCA : SQLCODE : ' || SQLCODE);
3328       debugmsg('SCA : SQLERRM : ' || SQLERRM);
3329       debugmsg('SCA : End of SCATM');
3330       cn_message_pkg.end_batch(l_process_audit_id);
3331     WHEN child_proc_fail_exception THEN
3332       debugmsg('SCA : Unexpected exception');
3333       debugmsg('SCA : Child Process Failed  ');
3334       debugmsg('SCA : Check Log of Child Process ');
3335     WHEN OTHERS THEN
3336       debugmsg('SCA : Unexpected exception');
3337       debugmsg('SCA : SQLCODE : ' || SQLCODE);
3338       debugmsg('SCA : SQLERRM : ' || SQLERRM);
3339       -- Call end_batch to end debug log file
3340       debugmsg('SCA : End of SCATM');
3341       cn_message_pkg.end_batch(l_process_audit_id);
3342       retcode  := 2;
3343       errbuf   := 'Unexpected Error : ' || SQLERRM;
3344   END get_assignments;
3345 
3346 PROCEDURE batch_process_txns(
3347    errbuf       OUT NOCOPY    VARCHAR2
3348   ,retcode      OUT NOCOPY    VARCHAR2
3349   ,p_org_id NUMBER
3350   ,p_run_mode VARCHAR2
3351   ,p_worker_id NUMBER)
3352   IS
3353 
3354   BEGIN
3355 
3356     IF (p_run_mode = 'NEW') THEN
3357       /* Process new and adjusted transactions */
3358       process_new_txns(p_org_id => p_org_id, p_worker_id => p_worker_id,
3359       errbuf => errbuf, retcode => retcode);
3360 
3361 
3362       IF (retcode <> 0) THEN
3363         debugmsg('SCA : CN_SCATM_TAE_PUB.process_new_txns has failed');
3364         RAISE fnd_api.g_exc_error;
3365       END IF;
3366 
3367 
3368       debugmsg('SCA : CN_SCATM_TAE_PUB.process_new_txns completed successfully');
3369     ELSIF(p_run_mode = 'ALL' or p_run_mode = 'INCREMENTAL') THEN
3370       /* Process all transactions */
3371       process_all_txns(p_org_id => p_org_id, p_worker_id => p_worker_id,
3372       errbuf => errbuf, retcode => retcode);
3373 
3374 
3375       IF (retcode <> 0) THEN
3376         debugmsg('SCA : CN_SCATM_TAE_PUB.process_all_txns has failed');
3377         RAISE fnd_api.g_exc_error;
3378       END IF;
3379 
3380         debugmsg('SCA : CN_SCATM_TAE_PUB.process_all_txns completed successfully');
3381     END IF;
3382 
3383      update_txns_processed(errbuf => errbuf, retcode => retcode,
3384      p_worker_id  => p_worker_id);
3385 
3386     debugmsg('SCA : Child Process '||p_worker_id ||' complete successfully at '||
3387     CURRENT_TIMESTAMP);
3388 
3389     COMMIT;
3390 
3391  EXCEPTION
3392     WHEN fnd_api.g_exc_error THEN
3393       debugmsg('SCA : CN_SCATM_TAE_PUB.get_assignments.g_exc_error');
3394       debugmsg('SCA : SQLCODE : ' || SQLCODE);
3395       debugmsg('SCA : SQLERRM : ' || SQLERRM);
3396       debugmsg('SCA : End of SCATM');
3397       -- cn_message_pkg.end_batch(l_process_audit_id);
3398     WHEN OTHERS THEN
3399       debugmsg('SCA : Unexpected exception');
3400       debugmsg('SCA : SQLCODE : ' || SQLCODE);
3401       debugmsg('SCA : SQLERRM : ' || SQLERRM);
3402       -- Call end_batch to end debug log file
3403       debugmsg('SCA : End of SCATM');
3404       --cn_message_pkg.end_batch(l_process_audit_id);
3405       retcode  := 2;
3406       errbuf   := 'Unexpected Error : ' || SQLERRM;
3407 
3408  END batch_process_txns;
3409 
3410  PROCEDURE batch_collect_txns(
3411      errbuf       OUT NOCOPY    VARCHAR2
3412    , retcode      OUT NOCOPY    VARCHAR2
3413    , lp_start_date IN DATE
3414    , lp_end_date IN DATE
3415    , p_org_id IN NUMBER
3416    , p_run_mode IN VARCHAR2
3417    , l_num_workers IN  NUMBER
3418    , p_request_id IN NUMBER
3419    )
3420  IS
3421    l_where_clause VARCHAR2(2000);
3422    l_return_status VARCHAR2(30);
3423    l_msg_count     NUMBER;
3424    l_msg_data      VARCHAR2(3000);
3425  BEGIN
3426 
3427    retcode := 0;
3428    /* Get the criterion to select transactions from api table */
3429 
3430    get_where_clause(
3431        p_start_date                 => lp_start_date
3432      , p_end_date                   => lp_end_date
3433      , p_org_id                     => p_org_id
3434      , p_run_mode                   => p_run_mode
3435      , x_where_clause               => l_where_clause
3436      , errbuf                       => errbuf
3437      , retcode                      => retcode
3438      );
3439 
3440    IF (retcode <> 0) THEN
3441       debugmsg('SCA : CN_SCATM_TAE_PUB.get_where_clause has failed');
3442       RAISE fnd_api.g_exc_error;
3443    END IF;
3444 
3445    debugmsg('SCA : CN_SCATM_TAE_PUB.get_where_clause completed successfully');
3446 
3447     /* insert the selected transactions from cn_comm_lines_api_all table */
3448     /* to the interface table jtf_tae_1001_sc_dea_trans                  */
3449     jty_assign_bulk_pub.collect_trans_data(
3450       p_api_version_number         => 1.0
3451     , p_init_msg_list              => fnd_api.g_false
3452     , p_source_id                  => -1001
3453     , p_trans_id                   => -1002
3454     , p_program_name               => 'SALES/INCENTIVE COMPENSATION PROGRAM'
3455     , p_mode                       => 'DATE EFFECTIVE'
3456     , p_where                      => l_where_clause
3457     , p_no_of_workers              => l_num_workers
3458     , p_percent_analyzed           => 20
3459     ,   -- this value can be either a profile option or a parameter to conc program
3460       p_request_id                 => p_request_id
3461     ,   -- request id of the concurrent program
3462       x_return_status              => l_return_status
3463     , x_msg_count                  => l_msg_count
3464     , x_msg_data                   => l_msg_data
3465     , errbuf                       => errbuf
3466     , retcode                      => retcode
3467     , p_oic_mode                   => 'INSERT'
3468     );
3469 
3470    IF (retcode <> 0) THEN
3471       debugmsg('SCA : CN_SCATM_TAE_PUB.get_credited_txns for INSERT has failed');
3472       RAISE fnd_api.g_exc_error;
3473     END IF;
3474 
3475     debugmsg('SCA : CN_SCATM_TAE_PUB.batch_collect_txns with oic_mode INSERT completed successfully');
3476 
3477   EXCEPTION
3478      WHEN fnd_api.g_exc_error THEN
3479         debugmsg('SCA : CN_SCATM_TAE_PUB.get_assignments.g_exc_error');
3480         debugmsg('SCA : SQLCODE : ' || SQLCODE);
3481         debugmsg('SCA : SQLERRM : ' || SQLERRM);
3482         debugmsg('SCA : End of SCATM');
3483      WHEN OTHERS THEN
3484         debugmsg('SCA : Unexpected exception');
3485         debugmsg('SCA : SQLCODE : ' || SQLCODE);
3486         debugmsg('SCA : SQLERRM : ' || SQLERRM);
3487         debugmsg('SCA : End of SCATM');
3488         retcode  := 2;
3489         errbuf   := 'Unexpected Error : ' || SQLERRM;
3490 END batch_collect_txns;
3491 
3492 
3493 PROCEDURE batch_process_winners(
3494      errbuf       OUT NOCOPY    VARCHAR2
3495    , retcode      OUT NOCOPY    VARCHAR2
3496    , p_worker_id  IN NUMBER
3497    , p_oic_mode   IN VARCHAR2
3498    , p_terr_id    IN NUMBER
3499    )
3500  IS
3501    l_where_clause VARCHAR2(2000);
3502    l_return_status VARCHAR2(30);
3503    l_msg_count     NUMBER;
3504    l_msg_data      VARCHAR2(3000);
3505  BEGIN
3506 
3507    retcode := 0;
3508    /* Get the criterion to select transactions from api table */
3509     debugmsg('SCA : Populating data to WINNERS table for worker_id '||p_worker_id ||' and mode '||
3510     p_oic_mode);
3511     /* this api will apply the rules to the transactions present in jtf_tae_1001_sc_dea_trans       */
3512     /* and populate the winning salesreps for each transaction in the table jtf_tae_1001_sc_winners */
3513 
3514        jty_assign_bulk_pub.get_winners(
3515           p_api_version_number         => 1.0
3516         , p_init_msg_list              => fnd_api.g_false
3517         , p_source_id                  => -1001
3518         , p_trans_id                   => -1002
3519         , p_program_name               => 'SALES/INCENTIVE COMPENSATION PROGRAM'
3520         , p_mode                       => 'DATE EFFECTIVE'
3521         , p_percent_analyzed           => 20
3522         ,   --  this value can be either a profile option or a parameter to conc program
3523           p_worker_id                  => p_worker_id
3524         , x_return_status              => l_return_status
3525         , x_msg_count                  => l_msg_count
3526         , x_msg_data                   => l_msg_data
3527         , errbuf                       => errbuf
3528         , retcode                      => retcode
3529         , p_oic_mode                   => p_oic_mode
3530 		, p_terr_id                    => p_terr_id
3531         );
3532 
3533         debugmsg('SCA : CN_SCATM_TAE_PUB.batch_process_winners status '||l_return_status
3534         ||' data '||l_msg_data);
3535 
3536         IF (retcode <> 0) THEN
3537           debugmsg('SCA : jty_assign_bulk_pub.get_winners has failed');
3538           RAISE fnd_api.g_exc_error;
3539         END IF;
3540 
3541 
3542     debugmsg('SCA : CN_SCATM_TAE_PUB.batch_process_winners completed successfully');
3543   EXCEPTION
3544      WHEN fnd_api.g_exc_error THEN
3545         debugmsg('SCA : CN_SCATM_TAE_PUB.get_assignments.g_exc_error');
3546         debugmsg('SCA : SQLCODE : ' || SQLCODE);
3547         debugmsg('SCA : SQLERRM : ' || SQLERRM);
3548         debugmsg('SCA : End of SCATM');
3549      WHEN OTHERS THEN
3550         debugmsg('SCA : Unexpected exception');
3551         debugmsg('SCA : SQLCODE : ' || SQLCODE);
3552         debugmsg('SCA : SQLERRM : ' || SQLERRM);
3553         debugmsg('SCA : End of SCATM');
3554         retcode  := 2;
3555         errbuf   := 'Unexpected Error : ' || SQLERRM;
3556 END batch_process_winners;
3557 
3558 FUNCTION convert_to_table
3559 RETURN cn_sca_insert_tbl_type IS
3560 
3561 BEGIN
3562 
3563  RETURN g_sca_insert_tbl_type;
3564 
3565 END convert_to_table;
3566 
3567 END cn_sca_credits_batch_pub;