DBA Data[Home] [Help]

PACKAGE BODY: APPS.CN_PAYMENT_WORKSHEET_PVT

Source


1 PACKAGE BODY cn_payment_worksheet_pvt AS
2     -- $Header: cnvwkshb.pls 120.26 2008/01/14 19:56:55 rnagired ship $
3     g_api_version CONSTANT NUMBER := 1.0;
4     g_pkg_name    CONSTANT VARCHAR2(30) := 'CN_Payment_Worksheet_PVT';
5     --G_last_update_date      DATE    := sysdate;
6     g_last_updated_by NUMBER := fnd_global.user_id;
7     --G_creation_date         DATE    := sysdate;
8     g_created_by        NUMBER := fnd_global.user_id;
9     g_last_update_login NUMBER := fnd_global.login_id;
10     g_credit_type_id CONSTANT NUMBER := -1000;
11 
12 
13     PROCEDURE update_ptd_details (
14        	p_salesrep_id IN NUMBER,
15        	p_payrun_id   IN NUMBER
16     )
17     IS
18         l_comm_ptd    number ;
19         l_bonus_ptd   number ;
20         l_bal         NUMBER ;
21         l_bb_earn     NUMBER ;
22         l_bb_pmt_recover NUMBER ;
23 
24     BEGIN
25 
26          BEGIN
27 
28               -- get data from summary record where quota_id is null
29               SELECT SUM(nvl(balance2_bbd, 0) - nvl(balance2_bbc, 0)) prior_earning,
30                      - (SUM(nvl(balance4_bbd, 0) - nvl(balance4_bbc, 0))) - (SUM(nvl(balance4_dtd, 0) - nvl(balance4_ctd, 0)))
31                 INTO l_bb_earn,
32                      l_bb_pmt_recover
33                 FROM cn_srp_periods_all s,
34                      cn_payruns_all pr
35                WHERE s.salesrep_id = p_salesrep_id
36                  AND s.org_id = pr.org_id
37                  AND pr.payrun_id = p_payrun_id
38                  AND s.quota_id IS NULL
39                  AND pr.pay_period_id = s.period_id
40                  AND s.credit_type_id = g_credit_type_id ;
41 
42          EXCEPTION
43               WHEN no_data_found THEN
44                   l_bb_earn    := 0;
45                   l_bb_pmt_recover := 0;
46          END;
47 
48          --l_bal := nvl(l_bb_earn,0) + nvl(l_bb_pmt_recover,0) ;
49 
50          BEGIN
51 
52             SELECT SUM(CASE
53                            WHEN quota.incentive_type_code = 'BONUS' THEN
54                             nvl(cspq.commission_payed_ptd, 0)
55                            ELSE
56                             0
57                        END) bonus_ptd,
58                    SUM(CASE
59                            WHEN quota.incentive_type_code = 'COMMISSION' THEN
60                             nvl(cspq.commission_payed_ptd, 0)
61                            ELSE
62                             0
63                        END) comm_ptd
64               INTO l_bonus_ptd,
65                    l_comm_ptd
66               FROM cn_srp_period_quotas_all cspq,
67                    cn_quotas_all            quota,
68                    cn_payruns_all           pr
69              WHERE cspq.quota_id = quota.quota_id
70                AND quota.quota_id > 0
71                AND quota.org_id = cspq.org_id
72                AND pr.pay_period_id = cspq.period_id
73                AND quota.credit_type_id = -1000
74                AND pr.payrun_id = p_payrun_id
75                AND cspq.salesrep_id = p_salesrep_id
76              GROUP BY cspq.salesrep_id,
77                       cspq.period_id;
78 
79         EXCEPTION
80             WHEN no_data_found THEN
81             l_comm_ptd := 0 ;
82             l_bonus_ptd := 0 ;
83         END;
84 
85         UPDATE cn_payment_worksheets_all w
86            SET w.comm_ptd = l_comm_ptd,
87                w.bonus_ptd = l_bonus_ptd,
88                w.comm_due_bb = l_bb_earn
89          WHERE w.salesrep_id = p_salesrep_id
90            AND w.payrun_id  = p_payrun_id
91            AND w.quota_id IS NULL ;
92 
93     END update_ptd_details ;
94 
95   /*
96       Procedure : conc_submit
97       Added for bug 5910965
98     */
99 
100       PROCEDURE conc_submit
101       (
102           p_conc_program     IN VARCHAR2,
103           p_description      IN VARCHAR2,
104           p_logical_batch_id IN NUMBER,
105           p_batch_id         IN NUMBER,
106           p_payrun_id        IN NUMBER,
107           p_org_id           IN cn_payruns.org_id%TYPE,
108           p_params           IN conc_params,
109           x_request_id       OUT NOCOPY NUMBER
110       ) IS
111       BEGIN
112           fnd_file.put_line(fnd_file.log, 'Conc_submit BatchId = ' || p_batch_id);
113 
114           x_request_id := fnd_request.submit_request(application => 'CN',
115                                                      program     => p_conc_program,
116                                                      description => p_description,
117                                                      argument1   => p_batch_id,
118                                                      argument2   => p_payrun_id,
119                                                      argument3   => p_logical_batch_id,
120                                                      argument4   => p_org_id
121                                                      );
122           IF x_request_id = 0
123           THEN
124               fnd_file.put_line(fnd_file.log, 'Failed to create concurrent request for (payrun_id,batch_id) = ' || p_payrun_id ||','|| p_batch_id);
125               fnd_file.put_line(fnd_file.log, 'Conc_submit: ' || fnd_message.get);
126               raise fnd_api.G_EXC_ERROR;
127           ELSE
128               fnd_file.put_line(fnd_file.log, 'Concurrent request, ID = ' || x_request_id || ', for (payrun_id,batch_id) = ' || p_payrun_id ||','|| p_batch_id );
129           END IF;
130 
131       EXCEPTION
132           WHEN OTHERS THEN
133               fnd_file.put_line(fnd_file.log, 'Conc_submit err:' || SQLERRM);
134               RAISE;
135       END conc_submit;
136 
137 
138 
139     -- ===========================================================================
140     --   Procedure   : get_pay_rec_period_ids
141     --   Description : This procedure is used to get pay period id and recover period id given
142     --                  pay_interval_type_id and recoverable_interval_type_id.
143     --                  Added for bug 2776847 by jjhuang.
144     --   Calls       :
145     -- ===========================================================================
146     PROCEDURE get_pay_rec_period_ids
147     (
148         p_period_id                    IN cn_period_statuses.period_id%TYPE,
149         p_quarter_num                  IN cn_period_statuses.quarter_num%TYPE,
150         p_period_year                  IN cn_period_statuses.period_year%TYPE,
151         p_pay_interval_type_id         IN cn_pmt_plans.pay_interval_type_id%TYPE,
152         p_recoverable_interval_type_id IN cn_pmt_plans.recoverable_interval_type_id%TYPE,
153         x_pay_period_id                OUT NOCOPY cn_pmt_plans.pay_interval_type_id%TYPE,
154         x_rec_period_id                OUT NOCOPY cn_pmt_plans.recoverable_interval_type_id%TYPE,
155         --R12
156         p_org_id IN cn_payruns.org_id%TYPE
157     ) IS
158         CURSOR get_max_period_id_in_qtr(p_quarter_num cn_period_statuses.quarter_num%TYPE, p_period_year cn_period_statuses.period_year%TYPE) IS
159             SELECT MAX(p.period_id) max_period_id
160               FROM cn_period_statuses p,
161                    cn_period_types    pt
162              WHERE p.quarter_num = p_quarter_num
163                AND p.period_year = p_period_year
164                AND p.period_type = pt.period_type
165                AND pt.period_type_id = 0
166                   --R12
167                AND p.org_id = p_org_id
168                AND pt.org_id = p_org_id;
169 
170         CURSOR get_max_period_id_in_yr(p_period_year cn_period_statuses.period_year%TYPE) IS
171             SELECT MAX(p.period_id) max_period_id
172               FROM cn_period_statuses p,
173                    cn_period_types    pt
174              WHERE period_year = p_period_year
175                AND p.period_type = pt.period_type
176                AND pt.period_type_id = 0
177                   --R12
178                AND p.org_id = p_org_id
179                AND pt.org_id = p_org_id;
180 
181         l_pay_period_id cn_pmt_plans.pay_interval_type_id%TYPE;
182         l_rec_period_id cn_pmt_plans.recoverable_interval_type_id%TYPE;
183     BEGIN
184         IF p_pay_interval_type_id = -1000 --pay interval is period
185         THEN
186             l_pay_period_id := p_period_id;
187         ELSIF p_pay_interval_type_id = -1001 --pay interval is quarter
188         THEN
189             FOR rec IN get_max_period_id_in_qtr(p_quarter_num, p_period_year)
190             LOOP
191                 l_pay_period_id := rec.max_period_id;
192             END LOOP;
193         ELSIF p_pay_interval_type_id = -1002 --pay interval is year
194         THEN
195             FOR rec IN get_max_period_id_in_yr(p_period_year)
196             LOOP
197                 l_pay_period_id := rec.max_period_id;
198             END LOOP;
199         END IF;
200 
201         IF p_recoverable_interval_type_id = -1000 --recover interval is period
202         THEN
203             l_rec_period_id := p_period_id;
204         ELSIF p_recoverable_interval_type_id = -1001 --recover interval is quarter
205         THEN
206             FOR rec IN get_max_period_id_in_qtr(p_quarter_num, p_period_year)
207             LOOP
208                 l_rec_period_id := rec.max_period_id;
209             END LOOP;
210         ELSIF p_recoverable_interval_type_id = -1002 --recover interval is year
211         THEN
212             FOR rec IN get_max_period_id_in_yr(p_period_year)
213             LOOP
214                 l_rec_period_id := rec.max_period_id;
215             END LOOP;
216         END IF;
217 
218         x_pay_period_id := l_pay_period_id;
219         x_rec_period_id := l_rec_period_id;
220     END get_pay_rec_period_ids;
221 
222     -- ===========================================================================
223     --   Procedure   : reset_payrun_id
224     --   Description : This procedure is used to Reset payrun_id to NULL in
225     --                  cn_payment_transactions for PMTPLN_REC, COMMISSION and BONUS
226     --                  to be included in the next payrun.
227     --                  Added for bug 2776847 by jjhuang.
228     --   Calls       :
229     -- ===========================================================================
230     PROCEDURE reset_payrun_id
231     (
232         p_payrun_id          IN cn_payruns.payrun_id%TYPE,
233         p_salesrep_id        IN cn_salesreps.salesrep_id%TYPE,
234         p_incentive_type     IN cn_payruns.incentive_type_code%TYPE,
235         p_payment_group_code IN cn_pmt_plans.payment_group_code%TYPE
236     ) IS
237     BEGIN
238         IF p_incentive_type = 'ALL'
239            OR p_incentive_type IS NULL
240         THEN
241             UPDATE cn_payment_transactions ptrx
242                SET payrun_id         = NULL,
243                    last_update_date  = SYSDATE,
244                    last_updated_by   = g_last_updated_by,
245                    last_update_login = g_last_update_login
246              WHERE ptrx.payrun_id = p_payrun_id
247                AND ptrx.credited_salesrep_id = p_salesrep_id
248                AND ptrx.incentive_type_code IN ('PMTPLN_REC', 'COMMISSION', 'BONUS')
249                AND EXISTS (SELECT 1
250                       FROM cn_quotas_all q
251                      WHERE q.quota_id = ptrx.quota_id
252                        AND q.payment_group_code = p_payment_group_code);
253         ELSE
254             UPDATE cn_payment_transactions ptrx
255                SET payrun_id         = NULL,
256                    last_update_date  = SYSDATE,
257                    last_updated_by   = g_last_updated_by,
258                    last_update_login = g_last_update_login
259              WHERE ptrx.payrun_id = p_payrun_id
260                AND ptrx.credited_salesrep_id = p_salesrep_id
261                AND ptrx.incentive_type_code IN ('PMTPLN_REC', decode(p_incentive_type, 'COMMISSION', 'COMMISSION', 'BONUS', 'BONUS'))
262                AND EXISTS (SELECT 1
263                       FROM cn_quotas_all q
264                      WHERE q.quota_id = ptrx.quota_id
265                        AND q.payment_group_code = p_payment_group_code);
266         END IF;
267     END reset_payrun_id;
268 
269     -- ===========================================================================
270     --   Procedure   : give_min_as_pmt_plan
271     --   Description : This procedure is used to give the minimum amount as a payment
272     --                  plan amount when it's a pay period, but not a recover period
273     --                  when pay against commission is 'N'.
274     --                  Added for bug 2776847 by jjhuang.
275     --   Calls       :
276     -- ===========================================================================
277     PROCEDURE give_min_as_pmt_plan
278     (
279         p_min                 IN cn_pmt_plans.minimum_amount%TYPE,
280         p_min_rec_flag        IN cn_pmt_plans.min_rec_flag%TYPE,
281         x_pmt_amount_adj_rec  OUT NOCOPY NUMBER,
282         x_pmt_amount_adj_nrec OUT NOCOPY NUMBER
283     ) IS
284         l_pmt_amount_adj_rec  NUMBER := 0;
285         l_pmt_amount_adj_nrec NUMBER := 0;
286     BEGIN
287         --minimum calculation
288         IF (p_min IS NOT NULL)
289         THEN
290             IF p_min_rec_flag = 'Y'
291             THEN
292                 l_pmt_amount_adj_rec := p_min;
293             ELSE
294                 l_pmt_amount_adj_nrec := p_min;
295             END IF;
296         END IF;
297 
298         x_pmt_amount_adj_rec  := l_pmt_amount_adj_rec;
299         x_pmt_amount_adj_nrec := l_pmt_amount_adj_nrec;
300     END give_min_as_pmt_plan;
301 
302     -- ===========================================================================
303     --   Procedure   : get_start_and_end_dates
304     --   Description : This procedure is used to get the start date and end date of
305     --                  a interval.  An interval could be period, quarter or year
306     --                  depending on p_interval_type_id.
307     --                  Added for bug 2776847 by jjhuang.
308     --   Calls       :
309     -- ===========================================================================
310     PROCEDURE get_start_and_end_dates
311     (
312         p_interval_type_id    IN NUMBER,
313         p_period_set_id       IN cn_period_statuses.period_set_id%TYPE,
314         p_period_type_id      IN cn_period_statuses.period_type_id%TYPE,
315         p_period_year         IN cn_period_statuses.period_year%TYPE,
316         p_quarter_num         IN cn_period_statuses.period_year%TYPE,
317         p_start_date          IN cn_period_statuses.start_date%TYPE,
318         p_end_date            IN cn_period_statuses.end_date%TYPE,
319         x_interval_start_date OUT NOCOPY cn_period_statuses.start_date%TYPE,
320         x_interval_end_date   OUT NOCOPY cn_period_statuses.end_date%TYPE,
321         --R12
322         p_org_id IN cn_payruns.org_id%TYPE
323     ) IS
324         l_interval_start_date cn_period_statuses.start_date%TYPE;
325         l_interval_end_date   cn_period_statuses.end_date%TYPE;
326     BEGIN
327         IF p_interval_type_id = -1000
328         THEN
329             --period
330             l_interval_start_date := p_start_date;
331             l_interval_end_date   := p_end_date;
332         ELSIF p_interval_type_id = -1001
333         THEN
334             --quarter, get the start, end dates of the quarter.
335             SELECT MIN(start_date),
336                    MAX(end_date)
337               INTO l_interval_start_date,
338                    l_interval_end_date
339               FROM cn_period_statuses
340              WHERE period_set_id = p_period_set_id
341                AND period_type_id = p_period_type_id
342                AND quarter_num = p_quarter_num
343                AND period_year = p_period_year
344                   --R12
345                AND org_id = p_org_id;
346         ELSIF p_interval_type_id = -1002
347         THEN
348             SELECT MIN(start_date),
349                    MAX(end_date)
350               INTO l_interval_start_date,
351                    l_interval_end_date
352               FROM cn_period_statuses
353              WHERE period_set_id = p_period_set_id
354                AND period_type_id = p_period_type_id
355                AND period_year = p_period_year
356                   --R12
357                AND org_id = p_org_id;
358         END IF;
359 
360         x_interval_start_date := l_interval_start_date;
361         x_interval_end_date   := l_interval_end_date;
362     END get_start_and_end_dates;
363 
364     -- ===========================================================================
365     --   Procedure   : distribute_pmt_plan_amount
366     --   Description : This procedure is used to distribute payment plan amount evenly on
367     --                  all quotas on a pay interval basis.  A pay interval could be
368     --                  a period, or a quarter or a year depending on the pay interval
369     --                  type that associates with the payment plan.
370     --                  Taken out from original calculate_totals procedure for bug 2776847 by jjhuang.
371     --   Calls       :
372     -- ===========================================================================
373     PROCEDURE distribute_pmt_plan_amount
374     (
375         p_salesrep_id         IN cn_salesreps.salesrep_id%TYPE,
376         p_pmt_amount_adj_rec  IN NUMBER,
377         p_pmt_amount_adj_nrec IN NUMBER,
378         p_payment_group_code  IN cn_srp_pmt_plans_v.payment_group_code%TYPE,
379         p_period_id           IN cn_payruns.pay_period_id%TYPE,
380         p_incentive_type      IN cn_quotas.incentive_type_code%TYPE,
381         x_calc_rec_tbl        IN OUT NOCOPY calc_rec_tbl_type,
382         --R12
383         p_org_id IN cn_payruns.org_id%TYPE
384     ) IS
385         CURSOR get_pe_pg_count(p_payment_group_code VARCHAR2) IS
386             SELECT COUNT(DISTINCT cnq.quota_id) num_pe
387               FROM cn_srp_period_quotas cspq,
388                    cn_quotas_all        cnq
389              WHERE cnq.payment_group_code = p_payment_group_code
390                AND cspq.quota_id = cnq.quota_id
391                AND cnq.credit_type_id = -1000
392                AND cspq.salesrep_id = p_salesrep_id
393                AND cspq.period_id = p_period_id
394                   --R12
395                AND cspq.org_id = cnq.org_id
396                AND cspq.org_id = p_org_id
397                   --bug 3107646, issue 4
398                AND cnq.incentive_type_code =
399                    decode(nvl(p_incentive_type, cnq.incentive_type_code), 'COMMISSION', 'COMMISSION', 'BONUS', 'BONUS', cnq.incentive_type_code)
400                   -- BUG 3140343 Payee design
401                AND cspq.quota_id NOT IN (SELECT spayee.quota_id
402                                            FROM cn_srp_payee_assigns spayee,
403                                                 cn_period_statuses   ps
404                                           WHERE (spayee.salesrep_id = p_salesrep_id OR spayee.payee_id = p_salesrep_id)
405                                             AND ps.period_id = p_period_id
406                                             AND ps.end_date >= spayee.start_date
407                                                --R12
408                                             AND spayee.org_id = ps.org_id
409                                             AND spayee.org_id = p_org_id
410                                             AND ps.start_date <= nvl(spayee.end_date, ps.end_date));
411         CURSOR get_pe_pg(p_payment_group_code VARCHAR2) IS
412             SELECT DISTINCT cnq.quota_id quota_id
413               FROM cn_srp_period_quotas cspq,
414                    cn_quotas_all        cnq
415              WHERE cnq.payment_group_code = p_payment_group_code
416                AND cspq.quota_id = cnq.quota_id
417                AND cnq.credit_type_id = -1000
418                AND cspq.salesrep_id = p_salesrep_id
419                AND cspq.period_id = p_period_id
420                   --R12
421                AND cspq.org_id = cnq.org_id
422                AND cspq.org_id = p_org_id
423                   --bug 3107646, issue 4
424                AND cnq.incentive_type_code =
425                    decode(nvl(p_incentive_type, cnq.incentive_type_code), 'COMMISSION', 'COMMISSION', 'BONUS', 'BONUS', cnq.incentive_type_code)
426                   -- BUG 3140343 Payee design
427                AND cspq.quota_id NOT IN (SELECT spayee.quota_id
428                                            FROM cn_srp_payee_assigns spayee,
429                                                 cn_period_statuses   ps
430                                           WHERE (spayee.salesrep_id = p_salesrep_id OR spayee.payee_id = p_salesrep_id)
431                                             AND ps.period_id = p_period_id
432                                             AND ps.end_date >= spayee.start_date
433                                                --R12
434                                             AND spayee.org_id = ps.org_id
435                                             AND spayee.org_id = p_org_id
436                                             AND ps.start_date <= nvl(spayee.end_date, ps.end_date));
437         l_pe_count NUMBER := 0;
438     BEGIN
439         -- If payment plan adjustments exist, determine how to distribute them
440         IF p_pmt_amount_adj_rec <> 0
441            OR p_pmt_amount_adj_nrec <> 0
442         THEN
443             -- How many plan elements assigned to this rep have this payment group code?
444             FOR rec IN get_pe_pg_count(p_payment_group_code)
445             LOOP
446                 l_pe_count := rec.num_pe;
447             END LOOP;
448 
449             -- Update rec and nrec amount for each worksheet
450             -- that is created for pe that is assigned the current payment group code
451             FOR pe IN get_pe_pg(p_payment_group_code)
452             LOOP
453                 FOR i IN x_calc_rec_tbl.FIRST .. x_calc_rec_tbl.LAST
454                 LOOP
455                     IF x_calc_rec_tbl(i).quota_id = pe.quota_id
456                     THEN
457                         x_calc_rec_tbl(i).pmt_amount_adj_rec := nvl(x_calc_rec_tbl(i).pmt_amount_adj_rec, 0) + p_pmt_amount_adj_rec / l_pe_count;
458                         x_calc_rec_tbl(i).pmt_amount_adj_nrec := nvl(x_calc_rec_tbl(i).pmt_amount_adj_nrec, 0) + p_pmt_amount_adj_nrec / l_pe_count;
459                     END IF;
460                 END LOOP;
461             END LOOP; -- end of loop to fetch plan elements for current payment group code
462         END IF; --end of p_pmt_amount_adj_rec <> 0 OR p_pmt_amount_adj_nrec <> 0
463     END distribute_pmt_plan_amount;
464 
465     -- ===========================================================================
466     --   Procedure   : proc_pmt_trans_by_pe
467     --   Description : This procedure is used to process (sum up) all payment transactions by pe.
468     --                  Taken out from original calculate_totals procedure for bug 2776847 by jjhuang.
469     --               : Comments for Bug 3198445 by jjhuang:
470     --               : 1. The following case does not exist for bug 3198445 by jjhuang:
471     --                  p_payment_group_code IS NOT NULL AND p_applied_pgc.COUNT = 0
472     --               : 2. When p_payment_group_code is NULL, it includes two cases:
473     --                  i.  No payment plan assignments for this salesrep at this period.
474     --                  ii. Post action for 1 to n-1 paymenet group codes applied to this srp at the period
475     --                      where there are n payment group codes at the current period.
476     --                  iii. If n payment group codes applied already given there are n payment group codes,
477     --                      do nothing.
478     --   Calls       :
479     -- ===========================================================================
480     PROCEDURE proc_pmt_trans_by_pe
481     (
482         p_salesrep_id        IN cn_payment_worksheets.salesrep_id%TYPE,
483         p_incentive_type     IN cn_payruns.incentive_type_code%TYPE,
484         p_payrun_id          IN cn_payruns.payrun_id%TYPE,
485         p_payment_group_code IN cn_pmt_plans.payment_group_code%TYPE, --bug 3175375 by jjhuang.
486         p_applied_pgc        IN dbms_sql.varchar2_table, --bug 3198445 by jjhuang.
487         x_calc_rec_tbl       IN OUT NOCOPY calc_rec_tbl_type,
488         --R12
489         p_org_id IN cn_payruns.org_id%TYPE
490     ) IS
491         -- 2/7/03 AC Bug 2792037 get list of PE from cn_payment_transactions
492         -- 2/12/03 AC Bug 2800968 union all to old cursor(against cn_srp_periods)
493         -- to take care srp with no transaction but want to apply pmt plan
494         -- Bug 3140343 : Payee Design.
495         -- Bug 3198445 by jjhuang:  Added payment_group_code for cursor get_srp_pe
496         CURSOR get_srp_pe IS
497         --Added cn_quotas_all for bug 3175375 by jjhuang.
498             SELECT DISTINCT v.quota_id,
499                             v.payment_group_code
500               FROM (SELECT cnpt.quota_id,
501                            cq.payment_group_code
502                       FROM cn_payment_transactions cnpt,
503                            cn_quotas_all           cq
504                      WHERE cnpt.credit_type_id = g_credit_type_id
505                        AND cnpt.credited_salesrep_id = p_salesrep_id
506                        AND cnpt.payrun_id = p_payrun_id
507                        AND ((cnpt.incentive_type_code NOT IN ('COMMISSION', 'BONUS')) OR
508                            (cnpt.incentive_type_code = nvl(p_incentive_type, cnpt.incentive_type_code)))
509                        AND cnpt.quota_id = cq.quota_id
510                        AND cq.payment_group_code = nvl(p_payment_group_code, cq.payment_group_code)
511                     UNION ALL
512                     SELECT cnsp.quota_id,
513                            cnq.payment_group_code
514                       FROM cn_srp_period_quotas cnsp,
515                            cn_quotas_all        cnq,
516                            cn_payruns           cnp
517                      WHERE cnsp.salesrep_id = p_salesrep_id
518                        AND cnq.credit_type_id = g_credit_type_id
519                        AND cnq.incentive_type_code = nvl(p_incentive_type, cnq.incentive_type_code)
520                        AND cnp.payrun_id = p_payrun_id
521                        AND cnp.pay_period_id = cnsp.period_id
522                        AND cnsp.quota_id = cnq.quota_id
523                        AND cnq.payment_group_code = nvl(p_payment_group_code, cnq.payment_group_code)
524                        AND NOT EXISTS (
525                             -- separate queries for performance reasons. merge cartesian reported
526                             SELECT 1
527                               FROM cn_srp_payee_assigns_all spayee,
528                                     cn_period_statuses_all   ps
529                              WHERE (spayee.salesrep_id = p_salesrep_id)
530                                AND ps.period_id = cnp.pay_period_id
531                                AND ps.end_date >= spayee.start_date
532                                AND ps.org_id = p_org_id
533                                AND cnsp.quota_id = spayee.quota_id
534                                AND ps.start_date <= nvl(spayee.end_date, ps.end_date)
535                             UNION ALL
536                             SELECT 1
537                               FROM cn_srp_payee_assigns_all spayee,
538                                    cn_period_statuses_all   ps
539                              WHERE spayee.payee_id = p_salesrep_id
540                                AND ps.period_id = cnp.pay_period_id
541                                AND ps.end_date >= spayee.start_date
542                                AND ps.org_id = p_org_id
543                                AND cnsp.quota_id = spayee.quota_id
544                                AND ps.start_date <= nvl(spayee.end_date, ps.end_date))) v;
545 
546         -- Bug 3198445 by jjhuang:  get distinct payment group code count.
547         --Added cn_quotas_all for bug 3175375 by jjhuang.
548         CURSOR get_pgc_count IS
549             SELECT COUNT(DISTINCT v.payment_group_code) pgc_count
550               FROM (SELECT cnpt.quota_id,
551                            cq.payment_group_code
552                       FROM cn_payment_transactions cnpt,
553                            cn_quotas_all           cq
554                      WHERE cnpt.credit_type_id = g_credit_type_id
555                        AND cnpt.credited_salesrep_id = p_salesrep_id
556                        AND cnpt.payrun_id = p_payrun_id
557                        AND ((cnpt.incentive_type_code NOT IN ('COMMISSION', 'BONUS')) OR
558                            (cnpt.incentive_type_code = nvl(p_incentive_type, cnpt.incentive_type_code)))
559                        AND cnpt.quota_id = cq.quota_id
560                        AND cq.payment_group_code = nvl(p_payment_group_code, cq.payment_group_code)
561                     UNION ALL
562                     SELECT cnsp.quota_id,
563                            cnq.payment_group_code
564                       FROM cn_srp_period_quotas cnsp,
565                            cn_quotas_all        cnq,
566                            cn_payruns           cnp
567                      WHERE cnsp.salesrep_id = p_salesrep_id
568                        AND cnq.credit_type_id = g_credit_type_id
569                        AND cnq.incentive_type_code = nvl(p_incentive_type, cnq.incentive_type_code)
570                        AND cnp.payrun_id = p_payrun_id
571                        AND cnp.pay_period_id = cnsp.period_id
572                        AND cnsp.quota_id = cnq.quota_id
573                        AND cnq.payment_group_code = nvl(p_payment_group_code, cnq.payment_group_code)
574                        AND NOT EXISTS (
575                             -- separate queries for performance reasons. merge cartesian reported
576                             SELECT 1
577                               FROM cn_srp_payee_assigns_all spayee,
578                                     cn_period_statuses_all   ps
579                              WHERE (spayee.salesrep_id = p_salesrep_id)
580                                AND ps.period_id = cnp.pay_period_id
581                                AND ps.end_date >= spayee.start_date
582                                AND ps.org_id = p_org_id
583                                AND cnsp.quota_id = spayee.quota_id
584                                AND ps.start_date <= nvl(spayee.end_date, ps.end_date)
585                             UNION ALL
586                             SELECT 1
587                               FROM cn_srp_payee_assigns_all spayee,
588                                    cn_period_statuses_all   ps
589                              WHERE spayee.payee_id = p_salesrep_id
590                                AND ps.period_id = cnp.pay_period_id
591                                AND ps.end_date >= spayee.start_date
592                                AND ps.org_id = p_org_id
593                                AND cnsp.quota_id = spayee.quota_id
594                                AND ps.start_date <= nvl(spayee.end_date, ps.end_date))) v;
595 
596         -- remove join to cn_quotas_all since can get quota_id from cnpt
597         -- 03/24/03 -9999 is used in cnupsp2.sql, change to -9990
598         CURSOR get_earnings_total_by_pe(p_quota_id NUMBER) IS
599         -- earnings to populate pmt_amount_calc
600             SELECT nvl(SUM(nvl(cnpt.amount, 0)), 0) pmt_amount_calc,
601                    cnpt.quota_id quota_id,
602                    0 pmt_amount_recovery,
603                    0 pmt_amount_adj,
604                    0 held_amount
605               FROM cn_payment_transactions cnpt
606              WHERE cnpt.credited_salesrep_id = p_salesrep_id
607                AND cnpt.incentive_type_code = nvl(p_incentive_type, cnpt.incentive_type_code)
608                AND cnpt.incentive_type_code IN ('COMMISSION', 'BONUS')
609                AND cnpt.payrun_id = p_payrun_id
610                AND nvl(hold_flag, 'N') = 'N'
611                AND nvl(cnpt.quota_id, -9990) = nvl(p_quota_id, -9990)
612                   --R12
613                AND cnpt.org_id = p_org_id
614              GROUP BY cnpt.quota_id
615             UNION ALL
616             -- Recovery to populate pmt_amount_recovery
617             SELECT 0 pmt_amount_calc,
618                    cnpt.quota_id quota_id,
619                    nvl(SUM(nvl(cnpt.amount, 0)), 0) pmt_amount_recovery,
620                    0 pmt_amount_adj,
621                    0 held_amount
622               FROM cn_payment_transactions cnpt
623              WHERE cnpt.credited_salesrep_id = p_salesrep_id
624                AND cnpt.incentive_type_code = 'PMTPLN_REC'
625                AND cnpt.payrun_id = p_payrun_id
626                AND nvl(cnpt.quota_id, -9990) = nvl(p_quota_id, -9990)
627                   --R12
628                AND cnpt.org_id = p_org_id
629              GROUP BY cnpt.quota_id
630             UNION ALL
631             -- to populate manual pay adjustments in pmt_amount_adj
632             SELECT 0 pmt_amount_calc,
633                    cnpt.quota_id quota_id,
634                    0 pmt_amount_recovery,
635                    nvl(SUM(nvl(cnpt.amount, 0)), 0) pmt_amount_adj,
636                    0 held_amount
637               FROM cn_payment_transactions cnpt
638              WHERE cnpt.credited_salesrep_id = p_salesrep_id
639                AND cnpt.incentive_type_code IN ('MANUAL_PAY_ADJ')
640                AND cnpt.payrun_id = p_payrun_id
641                AND nvl(cnpt.quota_id, -9990) = nvl(p_quota_id, -9990)
642                   --R12
643                AND cnpt.org_id = p_org_id
644              GROUP BY cnpt.quota_id
645             UNION ALL
646             -- to populate control payments in pmt_amount_adj
647             SELECT 0 pmt_amount_calc,
648                    cnpt.quota_id quota_id,
649                    0 pmt_amount_recovery,
650                    nvl(SUM(nvl(cnpt.payment_amount, 0)), 0) - nvl(SUM(nvl(cnpt.amount, 0)), 0) pmt_amount_adj,
651                    0 held_amount
652               FROM cn_payment_transactions cnpt
653              WHERE cnpt.credited_salesrep_id = p_salesrep_id
654                AND cnpt.incentive_type_code = nvl(p_incentive_type, cnpt.incentive_type_code)
655                AND cnpt.incentive_type_code IN ('COMMISSION', 'BONUS')
656                AND nvl(cnpt.hold_flag, 'N') = 'N'
657                AND cnpt.payrun_id = p_payrun_id
658                AND nvl(cnpt.quota_id, -9990) = nvl(p_quota_id, -9990)
659                   --R12
660                AND cnpt.org_id = p_org_id
661              GROUP BY cnpt.quota_id
662             UNION ALL
663             -- to populate hold in pmt_amount_adj
664             SELECT 0 pmt_amount_calc,
665                    cnpt.quota_id quota_id,
666                    0 pmt_amount_recovery,
667                    0 pmt_amount_adj,
668                    nvl(SUM(nvl(cnpt.payment_amount, 0)), 0) held_amount
669               FROM cn_payment_transactions cnpt
670              WHERE cnpt.credited_salesrep_id = p_salesrep_id
671                AND cnpt.incentive_type_code = nvl(p_incentive_type, cnpt.incentive_type_code)
672                AND cnpt.incentive_type_code IN ('COMMISSION', 'BONUS')
673                AND nvl(cnpt.hold_flag, 'N') = 'Y'
674                AND cnpt.payrun_id = p_payrun_id
675                AND nvl(cnpt.quota_id, -9990) = nvl(p_quota_id, -9990)
676                   --R12
677                AND cnpt.org_id = p_org_id
678              GROUP BY cnpt.quota_id
679             UNION ALL
680             -- to populate waive recovery in pmt_amount_adj
681             -- changed recovery amount to negative for fix  BUG#2545629|
682             SELECT 0 pmt_amount_calc,
683                    cnpt.quota_id quota_id,
684                    0 pmt_amount_recovery,
685                    -nvl(SUM(nvl(cnpt.amount, 0)), 0) pmt_amount_adj,
686                    0 held_amount
687               FROM cn_payment_transactions cnpt
688              WHERE cnpt.credited_salesrep_id = p_salesrep_id
689                AND cnpt.incentive_type_code = 'PMTPLN_REC'
690                AND nvl(cnpt.waive_flag, 'N') = 'Y'
691                AND cnpt.payrun_id = p_payrun_id
692                AND nvl(cnpt.quota_id, -9990) = nvl(p_quota_id, -9990)
693                   --R12
694                AND cnpt.org_id = p_org_id
695              GROUP BY cnpt.quota_id;
696 
697         --local variables
698         l_record_count    NUMBER := 0;
699         l_pmt_amount_calc NUMBER := 0;
700         l_pmt_amount_rec  NUMBER := 0;
701         l_pmt_amount_adj  NUMBER := 0;
702         l_held_amount     NUMBER := 0;
703         --variables used for bug 3198445 by jjhuang -begin
704         l_pgc_count   NUMBER := 0;
705         l_post_action NUMBER := 0; --0 is false, 1 is true;
706         l_count       NUMBER := 0;
707 
708         TYPE quotas_rec_type IS RECORD(
709             quota_id cn_quotas.quota_id%TYPE);
710 
711         TYPE quotas_rec_tbl_type IS TABLE OF quotas_rec_type INDEX BY BINARY_INTEGER;
712 
713         l_quota_tbl       quotas_rec_tbl_type;
714         l_quotas_to_apply NUMBER;
715         --variables used for bug 3198445 by jjhuang -end
716     BEGIN
717         -- Bug 3198445 by jjhuang.
718         --Find total number of payment group codes need to be applied.
719         FOR each_row IN get_pgc_count
720         LOOP
721             l_pgc_count := each_row.pgc_count;
722         END LOOP;
723 
724         --Post step after applying 1 to n-1 payment group codes out of n payment group codes
725         --for this srp at the current period. For bug 3198445 by jjhuang.
726         --Only create those quotas that are in different payment group codes.
727         IF (p_payment_group_code IS NULL AND p_applied_pgc.COUNT <> 0 AND l_pgc_count <> p_applied_pgc.COUNT)
728         THEN
729             l_post_action     := 1;
730             l_quotas_to_apply := 0;
731 
732             FOR each_quota IN get_srp_pe
733             LOOP
734                 l_count := 0;
735 
736                 FOR i IN p_applied_pgc.FIRST .. p_applied_pgc.LAST
737                 LOOP
738                     IF (each_quota.payment_group_code = p_applied_pgc(i))
739                     THEN
740                         l_count := l_count + 1;
741                     END IF;
742                 END LOOP;
743 
744                 IF l_count = 0
745                 THEN
746                     l_quota_tbl(l_quotas_to_apply).quota_id := each_quota.quota_id;
747                     l_quotas_to_apply := l_quotas_to_apply + 1;
748 
749                     --payment group codes already applied before, do nothing.
750                 ELSIF l_count > 0
751                 THEN
752                     NULL;
753                 END IF;
754             END LOOP;
755         END IF;
756 
757         -- Bug 3140343 : Payee Design.
758         l_record_count := x_calc_rec_tbl.COUNT;
759 
760         IF l_post_action = 1
761         THEN
762             FOR i IN l_quota_tbl.FIRST .. l_quota_tbl.LAST
763             LOOP
764                 x_calc_rec_tbl(l_record_count).quota_id := NULL;
765                 x_calc_rec_tbl(l_record_count).pmt_amount_adj_rec := 0;
766                 x_calc_rec_tbl(l_record_count).pmt_amount_adj_nrec := 0;
767                 x_calc_rec_tbl(l_record_count).pmt_amount_calc := 0;
768                 x_calc_rec_tbl(l_record_count).pmt_amount_rec := 0;
769                 x_calc_rec_tbl(l_record_count).pmt_amount_ctr := 0;
770                 x_calc_rec_tbl(l_record_count).held_amount := 0;
771                 l_pmt_amount_calc := 0;
772                 l_pmt_amount_rec := 0;
773                 l_pmt_amount_adj := 0;
774                 l_held_amount := 0;
775 
776                 FOR earnings IN get_earnings_total_by_pe(l_quota_tbl(i).quota_id)
777                 LOOP
778                     l_pmt_amount_calc := l_pmt_amount_calc + earnings.pmt_amount_calc;
779                     l_pmt_amount_rec  := l_pmt_amount_rec + earnings.pmt_amount_recovery;
780                     l_pmt_amount_adj  := l_pmt_amount_adj + earnings.pmt_amount_adj;
781                     l_held_amount     := l_held_amount + earnings.held_amount;
782                 END LOOP;
783 
784                 x_calc_rec_tbl(l_record_count).quota_id := l_quota_tbl(i).quota_id;
785                 x_calc_rec_tbl(l_record_count).pmt_amount_calc := l_pmt_amount_calc;
786                 x_calc_rec_tbl(l_record_count).pmt_amount_rec := l_pmt_amount_rec;
787                 x_calc_rec_tbl(l_record_count).pmt_amount_ctr := l_pmt_amount_adj;
788                 x_calc_rec_tbl(l_record_count).held_amount := l_held_amount;
789                 l_record_count := l_record_count + 1;
790             END LOOP;
791             -- This elsif branch includes the following cases for bug 3198445 by jjhuang.
792             -- 1.  No payment plans for this srp for this period. That is:
793             --      p_payment_group_code is NULL AND p_applied_pgc.COUNT = 0
794             -- 2.  Apply the current payment group code to this srp. That is:
795             --      p_payment_group_code IS NOT NULL AND p_applied_pgc.COUNT <> 0
796         ELSIF ((l_post_action = 0 AND p_payment_group_code IS NULL AND p_applied_pgc.COUNT = 0) OR
797               (l_post_action = 0 AND p_payment_group_code IS NOT NULL AND p_applied_pgc.COUNT <> 0))
798         THEN
799             FOR each_quota IN get_srp_pe
800             LOOP
801                 x_calc_rec_tbl(l_record_count).quota_id := NULL;
802                 x_calc_rec_tbl(l_record_count).pmt_amount_adj_rec := 0;
803                 x_calc_rec_tbl(l_record_count).pmt_amount_adj_nrec := 0;
804                 x_calc_rec_tbl(l_record_count).pmt_amount_calc := 0;
805                 x_calc_rec_tbl(l_record_count).pmt_amount_rec := 0;
806                 x_calc_rec_tbl(l_record_count).pmt_amount_ctr := 0;
807                 x_calc_rec_tbl(l_record_count).held_amount := 0;
808                 l_pmt_amount_calc := 0;
809                 l_pmt_amount_rec := 0;
810                 l_pmt_amount_adj := 0;
811                 l_held_amount := 0;
812 
813                 FOR earnings IN get_earnings_total_by_pe(each_quota.quota_id)
814                 LOOP
815                     l_pmt_amount_calc := l_pmt_amount_calc + earnings.pmt_amount_calc;
816                     l_pmt_amount_rec  := l_pmt_amount_rec + earnings.pmt_amount_recovery;
817                     l_pmt_amount_adj  := l_pmt_amount_adj + earnings.pmt_amount_adj;
818                     l_held_amount     := l_held_amount + earnings.held_amount;
819                 END LOOP;
820 
821                 x_calc_rec_tbl(l_record_count).quota_id := each_quota.quota_id;
822                 x_calc_rec_tbl(l_record_count).pmt_amount_calc := l_pmt_amount_calc;
823                 x_calc_rec_tbl(l_record_count).pmt_amount_rec := l_pmt_amount_rec;
824                 x_calc_rec_tbl(l_record_count).pmt_amount_ctr := l_pmt_amount_adj;
825                 x_calc_rec_tbl(l_record_count).held_amount := l_held_amount;
826                 l_record_count := l_record_count + 1;
827             END LOOP;
828             -- This elsif branch includes the following case for bug 3198445 by jjhuang.
829             -- All the payment group codes have been applied to this srp. Do nothing.
830         ELSIF (l_post_action = 0 AND p_payment_group_code IS NULL AND p_applied_pgc.COUNT <> 0 AND l_pgc_count = p_applied_pgc.COUNT)
831         THEN
832             NULL;
833         END IF;
834     END proc_pmt_trans_by_pe;
835 
836     -- ===========================================================================
837     --   Procedure   : Calculate_totals
838     --   Description : This procedure is used to calculate totals from payment plans.
839     --                  This procedure takes care of all cases which are accessiable from UI.
840     --                  All other cases will be blocked by UI.
841     --
842     --                  PayAgainstCommission        PayInterval     RecoveryInterval
843     --                  Y                           P               P
844     --                  Y                           Q               Q
845     --                  Y                           Y               Y
846     --                  N                           P               P
847     --                  N                           Q               Q
848     --                  N                           Y               Y
849     --                  N                           P               Q
850     --                  N                           P               Y
851     --                  N                           Q               Y
852     --
853     --                  P stands for period, Q stands for quarter and Y stands for Year in
854     --                  PayInterval and RecoveryInterval.
855     --                  Y stands for yes and N stands for no in PayAgainstCommission.
856     --
857     --                  The logic in this procedure is:
858     --
859     --                  IF payment plans exist
860     --                  THEN
861     --                      IF ( srp_pmt_plan.pay_against_commission in ('Y', 'N')
862     --                          AND l_period_id = l_pay_period_id
863     --                          AND l_period_id = l_rec_period_id )
864     --                      THEN
865     --                          do payment plans;
866     --                      ELSE
867     --                          IF ( srp_pmt_plan.pay_against_commission = 'N'
868     --                              AND l_period_id = l_pay_period_id
869     --                              AND l_period_id <> l_rec_period_id )
870     --                          THEN
871     --                              give min as payment plan;
872     --                          ELSIF ( srp_pmt_plan.pay_against_commission = 'N'
873     --                              AND l_period_id <> l_pay_period_id )
874     --                          THEN
875     --                              reset payrun_id to NULL to be included in the next payrun calculation;
876     --                          ELSIF ( srp_pmt_plan.pay_against_commission = 'Y'
877     --                              AND l_period_id <> l_rec_period_id )
878     --                          THEN
879     --                              pay earnings;
880     --                          END IF;
881     --                      END IF;
882     --                  END IF;
883     --
884     --                  IF no payment plans
885     --                  THEN
886     --                      pay earnings;
887     --                  END IF;
888     --   Calls       :
889     -- ===========================================================================
890     PROCEDURE calculate_totals
891     (
892         p_salesrep_id    IN cn_payment_worksheets.salesrep_id%TYPE,
893         p_period_id      IN cn_payruns.pay_period_id%TYPE,
894         p_incentive_type IN cn_payruns.incentive_type_code%TYPE,
895         p_payrun_id      IN cn_payruns.payrun_id%TYPE,
896         x_calc_rec_tbl   IN OUT NOCOPY calc_rec_tbl_type,
897         --R12
898         p_org_id IN cn_payruns.org_id%TYPE
899     ) IS
900         CURSOR get_earnings_total(p_payment_group_code VARCHAR2) IS
901             SELECT SUM(cnpt.payment_amount) payment_amount
902               FROM cn_payment_transactions cnpt,
903                    cn_quotas_all           cnq
904              WHERE cnpt.credited_salesrep_id = p_salesrep_id
905                AND cnpt.payrun_id = p_payrun_id
906                AND cnpt.quota_id = cnq.quota_id
907                AND nvl(hold_flag, 'N') = 'N'
908                AND nvl(waive_flag, 'N') = 'N'
909                AND cnq.payment_group_code = p_payment_group_code
910                AND cnpt.incentive_type_code <> 'PMTPLN';
911 
912         TYPE srppmtplncurtype IS REF CURSOR;
913 
914         srp_pmt_plan_cur srppmtplncurtype;
915         srp_pmt_plan     cn_srp_pmt_plans_v%ROWTYPE;
916         l_stmt           VARCHAR2(4000);
917 
918         --  Cursor to get the Periods
919         CURSOR get_prd_statuses(p_period_id NUMBER) IS
920             SELECT quarter_num,
921                    period_year,
922                    period_set_id,
923                    period_type_id,
924                    start_date,
925                    end_date
926               FROM cn_period_statuses
927              WHERE period_id = p_period_id
928                   --R12
929                AND org_id = p_org_id;
930 
931         l_get_prd_statuses get_prd_statuses%ROWTYPE;
932 
933         CURSOR get_qtr_sdate(p_period_set_id NUMBER, p_period_type_id NUMBER, p_period_year NUMBER, p_quarter_num NUMBER) IS
934             SELECT MIN(start_date)
935               FROM cn_period_statuses
936              WHERE period_set_id = p_period_set_id
937                AND period_type_id = p_period_type_id
938                AND period_year = p_period_year
939                AND quarter_num = p_quarter_num
940                   --R12
941                AND org_id = p_org_id;
942 
943         CURSOR get_qtr_edate(p_period_set_id NUMBER, p_period_type_id NUMBER, p_period_year NUMBER, p_quarter_num NUMBER) IS
944             SELECT MAX(end_date)
945               FROM cn_period_statuses
946              WHERE period_set_id = p_period_set_id
947                AND period_type_id = p_period_type_id
948                AND period_year = p_period_year
949                AND quarter_num = p_quarter_num
950                   --R12
951                AND org_id = p_org_id;
952 
953         CURSOR get_year_sdate(p_period_set_id NUMBER, p_period_type_id NUMBER, p_period_year NUMBER) IS
954             SELECT MIN(start_date)
955               FROM cn_period_statuses
956              WHERE period_set_id = p_period_set_id
957                AND period_type_id = p_period_type_id
958                AND period_year = p_period_year
959                AND org_id = p_org_id;
960 
961         CURSOR get_year_edate(p_period_set_id NUMBER, p_period_type_id NUMBER, p_period_year NUMBER) IS
962             SELECT MAX(end_date)
963               FROM cn_period_statuses
964              WHERE period_set_id = p_period_set_id
965                AND period_type_id = p_period_type_id
966                AND period_year = p_period_year
967                AND org_id = p_org_id;
968 
969         -- Bug 2875120/2892822 : combine 2 cursor
970         -- get the amount paid at the payment group code level
971         CURSOR get_itd_amount_paid(p_period_set_id NUMBER, p_period_type_id NUMBER, p_interval_sdate DATE, p_interval_edate DATE, p_pg_code cn_pmt_plans.payment_group_code%TYPE) IS
972             SELECT nvl(SUM(balance1_dtd - balance1_ctd), 0) payment
973               FROM cn_srp_periods     csp,
974                    cn_quotas_all      q,
975                    cn_period_statuses ps
976              WHERE csp.period_id = ps.period_id
977                AND ps.period_set_id = p_period_set_id
978                AND ps.period_type_id = p_period_type_id
979                AND ps.start_date >= p_interval_sdate
980                AND ps.end_date <= p_interval_edate
981                AND csp.salesrep_id = p_salesrep_id
982                AND csp.credit_type_id = g_credit_type_id
983                AND csp.quota_id = q.quota_id
984                AND q.payment_group_code = p_pg_code
985                AND csp.org_id = q.org_id
986                AND q.org_id = ps.org_id
987                AND ps.org_id = p_org_id;
988 
989         --local variables
990         -- variable to hold pre - pmt plan value
991         l_net_pre_pmtplan     NUMBER := 0;
992         l_itd_paid            NUMBER := 0;
993         l_pe_count            NUMBER := 0;
994         l_pmt_amount_adj_rec  NUMBER := 0;
995         l_pmt_amount_adj_nrec NUMBER := 0;
996         -- Variables for determining if current period is eligible for
997         -- payment plan adjustments
998         l_period_set_id  NUMBER;
999         l_period_type_id NUMBER;
1000         l_start_date     DATE;
1001         l_end_date       DATE;
1002         l_qtr_num        NUMBER;
1003         l_year_num       NUMBER;
1004         l_period_id      NUMBER;
1005         l_interval_sdate DATE;
1006         l_interval_edate DATE;
1007         l_count          NUMBER;
1008         l_srp_earnings   NUMBER := 0;
1009         l_srp_recovery   NUMBER := 0;
1010         l_total_amount   NUMBER := 0;
1011         l_amount         NUMBER := 0;
1012         l_earnings       NUMBER := 0;
1013         l_recovery       NUMBER := 0;
1014         l_ctr_amount     NUMBER := 0;
1015         --variables added for bug 2776847 by jjhuang
1016         l_pay_period_id  cn_period_statuses.period_id%TYPE;
1017         l_rec_period_id  cn_period_statuses.period_id%TYPE;
1018         l_pmt_plan_count NUMBER := 0;
1019         -- varialve added for Bug 3140343
1020         l_ispayee NUMBER := 0;
1021         --Bug 3198445 by jjhuang
1022         l_applied_pgc       dbms_sql.varchar2_table;
1023         l_applied_pgc_count NUMBER;
1024     BEGIN
1025         --
1026         -- get quarter Number and Year Number
1027         --
1028         OPEN get_prd_statuses(p_period_id);
1029 
1030         FETCH get_prd_statuses
1031             INTO l_get_prd_statuses;
1032 
1033         CLOSE get_prd_statuses;
1034 
1035         -- Build dynamic sql for cursor
1036         l_stmt := 'SELECT v.pay_interval_type_id, v.recoverable_interval_type_id, ' || 'v.pay_against_commission, v.payment_group_code, v.minimum_amount, ' ||
1037                   'v.maximum_amount, v.min_rec_flag, v.max_rec_flag, v.name ' || 'FROM ' || '(SELECT ' || ' cnpp.pay_interval_type_id,' ||
1038                   ' cnpp.recoverable_interval_type_id,' || ' nvl(cnpp.pay_against_commission, ''Y'') pay_against_commission,' || ' cnpp.payment_group_code,' ||
1039                   ' cspp.minimum_amount,' || ' cnpp.min_rec_flag,' || ' cnpp.max_rec_flag,' || ' cspp.maximum_amount,' || ' cnps.period_id,' ||
1040                   ' cspp.salesrep_id,' || ' cnps.start_date prd_start_date,' || ' cnps.end_date prd_end_date,' || ' cnpp.name,' ||
1041                   ' ROW_NUMBER() over (PARTITION BY cnpp.payment_group_code' || '       ORDER BY cspp.start_date DESC) AS row_nums ,' || ' cnpp.credit_type_id' ||
1042                   ' FROM cn_srp_pmt_plans cspp,cn_pmt_plans cnpp,cn_period_statuses cnps ' || ' WHERE ' || ' cspp.salesrep_id = :p_salesrep_id' ||
1043                   ' AND cnpp.pmt_plan_id = cspp.pmt_plan_id ' || ' AND cnps.period_id   = :p_period_id' || ' AND cnpp.credit_type_id = -1000' ||
1044                   ' AND cspp.start_date <= cnps.end_date' ||
1045                  -- ' AND Nvl(cspp.end_date,cnps.start_date) >= cnps.start_date' ||
1046                  --bug 3395792 by jjhuang on 1/23/04
1047                  --' AND NVL(cspp.end_date, cnpp.end_date) >= cnps.end_date ' ||
1048                  --for bug 3395792 on 2/4/04 by jjhuang.  This is to include the following test case:
1049                  --If there are two or more payment plans (with the same payment group code) within one period, for example:
1050                  --pmt_plan1 from "01-MAY-2003" to "15-MAY-2003", pmt_plan2 from "16-MAY-2003" to "28-MAY-2003".
1051                   ' AND NVL(NVL(cspp.end_date, cnpp.end_date),cnps.start_date) >= cnps.start_date ' || ' AND cspp.org_id = cnpp.org_id ' || --R12
1052                   ' AND cnpp.org_id = cnps.org_id ' || --R12
1053                   ' AND cnps.org_id = :p_org_id ' || --R12
1054                   ' ) v           ' || ' WHERE row_nums = 1' || '  AND EXISTS' || '  (' || '   SELECT ''x''' ||
1055                   '   FROM cn_srp_period_quotas cspq, cn_quotas_all cq' || '   WHERE decode(:p_incentive_type,''ALL'', cq.incentive_type_code,' ||
1056                   '                NULL, cq.incentive_type_code,' || '                 :p_incentive_type) = cq.incentive_type_code' ||
1057                   '   AND v.credit_type_id = cq.credit_type_id' || '   AND v.payment_group_code = cq.payment_group_code' ||
1058                   '   AND v.salesrep_id = cspq.salesrep_id' || '   AND cspq.quota_id = cq.quota_id' || '   AND cspq.org_id = cq.org_id' ||
1059                   '   AND v.period_id = cspq.period_id ' || '   AND cspq.org_id = cq.org_id ' || --R12
1060                   '   AND cq.org_id = :p_org_id ' || --R12
1061                   '   AND cspq.quota_id NOT IN ' || '   ( SELECT spayee.quota_id ' || '   FROM cn_srp_payee_assigns spayee' ||
1062                   '   WHERE (spayee.salesrep_id = v.salesrep_id OR ' || '    spayee.payee_id = v.salesrep_id)' || '   AND v.prd_end_date >= spayee.start_date' ||
1063                   '    AND spayee.org_id = :p_org_id' || --R12
1064                   '   AND v.prd_start_date <= Nvl(spayee.end_date, v.prd_end_date) )' || ' )';
1065         -- Bug 3140343 : Payee Design. Check if this salesrep is a Payee
1066         l_ispayee := cn_api.is_payee(p_period_id => p_period_id, p_salesrep_id => p_salesrep_id, p_org_id => p_org_id);
1067 
1068         -- if not a payee
1069         IF l_ispayee <> 1
1070         THEN
1071             --
1072             -- get Payment plans
1073             --
1074             -- Find payment plans assigned to the rep for the current payrun
1075             -- period that match the payment group codes of the plan elements
1076 
1077             --      FOR srp_pmt_plan IN get_srp_pmt_plan LOOP
1078 
1079             --Bug 3198445 by jjhuang
1080             l_applied_pgc.DELETE;
1081             l_applied_pgc_count := 0;
1082 
1083             OPEN srp_pmt_plan_cur FOR l_stmt
1084                 USING p_salesrep_id, p_period_id, p_org_id, p_incentive_type, p_incentive_type, p_org_id, p_org_id;
1085 
1086             LOOP
1087                 FETCH srp_pmt_plan_cur
1088                     INTO srp_pmt_plan.pay_interval_type_id, srp_pmt_plan.recoverable_interval_type_id,
1089                     srp_pmt_plan.pay_against_commission, srp_pmt_plan.payment_group_code, srp_pmt_plan.minimum_amount,
1090                     srp_pmt_plan.maximum_amount, srp_pmt_plan.min_rec_flag, srp_pmt_plan.max_rec_flag, srp_pmt_plan.NAME;
1091 
1092                 EXIT WHEN srp_pmt_plan_cur%NOTFOUND;
1093                 --With payment plans.
1094                 l_pmt_plan_count      := l_pmt_plan_count + 1;
1095                 l_period_id           := p_period_id;
1096                 l_pmt_amount_adj_rec  := 0;
1097                 l_pmt_amount_adj_nrec := 0;
1098 
1099                 --Bug 2776847 by jjhuang
1100                 get_pay_rec_period_ids(p_period_id                    => p_period_id,
1101                                        p_quarter_num                  => l_get_prd_statuses.quarter_num,
1102                                        p_period_year                  => l_get_prd_statuses.period_year,
1103                                        p_pay_interval_type_id         => srp_pmt_plan.pay_interval_type_id,
1104                                        p_recoverable_interval_type_id => srp_pmt_plan.recoverable_interval_type_id,
1105                                        x_pay_period_id                => l_pay_period_id,
1106                                        x_rec_period_id                => l_rec_period_id,
1107                                        --R12
1108                                        p_org_id => p_org_id);
1109                 --Bug 3198445 by jjhuang
1110                 l_applied_pgc(l_applied_pgc_count) := srp_pmt_plan.payment_group_code;
1111 
1112                 --Bug 2776847 by jjhuang
1113                 --It's recovery period and pay period regardless of pay_against_commission = 'Y' or 'N', do payment plans.
1114                 --IF 1.
1115                 IF ((srp_pmt_plan.pay_against_commission = 'Y' OR srp_pmt_plan.pay_against_commission = 'N') AND l_period_id = l_pay_period_id AND
1116                    l_period_id = l_rec_period_id)
1117                 THEN
1118                     proc_pmt_trans_by_pe(p_salesrep_id        => p_salesrep_id,
1119                                          p_incentive_type     => p_incentive_type,
1120                                          p_payrun_id          => p_payrun_id,
1121                                          p_payment_group_code => srp_pmt_plan.payment_group_code, --bug 3175375 by jjhuang.
1122                                          p_applied_pgc        => l_applied_pgc, --Bug 3198445 by jjhuang
1123                                          x_calc_rec_tbl       => x_calc_rec_tbl,
1124                                          --R12
1125                                          p_org_id => p_org_id);
1126                     --
1127                     -- get the start date and end date for the given period
1128                     --
1129                     l_qtr_num        := l_get_prd_statuses.quarter_num;
1130                     l_year_num       := l_get_prd_statuses.period_year;
1131                     l_period_set_id  := l_get_prd_statuses.period_set_id;
1132                     l_period_type_id := l_get_prd_statuses.period_type_id;
1133                     l_start_date     := l_get_prd_statuses.start_date;
1134                     l_end_date       := l_get_prd_statuses.end_date;
1135 
1136                     IF srp_pmt_plan.pay_interval_type_id = -1001 --interval is quarter
1137                     THEN
1138                         OPEN get_qtr_sdate(l_period_set_id, l_period_type_id, l_year_num, l_qtr_num);
1139 
1140                         FETCH get_qtr_sdate
1141                             INTO l_interval_sdate;
1142 
1143                         CLOSE get_qtr_sdate;
1144 
1145                         OPEN get_qtr_edate(l_period_set_id, l_period_type_id, l_year_num, l_qtr_num);
1146 
1147                         FETCH get_qtr_edate
1148                             INTO l_interval_edate;
1149 
1150                         CLOSE get_qtr_edate;
1151                     ELSIF srp_pmt_plan.pay_interval_type_id = -1002
1152                     THEN
1153                         OPEN get_year_sdate(l_period_set_id, l_period_type_id, l_year_num);
1154 
1155                         FETCH get_year_sdate
1156                             INTO l_interval_sdate;
1157 
1158                         CLOSE get_year_sdate;
1159 
1160                         OPEN get_year_edate(l_period_set_id, l_period_type_id, l_year_num);
1161 
1162                         FETCH get_year_edate
1163                             INTO l_interval_edate;
1164 
1165                         CLOSE get_year_edate;
1166                     ELSE
1167                         -- pay interval is period
1168                         l_interval_sdate := l_start_date;
1169                         l_interval_edate := l_end_date;
1170                     END IF;
1171 
1172                     l_itd_paid := 0;
1173 
1174                     --Get the cash paid interval to date
1175                     -- Bug 2875120 : combine 2 cursor and for loop into one
1176                     FOR amount IN get_itd_amount_paid(l_period_set_id, l_period_type_id, l_interval_sdate, l_interval_edate, srp_pmt_plan.payment_group_code)
1177                     LOOP
1178                         l_itd_paid := nvl(l_itd_paid, 0) + nvl(amount.payment, 0);
1179                     END LOOP;
1180 
1181                     -- Determine due amount for current payrun from payment transactions
1182                     -- Add earnings from current period
1183                     l_net_pre_pmtplan := 0;
1184 
1185                     OPEN get_earnings_total(srp_pmt_plan.payment_group_code);
1186 
1187                     FETCH get_earnings_total
1188                         INTO l_net_pre_pmtplan;
1189 
1190                     CLOSE get_earnings_total;
1191 
1192                     l_itd_paid := l_itd_paid + nvl(l_net_pre_pmtplan, 0);
1193 
1194                     IF srp_pmt_plan.minimum_amount IS NOT NULL
1195                        AND srp_pmt_plan.minimum_amount > l_itd_paid
1196                     THEN
1197                         IF nvl(srp_pmt_plan.min_rec_flag, 'N') = 'Y'
1198                         THEN
1199                             l_pmt_amount_adj_rec := srp_pmt_plan.minimum_amount - l_itd_paid;
1200                         ELSE
1201                             l_pmt_amount_adj_nrec := srp_pmt_plan.minimum_amount - l_itd_paid;
1202                         END IF;
1203                     END IF; -- End of minimum calculation
1204 
1205                     IF srp_pmt_plan.maximum_amount IS NOT NULL
1206                        AND srp_pmt_plan.maximum_amount < l_itd_paid
1207                     THEN
1208                         IF nvl(srp_pmt_plan.max_rec_flag, 'N') = 'Y'
1209                         THEN
1210                             l_pmt_amount_adj_rec := srp_pmt_plan.maximum_amount - l_itd_paid;
1211                         ELSE
1212                             l_pmt_amount_adj_nrec := srp_pmt_plan.maximum_amount - l_itd_paid;
1213                         END IF;
1214                     END IF; -- End of maximum calculation
1215 
1216                     --If payment plan adjustments exist, determine how to distribute them.
1217                     --In other words, do distribution evenly on all quotas on pay interval basis.
1218                     distribute_pmt_plan_amount(p_salesrep_id         => p_salesrep_id,
1219                                                p_pmt_amount_adj_rec  => l_pmt_amount_adj_rec,
1220                                                p_pmt_amount_adj_nrec => l_pmt_amount_adj_nrec,
1221                                                p_payment_group_code  => srp_pmt_plan.payment_group_code,
1222                                                p_period_id           => p_period_id,
1223                                                p_incentive_type      => p_incentive_type, --bug 3107646, issue 4
1224                                                x_calc_rec_tbl        => x_calc_rec_tbl,
1225                                                --R12
1226                                                p_org_id => p_org_id);
1227                 ELSE
1228                     --not recovery period, but pay period, reset payrun_id to NULL. Give min as payment plan, then distribute it.
1229                     IF (srp_pmt_plan.pay_against_commission = 'N' AND l_period_id = l_pay_period_id AND l_period_id <> l_rec_period_id)
1230                     THEN
1231                         reset_payrun_id(p_payrun_id          => p_payrun_id,
1232                                         p_salesrep_id        => p_salesrep_id,
1233                                         p_incentive_type     => p_incentive_type,
1234                                         p_payment_group_code => srp_pmt_plan.payment_group_code);
1235                         proc_pmt_trans_by_pe(p_salesrep_id        => p_salesrep_id,
1236                                              p_incentive_type     => p_incentive_type,
1237                                              p_payrun_id          => p_payrun_id,
1238                                              p_payment_group_code => srp_pmt_plan.payment_group_code, --bug 3175375 by jjhuang.
1239                                              p_applied_pgc        => l_applied_pgc, --Bug 3198445 by jjhuang
1240                                              x_calc_rec_tbl       => x_calc_rec_tbl,
1241                                              --R12
1242                                              p_org_id => p_org_id);
1243                         give_min_as_pmt_plan(p_min                 => srp_pmt_plan.minimum_amount,
1244                                              p_min_rec_flag        => nvl(srp_pmt_plan.min_rec_flag, 'N'),
1245                                              x_pmt_amount_adj_rec  => l_pmt_amount_adj_rec,
1246                                              x_pmt_amount_adj_nrec => l_pmt_amount_adj_nrec);
1247                         get_start_and_end_dates(p_interval_type_id    => srp_pmt_plan.pay_interval_type_id,
1248                                                 p_period_set_id       => l_get_prd_statuses.period_set_id,
1249                                                 p_period_type_id      => l_get_prd_statuses.period_type_id,
1250                                                 p_period_year         => l_get_prd_statuses.period_year,
1251                                                 p_quarter_num         => l_get_prd_statuses.quarter_num,
1252                                                 p_start_date          => l_get_prd_statuses.start_date,
1253                                                 p_end_date            => l_get_prd_statuses.end_date,
1254                                                 x_interval_start_date => l_interval_sdate,
1255                                                 x_interval_end_date   => l_interval_edate,
1256                                                 --R12
1257                                                 p_org_id => p_org_id);
1258                         --Do distribution evenly on all quotas on pay interval basis.
1259                         distribute_pmt_plan_amount(p_salesrep_id         => p_salesrep_id,
1260                                                    p_pmt_amount_adj_rec  => l_pmt_amount_adj_rec,
1261                                                    p_pmt_amount_adj_nrec => l_pmt_amount_adj_nrec,
1262                                                    p_payment_group_code  => srp_pmt_plan.payment_group_code,
1263                                                    p_period_id           => p_period_id,
1264                                                    p_incentive_type      => p_incentive_type, --bug 3107646, issue 4
1265                                                    x_calc_rec_tbl        => x_calc_rec_tbl,
1266                                                    --R12
1267                                                    p_org_id => p_org_id);
1268                         --not pay period, reset payrun_id to NULL so those amount will be included into the next payrun.
1269                     ELSIF (srp_pmt_plan.pay_against_commission = 'N' AND l_period_id <> l_pay_period_id)
1270                     THEN
1271                         reset_payrun_id(p_payrun_id          => p_payrun_id,
1272                                         p_salesrep_id        => p_salesrep_id,
1273                                         p_incentive_type     => p_incentive_type,
1274                                         p_payment_group_code => srp_pmt_plan.payment_group_code);
1275                         proc_pmt_trans_by_pe(p_salesrep_id        => p_salesrep_id,
1276                                              p_incentive_type     => p_incentive_type,
1277                                              p_payrun_id          => p_payrun_id,
1278                                              p_payment_group_code => srp_pmt_plan.payment_group_code, --bug 3175375 by jjhuang.
1279                                              p_applied_pgc        => l_applied_pgc, --Bug 3198445 by jjhuang
1280                                              x_calc_rec_tbl       => x_calc_rec_tbl,
1281                                              --R12
1282                                              p_org_id => p_org_id);
1283                         --not recovery period for pay_against_commission = 'Y', so pay earnings.
1284                     ELSIF (srp_pmt_plan.pay_against_commission = 'Y' AND l_period_id <> l_rec_period_id)
1285                     THEN
1286                         proc_pmt_trans_by_pe(p_salesrep_id        => p_salesrep_id,
1287                                              p_incentive_type     => p_incentive_type,
1288                                              p_payrun_id          => p_payrun_id,
1289                                              p_payment_group_code => srp_pmt_plan.payment_group_code, --bug 3175375 by jjhuang.
1290                                              p_applied_pgc        => l_applied_pgc, --Bug 3198445 by jjhuang
1291                                              x_calc_rec_tbl       => x_calc_rec_tbl,
1292                                              --R12
1293                                              p_org_id => p_org_id);
1294                     END IF;
1295                 END IF; --end of IF 1.
1296 
1297                 --Bug 3198445 by jjhuang
1298                 l_applied_pgc_count := l_applied_pgc_count + 1;
1299                 NULL;
1300             END LOOP; --end of loop FOR srp_pmt_plan IN get_srp_pmt_plan
1301 
1302             CLOSE srp_pmt_plan_cur;
1303         END IF; -- end if l_ispayee <> 1
1304 
1305         --For Bug 2776847 by jjhuang.
1306         --If no payment plans assigned, we need to only get x_calc_rec_tbl to pay the earnings.
1307         -- Commented out by jjhuang for bug 3198445.
1308         --proc_pmt_trans_by_pe includes the case where no payment plans assigned.
1309         proc_pmt_trans_by_pe(p_salesrep_id        => p_salesrep_id,
1310                              p_incentive_type     => p_incentive_type,
1311                              p_payrun_id          => p_payrun_id,
1312                              p_payment_group_code => NULL, --bug 3175375 by jjhuang.
1313                              p_applied_pgc        => l_applied_pgc, --Bug 3198445 by jjhuang
1314                              x_calc_rec_tbl       => x_calc_rec_tbl,
1315                              --R12
1316                              p_org_id => p_org_id);
1317         -- Commented out by jjhuang for bug 3198445. END IF;
1318     END calculate_totals;
1319 
1320     -- ===========================================================================
1321     -- Procedure  : Create_Worksheet
1322     -- Description: Private API to create a payment worksheet
1323     -- ===========================================================================
1324     PROCEDURE create_worksheet
1325     (
1326         p_api_version      IN NUMBER,
1327         p_init_msg_list    IN VARCHAR2,
1328         p_commit           IN VARCHAR2,
1329         p_validation_level IN NUMBER,
1330         x_return_status    OUT NOCOPY VARCHAR2,
1331         x_msg_count        OUT NOCOPY NUMBER,
1332         x_msg_data         OUT NOCOPY VARCHAR2,
1333         p_worksheet_rec    IN worksheet_rec_type,
1334         x_loading_status   OUT NOCOPY VARCHAR2,
1335         x_status           OUT NOCOPY VARCHAR2
1336     ) IS
1337         l_api_name CONSTANT VARCHAR2(30) := 'Create_Worksheet';
1338         l_payment_worksheet_id NUMBER;
1339         l_calc_pmt_amount      NUMBER;
1340         l_adj_pmt_amount_rec   NUMBER;
1341         l_adj_pmt_amount_nrec  NUMBER;
1342         l_held_amount          NUMBER;
1343         l_pay_element_type_id  NUMBER;
1344         l_quota_id             NUMBER;
1345         l_count                NUMBER := 0;
1346         l_payroll_flag         VARCHAR2(01);
1347         l_period_id            NUMBER;
1348         l_pbt_profile_value    VARCHAR2(01) := 'N';
1349         l_calc_rec_tbl         calc_rec_tbl_type;
1350         cls_posting_batch_id   NUMBER;
1351         recv_posting_batch_id  NUMBER;
1352         l_pmt_amount_rec       NUMBER := 0;
1353         l_pmt_amount_ctr       NUMBER := 0;
1354         l_incentive_type       VARCHAR2(30);
1355         l_rowid                VARCHAR2(30);
1356         l_srp_total            NUMBER;
1357         l_pmt_total            NUMBER;
1358         l_comm_total           NUMBER;
1359         l_found                NUMBER;
1360         l_call_from            VARCHAR2(30);
1361         TYPE num_tab IS TABLE OF NUMBER;
1362         l_wk_plan_elements num_tab;
1363 
1364         -- changes for bug#2568937
1365         -- for ap integration population of account
1366         l_payables_flag       cn_repositories.payables_flag%TYPE;
1367         l_payables_ccid_level cn_repositories.payables_ccid_level%TYPE;
1368 
1369         -- changes for bug#2568937
1370         -- for ap integration population of account
1371         --R12
1372         CURSOR get_apps IS
1373             SELECT payables_flag,
1374                    payroll_flag,
1375                    payables_ccid_level
1376               FROM cn_repositories
1377              WHERE org_id = p_worksheet_rec.org_id;
1378 
1379         CURSOR get_worksheet IS
1380             SELECT 1
1381               FROM cn_payment_worksheets,
1382                    cn_payruns
1383              WHERE cn_payment_worksheets.salesrep_id = p_worksheet_rec.salesrep_id
1384                AND cn_payment_worksheets.payrun_id = cn_payruns.payrun_id
1385                AND quota_id IS NULL
1386                AND cn_payruns.status <> 'PAID';
1387 
1388         err_num NUMBER;
1389 
1390         -- Get the Payrun informations
1391         CURSOR get_payrun IS
1392             SELECT payrun_id,
1393                    pay_period_id,
1394                    incentive_type_code,
1395                    pay_date
1396               FROM cn_payruns
1397              WHERE payrun_id = p_worksheet_rec.payrun_id
1398                FOR UPDATE NOWAIT;
1399 
1400        -- Get the Payrun informations for conc program
1401         CURSOR get_payrun_for_conc_program IS
1402             SELECT payrun_id,
1403                    pay_period_id,
1404                    incentive_type_code,
1405                    pay_date
1406               FROM cn_payruns
1407              WHERE payrun_id = p_worksheet_rec.payrun_id;
1408 
1409         -- Get the period information
1410         CURSOR get_prd_statuses(p_period_id NUMBER) IS
1411             SELECT quarter_num,
1412                    period_year,
1413                    period_set_id,
1414                    period_type_id,
1415                    start_date,
1416                    end_date
1417               FROM cn_period_statuses
1418              WHERE period_id = p_period_id
1419                AND org_id = p_worksheet_rec.org_id;
1420 
1421         CURSOR get_srp_total(p_period_id NUMBER) IS
1422             SELECT nvl(SUM(nvl(srp.balance2_dtd, 0) - nvl(srp.balance2_ctd, 0) + nvl(srp.balance2_bbd, 0) - nvl(srp.balance2_bbc, 0)), 0)
1423               FROM cn_srp_periods srp
1424              WHERE srp.period_id = p_period_id
1425                AND srp.salesrep_id = p_worksheet_rec.salesrep_id
1426                AND srp.credit_type_id = g_credit_type_id
1427                AND quota_id IS NULL
1428                AND org_id = p_worksheet_rec.org_id;
1429 
1430         CURSOR get_pmt_total(p_period_id NUMBER) IS
1431             SELECT nvl(SUM(nvl(amount, 0)), 0)
1432               FROM cn_payment_transactions pmt
1433              WHERE pmt.pay_period_id <= p_period_id
1434                AND pmt.credited_salesrep_id = p_worksheet_rec.salesrep_id
1435                AND pmt.credit_type_id = g_credit_type_id
1436                AND pmt.incentive_type_code IN ('COMMISSION', 'BONUS')
1437                AND (pmt.payrun_id IS NULL OR pmt.payrun_id = p_worksheet_rec.payrun_id)
1438                   --R12
1439                AND pmt.org_id = p_worksheet_rec.org_id;
1440 
1441         -- 12/27/04 : Bug 4090737 Performance Issue Creating Worksheet START
1442         CURSOR get_comm_total(p_period_id NUMBER) IS
1443             SELECT
1444              nvl(SUM(nvl(commission_amount, 0)), 0)
1445               FROM cn_commission_lines_all ccl
1446              WHERE credited_salesrep_id = p_worksheet_rec.salesrep_id
1447                AND processed_period_id <= p_period_id
1448                AND credit_type_id = g_credit_type_id
1449                AND status = 'CALC'
1450                AND posting_status = 'UNPOSTED'
1451                AND srp_payee_assign_id IS NULL
1452                   -- posting_status not set to posted yet
1453                AND NOT EXISTS (SELECT NULL
1454                       FROM cn_payment_transactions_all pmt
1455                      WHERE pmt.credited_salesrep_id = ccl.credited_salesrep_id
1456                        AND pmt.commission_line_id = ccl.commission_line_id
1457                        AND pmt.credit_type_id = ccl.credit_type_id
1458                        AND pmt.incentive_type_code IN ('COMMISSION', 'BONUS')
1459                        AND pmt.payrun_id = p_worksheet_rec.payrun_id)
1460                AND ccl.org_id = p_worksheet_rec.org_id;
1461 
1462         -- 12/27/04 : Bug 4090737 Performance Issue Creating Worksheet END
1463 
1464         -- Bug 3140343 : Payee Design
1465         CURSOR get_comm_total_payee(p_period_id NUMBER) IS
1466             SELECT /*+ index(cl CN_COMMISSION_LINES_N14) */
1467              nvl(SUM(nvl(commission_amount, 0)), 0)
1468               FROM cn_commission_lines      cl,
1469                    cn_srp_payee_assigns_all spayee
1470              WHERE cl.srp_payee_assign_id IS NOT NULL
1471                AND cl.srp_payee_assign_id = spayee.srp_payee_assign_id
1472                AND spayee.payee_id = p_worksheet_rec.salesrep_id
1473                AND cl.credited_salesrep_id = spayee.salesrep_id
1474                AND cl.processed_period_id <= p_period_id
1475                AND cl.status = 'CALC'
1476                AND cl.credit_type_id = g_credit_type_id
1477                AND cl.posting_status = 'UNPOSTED'
1478                AND cl.org_id = spayee.org_id
1479                AND cl.commission_line_id NOT IN (SELECT pmt.commission_line_id
1480                                                    FROM cn_payment_transactions pmt
1481                                                   WHERE pmt.credited_salesrep_id = p_worksheet_rec.salesrep_id
1482                                                     AND pmt.credit_type_id = g_credit_type_id
1483                                                     AND pmt.incentive_type_code IN ('COMMISSION', 'BONUS')
1484                                                     AND pmt.payrun_id = p_worksheet_rec.payrun_id)
1485                   --R12
1486                AND cl.org_id = p_worksheet_rec.org_id
1487                AND spayee.org_id = p_worksheet_rec.org_id;
1488 
1489         CURSOR get_worksheet_id IS
1490             SELECT payment_worksheet_id
1491               FROM cn_payment_worksheets
1492              WHERE payrun_id = p_worksheet_rec.payrun_id
1493                AND salesrep_id = p_worksheet_rec.salesrep_id
1494                AND quota_id IS NULL;
1495 
1496         l_get_payrun_rec   get_payrun%ROWTYPE; -- Payrun
1497         l_get_prd_statuses get_prd_statuses%ROWTYPE; -- Period
1498         l_pmt_trans_rec    cn_pmt_trans_pkg.pmt_trans_rec_type; -- PmtTrans
1499         l_batch_rec        cn_prepostbatches.posting_batch_rec_type;
1500         l_tmp              NUMBER := 0;
1501         l_calc_status      cn_srp_intel_periods.processing_status_code%TYPE;
1502         l_ispayee          NUMBER := 0;
1503         l_has_access       BOOLEAN;
1504 
1505     BEGIN
1506         -- Standard Start of API savepoint
1507         SAVEPOINT create_worksheet;
1508 
1509         -- Standard call to check for call compatibility.
1510         IF NOT fnd_api.compatible_api_call(g_api_version, p_api_version, l_api_name, g_pkg_name)
1511         THEN
1512             RAISE fnd_api.g_exc_unexpected_error;
1513         END IF;
1514 
1515         -- Initialize message list if p_init_msg_list is set to TRUE.
1516         IF fnd_api.to_boolean(p_init_msg_list)
1517         THEN
1518             fnd_msg_pub.initialize;
1519         END IF;
1520 
1521         --  Initialize API return status to success
1522         x_return_status  := fnd_api.g_ret_sts_success;
1523         x_loading_status := 'CN_INSERTED';
1524         --Added for R12 payment security check begin.
1525         l_has_access := cn_payment_security_pvt.get_security_access(cn_payment_security_pvt.g_type_wksht, cn_payment_security_pvt.g_access_wksht_create);
1526 
1527         IF (l_has_access = FALSE)
1528         THEN
1529             RAISE fnd_api.g_exc_error;
1530         END IF;
1531 
1532         -- API body
1533         -- The following validations are performed by this API
1534         -- Check for the following mandatory parameters payrun_id, salesrep_id,
1535         -- Pay run should be unpaid
1536         -- Salesrep should not be on hold -cn_salesreps.hold_payment
1537         -- Subledger entry should exist for salesrep,  credit_type and period
1538         -- cn_srp_periods
1539         -- Mandatory parameters check for payrun_id, salesrep_id
1540         IF ((cn_api.chk_miss_null_num_para(p_num_para       => p_worksheet_rec.payrun_id,
1541                                            p_obj_name       => cn_api.get_lkup_meaning('PAY_RUN_NAME', 'PAY_RUN_VALIDATION_TYPE'),
1542                                            p_loading_status => x_loading_status,
1543                                            x_loading_status => x_loading_status)) = fnd_api.g_true)
1544         THEN
1545             RAISE fnd_api.g_exc_error;
1546         END IF;
1547 
1548         IF ((cn_api.chk_miss_null_num_para(p_num_para       => p_worksheet_rec.salesrep_id,
1549                                            p_obj_name       => cn_api.get_lkup_meaning('SALES_PERSON', 'PAY_RUN_VALIDATION_TYPE'),
1550                                            p_loading_status => x_loading_status,
1551                                            x_loading_status => x_loading_status)) = fnd_api.g_true)
1552         THEN
1553             RAISE fnd_api.g_exc_error;
1554         END IF;
1555 
1556         -- Check Payrun Status
1557         IF cn_api.chk_payrun_status_paid(p_payrun_id => p_worksheet_rec.payrun_id, p_loading_status => x_loading_status, x_loading_status => x_loading_status) =
1558            fnd_api.g_true
1559         THEN
1560             RAISE fnd_api.g_exc_error;
1561         END IF;
1562 
1563         -- Check if the salesrep is on hold
1564         IF cn_api.chk_srp_hold_status(p_salesrep_id => p_worksheet_rec.salesrep_id,
1565                                       --R12
1566                                       p_org_id         => p_worksheet_rec.org_id,
1567                                       p_loading_status => x_loading_status,
1568                                       x_loading_status => x_loading_status) = fnd_api.g_true
1569         THEN
1570             RAISE fnd_api.g_exc_error;
1571         END IF;
1572 
1573         -- Get the Payrun
1574         BEGIN
1575             l_call_from := p_worksheet_rec.call_from;
1576 
1577             IF l_call_from = cn_payment_worksheet_pvt.concurrent_program_call
1578             THEN
1579                 OPEN get_payrun_for_conc_program;
1580                 FETCH get_payrun_for_conc_program
1581                     INTO l_get_payrun_rec;
1582                 CLOSE get_payrun_for_conc_program;
1583             ELSE
1584                 OPEN get_payrun;
1585                 FETCH get_payrun
1586                     INTO l_get_payrun_rec;
1587                 CLOSE get_payrun;
1588             END IF;
1589         EXCEPTION
1590             WHEN OTHERS THEN
1591                 err_num := SQLCODE;
1592                 IF l_call_from = cn_payment_worksheet_pvt.concurrent_program_call
1593                 THEN
1594                     CLOSE get_payrun_for_conc_program;
1595                 ELSE
1596                     CLOSE get_payrun;
1597                 END IF;
1598 
1599                 IF err_num = -54
1600                 THEN
1601                     fnd_message.set_name('CN', 'CN_INVALID_OBJECT_VERSION');
1602                     fnd_msg_pub.add;
1603                     RAISE fnd_api.g_exc_error;
1604                 ELSE
1605                     RAISE;
1606                 END IF;
1607         END;
1608 
1609         -- fix for bug 5334261
1610         OPEN get_worksheet;
1611         FETCH get_worksheet
1612             INTO l_found;
1613         CLOSE get_worksheet;
1614 
1615         IF l_found = 1
1616         THEN
1617             IF fnd_msg_pub.check_msg_level(fnd_msg_pub.g_msg_lvl_error)
1618             THEN
1619                 fnd_message.set_name('CN', 'CN_DUPLICATE_WORKSHEET');
1620                 fnd_msg_pub.add;
1621             END IF;
1622 
1623             x_loading_status := 'CN_DUPLICATE_WORKSHEET';
1624             RAISE fnd_api.g_exc_error;
1625         END IF;
1626 
1627         -- Get the Pay By Summary Profile value
1628         -- N - Pay by Summary Y - Pay by Transaction
1629         l_pbt_profile_value := cn_payment_security_pvt.get_pay_by_mode(p_worksheet_rec.payrun_id);
1630 
1631         -- Bug 3140343 : Payee Design. Check if this salesrep is a Payee
1632         l_ispayee := cn_api.is_payee(p_period_id   => l_get_payrun_rec.pay_period_id,
1633                                      p_salesrep_id => p_worksheet_rec.salesrep_id,
1634                                      p_org_id      => p_worksheet_rec.org_id);
1635 
1636         -- Check duplicate worksheet
1637         IF cn_api.chk_duplicate_worksheet(p_payrun_id      => p_worksheet_rec.payrun_id,
1638                                           p_salesrep_id    => p_worksheet_rec.salesrep_id,
1639                                           p_org_id         => p_worksheet_rec.org_id,
1640                                           p_loading_status => x_loading_status,
1641                                           x_loading_status => x_loading_status) = fnd_api.g_true
1642         THEN
1643             RAISE fnd_api.g_exc_error;
1644         END IF;
1645 
1646         -- get quarter Number and Year Number
1647         OPEN get_prd_statuses(l_get_payrun_rec.pay_period_id);
1648 
1649         FETCH get_prd_statuses
1650             INTO l_get_prd_statuses;
1651 
1652         CLOSE get_prd_statuses;
1653 
1654         -- get the posting batch id
1655         SELECT cn_posting_batches_s.NEXTVAL
1656           INTO cls_posting_batch_id
1657           FROM dual;
1658 
1659         -- if the payrun incentive type code is ALL
1660         -- we will set the incentive type as NULL
1661         -- which means we will get both Bonus and Commissions
1662         IF l_get_payrun_rec.incentive_type_code = 'ALL'
1663         THEN
1664             l_incentive_type := NULL;
1665         ELSE
1666             l_incentive_type := l_get_payrun_rec.incentive_type_code;
1667         END IF;
1668 
1669         -- Main Insert started for Create Worksheet
1670         -- Call the Table hander to Insert Records
1671         cn_pmt_trans_pkg.insert_record(p_pay_by_transaction => nvl(l_pbt_profile_value, 'N'),
1672                                        p_salesrep_id        => p_worksheet_rec.salesrep_id,
1673                                        p_payrun_id          => p_worksheet_rec.payrun_id,
1674                                        p_pay_date           => l_get_payrun_rec.pay_date,
1675                                        p_incentive_type     => l_incentive_type,
1676                                        p_pay_period_id      => l_get_payrun_rec.pay_period_id,
1677                                        p_credit_type_id     => g_credit_type_id,
1678                                        p_posting_batch_id   => cls_posting_batch_id,
1679                                        p_org_id             => p_worksheet_rec.org_id);
1680 
1681         -- Bug 2760379 : only check bal mismatch when it's pay by trx
1682         -- check Balance Miss Match
1683         IF l_pbt_profile_value = 'Y'
1684         THEN
1685             OPEN get_srp_total(l_get_payrun_rec.pay_period_id);
1686 
1687             FETCH get_srp_total
1688                 INTO l_srp_total;
1689 
1690             CLOSE get_srp_total;
1691 
1692             OPEN get_pmt_total(l_get_payrun_rec.pay_period_id);
1693 
1694             FETCH get_pmt_total
1695                 INTO l_pmt_total;
1696 
1697             CLOSE get_pmt_total;
1698 
1699             -- Bug 3140343 : Payee Design.
1700             IF l_ispayee <> 1
1701             THEN
1702                 -- 08/26/03 : Bug 3114349 Issue 2
1703                 OPEN get_comm_total(l_get_payrun_rec.pay_period_id);
1704 
1705                 FETCH get_comm_total
1706                     INTO l_comm_total;
1707 
1708                 CLOSE get_comm_total;
1709             ELSE
1710                 OPEN get_comm_total_payee(l_get_payrun_rec.pay_period_id);
1711 
1712                 FETCH get_comm_total_payee
1713                     INTO l_comm_total;
1714 
1715                 CLOSE get_comm_total_payee;
1716             END IF;
1717 
1718             IF abs(nvl(l_srp_total, 0) - nvl(l_pmt_total, 0) - nvl(l_comm_total, 0)) > .1
1719             THEN
1720                 SELECT processing_status_code
1721                   INTO l_calc_status
1722                   FROM cn_srp_intel_periods
1723                  WHERE salesrep_id = p_worksheet_rec.salesrep_id
1724                    AND period_id = l_get_payrun_rec.pay_period_id
1725                    AND org_id = p_worksheet_rec.org_id;
1726 
1727                 IF l_calc_status NOT IN ('CALCULATED', 'CLEAN', 'ROLLED_UP')
1728                 THEN
1729                     IF fnd_msg_pub.check_msg_level(fnd_msg_pub.g_msg_lvl_error)
1730                     THEN
1731                         fnd_message.set_name('CN', 'CN_CALC_NOT_COMPLETE');
1732                         fnd_msg_pub.add;
1733                     END IF;
1734 
1735                     x_loading_status := 'CN_CALC_NOT_COMPLETE';
1736                     RAISE fnd_api.g_exc_error;
1737                 END IF;
1738 
1739                 IF fnd_msg_pub.check_msg_level(fnd_msg_pub.g_msg_lvl_error)
1740                 THEN
1741                     fnd_message.set_name('CN', 'CN_WKSHT_SRP_COMM_MISMATCH');
1742                     fnd_msg_pub.add;
1743                 END IF;
1744 
1745                 x_loading_status := 'CN_WKSHT_SRP_COMM_MISMATCH';
1746                 RAISE fnd_api.g_exc_error;
1747             END IF; -- end if ABS() > .1
1748         END IF; --end if l_pbt_profile_value = 'Y'
1749 
1750         -- calculate values for payment plan records
1751         calculate_totals(p_salesrep_id    => p_worksheet_rec.salesrep_id,
1752                          p_period_id      => l_get_payrun_rec.pay_period_id,
1753                          p_incentive_type => l_incentive_type,
1754                          p_payrun_id      => l_get_payrun_rec.payrun_id,
1755                          x_calc_rec_tbl   => l_calc_rec_tbl,
1756                          --R12
1757                          p_org_id => p_worksheet_rec.org_id);
1758 
1759         -- Bug 2692801 : avoid PL/SQL error when l_calc_rec_tbl is null
1760         IF l_calc_rec_tbl.COUNT > 0
1761         THEN
1762             FOR i IN l_calc_rec_tbl.FIRST .. l_calc_rec_tbl.LAST
1763             LOOP
1764                 IF l_calc_rec_tbl(i).quota_id IS NOT NULL
1765                 THEN
1766                     IF l_calc_rec_tbl(i).pmt_amount_adj_rec <> 0
1767                        OR l_calc_rec_tbl(i).pmt_amount_adj_nrec <> 0
1768                     THEN
1769                         -- Bug 2880233:  should find pay_element for PMTPLN base on quota_id
1770 
1771                         -- IF l_calc_rec_tbl(i).pmt_amount_adj_rec <> 0  THEN
1772                         l_pay_element_type_id := cn_api.get_pay_element_id(l_calc_rec_tbl(i).quota_id,
1773                                                                            p_worksheet_rec.salesrep_id,
1774                                                                            --R12
1775                                                                            p_worksheet_rec.org_id,
1776                                                                            l_get_payrun_rec.pay_date);
1777 
1778                         -- Get the Sequence Number
1779                         SELECT cn_posting_batches_s.NEXTVAL
1780                           INTO recv_posting_batch_id
1781                           FROM dual;
1782 
1783                         l_batch_rec.posting_batch_id  := recv_posting_batch_id;
1784                         l_batch_rec.NAME              := 'PMTPLN batch number:' || l_get_payrun_rec.payrun_id || ':' || p_worksheet_rec.salesrep_id || ':' ||
1785                                                          l_calc_rec_tbl(i).quota_id || ':' || recv_posting_batch_id;
1786                         l_batch_rec.created_by        := fnd_global.user_id;
1787                         l_batch_rec.creation_date     := SYSDATE;
1788                         l_batch_rec.last_updated_by   := fnd_global.user_id;
1789                         l_batch_rec.last_update_date  := SYSDATE;
1790                         l_batch_rec.last_update_login := fnd_global.login_id;
1791                         -- Create the Posting Batches
1792                         cn_prepostbatches.begin_record(x_operation         => 'INSERT',
1793                                                        x_rowid             => l_rowid,
1794                                                        x_posting_batch_rec => l_batch_rec,
1795                                                        x_program_type      => NULL,
1796                                                        p_org_id            => p_worksheet_rec.org_id);
1797                         l_pmt_trans_rec.posting_batch_id     := recv_posting_batch_id;
1798                         l_pmt_trans_rec.incentive_type_code  := 'PMTPLN';
1799                         l_pmt_trans_rec.credit_type_id       := g_credit_type_id;
1800                         l_pmt_trans_rec.payrun_id            := p_worksheet_rec.payrun_id;
1801                         l_pmt_trans_rec.credited_salesrep_id := p_worksheet_rec.salesrep_id;
1802                         l_pmt_trans_rec.payee_salesrep_id    := p_worksheet_rec.salesrep_id;
1803                         l_pmt_trans_rec.pay_period_id        := l_get_payrun_rec.pay_period_id;
1804                         l_pmt_trans_rec.hold_flag            := 'N';
1805                         l_pmt_trans_rec.waive_flag           := 'N';
1806                         l_pmt_trans_rec.paid_flag            := 'N';
1807                         l_pmt_trans_rec.recoverable_flag     := 'N';
1808                         l_pmt_trans_rec.pay_element_type_id  := l_pay_element_type_id;
1809                         l_pmt_trans_rec.quota_id             := l_calc_rec_tbl(i).quota_id;
1810                         l_pmt_trans_rec.amount               := nvl(l_calc_rec_tbl(i).pmt_amount_adj_rec, 0) + nvl(l_calc_rec_tbl(i).pmt_amount_adj_nrec, 0);
1811                         l_pmt_trans_rec.payment_amount       := nvl(l_calc_rec_tbl(i).pmt_amount_adj_rec, 0) + nvl(l_calc_rec_tbl(i).pmt_amount_adj_nrec, 0);
1812                         --R12
1813                         l_pmt_trans_rec.org_id                := p_worksheet_rec.org_id;
1814                         l_pmt_trans_rec.object_version_number := 1;
1815                         -- Create the Payment Plan Record
1816                         cn_pmt_trans_pkg.insert_record(p_tran_rec => l_pmt_trans_rec);
1817                     END IF;
1818 
1819                     IF l_calc_rec_tbl(i).quota_id <> -1000
1820                        OR abs(nvl(l_calc_rec_tbl(i).pmt_amount_calc, 0)) + abs(nvl(l_calc_rec_tbl(i).pmt_amount_adj_rec, 0)) +
1821                        abs(nvl(l_calc_rec_tbl(i).pmt_amount_adj_nrec, 0)) + abs(nvl(l_calc_rec_tbl(i).pmt_amount_ctr, 0)) +
1822                        abs(nvl(l_calc_rec_tbl(i).pmt_amount_rec, 0)) + abs(nvl(l_calc_rec_tbl(i).held_amount, 0)) <> 0
1823                     THEN
1824                         -- Create the Worksheet at the Quota Level
1825                         cn_payment_worksheets_pkg.insert_record(x_payrun_id             => p_worksheet_rec.payrun_id,
1826                                                                 x_salesrep_id           => p_worksheet_rec.salesrep_id,
1827                                                                 x_quota_id              => l_calc_rec_tbl(i).quota_id,
1828                                                                 x_credit_type_id        => g_credit_type_id,
1829                                                                 x_calc_pmt_amount       => nvl(l_calc_rec_tbl(i).pmt_amount_calc, 0),
1830                                                                 x_adj_pmt_amount_rec    => nvl(l_calc_rec_tbl(i).pmt_amount_adj_rec, 0),
1831                                                                 x_adj_pmt_amount_nrec   => nvl(l_calc_rec_tbl(i).pmt_amount_adj_nrec, 0),
1832                                                                 x_adj_pmt_amount        => nvl(l_calc_rec_tbl(i).pmt_amount_ctr, 0),
1833                                                                 x_held_amount           => nvl(l_calc_rec_tbl(i).held_amount, 0),
1834                                                                 x_pmt_amount_recovery   => nvl(l_calc_rec_tbl(i).pmt_amount_rec, 0),
1835                                                                 x_worksheet_status      => 'UNPAID',
1836                                                                 x_created_by            => g_created_by,
1837                                                                 x_creation_date         => SYSDATE,
1838                                                                 p_org_id                => p_worksheet_rec.org_id,
1839                                                                 p_object_version_number => 1);
1840                         x_loading_status := 'CN_INSERTED';
1841                     END IF;
1842                 END IF;
1843 
1844                 -- for summary record
1845                 l_calc_pmt_amount     := nvl(l_calc_pmt_amount, 0) + nvl(l_calc_rec_tbl(i).pmt_amount_calc, 0);
1846                 l_adj_pmt_amount_rec  := nvl(l_adj_pmt_amount_rec, 0) + nvl(l_calc_rec_tbl(i).pmt_amount_adj_rec, 0);
1847                 l_adj_pmt_amount_nrec := nvl(l_adj_pmt_amount_nrec, 0) + nvl(l_calc_rec_tbl(i).pmt_amount_adj_nrec, 0);
1848                 l_pmt_amount_rec      := nvl(l_pmt_amount_rec, 0) + nvl(l_calc_rec_tbl(i).pmt_amount_rec, 0);
1849                 l_held_amount         := nvl(l_held_amount, 0) + nvl(l_calc_rec_tbl(i).held_amount, 0);
1850             END LOOP;
1851         END IF; -- end  IF l_calc_rec_tbl.COUNT > 0 THEN
1852 
1853         -- Create the Summary Record for for each salesrep
1854         x_loading_status := 'CN_INSERTED';
1855 
1856         -- BUG 2774167 : Check duplicate summary worksheet
1857         BEGIN
1858             l_tmp := 0;
1859 
1860             SELECT 1
1861               INTO l_tmp
1862               FROM cn_payment_worksheets
1863              WHERE payrun_id = p_worksheet_rec.payrun_id
1864                AND salesrep_id = p_worksheet_rec.salesrep_id
1865                AND quota_id IS NULL;
1866 
1867             IF l_tmp <> 0
1868             THEN
1869                 --Error condition
1870                 IF fnd_msg_pub.check_msg_level(fnd_msg_pub.g_msg_lvl_error)
1871                 THEN
1872                     fnd_message.set_name('CN', 'CN_DUPLICATE_WORKSHEET');
1873                     fnd_msg_pub.add;
1874                 END IF;
1875 
1876                 x_loading_status := 'CN_DUPLICATE_WORKSHEET';
1877                 RAISE fnd_api.g_exc_error;
1878             END IF;
1879         EXCEPTION
1880             WHEN no_data_found THEN
1881                 NULL;
1882         END;
1883 
1884         -- Create the Summary Record in the Worksheet
1885         cn_payment_worksheets_pkg.insert_record(x_payrun_id             => p_worksheet_rec.payrun_id,
1886                                                 x_salesrep_id           => p_worksheet_rec.salesrep_id,
1887                                                 x_credit_type_id        => g_credit_type_id,
1888                                                 x_calc_pmt_amount       => nvl(l_calc_pmt_amount, 0),
1889                                                 x_adj_pmt_amount_rec    => nvl(l_adj_pmt_amount_rec, 0),
1890                                                 x_adj_pmt_amount_nrec   => nvl(l_adj_pmt_amount_nrec, 0),
1891                                                 x_adj_pmt_amount        => nvl(l_pmt_amount_ctr, 0),
1892                                                 x_held_amount           => nvl(l_held_amount, 0),
1893                                                 x_pmt_amount_recovery   => nvl(l_pmt_amount_rec, 0),
1894                                                 x_worksheet_status      => 'UNPAID',
1895                                                 x_created_by            => g_created_by,
1896                                                 x_creation_date         => SYSDATE,
1897                                                 p_org_id                => p_worksheet_rec.org_id,
1898                                                 p_object_version_number => 1);
1899 
1900         IF x_loading_status <> 'CN_INSERTED'
1901         THEN
1902             RAISE fnd_api.g_exc_error;
1903         END IF;
1904 
1905         OPEN get_worksheet_id;
1906 
1907         FETCH get_worksheet_id
1908             INTO l_payment_worksheet_id;
1909 
1910         CLOSE get_worksheet_id;
1911 
1912        update_ptd_details (
1913    	     p_salesrep_id => p_worksheet_rec.salesrep_id ,
1914    	     p_payrun_id   => p_worksheet_rec.payrun_id
1915        ) ;
1916 
1917         -- Bug 3140343 : Payee Design.
1918         IF l_ispayee <> 1
1919         THEN
1920             x_loading_status := 'CN_INSERTED';
1921         END IF;
1922 
1923         -- Bug 3140343 : Payee Design. set commission_lines to POSTED
1924         IF l_pbt_profile_value = 'Y'
1925         THEN
1926             IF l_ispayee <> 1
1927             THEN
1928                 UPDATE cn_commission_lines cls
1929                    SET posting_status    = 'POSTED',
1930                        last_update_date  = SYSDATE,
1931                        last_updated_by   = g_last_updated_by,
1932                        last_update_login = g_last_update_login
1933                  WHERE posting_status <> 'POSTED'
1934                    AND status = 'CALC'
1935                    AND srp_payee_assign_id IS NULL
1936                    AND commission_line_id IN (SELECT commission_line_id
1937                                                 FROM cn_payment_transactions
1938                                                WHERE posting_batch_id = cls_posting_batch_id
1939                                                  AND commission_line_id IS NOT NULL);
1940             ELSE
1941                 --payee
1942                 UPDATE cn_commission_lines cls
1943                    SET posting_status    = 'POSTED',
1944                        last_update_date  = SYSDATE,
1945                        last_updated_by   = g_last_updated_by,
1946                        last_update_login = g_last_update_login
1947                  WHERE posting_status <> 'POSTED'
1948                    AND status = 'CALC'
1949                    AND srp_payee_assign_id IS NOT NULL
1950                    AND commission_line_id IN (SELECT commission_line_id
1951                                                 FROM cn_payment_transactions
1952                                                WHERE posting_batch_id = cls_posting_batch_id
1953                                                  AND commission_line_id IS NOT NULL);
1954             END IF;
1955 
1956         ELSE
1957 
1958             SELECT DISTINCT pw.quota_id
1959              BULK COLLECT INTO l_wk_plan_elements
1960               FROM cn_payment_worksheets pw
1961              WHERE pw.payrun_id = l_get_payrun_rec.payrun_id
1962                AND pw.salesrep_id = p_worksheet_rec.salesrep_id
1963                AND pw.quota_id IS NOT NULL ;
1964 
1965             --PBS
1966             IF l_ispayee <> 1
1967             THEN
1968 
1969                     FORALL m IN 1..l_wk_plan_elements.COUNT
1970                         UPDATE cn_commission_lines cls
1971                            SET posting_status    = 'POSTED',
1972                                last_update_date  = SYSDATE,
1973                                last_updated_by   = g_last_updated_by,
1974                                last_update_login = g_last_update_login
1975                          WHERE posting_status <> 'POSTED'
1976                            AND credit_type_id = g_credit_type_id
1977                            AND processed_period_id <= l_get_payrun_rec.pay_period_id
1978                            AND status = 'CALC'
1979                            AND srp_payee_assign_id IS NULL
1980                            AND credited_salesrep_id = p_worksheet_rec.salesrep_id
1981                            AND quota_id = l_wk_plan_elements(m) ;
1982 
1983             ELSE
1984 
1985                 UPDATE cn_commission_lines clk
1986                    SET posting_status    = 'POSTED',
1987                        last_update_date  = SYSDATE,
1988                        last_updated_by   = g_last_updated_by,
1989                        last_update_login = g_last_update_login
1990                  WHERE processed_period_id <= l_get_payrun_rec.pay_period_id
1991                    AND status = 'CALC'
1992                    AND credit_type_id = g_credit_type_id
1993                    AND posting_status <> 'POSTED'
1994                    AND org_id = p_worksheet_rec.org_id
1995                    AND clk.srp_payee_assign_id IS NOT NULL
1996                    AND EXISTS (SELECT 1
1997                           FROM cn_srp_payee_assigns_all spayee,
1998                                cn_payment_worksheets    wksht
1999                          WHERE clk.srp_payee_assign_id = spayee.srp_payee_assign_id
2000                            AND spayee.quota_id = wksht.quota_id
2001                            AND spayee.payee_id = p_worksheet_rec.salesrep_id
2002                            AND wksht.payrun_id = l_get_payrun_rec.payrun_id
2003                            AND wksht.salesrep_id = p_worksheet_rec.salesrep_id);
2004 
2005             END IF; -- end IF l_ispayee <> 1
2006         END IF; -- end IF l_pbt_profile_value = 'Y'
2007 
2008         -- changes for bug#2568937
2009         -- for payroll integration population of account
2010         OPEN get_apps;
2011 
2012         FETCH get_apps
2013             INTO l_payables_flag, l_payroll_flag, l_payables_ccid_level;
2014 
2015         CLOSE get_apps;
2016 
2017         -- changes for bug#2568937
2018         -- for payroll integration population of account
2019         -- use if AP / Payroll integration has been enabled.
2020         IF l_payables_flag = 'Y'
2021         THEN
2022             -- Populate ccid's in payment worksheets
2023             IF (cn_payrun_pvt.populate_ccids(p_payrun_id      => p_worksheet_rec.payrun_id,
2024                                              p_salesrep_id    => p_worksheet_rec.salesrep_id,
2025                                              p_loading_status => x_loading_status,
2026                                              x_loading_status => x_loading_status)) = fnd_api.g_true
2027             THEN
2028                 RAISE fnd_api.g_exc_unexpected_error;
2029             END IF;
2030         END IF;
2031 
2032         -- End of API body.
2033         -- Standard check of p_commit.
2034         IF fnd_api.to_boolean(p_commit)
2035         THEN
2036             COMMIT WORK;
2037         END IF;
2038 
2039         --
2040         -- Standard call to get message count and if count is 1, get message info.
2041         --
2042         fnd_msg_pub.count_and_get(p_count => x_msg_count, p_data => x_msg_data, p_encoded => fnd_api.g_false);
2043     EXCEPTION
2044         WHEN fnd_api.g_exc_error THEN
2045             ROLLBACK TO create_worksheet;
2046             x_return_status := fnd_api.g_ret_sts_error;
2047             fnd_msg_pub.count_and_get(p_count => x_msg_count, p_data => x_msg_data, p_encoded => fnd_api.g_false);
2048         WHEN fnd_api.g_exc_unexpected_error THEN
2049             ROLLBACK TO create_worksheet;
2050             x_loading_status := 'UNEXPECTED_ERR';
2051             x_return_status  := fnd_api.g_ret_sts_unexp_error;
2052             fnd_msg_pub.count_and_get(p_count => x_msg_count, p_data => x_msg_data, p_encoded => fnd_api.g_false);
2053         WHEN OTHERS THEN
2054             ROLLBACK TO create_worksheet;
2055             x_loading_status := 'UNEXPECTED_ERR';
2056             x_return_status  := fnd_api.g_ret_sts_unexp_error;
2057 
2058             IF fnd_msg_pub.check_msg_level(fnd_msg_pub.g_msg_lvl_unexp_error)
2059             THEN
2060                 fnd_msg_pub.add_exc_msg(g_pkg_name, l_api_name);
2061             END IF;
2062 
2063             fnd_msg_pub.count_and_get(p_count => x_msg_count, p_data => x_msg_data, p_encoded => fnd_api.g_false);
2064     END create_worksheet;
2065 
2066     -- ===========================================================================
2067     -- Procedure   : Create_Multiple_Worksheets
2068     -- Description : This API is used to create multiple worksheets
2069     -- ===========================================================================
2070     PROCEDURE create_multiple_worksheets (
2071               errbuf             OUT NOCOPY VARCHAR2,
2072               retcode            OUT NOCOPY NUMBER,
2073               p_batch_id         IN NUMBER,
2074               p_payrun_id        IN NUMBER,
2075               p_logical_batch_id IN NUMBER,
2076               --R12
2077               p_org_id                   IN       cn_payruns.org_id%TYPE
2078            )
2079            IS
2080               l_api_name           CONSTANT VARCHAR2 (30) := 'Create_Multiple_Worksheets';
2081               g_api_version        CONSTANT NUMBER := 1.0;
2082               x_return_status  VARCHAR2(10) := fnd_api.g_ret_sts_success;
2083               x_msg_count      NUMBER;
2084               x_msg_data       VARCHAR2(4000);
2085               l_worksheet_rec  cn_payment_worksheet_pvt.worksheet_rec_type;
2086               x_status         VARCHAR2(200);
2087               x_loading_status VARCHAR2(20) := 'CN_INSERTED';
2088               l_start_time     DATE;
2089               l_error_count    NUMBER := 0;
2090 
2091               --Cursor below was modified by Sundar Venkat to fix bug 2775288
2092               --The following change is made to ensure, that worksheets are created
2093               --only for those salesreps, who have a valid comp. plan assignment
2094               --during the payperiod of the payrun
2095               -- Bug 3140343 : Payee Design.
2096           BEGIN
2097               --
2098               --  Initialize API return status to success
2099               --
2100               x_return_status := fnd_api.g_ret_sts_success;
2101               x_loading_status := 'CN_INSERTED';
2102               --
2103               -- API body
2104               --
2105               l_start_time := SYSDATE;
2106               fnd_file.put_line(fnd_file.log, '  Input Parameters Payrun_id = ' || p_payrun_id);
2107               fnd_file.put_line(fnd_file.log, '  Input Parameters Batch_id  = ' || p_batch_id);
2108               fnd_file.put_line(fnd_file.log, '  Current time               = ' || to_char(l_start_time, 'Dy DD-Mon-YYYY HH24:MI:SS'));
2109 
2110               l_worksheet_rec.payrun_id := p_payrun_id;
2111               l_worksheet_rec.org_id := p_org_id;
2112               l_worksheet_rec.call_from   := cn_payment_worksheet_pvt.concurrent_program_call;
2113 
2114                 FOR emp IN (SELECT salesrep_id
2115                             FROM cn_process_batches
2116                             WHERE logical_batch_id = p_logical_batch_id
2117                             AND physical_batch_id = p_batch_id)
2118                 LOOP
2119 
2120                     -- Run create worksheet for this salesrep.
2121                     l_worksheet_rec.salesrep_id := emp.salesrep_id;
2122                     l_worksheet_rec.call_from   := cn_payment_worksheet_pvt.concurrent_program_call;
2123 
2124                     fnd_file.put_line(fnd_file.log, '    Create worksheet for  = ' || l_worksheet_rec.salesrep_id || ' salesrepID');
2125 
2126                     cn_payment_worksheet_pvt.create_worksheet(p_api_version      => 1.0,
2127                                                               p_init_msg_list    => 'T',
2128                                                               p_commit           => 'F',
2129                                                               p_validation_level => fnd_api.g_valid_level_full,
2130                                                               x_return_status    => x_return_status,
2131                                                               x_msg_count        => x_msg_count,
2132                                                               x_msg_data         => x_msg_data,
2133                                                               p_worksheet_rec    => l_worksheet_rec,
2134                                                               x_loading_status   => x_loading_status,
2135                                                               x_status           => x_status);
2136 
2137                     IF x_return_status <> fnd_api.g_ret_sts_success
2138                     THEN
2139                         l_error_count := l_error_count + 1;
2140                         cn_message_pkg.debug('Error when creating Worksheet for :  ' || l_worksheet_rec.salesrep_id);
2141                         fnd_file.put_line(fnd_file.log, 'Failed to create worksheet for ' || l_worksheet_rec.salesrep_id);
2142                         FOR i IN 1 .. x_msg_count
2143                         LOOP
2144                             fnd_file.put_line(fnd_file.log, 'msg: ' || fnd_msg_pub.get(i, 'F'));
2145                         END LOOP;
2146                         fnd_file.put_line(fnd_file.log, '+------------------------------+');
2147                         ROLLBACK;
2148                     ELSE
2149                         COMMIT;
2150                     END IF;
2151 
2152                 END LOOP;
2153 
2154 
2155            IF l_error_count <> 0
2156                 THEN
2157                     retcode := 2;
2158                     errbuf  := '  Batch# '||p_batch_id||' : Creation of worksheets was not successful for some resources. Count = ' || to_char(l_error_count) ;
2159                     fnd_file.put_line(fnd_file.log,errbuf) ;
2160                 END IF;
2161 
2162                 fnd_file.put_line(fnd_file.log, '  Finish time = ' || to_char(SYSDATE, 'Dy DD-Mon-YYYY HH24:MI:SS'));
2163                 fnd_file.put_line(fnd_file.log, '  Batch time  = ' || (SYSDATE - l_start_time) * 1400 || ' minutes ');
2164 
2165             EXCEPTION
2166                 WHEN OTHERS THEN
2167                     fnd_file.put_line(fnd_file.log, 'Unexpected exception in processing the (payrun_id,batch) = ' || p_payrun_id || ',' || p_batch_id);
2168                     fnd_file.put_line(fnd_file.log, SQLERRM);
2169                     RAISE;
2170        END create_multiple_worksheets;
2171 
2172 
2173     --============================================================================
2174     --Name :create_worksheet_conc
2175     --Description : Procedure which will be used as the executable for the
2176     --            : concurrent program. Create Worksheet
2177     --============================================================================
2178     PROCEDURE create_mult_worksheet_conc
2179             (
2180                 errbuf  OUT NOCOPY VARCHAR2,
2181                 retcode OUT NOCOPY NUMBER,
2182                 p_name  cn_payruns.NAME%TYPE
2183               ) IS
2184                 l_proc_audit_id  NUMBER;
2185                 l_return_status  VARCHAR2(1000);
2186                 l_msg_data       VARCHAR2(2000);
2187                 l_msg_count      NUMBER;
2188                 l_loading_status VARCHAR2(1000);
2189                 l_status         VARCHAR2(2000);
2190                 l_payrun_id      NUMBER;
2191                 --R12
2192                 l_org_id cn_payruns.org_id%TYPE;
2193                 l_conc_params conc_params;
2194                 errmsg       VARCHAR2(4000) := '';
2195                 l_max_batch_id      NUMBER;
2196                 salesrep_t          salesrep_tab_typ;
2197                 l_batch_sz          NUMBER := 80;
2198 
2199                 CURSOR get_payrun_id_curs(c_name cn_payruns.NAME%TYPE, c_org_id cn_payruns.org_id%TYPE) IS
2200                     SELECT cp.payrun_id,
2201                            cp.org_id,
2202                            cp.status
2203                      FROM cn_payruns cp
2204                      WHERE cp.NAME = c_name
2205                        AND cp.org_id = c_org_id;
2206 
2207                 l_has_access BOOLEAN;
2208             BEGIN
2209                 fnd_file.put_line(fnd_file.log, 'Entering create_mult_worksheet_conc ');
2210                 retcode := 0;
2211                 --Added for R12 payment security check begin.
2212                 l_has_access := cn_payment_security_pvt.get_security_access(cn_payment_security_pvt.g_type_wksht, cn_payment_security_pvt.g_access_wksht_create);
2213                 --Get the salesrep batch size from profile option.
2214         	    l_batch_sz := nvl(fnd_profile.value('CN_PMT_SRP_BATCH_SIZE'),251);
2215         	    fnd_file.put_line(fnd_file.log,'Batch size : ' ||l_batch_sz);
2216 
2217         	   IF l_batch_sz < 1
2218         	     THEN
2219         	     errmsg := 'The batch size should be greater than zero.';
2220         	     fnd_file.put_line(fnd_file.log, errmsg);
2221         	     raise_application_error(-20000, errmsg);
2222                 END IF;
2223 
2224                 IF (l_has_access = FALSE) THEN
2225                   RAISE fnd_api.g_exc_error;
2226                 END IF;
2227 
2228                 --Added for R12 payment security check end.
2229                 l_org_id := mo_global.get_current_org_id;
2230 
2231 
2232                 -- get payrun id
2233                 OPEN get_payrun_id_curs(p_name, l_org_id);
2234                 FETCH get_payrun_id_curs
2235                     INTO l_payrun_id, l_org_id,l_status;
2236                 CLOSE get_payrun_id_curs;
2237                 IF l_status <> 'UNPAID'
2238                 THEN
2239                     errmsg := 'Worksheets can only be created for payruns in UNPAID status.';
2240                     fnd_file.put_line(fnd_file.log, errmsg);
2241                     raise_application_error(-20000, errmsg);
2242                 END IF;
2243                 cn_message_pkg.begin_batch(x_process_type         => 'WKSHT',
2244                                            x_process_audit_id     => l_proc_audit_id,
2245                                            x_parent_proc_audit_id => l_payrun_id,
2246                                            x_request_id           => NULL,
2247                                            --R12
2248                                            p_org_id => l_org_id);
2249                 BEGIN
2250                     -- get the salesreps for the payrun.
2251         	        SELECT salesrep_id,ceil(rownum / l_batch_sz)
2252                     BULK COLLECT INTO salesrep_t
2253         	        FROM (SELECT DISTINCT cns.salesrep_id salesrep_id,
2254                                         cns.NAME        salesrep_name
2255                           FROM cn_payruns         cnp,
2256                                cn_srp_pay_groups  cnspg,
2257                                cn_salesreps       cns,
2258                                cn_period_statuses cnps
2259                           WHERE cnp.payrun_id = l_payrun_id
2260                           AND cnp.status = 'UNPAID'
2261                           AND cnp.pay_group_id = cnspg.pay_group_id
2262                           AND cnspg.salesrep_id = cns.salesrep_id
2263                           AND cns.hold_payment = 'N'
2264                           AND cnp.pay_period_id = cnps.period_id
2265                           AND cnp.org_id = cnps.org_id
2266                           AND cnp.org_id = cnspg.org_id
2267                           AND cnp.org_id = cns.org_id
2268                           AND ((cnspg.start_date <= cnps.end_date) AND (cnps.start_date <= nvl(cnspg.end_date, cnps.start_date)))
2269                           AND NOT EXISTS (SELECT 1
2270                                           FROM cn_payment_worksheets_all cnpw
2271                                           WHERE cnpw.salesrep_id = cnspg.salesrep_id
2272                                           AND cnp.payrun_id = cnpw.payrun_id)
2273                           AND (EXISTS (SELECT 1
2274                                        FROM cn_srp_payee_assigns cnspa
2275                                        WHERE ((cnspa.start_date <= cnps.end_date) AND (cnps.start_date <= nvl(cnspa.end_date, cnps.start_date)))
2276                                        AND cnspa.payee_id = cnspg.salesrep_id
2277                                           --R12
2278                                        AND cnspa.org_id = cnp.org_id) OR EXISTS
2279                             (SELECT 1
2280                                FROM cn_srp_plan_assigns cnspa
2281                                WHERE ((cnspa.start_date <= cnps.end_date) AND (cnps.start_date <= nvl(cnspa.end_date, cnps.start_date)))
2282                                AND cnspa.salesrep_id = cnspg.salesrep_id
2283                                    --R12
2284                                AND cnspa.org_id = cnp.org_id)));
2285                    -- Call the CN_CREATE_WKSHT_INT conc program
2286         	       l_conc_params.conc_program_name := 'CN_CREATE_WKSHT_INT' ;
2287 
2288     	           generic_conc_processor(p_payrun_id    => l_payrun_id,
2289         	                              p_salesrep_tbl => salesrep_t,
2290         	                              p_org_id       => l_org_id,
2291         	                              p_params       => l_conc_params,
2292         	                              x_errbuf       => errbuf,
2293         	                              x_retcode      => retcode);
2294 
2295         	        EXCEPTION
2296         	        WHEN no_data_found THEN
2297         	            errmsg := 'No salesreps found that were eligible for worksheet creation in the payrun : ';
2298         	            fnd_file.put_line(fnd_file.log, errmsg);
2299         	            retcode := 2;
2300         	            errbuf  := errmsg;
2301         	            RAISE ;
2302         	        WHEN OTHERS THEN
2303         	            fnd_file.put_line(fnd_file.log, 'Unexpected exception in cn_payment_worksheet_pvt.create_mult_worksheet_conc');
2304         	            fnd_file.put_line(fnd_file.log, errmsg);
2305         	            fnd_file.put_line(fnd_file.log, SQLERRM);
2306                     RAISE;
2307                   END;
2308 
2309 
2310         	      fnd_file.put_line(fnd_file.log, errbuf);
2311         	      fnd_file.put_line(fnd_file.log, 'Count of worksheets to be created = ' || salesrep_t.COUNT);
2312         	      fnd_file.put_line(fnd_file.log, 'Completed create worksheet process....');
2313 
2314         	    IF l_return_status <> fnd_api.g_ret_sts_success
2315                 THEN
2316                     retcode := 2;
2317                     fnd_message.set_name('CN', 'CN_CONC_REQ_FAIL');
2318                     fnd_msg_pub.add;
2319                     errbuf := fnd_msg_pub.get(p_msg_index => fnd_msg_pub.g_last, p_encoded => fnd_api.g_false);
2320                 END IF;
2321 
2322                 cn_message_pkg.end_batch(l_proc_audit_id);
2323                 COMMIT;
2324     END create_mult_worksheet_conc;
2325     -- ===========================================================================
2326     -- Procedure : Update_Worksheet
2327     -- Description used for Refreshing the Worksheets
2328     --                      Locking and Unlocking the Worksheets
2329     -- ===========================================================================
2330     PROCEDURE update_worksheet
2331     (
2332         p_api_version      IN NUMBER,
2333         p_init_msg_list    IN VARCHAR2,
2334         p_commit           IN VARCHAR2,
2335         p_validation_level IN NUMBER,
2336         x_return_status    OUT NOCOPY VARCHAR2,
2337         x_msg_count        OUT NOCOPY NUMBER,
2338         x_msg_data         OUT NOCOPY VARCHAR2,
2339         p_worksheet_id     IN NUMBER,
2340         p_operation        IN VARCHAR2,
2341         x_status           OUT NOCOPY VARCHAR2,
2342         x_loading_status   OUT NOCOPY VARCHAR2,
2343         x_ovn              IN OUT NOCOPY NUMBER
2344     ) IS
2345         l_api_name CONSTANT VARCHAR2(30) := 'Update_Worksheet';
2346 
2347         CURSOR get_worksheet_id IS
2348             SELECT cnpw.salesrep_id,
2349                    cnp.payrun_id,
2350                    cnpw.worksheet_status,
2351                    cnp.pay_period_id,
2352                    decode(cnp.incentive_type_code, 'ALL', '', cnp.incentive_type_code) incentive_type_code,
2353                    cnp.pay_date,
2354                    cnpw.object_version_number ovn,
2355                    cnpw.org_id
2356               FROM cn_payment_worksheets cnpw,
2357                    cn_payruns            cnp
2358              WHERE payment_worksheet_id = p_worksheet_id
2359                AND cnpw.payrun_id = cnp.payrun_id;
2360 
2361         -- changes for bug#2568937
2362         -- for payroll integration population of account
2363         CURSOR get_apps IS
2364             SELECT payables_flag,
2365                    payroll_flag,
2366                    payables_ccid_level
2367               FROM cn_repositories       rp,
2368                    cn_payment_worksheets wk
2369              WHERE rp.org_id = wk.org_id;
2370 
2371         wksht_rec                  get_worksheet_id%ROWTYPE;
2372         l_status                   cn_payment_worksheets.worksheet_status%TYPE;
2373         l_posting_batch_id         NUMBER;
2374         recv_posting_batch_id      NUMBER;
2375         carryover_posting_batch_id NUMBER;
2376 
2377         l_calc_rec_tbl        calc_rec_tbl_type;
2378         l_batch_rec           cn_prepostbatches.posting_batch_rec_type;
2379         l_calc_pmt_amount     NUMBER;
2380         l_adj_pmt_amount_rec  NUMBER;
2381         l_adj_pmt_amount_nrec NUMBER;
2382         l_pmt_amount_rec      NUMBER;
2383         l_pmt_trans_rec       cn_pmt_trans_pkg.pmt_trans_rec_type; -- PmtTrans
2384         l_pmt_amount_ctr      NUMBER;
2385         l_rowid               VARCHAR2(30);
2386         -- changes for bug#2568937
2387         -- for payroll integration population of account
2388         l_payables_flag       cn_repositories.payables_flag%TYPE;
2389         l_payroll_flag        cn_repositories.payroll_flag%TYPE;
2390         l_payables_ccid_level cn_repositories.payables_ccid_level%TYPE;
2391         l_ispayee             NUMBER := 0;
2392         TYPE num_tab IS TABLE OF NUMBER;
2393         l_wk_plan_elements num_tab;
2394         l_has_access          BOOLEAN;
2395         l_org_id              NUMBER;
2396         l_pay_by_mode         VARCHAR2(1);
2397         l_srp_status          cn_salesreps.status%TYPE;
2398 
2399     BEGIN
2400         -- Standard Start of API savepoint
2401         SAVEPOINT update_worksheet;
2402 
2403         -- Standard call to check for call compatibility.
2404         IF NOT fnd_api.compatible_api_call(g_api_version, p_api_version, l_api_name, g_pkg_name)
2405         THEN
2406             RAISE fnd_api.g_exc_unexpected_error;
2407         END IF;
2408 
2409         --
2410         -- Initialize message list if p_init_msg_list is set to TRUE.
2411         --
2412         IF fnd_api.to_boolean(p_init_msg_list)
2413         THEN
2414             fnd_msg_pub.initialize;
2415         END IF;
2416 
2417         --
2418         --  Initialize API return status to success
2419         --
2420         x_return_status  := fnd_api.g_ret_sts_success;
2421         x_loading_status := 'CN_UPDATED';
2422 
2423         OPEN get_worksheet_id;
2424 
2425         FETCH get_worksheet_id
2426             INTO wksht_rec;
2427 
2428         CLOSE get_worksheet_id;
2429 
2430         --This part is added for OA.
2431         IF wksht_rec.ovn <> x_ovn
2432         THEN
2433             IF (fnd_msg_pub.check_msg_level(fnd_msg_pub.g_msg_lvl_error))
2434             THEN
2435                 fnd_message.set_name('CN', 'CN_RECORD_CHANGED');
2436                 fnd_msg_pub.add;
2437             END IF;
2438 
2439             RAISE fnd_api.g_exc_error;
2440         END IF;
2441 
2442         l_pay_by_mode := cn_payment_security_pvt.get_pay_by_mode(wksht_rec.payrun_id);
2443 
2444         SELECT s.status,
2445                nvl(r.payroll_flag, 'N'),
2446                r.payables_flag
2447           INTO l_srp_status,
2448                l_payroll_flag,
2449                l_payables_flag
2450           FROM cn_salesreps        s,
2451                cn_repositories_all r,
2452                cn_payruns_all      pr
2453          WHERE s.salesrep_id = wksht_rec.salesrep_id
2454            AND s.org_id = r.org_id
2455            AND pr.org_id = r.org_id
2456            AND pr.payrun_id = wksht_rec.payrun_id;
2457 
2458         -- Bug 3140343 : Payee Design. Check if this salesrep is a Payee
2459         l_ispayee := cn_api.is_payee(p_period_id => wksht_rec.pay_period_id, p_salesrep_id => wksht_rec.salesrep_id, p_org_id => wksht_rec.org_id);
2460 
2461         IF p_operation = 'REFRESH'
2462         THEN
2463 
2464             --Added for R12 payment security check end.
2465             cn_payment_security_pvt.worksheet_action(p_api_version      => p_api_version,
2466                                                      p_init_msg_list    => p_init_msg_list,
2467                                                      p_commit           => 'F',
2468                                                      p_validation_level => p_validation_level,
2469                                                      x_return_status    => x_return_status,
2470                                                      x_msg_count        => x_msg_count,
2471                                                      x_msg_data         => x_msg_data,
2472                                                      p_worksheet_id     => p_worksheet_id,
2473                                                      p_action           => p_operation);
2474 
2475             IF x_return_status <> fnd_api.g_ret_sts_success
2476             THEN
2477                 RAISE fnd_api.g_exc_error;
2478             END IF;
2479 
2480             --  get sequence number
2481             SELECT cn_posting_batches_s.NEXTVAL
2482               INTO l_posting_batch_id
2483               FROM dual;
2484 
2485             -- Refresh payment transactions
2486             IF l_pay_by_mode = 'N'
2487             THEN
2488                 -- Update amount on all payment transactions
2489                 -- The following change was made by Sundar for bug fix 2772834
2490                 -- This will handle scenarios where a salesrep has multiple role assignments
2491                 -- during the same period, with an overlapping quota assignment
2492                 -- changes records that have changed and not held
2493                 UPDATE cn_payment_transactions cnpt
2494                    SET (                    amount, payment_amount) = (SELECT SUM(balance2_bbd - balance2_bbc + balance2_dtd - balance2_ctd),
2495                                                                               SUM(balance2_bbd - balance2_bbc + balance2_dtd - balance2_ctd)
2496                                                                          FROM cn_srp_periods csp
2497                                                                         WHERE csp.period_id = wksht_rec.pay_period_id
2498                                                                           AND csp.salesrep_id = cnpt.credited_salesrep_id
2499                                                                           AND csp.quota_id = cnpt.quota_id
2500                                                                           AND csp.credit_type_id = cnpt.credit_type_id
2501                                                                              --R12
2502                                                                           AND csp.org_id = wksht_rec.org_id),
2503                        pay_element_type_id   = (SELECT decode(r.payroll_flag, NULL, NULL, 'N', NULL, 'Y', p.pay_element_type_id, NULL) pay_element_type_id
2504                                                   FROM cn_quota_pay_elements p,
2505                                                        cn_rs_salesreps       s,
2506                                                        cn_repositories       r
2507                                                  WHERE p.quota_id = cnpt.quota_id
2508                                                    AND wksht_rec.pay_date BETWEEN p.start_date AND p.end_date
2509                                                    AND s.salesrep_id = cnpt.credited_salesrep_id
2510                                                    AND nvl(s.status, 'A') = p.status
2511                                                       --R12
2512                                                    AND p.org_id = wksht_rec.org_id
2513                                                    AND s.org_id = wksht_rec.org_id
2514                                                    AND r.org_id = wksht_rec.org_id),
2515                        last_update_date      = SYSDATE,
2516                        last_updated_by       = g_last_updated_by,
2517                        last_update_login     = g_last_update_login,
2518                        object_version_number = nvl(object_version_number, 0) + 1
2519                  WHERE cnpt.payrun_id = wksht_rec.payrun_id
2520                    AND cnpt.amount = cnpt.payment_amount
2521                    AND incentive_type_code IN ('COMMISSION', 'BONUS')
2522                       -- 01/03/03 gasriniv added hold flag check for bug 2710066
2523                    AND (cnpt.hold_flag IS NULL OR cnpt.hold_flag = 'N')
2524                    AND cnpt.credited_salesrep_id = wksht_rec.salesrep_id
2525                       --R12
2526                    AND cnpt.org_id = wksht_rec.org_id;
2527 
2528                 -- for those records that have changed, dont update the payment amount
2529                 UPDATE cn_payment_transactions cnpt
2530                    SET amount              = (SELECT SUM(balance2_bbd - balance2_bbc + balance2_dtd - balance2_ctd)
2531                                                 FROM cn_srp_periods csp
2532                                                WHERE csp.period_id = wksht_rec.pay_period_id
2533                                                  AND csp.salesrep_id = cnpt.credited_salesrep_id
2534                                                  AND csp.quota_id = cnpt.quota_id
2535                                                  AND csp.credit_type_id = cnpt.credit_type_id
2536                                                     --R12
2537                                                  AND csp.org_id = wksht_rec.org_id),
2538                        pay_element_type_id = (SELECT decode(r.payroll_flag, NULL, NULL, 'N', NULL, 'Y', p.pay_element_type_id, NULL) pay_element_type_id
2539                                                 FROM cn_quota_pay_elements p,
2540                                                      cn_rs_salesreps       s,
2541                                                      cn_repositories       r
2542                                                WHERE p.quota_id = cnpt.quota_id
2543                                                  AND wksht_rec.pay_date BETWEEN p.start_date AND p.end_date
2544                                                  AND s.salesrep_id = cnpt.credited_salesrep_id
2545                                                  AND nvl(s.status, 'A') = p.status
2546                                                     --R12
2547                                                  AND p.org_id = wksht_rec.org_id
2548                                                  AND s.org_id = wksht_rec.org_id
2549                                                  AND r.org_id = wksht_rec.org_id),
2550                        last_update_date    = SYSDATE,
2551                        last_updated_by     = g_last_updated_by,
2552                        last_update_login   = g_last_update_login
2553                  WHERE cnpt.payrun_id = wksht_rec.payrun_id
2554                    AND cnpt.amount <> cnpt.payment_amount
2555                    AND incentive_type_code IN ('COMMISSION', 'BONUS')
2556                       -- 01/03/03 gasriniv added hold flag check for bug 2710066
2557                    AND (cnpt.hold_flag IS NULL OR cnpt.hold_flag = 'N')
2558                    AND cnpt.credited_salesrep_id = wksht_rec.salesrep_id
2559                       --R12
2560                    AND cnpt.org_id = wksht_rec.org_id;
2561 
2562                 -- Bug 2868584 :Add SUM and Group By clause
2563                 -- handle scenarios where a salesrep has multiple role assignments
2564                 -- during the same period, with an overlapping quota assignment
2565                 INSERT INTO cn_payment_transactions
2566                     (payment_transaction_id,
2567                      posting_batch_id,
2568                      incentive_type_code,
2569                      credit_type_id,
2570                      pay_period_id,
2571                      amount,
2572                      payment_amount,
2573                      credited_salesrep_id,
2574                      payee_salesrep_id,
2575                      paid_flag,
2576                      hold_flag,
2577                      waive_flag,
2578                      payrun_id,
2579                      quota_id,
2580                      pay_element_type_id,
2581                      created_by,
2582                      creation_date,
2583                      --R12
2584                      org_id)
2585                     SELECT cn_payment_transactions_s.NEXTVAL,
2586                            l_posting_batch_id,
2587                            v1.incentive_type_code,
2588                            v1.credit_type_id,
2589                            v1.period_id,
2590                            v1.amount,
2591                            v1.payment_amount,
2592                            v1.salesrep_id,
2593                            v1.salesrep_id,
2594                            'N',
2595                            'N',
2596                            'N',
2597                            wksht_rec.payrun_id,
2598                            v1.quota_id,
2599                            v1.pay_element_type_id,
2600                            g_created_by,
2601                            SYSDATE,
2602                            --R12
2603                            wksht_rec.org_id
2604                       FROM (SELECT q.incentive_type_code,
2605                                    srp.credit_type_id,
2606                                    srp.period_id,
2607                                    SUM((nvl(srp.balance2_dtd, 0) - nvl(srp.balance2_ctd, 0) + nvl(srp.balance2_bbd, 0) - nvl(srp.balance2_bbc, 0))) amount,
2608                                    SUM((nvl(srp.balance2_dtd, 0) - nvl(srp.balance2_ctd, 0) + nvl(srp.balance2_bbd, 0) - nvl(srp.balance2_bbc, 0))) payment_amount,
2609                                    srp.salesrep_id,
2610                                    srp.quota_id,
2611                                    decode(r.payroll_flag, NULL, NULL, 'N', NULL, 'Y', qp.pay_element_type_id, NULL) pay_element_type_id
2612                               FROM cn_srp_periods            srp,
2613                                    cn_quotas_all             q,
2614                                    cn_quota_pay_elements_all qp,
2615                                    cn_rs_salesreps           s,
2616                                    cn_repositories           r
2617                             -- 01/03/03 gasriniv added hold flag check for bug 2710066
2618                              WHERE srp.salesrep_id = wksht_rec.salesrep_id
2619                                AND srp.period_id = wksht_rec.pay_period_id
2620                                AND srp.quota_id = q.quota_id
2621                                AND srp.quota_id <> -1000
2622                                   -- Bug 2819874
2623                                AND srp.credit_type_id = -1000
2624                                AND q.incentive_type_code = decode(nvl(wksht_rec.incentive_type_code, q.incentive_type_code),
2625                                                                   'COMMISSION',
2626                                                                   'COMMISSION',
2627                                                                   'BONUS',
2628                                                                   'BONUS',
2629                                                                   q.incentive_type_code)
2630                                AND qp.quota_id(+) = srp.quota_id
2631                                AND wksht_rec.pay_date BETWEEN qp.start_date(+) AND qp.end_date(+)
2632                                AND s.salesrep_id = srp.salesrep_id
2633                                AND nvl(s.status, 'A') = nvl(qp.status, nvl(s.status, 'A'))
2634                                   --R12
2635                                AND srp.org_id = s.org_id
2636                                AND srp.org_id = r.org_id
2637                                AND srp.org_id = wksht_rec.org_id
2638                                AND NOT EXISTS (SELECT 'X'
2639                                       FROM cn_payment_transactions_all cnpt
2640                                      WHERE cnpt.payrun_id = wksht_rec.payrun_id
2641                                        AND cnpt.credited_salesrep_id = wksht_rec.salesrep_id
2642                                        AND cnpt.quota_id = q.quota_id
2643                                        AND cnpt.incentive_type_code IN ('COMMISSION', 'BONUS')
2644                                           -- 01/03/03 gasriniv added hold flag check for bug 2710066
2645                                        AND (cnpt.hold_flag IS NULL OR cnpt.hold_flag = 'N')
2646                                           --R12
2647                                        AND cnpt.org_id = wksht_rec.org_id)
2648                              GROUP BY srp.quota_id,
2649                                       q.incentive_type_code,
2650                                       srp.credit_type_id,
2651                                       srp.period_id,
2652                                       srp.salesrep_id,
2653                                       r.payroll_flag,
2654                                       qp.pay_element_type_id) v1;
2655 
2656                 IF SQL%ROWCOUNT <> 0
2657                 THEN
2658                     l_batch_rec.posting_batch_id  := l_posting_batch_id;
2659                     l_batch_rec.NAME              := 'Refresh batch number:' || wksht_rec.payrun_id || ':' || wksht_rec.salesrep_id || ':' ||
2660                                                      l_posting_batch_id;
2661                     l_batch_rec.created_by        := fnd_global.user_id;
2662                     l_batch_rec.creation_date     := SYSDATE;
2663                     l_batch_rec.last_updated_by   := fnd_global.user_id;
2664                     l_batch_rec.last_update_date  := SYSDATE;
2665                     l_batch_rec.last_update_login := fnd_global.login_id;
2666                     -- Create the Posting Batches
2667                     cn_prepostbatches.begin_record(x_operation         => 'INSERT',
2668                                                    x_rowid             => l_rowid,
2669                                                    x_posting_batch_rec => l_batch_rec,
2670                                                    x_program_type      => NULL,
2671                                                    p_org_id            => wksht_rec.org_id);
2672                 END IF;
2673 
2674                 -- Bug 2819874 :Add in carry over record if exist,regardless
2675                 -- incentive type code
2676                 --  get sequence number
2677                 SELECT cn_posting_batches_s.NEXTVAL
2678                   INTO carryover_posting_batch_id
2679                   FROM dual;
2680 
2681                 INSERT INTO cn_payment_transactions
2682                     (payment_transaction_id,
2683                      posting_batch_id,
2684                      incentive_type_code,
2685                      credit_type_id,
2686                      pay_period_id,
2687                      amount,
2688                      payment_amount,
2689                      credited_salesrep_id,
2690                      payee_salesrep_id,
2691                      paid_flag,
2692                      hold_flag,
2693                      waive_flag,
2694                      payrun_id,
2695                      quota_id,
2696                      pay_element_type_id,
2697                      created_by,
2698                      creation_date,
2699                      --R12
2700                      org_id)
2701                     SELECT cn_payment_transactions_s.NEXTVAL,
2702                            carryover_posting_batch_id,
2703                            'COMMISSION',
2704                            srp.credit_type_id,
2705                            srp.period_id,
2706                            nvl((nvl(srp.balance2_dtd, 0) - nvl(srp.balance2_ctd, 0) + nvl(srp.balance2_bbd, 0) - nvl(srp.balance2_bbc, 0)), 0),
2707                            nvl((nvl(srp.balance2_dtd, 0) - nvl(srp.balance2_ctd, 0) + nvl(srp.balance2_bbd, 0) - nvl(srp.balance2_bbc, 0)), 0),
2708                            srp.salesrep_id,
2709                            srp.salesrep_id,
2710                            'N',
2711                            'N',
2712                            'N',
2713                            wksht_rec.payrun_id,
2714                            -1000,
2715                            decode(r.payroll_flag, NULL, NULL, 'N', NULL, 'Y', qp.pay_element_type_id, NULL) pay_element_type_id,
2716                            g_created_by,
2717                            SYSDATE,
2718                            --R12
2719                            wksht_rec.org_id
2720                       FROM cn_srp_periods            srp,
2721                            cn_quota_pay_elements_all qp,
2722                            cn_rs_salesreps           s,
2723                            cn_repositories           r
2724                      WHERE srp.salesrep_id = wksht_rec.salesrep_id
2725                        AND srp.period_id = wksht_rec.pay_period_id
2726                        AND srp.credit_type_id = -1000
2727                        AND srp.quota_id = -1000
2728                        AND nvl((nvl(srp.balance2_dtd, 0) - nvl(srp.balance2_ctd, 0) + nvl(srp.balance2_bbd, 0) - nvl(srp.balance2_bbc, 0)), 0) <> 0
2729                        AND qp.quota_id(+) = srp.quota_id
2730                        AND wksht_rec.pay_date BETWEEN qp.start_date(+) AND qp.end_date(+)
2731                        AND s.salesrep_id = srp.salesrep_id
2732                        AND nvl(s.status, 'A') = nvl(qp.status, nvl(s.status, 'A'))
2733                           --R12
2734                        AND srp.org_id = s.org_id
2735                        AND srp.org_id = r.org_id
2736                        AND srp.org_id = wksht_rec.org_id
2737                        AND NOT EXISTS (SELECT 'X'
2738                               FROM cn_payment_transactions cnpt
2739                              WHERE cnpt.payrun_id = wksht_rec.payrun_id
2740                                AND cnpt.credited_salesrep_id = wksht_rec.salesrep_id
2741                                AND cnpt.quota_id = -1000
2742                                   -- 07/18/03 check exist only for commission/bonus
2743                                AND cnpt.incentive_type_code IN ('COMMISSION', 'BONUS')
2744                                AND (cnpt.hold_flag IS NULL OR cnpt.hold_flag = 'N'));
2745 
2746                 IF SQL%ROWCOUNT <> 0
2747                 THEN
2748                     l_batch_rec.posting_batch_id  := carryover_posting_batch_id;
2749                     l_batch_rec.NAME              := 'Refresh batch number:' || wksht_rec.payrun_id || ':' || wksht_rec.salesrep_id || ':' ||
2750                                                      carryover_posting_batch_id;
2751                     l_batch_rec.created_by        := fnd_global.user_id;
2752                     l_batch_rec.creation_date     := SYSDATE;
2753                     l_batch_rec.last_updated_by   := fnd_global.user_id;
2754                     l_batch_rec.last_update_date  := SYSDATE;
2755                     l_batch_rec.last_update_login := fnd_global.login_id;
2756                     -- Create the Posting Batches
2757                     cn_prepostbatches.begin_record(x_operation         => 'INSERT',
2758                                                    x_rowid             => l_rowid,
2759                                                    x_posting_batch_rec => l_batch_rec,
2760                                                    x_program_type      => NULL,
2761                                                    p_org_id            => wksht_rec.org_id);
2762                 END IF;
2763 
2764                 -- 01/03/03 gasriniv added hold flag check for bug 2710066
2765                 UPDATE cn_payment_transactions cnpt
2766                    SET (                amount, payment_amount) = (SELECT cnpt.amount - SUM(cnptheld.amount),
2767                                                                           cnpt.payment_amount - SUM(cnptheld.amount)
2768                                                                      FROM cn_payment_transactions cnptheld
2769                                                                     WHERE cnptheld.payrun_id = wksht_rec.payrun_id
2770                                                                       AND cnptheld.credited_salesrep_id = wksht_rec.salesrep_id
2771                                                                       AND cnptheld.quota_id = cnpt.quota_id
2772                                                                       AND cnptheld.hold_flag = 'Y'
2773                                                                       AND cnptheld.paid_flag = 'N'
2774                                                                          --R12
2775                                                                       AND cnptheld.org_id = wksht_rec.org_id),
2776                        last_update_date  = SYSDATE,
2777                        last_updated_by   = g_last_updated_by,
2778                        last_update_login = g_last_update_login
2779                  WHERE cnpt.payrun_id = wksht_rec.payrun_id
2780                    AND cnpt.credited_salesrep_id = wksht_rec.salesrep_id
2781                    AND cnpt.hold_flag = 'N'
2782                    AND cnpt.paid_flag = 'N'
2783                    AND incentive_type_code IN ('COMMISSION', 'BONUS')
2784                       --R12
2785                    AND cnpt.org_id = wksht_rec.org_id
2786                    AND EXISTS (SELECT 'X'
2787                           FROM cn_payment_transactions cnptchk
2788                          WHERE cnptchk.payrun_id = wksht_rec.payrun_id
2789                            AND cnptchk.credited_salesrep_id = wksht_rec.salesrep_id
2790                            AND cnptchk.quota_id = cnpt.quota_id
2791                            AND cnptchk.hold_flag = 'Y'
2792                               --R12
2793                            AND cnptchk.org_id = wksht_rec.org_id);
2794             ELSE
2795                 -- PBT
2796 
2797                 -- Bug 3140343 : Payee Design
2798                 IF l_ispayee <> 1
2799                 THEN
2800                     -- IF PBT, then create all unposted lines
2801                     -- Create new payment transactions for unposted payment transactions
2802                     INSERT INTO cn_payment_transactions
2803                         (payment_transaction_id,
2804                          posting_batch_id,
2805                          trx_type,
2806                          payee_salesrep_id,
2807                          role_id,
2808                          incentive_type_code,
2809                          credit_type_id,
2810                          pay_period_id,
2811                          amount,
2812                          commission_header_id,
2813                          commission_line_id,
2814                          srp_plan_assign_id,
2815                          quota_id,
2816                          credited_salesrep_id,
2817                          processed_period_id,
2818                          quota_rule_id,
2819                          event_factor,
2820                          payment_factor,
2821                          quota_factor,
2822                          input_achieved,
2823                          rate_tier_id,
2824                          payee_line_id,
2825                          commission_rate,
2826                          hold_flag,
2827                          paid_flag,
2828                          waive_flag,
2829                          recoverable_flag,
2830                          payrun_id,
2831                          payment_amount,
2832                          pay_element_type_id,
2833                          creation_date,
2834                          created_by,
2835                          --R12
2836                          org_id,
2837                          object_version_number,
2838                          processed_date)
2839                         SELECT
2840                          cn_payment_transactions_s.NEXTVAL,
2841                          l_posting_batch_id,
2842                          cl.trx_type,
2843                          cl.credited_salesrep_id,
2844                          cl.role_id,
2845                          pe.incentive_type_code,
2846                          pe.credit_type_id,
2847                          cl.pay_period_id,
2848                          nvl(cl.commission_amount, 0),
2849                          cl.commission_header_id,
2850                          cl.commission_line_id,
2851                          cl.srp_plan_assign_id,
2852                          cl.quota_id,
2853                          cl.credited_salesrep_id,
2854                          cl.processed_period_id,
2855                          cl.quota_rule_id,
2856                          cl.event_factor,
2857                          cl.payment_factor,
2858                          cl.quota_factor,
2859                          cl.input_achieved,
2860                          cl.rate_tier_id,
2861                          cl.payee_line_id,
2862                          cl.commission_rate,
2863                          'N',
2864                          'N',
2865                          'N',
2866                          'N',
2867                          wksht_rec.payrun_id,
2868                          nvl(cl.commission_amount, 0),
2869                          -- Bug 2875120 : remove cn_api function call in sql statement
2870                          decode(l_payroll_flag, NULL, NULL, 'N', NULL, 'Y', qp.pay_element_type_id, NULL) pay_element_type_id,
2871                          SYSDATE,
2872                          fnd_global.user_id,
2873                          --R12
2874                          wksht_rec.org_id,
2875                          1,
2876                          cl.processed_date
2877                           FROM cn_commission_lines   cl,
2878                                cn_quotas_all         pe,
2879                                cn_quota_pay_elements qp
2880                          WHERE cl.credited_salesrep_id = wksht_rec.salesrep_id
2881                            AND cl.processed_period_id <= wksht_rec.pay_period_id
2882                            AND cl.processed_date <= wksht_rec.pay_date
2883                            AND cl.status = 'CALC'
2884                            AND cl.srp_payee_assign_id IS NULL
2885                            AND cl.posting_status = 'UNPOSTED'
2886                            AND cl.quota_id = pe.quota_id
2887                            AND cl.credit_type_id = -1000
2888                            AND pe.incentive_type_code = decode(nvl(wksht_rec.incentive_type_code, pe.incentive_type_code),
2889                                                                'COMMISSION',
2890                                                                'COMMISSION',
2891                                                                'BONUS',
2892                                                                'BONUS',
2893                                                                pe.incentive_type_code)
2894                            AND qp.quota_id(+) = cl.quota_id
2895                            AND wksht_rec.pay_date BETWEEN qp.start_date(+) AND qp.end_date(+)
2896                            AND nvl(l_srp_status, 'A') = nvl(qp.status, nvl(l_srp_status, 'A'))
2897                            AND cl.org_id = wksht_rec.org_id;
2898 
2899                 ELSE
2900                     -- refresh record for Payee. Get unposted trx from comm_lines
2901                     INSERT INTO cn_payment_transactions
2902                         (payment_transaction_id,
2903                          posting_batch_id,
2904                          trx_type,
2905                          payee_salesrep_id,
2906                          role_id,
2907                          incentive_type_code,
2908                          credit_type_id,
2909                          pay_period_id,
2910                          amount,
2911                          commission_header_id,
2912                          commission_line_id,
2913                          srp_plan_assign_id,
2914                          quota_id,
2915                          credited_salesrep_id,
2916                          processed_period_id,
2917                          quota_rule_id,
2918                          event_factor,
2919                          payment_factor,
2920                          quota_factor,
2921                          input_achieved,
2922                          rate_tier_id,
2923                          payee_line_id,
2924                          commission_rate,
2925                          hold_flag,
2926                          paid_flag,
2927                          waive_flag,
2928                          recoverable_flag,
2929                          payrun_id,
2930                          payment_amount,
2931                          pay_element_type_id,
2932                          creation_date,
2933                          created_by,
2934                          --R12
2935                          org_id,
2936                          object_version_number,
2937                          processed_date)
2938                         SELECT
2939                          cn_payment_transactions_s.NEXTVAL,
2940                          l_posting_batch_id,
2941                          cl.trx_type,
2942                          spayee.payee_id,
2943                          cl.role_id,
2944                          pe.incentive_type_code,
2945                          pe.credit_type_id,
2946                          cl.pay_period_id,
2947                          nvl(cl.commission_amount, 0),
2948                          cl.commission_header_id,
2949                          cl.commission_line_id,
2950                          cl.srp_plan_assign_id,
2951                          cl.quota_id,
2952                          spayee.payee_id,
2953                          cl.processed_period_id,
2954                          cl.quota_rule_id,
2955                          cl.event_factor,
2956                          cl.payment_factor,
2957                          cl.quota_factor,
2958                          cl.input_achieved,
2959                          cl.rate_tier_id,
2960                          cl.payee_line_id,
2961                          cl.commission_rate,
2962                          'N',
2963                          'N',
2964                          'N',
2965                          'N',
2966                          wksht_rec.payrun_id,
2967                          nvl(cl.commission_amount, 0),
2968                          -- Bug 2875120 : remove cn_api function call in sql statement
2969                          decode(l_payroll_flag, NULL, NULL, 'N', NULL, 'Y', qp.pay_element_type_id, NULL) pay_element_type_id,
2970                          SYSDATE,
2971                          fnd_global.user_id,
2972                          --R12
2973                          wksht_rec.org_id,
2974                          1,
2975                          cl.processed_date
2976                           FROM cn_commission_lines       cl,
2977                                cn_srp_payee_assigns_all  spayee,
2978                                cn_quotas_all             pe,
2979                                cn_quota_pay_elements_all qp
2980                          WHERE cl.srp_payee_assign_id IS NOT NULL
2981                            AND cl.srp_payee_assign_id = spayee.srp_payee_assign_id
2982                            AND spayee.payee_id = wksht_rec.salesrep_id
2983                            AND cl.credited_salesrep_id = spayee.salesrep_id
2984                            AND cl.processed_period_id <= wksht_rec.pay_period_id
2985                            AND cl.processed_date <= wksht_rec.pay_date
2986                            AND cl.status = 'CALC'
2987                            AND cl.posting_status = 'UNPOSTED'
2988                            AND cl.quota_id = pe.quota_id
2989                            AND cl.credit_type_id = -1000
2990                            AND pe.incentive_type_code = decode(nvl(wksht_rec.incentive_type_code, pe.incentive_type_code),
2991                                                                'COMMISSION',
2992                                                                'COMMISSION',
2993                                                                'BONUS',
2994                                                                'BONUS',
2995                                                                pe.incentive_type_code)
2996                            AND qp.quota_id(+) = cl.quota_id
2997                            AND wksht_rec.pay_date BETWEEN qp.start_date(+) AND qp.end_date(+)
2998                            AND nvl(l_srp_status, 'A') = nvl(qp.status, nvl(l_srp_status, 'A'))
2999                            AND cl.org_id = spayee.org_id
3000                            AND cl.org_id = wksht_rec.org_id;
3001 
3002                 END IF;
3003                 -- end IF l_ispayee <> 1 THEN
3004 
3005                 -- update payrun id on all payment transactions
3006                 UPDATE cn_payment_transactions cnpt
3007                    SET payrun_id             = wksht_rec.payrun_id,
3008                        pay_element_type_id   = (SELECT decode(l_payroll_flag, 'Y', p.pay_element_type_id, NULL) pay_element_type_id
3009                                                   FROM cn_quota_pay_elements p
3010                                                  WHERE p.quota_id = cnpt.quota_id
3011                                                    AND wksht_rec.pay_date BETWEEN p.start_date AND p.end_date
3012                                                    AND nvl(l_srp_status, 'A') = nvl(p.status, nvl(l_srp_status, 'A'))),
3013                        last_update_date      = SYSDATE,
3014                        last_updated_by       = g_last_updated_by,
3015                        last_update_login     = g_last_update_login,
3016                        object_version_number = nvl(object_version_number, 0) + 1
3017                  WHERE credited_salesrep_id = wksht_rec.salesrep_id
3018                    AND pay_period_id <= wksht_rec.pay_period_id
3019                    AND incentive_type_code =
3020                        decode(nvl(wksht_rec.incentive_type_code, incentive_type_code), 'COMMISSION', 'COMMISSION', 'BONUS', 'BONUS', incentive_type_code)
3021                    AND incentive_type_code IN ('COMMISSION', 'BONUS')
3022                    AND payrun_id IS NULL
3023                    AND processed_date <= wksht_rec.pay_date;
3024 
3025                 -- update pay_element_type_id
3026                 UPDATE cn_payment_transactions cnpt
3027                    SET pay_element_type_id   = (SELECT decode(l_payroll_flag, 'Y', p.pay_element_type_id, NULL) pay_element_type_id
3028                                                   FROM cn_quota_pay_elements p
3029                                                  WHERE p.quota_id = decode(cnpt.incentive_type_code, 'PMTPLN_REC', -1001, cnpt.quota_id)
3030                                                    AND wksht_rec.pay_date BETWEEN p.start_date AND p.end_date
3031                                                    AND nvl(l_srp_status, 'A') = nvl(p.status, nvl(l_srp_status, 'A'))
3032                                                    AND p.org_id = wksht_rec.org_id),
3033                        last_update_date      = SYSDATE,
3034                        last_updated_by       = g_last_updated_by,
3035                        last_update_login     = g_last_update_login,
3036                        object_version_number = nvl(object_version_number, 0) + 1
3037                  WHERE credited_salesrep_id = wksht_rec.salesrep_id
3038                    AND payrun_id = wksht_rec.payrun_id;
3039             END IF;
3040             -- end IF CN_PAY_BY_MODE = 'N'
3041 
3042             -- calculate totals
3043             calculate_totals(p_salesrep_id    => wksht_rec.salesrep_id,
3044                              p_period_id      => wksht_rec.pay_period_id,
3045                              p_incentive_type => wksht_rec.incentive_type_code,
3046                              p_payrun_id      => wksht_rec.payrun_id,
3047                              x_calc_rec_tbl   => l_calc_rec_tbl,
3048                              --R12
3049                              p_org_id => wksht_rec.org_id);
3050 
3051             -- Bug 2692801 : avoid PL/SQL error when l_calc_rec_tbl is null
3052             IF l_calc_rec_tbl.COUNT > 0
3053             THEN
3054                 FOR i IN l_calc_rec_tbl.FIRST .. l_calc_rec_tbl.LAST
3055                 LOOP
3056                     IF l_calc_rec_tbl(i).quota_id IS NOT NULL
3057                     THEN
3058                         IF l_calc_rec_tbl(i).pmt_amount_adj_rec <> 0
3059                            OR l_calc_rec_tbl(i).pmt_amount_adj_nrec <> 0
3060                         THEN
3061                             UPDATE cn_payment_transactions cnpt
3062                                SET amount                = l_calc_rec_tbl(i).pmt_amount_adj_rec + l_calc_rec_tbl(i).pmt_amount_adj_nrec,
3063                                    payment_amount        = l_calc_rec_tbl(i).pmt_amount_adj_rec + l_calc_rec_tbl(i).pmt_amount_adj_nrec,
3064                                    pay_element_type_id   = (SELECT decode(r.payroll_flag, NULL, NULL, 'N', NULL, 'Y', p.pay_element_type_id, NULL) pay_element_type_id
3065                                                               FROM cn_quota_pay_elements p,
3066                                                                    cn_rs_salesreps       s,
3067                                                                    cn_repositories       r
3068                                                              WHERE p.quota_id = cnpt.quota_id
3069                                                                AND wksht_rec.pay_date BETWEEN p.start_date AND p.end_date
3070                                                                AND s.salesrep_id = cnpt.credited_salesrep_id
3071                                                                AND nvl(s.status, 'A') = p.status
3072                                                                   --R12
3073                                                                AND p.org_id = wksht_rec.org_id
3074                                                                AND s.org_id = wksht_rec.org_id
3075                                                                AND r.org_id = wksht_rec.org_id),
3076                                    last_update_date      = SYSDATE,
3077                                    last_updated_by       = g_last_updated_by,
3078                                    last_update_login     = g_last_update_login,
3079                                    object_version_number = nvl(object_version_number, 0) + 1
3080                              WHERE credited_salesrep_id = wksht_rec.salesrep_id
3081                                AND payrun_id = wksht_rec.payrun_id
3082                                AND incentive_type_code = 'PMTPLN'
3083                                AND quota_id = l_calc_rec_tbl(i).quota_id
3084                                   --R12
3085                                AND cnpt.org_id = wksht_rec.org_id;
3086 
3087                             IF SQL%ROWCOUNT = 0
3088                             THEN
3089                                 -- Get the Sequence Number
3090                                 SELECT cn_posting_batches_s.NEXTVAL
3091                                   INTO recv_posting_batch_id
3092                                   FROM dual;
3093 
3094                                 l_batch_rec.posting_batch_id  := recv_posting_batch_id;
3095                                 l_batch_rec.NAME              := 'PMTPLN batch number:' || wksht_rec.payrun_id || ':' || wksht_rec.salesrep_id || ':' ||
3096                                                                  l_calc_rec_tbl(i).quota_id || ':' || recv_posting_batch_id;
3097                                 l_batch_rec.created_by        := fnd_global.user_id;
3098                                 l_batch_rec.creation_date     := SYSDATE;
3099                                 l_batch_rec.last_updated_by   := fnd_global.user_id;
3100                                 l_batch_rec.last_update_date  := SYSDATE;
3101                                 l_batch_rec.last_update_login := fnd_global.login_id;
3102                                 -- Create the Posting Batches
3103                                 cn_prepostbatches.begin_record(x_operation         => 'INSERT',
3104                                                                x_rowid             => l_rowid,
3105                                                                x_posting_batch_rec => l_batch_rec,
3106                                                                x_program_type      => NULL,
3107                                                                p_org_id            => wksht_rec.org_id);
3108                                 l_pmt_trans_rec.posting_batch_id     := recv_posting_batch_id;
3109                                 l_pmt_trans_rec.incentive_type_code  := 'PMTPLN';
3110                                 l_pmt_trans_rec.credit_type_id       := -1000;
3111                                 l_pmt_trans_rec.payrun_id            := wksht_rec.payrun_id;
3112                                 l_pmt_trans_rec.credited_salesrep_id := wksht_rec.salesrep_id;
3113                                 l_pmt_trans_rec.payee_salesrep_id    := wksht_rec.salesrep_id;
3114                                 l_pmt_trans_rec.pay_period_id        := wksht_rec.pay_period_id;
3115                                 l_pmt_trans_rec.hold_flag            := 'N';
3116                                 l_pmt_trans_rec.waive_flag           := 'N';
3117                                 l_pmt_trans_rec.paid_flag            := 'N';
3118                                 l_pmt_trans_rec.recoverable_flag     := 'N';
3119                                 l_pmt_trans_rec.quota_id             := l_calc_rec_tbl(i).quota_id;
3120                                 l_pmt_trans_rec.amount               := nvl(l_calc_rec_tbl(i).pmt_amount_adj_rec, 0) +
3121                                                                         nvl(l_calc_rec_tbl(i).pmt_amount_adj_nrec, 0);
3122                                 l_pmt_trans_rec.payment_amount       := nvl(l_calc_rec_tbl(i).pmt_amount_adj_rec, 0) +
3123                                                                         nvl(l_calc_rec_tbl(i).pmt_amount_adj_nrec, 0);
3124                                 --R12
3125                                 l_pmt_trans_rec.org_id                := wksht_rec.org_id;
3126                                 l_pmt_trans_rec.object_version_number := 1;
3127                                 l_pmt_trans_rec.pay_element_type_id   := cn_api.get_pay_element_id(l_calc_rec_tbl(i).quota_id,
3128                                                                                                    wksht_rec.salesrep_id,
3129                                                                                                    wksht_rec.org_id,
3130                                                                                                    wksht_rec.pay_date);
3131                                 -- Create the Payment Plan Record
3132                                 cn_pmt_trans_pkg.insert_record(p_tran_rec => l_pmt_trans_rec);
3133                             END IF;
3134                         ELSE
3135                             UPDATE cn_payment_transactions cnpt
3136                                SET amount                = 0,
3137                                    payment_amount        = 0,
3138                                    pay_element_type_id   = (SELECT decode(r.payroll_flag, NULL, NULL, 'N', NULL, 'Y', p.pay_element_type_id, NULL) pay_element_type_id
3139                                                               FROM cn_quota_pay_elements p,
3140                                                                    cn_rs_salesreps       s,
3141                                                                    cn_repositories       r
3142                                                              WHERE p.quota_id = cnpt.quota_id
3143                                                                AND wksht_rec.pay_date BETWEEN p.start_date AND p.end_date
3144                                                                AND s.salesrep_id = cnpt.credited_salesrep_id
3145                                                                AND nvl(s.status, 'A') = p.status
3146                                                                   --R12
3147                                                                AND p.org_id = wksht_rec.org_id
3148                                                                AND s.org_id = wksht_rec.org_id
3149                                                                AND r.org_id = wksht_rec.org_id),
3150                                    last_update_date      = SYSDATE,
3151                                    last_updated_by       = g_last_updated_by,
3152                                    last_update_login     = g_last_update_login,
3153                                    object_version_number = nvl(object_version_number, 0) + 1
3154                              WHERE incentive_type_code = 'PMTPLN'
3155                                AND payrun_id = wksht_rec.payrun_id
3156                                AND credited_salesrep_id = wksht_rec.salesrep_id
3157                                AND quota_id = l_calc_rec_tbl(i).quota_id
3158                                   --R12
3159                                AND cnpt.org_id = wksht_rec.org_id;
3160                         END IF; -- End IF l_calc_rec_tbl(i).pmt_amount_adj_rec  <> 0
3161 
3162                         -- Update the Worksheet at the Quota Level
3163                         UPDATE cn_payment_worksheets
3164                            SET pmt_amount_calc       = nvl(l_calc_rec_tbl(i).pmt_amount_calc, 0),
3165                                pmt_amount_adj_rec    = nvl(l_calc_rec_tbl(i).pmt_amount_adj_rec, 0),
3166                                pmt_amount_adj_nrec   = nvl(l_calc_rec_tbl(i).pmt_amount_adj_nrec, 0),
3167                                pmt_amount_adj        = nvl(l_calc_rec_tbl(i).pmt_amount_ctr, 0),
3168                                pmt_amount_recovery   = nvl(l_calc_rec_tbl(i).pmt_amount_rec, 0),
3169                                last_update_date      = SYSDATE,
3170                                last_updated_by       = g_last_updated_by,
3171                                last_update_login     = g_last_update_login,
3172                                object_version_number = nvl(object_version_number, 0) + 1
3173                          WHERE payrun_id = wksht_rec.payrun_id
3174                            AND salesrep_id = wksht_rec.salesrep_id
3175                            AND quota_id = l_calc_rec_tbl(i).quota_id;
3176 
3177                         IF SQL%ROWCOUNT = 0
3178                            AND (l_calc_rec_tbl(i)
3179                            .quota_id <> -1000 OR abs(nvl(l_calc_rec_tbl(i).pmt_amount_calc, 0)) + abs(nvl(l_calc_rec_tbl(i).pmt_amount_adj_rec, 0)) +
3180                             abs(nvl(l_calc_rec_tbl(i).pmt_amount_adj_nrec, 0)) + abs(nvl(l_calc_rec_tbl(i).pmt_amount_ctr, 0)) +
3181                             abs(nvl(l_calc_rec_tbl(i).pmt_amount_rec, 0)) <> 0)
3182                         THEN
3183                             -- Create the Worksheet at the Quota Level
3184                             cn_payment_worksheets_pkg.insert_record(x_payrun_id             => wksht_rec.payrun_id,
3185                                                                     x_salesrep_id           => wksht_rec.salesrep_id,
3186                                                                     x_quota_id              => l_calc_rec_tbl(i).quota_id,
3187                                                                     x_credit_type_id        => -1000,
3188                                                                     x_calc_pmt_amount       => nvl(l_calc_rec_tbl(i).pmt_amount_calc, 0),
3189                                                                     x_adj_pmt_amount_rec    => nvl(l_calc_rec_tbl(i).pmt_amount_adj_rec, 0),
3190                                                                     x_adj_pmt_amount_nrec   => nvl(l_calc_rec_tbl(i).pmt_amount_adj_nrec, 0),
3191                                                                     x_adj_pmt_amount        => nvl(l_calc_rec_tbl(i).pmt_amount_ctr, 0),
3192                                                                     x_pmt_amount_recovery   => nvl(l_calc_rec_tbl(i).pmt_amount_rec, 0),
3193                                                                     x_worksheet_status      => 'UNPAID',
3194                                                                     x_created_by            => g_created_by,
3195                                                                     x_creation_date         => SYSDATE,
3196                                                                     p_org_id                => wksht_rec.org_id,
3197                                                                     p_object_version_number => 1);
3198                         END IF;
3199                     END IF; -- End  IF l_calc_rec_tbl(i).quota_id is NOT NULL
3200 
3201                     -- for summary record
3202                     l_calc_pmt_amount     := nvl(l_calc_pmt_amount, 0) + nvl(l_calc_rec_tbl(i).pmt_amount_calc, 0);
3203                     l_adj_pmt_amount_rec  := nvl(l_adj_pmt_amount_rec, 0) + nvl(l_calc_rec_tbl(i).pmt_amount_adj_rec, 0);
3204                     l_adj_pmt_amount_nrec := nvl(l_adj_pmt_amount_nrec, 0) + nvl(l_calc_rec_tbl(i).pmt_amount_adj_nrec, 0);
3205                     l_pmt_amount_rec      := nvl(l_pmt_amount_rec, 0) + nvl(l_calc_rec_tbl(i).pmt_amount_rec, 0);
3206                     l_pmt_amount_ctr      := nvl(l_pmt_amount_ctr, 0) + nvl(l_calc_rec_tbl(i).pmt_amount_ctr, 0);
3207                 END LOOP;
3208             END IF; -- end  IF l_calc_rec_tbl.COUNT > 0 THEN
3209 
3210             -- UPDATE the Summary Record in the Worksheet
3211             UPDATE cn_payment_worksheets
3212                SET pmt_amount_calc       = l_calc_pmt_amount,
3213                    pmt_amount_adj_rec    = l_adj_pmt_amount_rec,
3214                    pmt_amount_adj_nrec   = l_adj_pmt_amount_nrec,
3215                    pmt_amount_adj        = l_pmt_amount_ctr,
3216                    pmt_amount_recovery   = l_pmt_amount_rec,
3217                    last_update_date      = SYSDATE,
3218                    last_updated_by       = g_last_updated_by,
3219                    last_update_login     = g_last_update_login,
3220                    object_version_number = nvl(object_version_number, 0) + 1
3221              WHERE payrun_id = wksht_rec.payrun_id
3222                AND salesrep_id = wksht_rec.salesrep_id
3223                AND quota_id IS NULL;
3224 
3225            update_ptd_details (
3226        	     p_salesrep_id => wksht_rec.salesrep_id ,
3227        	     p_payrun_id   =>  wksht_rec.payrun_id
3228            ) ;
3229 
3230             -- Bug 3140343 : Payee Design. set commission_lines to POSTED
3231             IF l_pay_by_mode = 'Y'
3232             THEN
3233                 -- Bug 3191079 by jjhuang.
3234                 IF l_ispayee <> 1
3235                 THEN
3236                     UPDATE cn_commission_lines cls
3237                        SET posting_status    = 'POSTED',
3238                            last_update_date  = SYSDATE,
3239                            last_updated_by   = g_last_updated_by,
3240                            last_update_login = g_last_update_login
3241                      WHERE posting_status <> 'POSTED'
3242                        AND status = 'CALC'
3243                        AND srp_payee_assign_id IS NULL
3244                        AND commission_line_id IN (SELECT commission_line_id
3245                                                     FROM cn_payment_transactions
3246                                                    WHERE posting_batch_id = l_posting_batch_id);
3247 
3248                 ELSE
3249                     -- payee
3250                     UPDATE cn_commission_lines cls
3251                        SET posting_status    = 'POSTED',
3252                            last_update_date  = SYSDATE,
3253                            last_updated_by   = g_last_updated_by,
3254                            last_update_login = g_last_update_login
3255                      WHERE posting_status <> 'POSTED'
3256                        AND status = 'CALC'
3257                        AND srp_payee_assign_id IS NOT NULL
3258                        AND commission_line_id IN (SELECT commission_line_id
3259                                                     FROM cn_payment_transactions
3260                                                    WHERE posting_batch_id = l_posting_batch_id);
3261                 END IF;
3262             ELSE
3263 
3264                 SELECT DISTINCT pw.quota_id
3265                  BULK COLLECT INTO l_wk_plan_elements
3266                   FROM cn_payment_worksheets pw
3267                  WHERE pw.payrun_id = wksht_rec.payrun_id
3268                    AND pw.salesrep_id = wksht_rec.salesrep_id
3269                    AND pw.quota_id IS NOT NULL ;
3270 
3271                 --PBS
3272                 IF l_ispayee <> 1
3273                 THEN
3274 
3275                   FORALL m IN 1..l_wk_plan_elements.COUNT
3276                     UPDATE  cn_commission_lines cls
3277                        SET posting_status    = 'POSTED',
3278                            last_update_date  = SYSDATE,
3279                            last_updated_by   = g_last_updated_by,
3280                            last_update_login = g_last_update_login
3281                      WHERE posting_status <> 'POSTED'
3282                        AND credit_type_id = g_credit_type_id
3283                        AND processed_period_id <= wksht_rec.pay_period_id
3284                        AND status = 'CALC'
3285                        AND srp_payee_assign_id IS NULL
3286                           --R12
3287                        AND org_id = wksht_rec.org_id
3288                        AND credited_salesrep_id = wksht_rec.salesrep_id
3289                        AND quota_id = l_wk_plan_elements(m);
3290 
3291                 ELSE
3292                     UPDATE cn_commission_lines clk
3293                        SET posting_status    = 'POSTED',
3294                            last_update_date  = SYSDATE,
3295                            last_updated_by   = g_last_updated_by,
3296                            last_update_login = g_last_update_login
3297                      WHERE processed_period_id <= wksht_rec.pay_period_id
3298                        AND status = 'CALC'
3299                        AND credit_type_id = g_credit_type_id
3300                        AND posting_status <> 'POSTED'
3301                        AND org_id = wksht_rec.org_id
3302                        AND clk.srp_payee_assign_id IS NOT NULL
3303                        AND EXISTS (SELECT 1
3304                               FROM cn_srp_payee_assigns_all spayee,
3305                                    cn_payment_worksheets    wksht
3306                              WHERE clk.srp_payee_assign_id = spayee.srp_payee_assign_id
3307                                AND spayee.quota_id = wksht.quota_id
3308                                AND spayee.payee_id = wksht_rec.salesrep_id
3309                                AND wksht.payrun_id = wksht_rec.payrun_id
3310                                AND wksht.salesrep_id = wksht_rec.salesrep_id);
3311 
3312                 END IF; -- end IF l_ispayee <> 1
3313             END IF; -- end IF l_pbt_profile_value = 'Y'
3314 
3315             -- for payroll integration population of account
3316             -- changes for bug#2568937
3317             -- use if AP / Payroll integration has been enabled.
3318             IF l_payables_flag = 'Y'
3319             THEN
3320                 -- Populate ccid's in payment worksheets
3321                 IF (cn_payrun_pvt.populate_ccids(p_payrun_id      => wksht_rec.payrun_id,
3322                                                  p_salesrep_id    => wksht_rec.salesrep_id,
3323                                                  p_loading_status => x_loading_status,
3324                                                  x_loading_status => x_loading_status)) = fnd_api.g_true
3325                 THEN
3326                     RAISE fnd_api.g_exc_unexpected_error;
3327                 END IF;
3328             END IF;
3329 
3330         ELSIF p_operation IN ('LOCK', 'RELEASE_HOLD')
3331         THEN
3332 
3333             cn_payment_security_pvt.worksheet_action(p_api_version      => p_api_version,
3334                                                      p_init_msg_list    => p_init_msg_list,
3335                                                      p_commit           => 'F',
3336                                                      p_validation_level => p_validation_level,
3337                                                      x_return_status    => x_return_status,
3338                                                      x_msg_count        => x_msg_count,
3339                                                      x_msg_data         => x_msg_data,
3340                                                      p_worksheet_id     => p_worksheet_id,
3341                                                      p_action           => p_operation,
3342                                                      p_do_audit         => fnd_api.g_false);
3343 
3344             IF x_return_status <> fnd_api.g_ret_sts_success
3345             THEN
3346                 RAISE fnd_api.g_exc_error;
3347             END IF;
3348 
3349             IF p_operation = 'LOCK'
3350             THEN
3351 
3352                 -- save current image if LOCK worksheet
3353                 set_ced_and_bb(p_api_version   => 1.0,
3354                                x_return_status => x_return_status,
3355                                x_msg_count     => x_msg_count,
3356                                x_msg_data      => x_msg_data,
3357                                p_worksheet_id  => p_worksheet_id);
3358 
3359                 IF x_return_status <> fnd_api.g_ret_sts_success
3360                 THEN
3361                     RAISE fnd_api.g_exc_error;
3362                 END IF;
3363             ELSIF p_operation = 'RELEASE_HOLD'
3364             THEN
3365 
3366                 -- Call api to release all hold pmt trx
3367                 cn_pmt_trans_pvt.release_wksht_hold(p_api_version          => p_api_version,
3368                                                     p_init_msg_list        => p_init_msg_list,
3369                                                     p_commit               => 'F',
3370                                                     p_validation_level     => p_validation_level,
3371                                                     x_return_status        => x_return_status,
3372                                                     x_msg_count            => x_msg_count,
3373                                                     x_msg_data             => x_msg_data,
3374                                                     p_payment_worksheet_id => p_worksheet_id);
3375 
3376                 IF x_return_status <> fnd_api.g_ret_sts_success
3377                 THEN
3378                     RAISE fnd_api.g_exc_error;
3379                 END IF;
3380             END IF;
3381 
3382             -- set wksht audit
3383             cn_payment_security_pvt.worksheet_audit(p_worksheet_id  => p_worksheet_id,
3384                                                     p_payrun_id     => wksht_rec.payrun_id,
3385                                                     p_salesrep_id   => wksht_rec.salesrep_id,
3386                                                     p_action        => p_operation,
3387                                                     x_return_status => x_return_status,
3388                                                     x_msg_count     => x_msg_count,
3389                                                     x_msg_data      => x_msg_data);
3390 
3391             IF x_return_status <> fnd_api.g_ret_sts_success
3392             THEN
3393                 RAISE fnd_api.g_exc_error;
3394             END IF;
3395         ELSIF p_operation IN ('UNLOCK', 'SUBMIT')
3396         THEN
3397             -- 'UNLOCK', 'SUBMIT'
3398             cn_payment_security_pvt.worksheet_action(p_api_version      => p_api_version,
3399                                                      p_init_msg_list    => p_init_msg_list,
3400                                                      p_commit           => 'F',
3401                                                      p_validation_level => p_validation_level,
3402                                                      x_return_status    => x_return_status,
3403                                                      x_msg_count        => x_msg_count,
3404                                                      x_msg_data         => x_msg_data,
3405                                                      p_worksheet_id     => p_worksheet_id,
3406                                                      p_action           => p_operation);
3407 
3408             IF x_return_status <> fnd_api.g_ret_sts_success
3409             THEN
3410                 RAISE fnd_api.g_exc_error;
3411             END IF;
3412         ELSIF p_operation IN ('APPROVE', 'REJECT')
3413         THEN
3414             cn_payment_security_pvt.worksheet_action(p_api_version      => p_api_version,
3415                                                      p_init_msg_list    => p_init_msg_list,
3416                                                      p_commit           => 'F',
3417                                                      p_validation_level => p_validation_level,
3418                                                      x_return_status    => x_return_status,
3419                                                      x_msg_count        => x_msg_count,
3420                                                      x_msg_data         => x_msg_data,
3421                                                      p_worksheet_id     => p_worksheet_id,
3422                                                      p_action           => p_operation,
3423                                                      p_do_audit         => fnd_api.g_true);
3424 
3425             IF x_return_status <> fnd_api.g_ret_sts_success
3426             THEN
3427                 RAISE fnd_api.g_exc_error;
3428             END IF;
3429         ELSIF p_operation IN ('HOLD_ALL', 'RELEASE_ALL', 'RESET_TO_UNPAID')
3430         THEN
3431             cn_payment_security_pvt.worksheet_action(p_api_version      => p_api_version,
3432                                                      p_init_msg_list    => p_init_msg_list,
3433                                                      p_commit           => 'F',
3434                                                      p_validation_level => p_validation_level,
3435                                                      x_return_status    => x_return_status,
3436                                                      x_msg_count        => x_msg_count,
3437                                                      x_msg_data         => x_msg_data,
3438                                                      p_worksheet_id     => p_worksheet_id,
3439                                                      p_action           => p_operation,
3440                                                      p_do_audit         => fnd_api.g_true);
3441 
3442             IF x_return_status <> fnd_api.g_ret_sts_success
3443             THEN
3444                 RAISE fnd_api.g_exc_error;
3445             END IF;
3446         END IF;
3447 
3448         --Update object_version_number
3449         UPDATE cn_payment_worksheets
3450            SET object_version_number = nvl(object_version_number, 0) + 1,
3451                last_update_date      = SYSDATE,
3452                last_updated_by       = g_last_updated_by,
3453                last_update_login     = g_last_update_login
3454          WHERE (payrun_id, salesrep_id) IN (SELECT payrun_id,
3455                                                    salesrep_id
3456                                               FROM cn_payment_worksheets
3457                                              WHERE payment_worksheet_id = p_worksheet_id);
3458 
3459         SELECT object_version_number
3460           INTO x_ovn
3461           FROM cn_payment_worksheets
3462          WHERE payment_worksheet_id = p_worksheet_id;
3463 
3464         -- End of API body.
3465         -- Standard check of p_commit.
3466         IF fnd_api.to_boolean(p_commit)
3467         THEN
3468             COMMIT WORK;
3469         END IF;
3470 
3471         -- Standard call to get message count and if count is 1, get message info.
3472         fnd_msg_pub.count_and_get(p_count => x_msg_count, p_data => x_msg_data, p_encoded => fnd_api.g_false);
3473     EXCEPTION
3474         WHEN fnd_api.g_exc_error THEN
3475             ROLLBACK TO update_worksheet;
3476             x_return_status := fnd_api.g_ret_sts_error;
3477             fnd_msg_pub.count_and_get(p_count => x_msg_count, p_data => x_msg_data, p_encoded => fnd_api.g_false);
3478         WHEN fnd_api.g_exc_unexpected_error THEN
3479             ROLLBACK TO update_worksheet;
3480             x_loading_status := 'UNEXPECTED_ERR';
3481             x_return_status  := fnd_api.g_ret_sts_unexp_error;
3482             fnd_msg_pub.count_and_get(p_count => x_msg_count, p_data => x_msg_data, p_encoded => fnd_api.g_false);
3483         WHEN OTHERS THEN
3484             ROLLBACK TO update_worksheet;
3485             x_loading_status := 'UNEXPECTED_ERR';
3486             x_return_status  := fnd_api.g_ret_sts_unexp_error;
3487 
3488             IF fnd_msg_pub.check_msg_level(fnd_msg_pub.g_msg_lvl_unexp_error)
3489             THEN
3490                 fnd_msg_pub.add_exc_msg(g_pkg_name, l_api_name);
3491             END IF;
3492 
3493             fnd_msg_pub.count_and_get(p_count => x_msg_count, p_data => x_msg_data, p_encoded => fnd_api.g_false);
3494     END update_worksheet;
3495 
3496     -- ===========================================================================
3497     -- Procedure : delete_worksheet
3498     -- Description :
3499     -- ===========================================================================
3500     PROCEDURE delete_worksheet
3501     (
3502         p_api_version      IN NUMBER,
3503         p_init_msg_list    IN VARCHAR2,
3504         p_commit           IN VARCHAR2,
3505         p_validation_level IN NUMBER,
3506         x_return_status    OUT NOCOPY VARCHAR2,
3507         x_msg_count        OUT NOCOPY NUMBER,
3508         x_msg_data         OUT NOCOPY VARCHAR2,
3509         p_worksheet_id     IN NUMBER,
3510         p_validation_only  IN VARCHAR2,
3511         x_status           OUT NOCOPY VARCHAR2,
3512         x_loading_status   OUT NOCOPY VARCHAR2,
3513         p_ovn              IN NUMBER
3514     ) IS
3515         l_api_name CONSTANT VARCHAR2(30) := 'Delete_Worksheet';
3516         l_profile_value VARCHAR2(02);
3517 
3518         CURSOR get_worksheet_dtls IS
3519             SELECT wk.salesrep_id,
3520                    wk.payrun_id,
3521                    wk.org_id,
3522                    pr.payrun_mode
3523               FROM cn_payment_worksheets wk,
3524                    cn_payruns            pr
3525              WHERE payment_worksheet_id = p_worksheet_id
3526                AND wk.payrun_id = pr.payrun_id;
3527 
3528         --R12 for OA.
3529         l_validation_only VARCHAR2(1);
3530         l_has_access      BOOLEAN;
3531         l_ovn             NUMBER;
3532     BEGIN
3533         --
3534         -- Standard Start of API savepoint
3535         --
3536         SAVEPOINT delete_worksheet;
3537 
3538         --
3539         -- Standard call to check for call compatibility.
3540         --
3541         IF NOT fnd_api.compatible_api_call(g_api_version, p_api_version, l_api_name, g_pkg_name)
3542         THEN
3543             RAISE fnd_api.g_exc_unexpected_error;
3544         END IF;
3545 
3546         --
3547         -- Initialize message list if p_init_msg_list is set to TRUE.
3548         --
3549         IF fnd_api.to_boolean(p_init_msg_list)
3550         THEN
3551             fnd_msg_pub.initialize;
3552         END IF;
3553 
3554         --
3555         --  Initialize API return status to success
3556         --
3557         x_return_status  := fnd_api.g_ret_sts_success;
3558         x_loading_status := 'CN_DELETED';
3559 
3560         -- API body
3561         --R12 for OA.  When p_validation_only = 'Y', only do validation for delete from OA.
3562         l_validation_only := nvl(p_validation_only, 'N');
3563 
3564         FOR wksht IN get_worksheet_dtls
3565         LOOP
3566             cn_payment_security_pvt.worksheet_action(p_api_version      => p_api_version,
3567                                                      p_init_msg_list    => p_init_msg_list,
3568                                                      p_commit           => 'F',
3569                                                      p_validation_level => p_validation_level,
3570                                                      x_return_status    => x_return_status,
3571                                                      x_msg_count        => x_msg_count,
3572                                                      x_msg_data         => x_msg_data,
3573                                                      p_worksheet_id     => p_worksheet_id,
3574                                                      p_action           => 'REMOVE',
3575                                                      p_do_audit         => fnd_api.g_false);
3576 
3577             IF x_return_status <> fnd_api.g_ret_sts_success
3578             THEN
3579                 RAISE fnd_api.g_exc_error;
3580             END IF;
3581 
3582             --R12
3583             EXIT WHEN l_validation_only = 'Y';
3584 
3585             UPDATE cn_payment_transactions
3586                SET payrun_id         = NULL,
3587                    waive_flag        = 'N',
3588                    last_update_date  = SYSDATE,
3589                    last_updated_by   = g_last_updated_by,
3590                    last_update_login = g_last_update_login
3591              WHERE payrun_id = wksht.payrun_id
3592                AND credited_salesrep_id = wksht.salesrep_id
3593                AND incentive_type_code = 'PMTPLN_REC';
3594 
3595             -- Bug 2760379 : Do not reset cn_commission_lines
3596             DELETE FROM cn_payment_transactions
3597              WHERE incentive_type_code IN ('PMTPLN', 'MANUAL_PAY_ADJ')
3598                AND payrun_id = wksht.payrun_id
3599                AND credited_salesrep_id = wksht.salesrep_id;
3600 
3601             -- Bug 2715543
3602             IF wksht.payrun_mode = 'Y'
3603             THEN
3604                 -- Bug 2760379 : Do not delete from cn_payment_transactions,
3605                 -- just set the payrun_id to null
3606                 -- 3. Set payrun_id to null for remaining tr
3607                 -- Bug 2795606 : reset paymnet_amount when delete wkshtx
3608                 UPDATE cn_payment_transactions
3609                    SET payrun_id         = NULL,
3610                        payment_amount    = amount,
3611                        last_update_date  = SYSDATE,
3612                        last_updated_by   = g_last_updated_by,
3613                        last_update_login = g_last_update_login
3614                  WHERE payrun_id = wksht.payrun_id
3615                    AND credited_salesrep_id = wksht.salesrep_id
3616                    AND commission_line_id IS NOT NULL;
3617             ELSE
3618                 -- Delete cn_payment_transactions for Pay by Summary
3619                 DELETE FROM cn_payment_transactions
3620                  WHERE payrun_id = wksht.payrun_id
3621                    AND credited_salesrep_id = wksht.salesrep_id
3622                    AND nvl(hold_flag, 'N') = 'N';
3623 
3624                 UPDATE cn_payment_transactions
3625                    SET payrun_id         = '',
3626                        last_update_date  = SYSDATE,
3627                        last_updated_by   = g_last_updated_by,
3628                        last_update_login = g_last_update_login
3629                  WHERE payrun_id = wksht.payrun_id
3630                    AND credited_salesrep_id = wksht.salesrep_id
3631                    AND nvl(hold_flag, 'N') = 'Y';
3632             END IF;
3633 
3634             -- Delete the Posting Batches
3635             DELETE FROM cn_posting_batches cnpb
3636              WHERE cnpb.posting_batch_id IN (SELECT cnpd.posting_batch_id
3637                                                FROM cn_payment_transactions cnpd
3638                                               WHERE cnpd.payrun_id = wksht.payrun_id
3639                                                 AND cnpd.credited_salesrep_id = wksht.salesrep_id
3640                                                 AND nvl(cnpd.hold_flag, 'N') = 'N');
3641 
3642             -- add notes and audit
3643             cn_payment_security_pvt.worksheet_audit(p_worksheet_id  => p_worksheet_id,
3644                                                     p_payrun_id     => wksht.payrun_id,
3645                                                     p_salesrep_id   => wksht.salesrep_id,
3646                                                     p_action        => 'REMOVE',
3647                                                     x_return_status => x_return_status,
3648                                                     x_msg_count     => x_msg_count,
3649                                                     x_msg_data      => x_msg_data);
3650 
3651             -- Delete the Worksheets
3652             cn_payment_worksheets_pkg.delete_record(p_salesrep_id => wksht.salesrep_id, p_payrun_id => wksht.payrun_id);
3653         END LOOP;
3654 
3655         -- End of API body.
3656         -- Standard check of p_commit.
3657         IF fnd_api.to_boolean(p_commit)
3658         THEN
3659             COMMIT WORK;
3660         END IF;
3661 
3662         --
3663         -- Standard call to get message count and if count is 1, get message info.
3664         --
3665         fnd_msg_pub.count_and_get(p_count => x_msg_count, p_data => x_msg_data, p_encoded => fnd_api.g_false);
3666     EXCEPTION
3667         WHEN fnd_api.g_exc_error THEN
3668             ROLLBACK TO delete_worksheet;
3669             x_return_status := fnd_api.g_ret_sts_error;
3670             fnd_msg_pub.count_and_get(p_count => x_msg_count, p_data => x_msg_data, p_encoded => fnd_api.g_false);
3671         WHEN fnd_api.g_exc_unexpected_error THEN
3672             ROLLBACK TO delete_worksheet;
3673             x_loading_status := 'UNEXPECTED_ERR';
3674             x_return_status  := fnd_api.g_ret_sts_unexp_error;
3675             fnd_msg_pub.count_and_get(p_count => x_msg_count, p_data => x_msg_data, p_encoded => fnd_api.g_false);
3676         WHEN OTHERS THEN
3677             ROLLBACK TO delete_worksheet;
3678             x_loading_status := 'UNEXPECTED_ERR';
3679             x_return_status  := fnd_api.g_ret_sts_unexp_error;
3680 
3681             IF fnd_msg_pub.check_msg_level(fnd_msg_pub.g_msg_lvl_unexp_error)
3682             THEN
3683                 fnd_msg_pub.add_exc_msg(g_pkg_name, l_api_name);
3684             END IF;
3685 
3686             fnd_msg_pub.count_and_get(p_count => x_msg_count, p_data => x_msg_data, p_encoded => fnd_api.g_false);
3687     END delete_worksheet;
3688 
3689 
3690     PROCEDURE get_ced_and_bb
3691     (
3692         p_api_version           IN NUMBER,
3693         p_init_msg_list         IN VARCHAR2,
3694         p_commit                IN VARCHAR2,
3695         p_validation_level      IN NUMBER,
3696         x_return_status         OUT NOCOPY VARCHAR2,
3697         x_msg_count             OUT NOCOPY NUMBER,
3698         x_msg_data              OUT NOCOPY VARCHAR2,
3699         p_worksheet_id          IN NUMBER,
3700         x_bb_prior_period_adj   OUT NOCOPY NUMBER,
3701         x_bb_pmt_recovery_plans OUT NOCOPY NUMBER,
3702         x_curr_earnings         OUT NOCOPY NUMBER,
3703         x_curr_earnings_due     OUT NOCOPY NUMBER,
3704         x_bb_total              OUT NOCOPY NUMBER
3705     ) IS
3706         l_api_name    CONSTANT VARCHAR2(30) := 'get_ced_and_bb';
3707         l_api_version CONSTANT NUMBER := 1.0;
3708         l_held_amount_prior NUMBER := 0;
3709 
3710         CURSOR c_wksht_csr IS
3711             SELECT w.worksheet_status wksht_status,
3712                    w.quota_id,
3713                    w.salesrep_id,
3714                    p.status payrun_status,
3715                    p.pay_period_id,
3716                    p.payrun_id,
3717                    w.org_id --R12
3718               FROM cn_payment_worksheets w,
3719                    cn_payruns            p
3720              WHERE w.payment_worksheet_id = p_worksheet_id
3721                AND w.payrun_id = p.payrun_id
3722                   --R12
3723                AND w.org_id = p.org_id;
3724 
3725         l_wksht_rec c_wksht_csr%ROWTYPE;
3726     BEGIN
3727         -- Standard Start of API savepoint
3728         SAVEPOINT get_ced_and_bb;
3729 
3730         -- Standard call to check for call compatibility.
3731         IF NOT fnd_api.compatible_api_call(l_api_version, p_api_version, l_api_name, g_pkg_name)
3732         THEN
3733             RAISE fnd_api.g_exc_unexpected_error;
3734         END IF;
3735 
3736         -- Initialize message list if p_init_msg_list is set to TRUE.
3737         IF fnd_api.to_boolean(p_init_msg_list)
3738         THEN
3739             fnd_msg_pub.initialize;
3740         END IF;
3741 
3742         --  Initialize API return status to success
3743         x_return_status := fnd_api.g_ret_sts_success;
3744         -- API Body
3745         x_curr_earnings         := 0;
3746         x_curr_earnings_due     := 0;
3747         x_bb_prior_period_adj   := 0;
3748         x_bb_pmt_recovery_plans := 0;
3749         x_bb_total              := 0;
3750 
3751         -- Get the Worksheet Info
3752         OPEN c_wksht_csr;
3753 
3754         FETCH c_wksht_csr
3755             INTO l_wksht_rec;
3756 
3757         IF c_wksht_csr%ROWCOUNT = 0
3758         THEN
3759             IF fnd_msg_pub.check_msg_level(fnd_msg_pub.g_msg_lvl_error)
3760             THEN
3761                 fnd_message.set_name('CN', 'CN_WKSHT_DOES_NOT_EXIST');
3762                 fnd_msg_pub.add;
3763             END IF;
3764 
3765             RAISE fnd_api.g_exc_error;
3766         END IF;
3767 
3768         CLOSE c_wksht_csr;
3769 
3770         -- only show summary record
3771         IF (l_wksht_rec.quota_id IS NULL)
3772         THEN
3773             IF ((l_wksht_rec.payrun_status <> 'UNPAID') OR (l_wksht_rec.wksht_status <> 'UNPAID'))
3774             THEN
3775                 -- get data from cn_payment_worksheets
3776                 SELECT bb_prior_period_adj,
3777                        bb_pmt_recovery_plans,
3778                        current_earnings
3779                   INTO x_bb_prior_period_adj,
3780                        x_bb_pmt_recovery_plans,
3781                        x_curr_earnings
3782                   FROM cn_payment_worksheets
3783                  WHERE payment_worksheet_id = p_worksheet_id;
3784             ELSE
3785                 -- get data from cn_srp_periods
3786                 BEGIN
3787                     -- get curr_earnings from all not null quota_id
3788                     -- Bug 2690859 :  add '     AND srp.credit_type_id = -1000'
3789                     -- so only get functional currecny credit type records
3790                     SELECT SUM(nvl(balance2_dtd, 0) - nvl(balance2_ctd, 0)) curr_earnings
3791                       INTO x_curr_earnings
3792                       FROM cn_srp_periods srp
3793                      WHERE srp.salesrep_id = l_wksht_rec.salesrep_id
3794                        AND srp.period_id = l_wksht_rec.pay_period_id
3795                        AND srp.quota_id IS NOT NULL
3796                        AND srp.credit_type_id = g_credit_type_id
3797                           --R12
3798                        AND srp.org_id = l_wksht_rec.org_id;
3799                 EXCEPTION
3800                     WHEN no_data_found THEN
3801                         x_curr_earnings := 0;
3802                 END;
3803 
3804                 BEGIN
3805                     -- get data from summary record where quota_id is null
3806                     SELECT SUM(nvl(balance2_bbd, 0) - nvl(balance2_bbc, 0)) pri_adj,
3807                            - (SUM(nvl(balance4_bbd, 0) - nvl(balance4_bbc, 0))) - (SUM(nvl(balance4_dtd, 0) - nvl(balance4_ctd, 0))) pmt_recovery
3808                       INTO x_bb_prior_period_adj,
3809                            x_bb_pmt_recovery_plans
3810                       FROM cn_srp_periods srp
3811                      WHERE srp.quota_id IS NULL
3812                        AND srp.salesrep_id = l_wksht_rec.salesrep_id
3813                        AND srp.period_id = l_wksht_rec.pay_period_id
3814                        AND srp.credit_type_id = g_credit_type_id
3815                           --R12
3816                        AND srp.org_id = l_wksht_rec.org_id;
3817                 EXCEPTION
3818                     WHEN no_data_found THEN
3819                         x_bb_prior_period_adj   := 0;
3820                         x_bb_pmt_recovery_plans := 0;
3821                 END;
3822             END IF;
3823             -- 01/03/03 pramadas added hold flag check for bug 2710066
3824             -- commented the code for Bug Fix 2849715
3825             /* BEGIN
3826                SELECT SUM(nvl(amount,0))
3827                   INTO l_held_amount_prior
3828                   FROM cn_payment_transactions cnpt
3829                   WHERE cnpt.quota_id IS NOT NULL
3830                   AND cnpt.credited_salesrep_id = l_wksht_rec.salesrep_id
3831                   AND cnpt.pay_period_id < l_wksht_rec.pay_period_id
3832                   AND cnpt.credit_type_id = G_credit_type_id
3833                   AND cnpt.hold_flag = 'Y'
3834                   AND cnpt.paid_flag ='N'
3835                             ;
3836             EXCEPTION
3837                WHEN no_data_found THEN
3838                   l_held_amount_prior := 0 ;
3839             END;*/
3840             -- 01/03/03 pramadas added hold flag check for bug 2710066
3841         END IF;
3842 
3843         x_bb_total          := nvl(x_bb_prior_period_adj, 0) + nvl(x_bb_pmt_recovery_plans, 0);
3844         x_curr_earnings_due := x_bb_total + nvl(x_curr_earnings, 0); -- + Nvl(l_held_amount_prior,0);
3845 
3846         -- End of API body.
3847         -- Standard check of p_commit.
3848         IF fnd_api.to_boolean(p_commit)
3849         THEN
3850             COMMIT WORK;
3851         END IF;
3852 
3853         --
3854         -- Standard call to get message count and if count is 1, get message info.
3855         fnd_msg_pub.count_and_get(p_count => x_msg_count, p_data => x_msg_data, p_encoded => fnd_api.g_false);
3856     EXCEPTION
3857         WHEN fnd_api.g_exc_error THEN
3858             ROLLBACK TO get_ced_and_bb;
3859             x_return_status := fnd_api.g_ret_sts_error;
3860             fnd_msg_pub.count_and_get(p_count => x_msg_count, p_data => x_msg_data, p_encoded => fnd_api.g_false);
3861         WHEN fnd_api.g_exc_unexpected_error THEN
3862             ROLLBACK TO get_ced_and_bb;
3863             x_return_status := fnd_api.g_ret_sts_unexp_error;
3864             fnd_msg_pub.count_and_get(p_count => x_msg_count, p_data => x_msg_data, p_encoded => fnd_api.g_false);
3865         WHEN OTHERS THEN
3866             ROLLBACK TO get_ced_and_bb;
3867             x_return_status := fnd_api.g_ret_sts_unexp_error;
3868 
3869             IF fnd_msg_pub.check_msg_level(fnd_msg_pub.g_msg_lvl_unexp_error)
3870             THEN
3871                 fnd_msg_pub.add_exc_msg(g_pkg_name, l_api_name);
3872             END IF;
3873 
3874             fnd_msg_pub.count_and_get(p_count => x_msg_count, p_data => x_msg_data, p_encoded => fnd_api.g_false);
3875     END get_ced_and_bb;
3876 
3877     --============================================================================
3878     --Name :set_ced_and_bb
3879     --Description : Procedure which will be used to set value of current earning
3880     --              due, begin balance values
3881     --============================================================================
3882     PROCEDURE set_ced_and_bb
3883     (
3884         p_api_version      IN NUMBER,
3885         p_init_msg_list    IN VARCHAR2,
3886         p_commit           IN VARCHAR2,
3887         p_validation_level IN NUMBER,
3888         x_return_status    OUT NOCOPY VARCHAR2,
3889         x_msg_count        OUT NOCOPY NUMBER,
3890         x_msg_data         OUT NOCOPY VARCHAR2,
3891         p_worksheet_id     IN NUMBER
3892     ) IS
3893         l_api_name    CONSTANT VARCHAR2(30) := 'set_ced_and_bb';
3894         l_api_version CONSTANT NUMBER := 1.0;
3895         l_held_amount_prior NUMBER := 0;
3896 
3897         CURSOR c_status_csr IS
3898             SELECT w.worksheet_status wksht_status,
3899                    w.salesrep_id,
3900                    p.status payrun_status,
3901                    p.pay_period_id,
3902                    p.payrun_id,
3903                    w.org_id
3904               FROM cn_payment_worksheets w,
3905                    cn_payruns            p
3906              WHERE w.payment_worksheet_id = p_worksheet_id
3907                AND w.payrun_id = p.payrun_id;
3908 
3909         l_status_rec c_status_csr%ROWTYPE;
3910 
3911         CURSOR c_wksht_sum_csr(l_payrun_id cn_payruns.payrun_id%TYPE, l_srp_id cn_payment_worksheets.salesrep_id%TYPE,
3912         --R12
3913         p_org_id cn_payment_worksheets.org_id%TYPE) IS
3914             SELECT w.payment_worksheet_id,
3915                    w.quota_id,
3916                    w.salesrep_id,
3917                    w.object_version_number
3918               FROM cn_payment_worksheets w
3919              WHERE w.payrun_id = l_payrun_id
3920                AND w.salesrep_id = l_srp_id
3921                AND w.quota_id IS NULL
3922                AND w.org_id = p_org_id;
3923 
3924         l_wksht_sum_rec         c_wksht_sum_csr%ROWTYPE;
3925         l_curr_earnings         NUMBER := 0;
3926         s_bb_prior_period_adj   NUMBER := 0;
3927         s_bb_pmt_recovery_plans NUMBER := 0;
3928         s_curr_earnings_due     NUMBER := 0;
3929         l_loading_status        VARCHAR2(30);
3930         -- varialve added for Bug 3140343
3931         l_ispayee NUMBER := 0;
3932     BEGIN
3933         -- Standard Start of API savepoint
3934         SAVEPOINT set_ced_and_bb;
3935 
3936         -- Standard call to check for call compatibility.
3937         IF NOT fnd_api.compatible_api_call(l_api_version, p_api_version, l_api_name, g_pkg_name)
3938         THEN
3939             RAISE fnd_api.g_exc_unexpected_error;
3940         END IF;
3941 
3942         -- Initialize message list if p_init_msg_list is set to TRUE.
3943         IF fnd_api.to_boolean(p_init_msg_list)
3944         THEN
3945             fnd_msg_pub.initialize;
3946         END IF;
3947 
3948         --  Initialize API return status to success
3949         x_return_status := fnd_api.g_ret_sts_success;
3950 
3951         -- API Body
3952         -- Get the Status Info
3953         OPEN c_status_csr;
3954 
3955         FETCH c_status_csr
3956             INTO l_status_rec;
3957 
3958         IF c_status_csr%ROWCOUNT = 0
3959         THEN
3960             IF fnd_msg_pub.check_msg_level(fnd_msg_pub.g_msg_lvl_error)
3961             THEN
3962                 fnd_message.set_name('CN', 'CN_WKSHT_DOES_NOT_EXIST');
3963                 fnd_msg_pub.add;
3964             END IF;
3965 
3966             RAISE fnd_api.g_exc_error;
3967         END IF;
3968 
3969         CLOSE c_status_csr;
3970 
3971         IF ((l_status_rec.payrun_status = 'UNPAID') AND (l_status_rec.wksht_status = 'UNPAID'))
3972         THEN
3973             -- quota_id is null, summary record
3974             FOR l_wksht_sum_rec IN c_wksht_sum_csr(l_status_rec.payrun_id, l_status_rec.salesrep_id, l_status_rec.org_id)
3975             LOOP
3976                 BEGIN
3977                     -- get curr_earnings from all not null quota_id
3978                     -- Bug 2690859 :  add '     AND srp.credit_type_id = -1000'
3979                     -- so only get functional currecny credit type records
3980                     SELECT SUM(nvl(balance2_dtd, 0) - nvl(balance2_ctd, 0)) curr_earnings
3981                       INTO l_curr_earnings
3982                       FROM cn_srp_periods srp
3983                      WHERE srp.salesrep_id = l_wksht_sum_rec.salesrep_id
3984                        AND srp.period_id = l_status_rec.pay_period_id
3985                        AND srp.quota_id IS NOT NULL
3986                        AND srp.credit_type_id = g_credit_type_id
3987                        AND srp.org_id = l_status_rec.org_id;
3988                 EXCEPTION
3989                     WHEN no_data_found THEN
3990                         l_curr_earnings := 0;
3991                 END;
3992 
3993                 BEGIN
3994                     -- get data from summary record where quota_id is null
3995                     SELECT SUM(nvl(balance2_bbd, 0) - nvl(balance2_bbc, 0)) pri_adj,
3996                            - (SUM(nvl(balance4_bbd, 0) - nvl(balance4_bbc, 0))) - (SUM(nvl(balance4_dtd, 0) - nvl(balance4_ctd, 0))) pmt_recovery
3997                       INTO s_bb_prior_period_adj,
3998                            s_bb_pmt_recovery_plans
3999                       FROM cn_srp_periods srp
4000                      WHERE srp.quota_id IS NULL
4001                        AND srp.salesrep_id = l_wksht_sum_rec.salesrep_id
4002                        AND srp.period_id = l_status_rec.pay_period_id
4003                        AND srp.credit_type_id = g_credit_type_id
4004                        AND srp.org_id = l_status_rec.org_id;
4005                 EXCEPTION
4006                     WHEN no_data_found THEN
4007                         s_bb_prior_period_adj   := 0;
4008                         s_bb_pmt_recovery_plans := 0;
4009                 END;
4010 
4011                 -- 01/03/03 pramadas added hold flag check for bug 2710066
4012                 -- commented the code for Bug Fix 2849715
4013 
4014                 s_curr_earnings_due := s_bb_prior_period_adj + s_bb_pmt_recovery_plans + l_curr_earnings;
4015                 -- removed  + l_held_amount_prior; (held amount is in s_bb_prior_period_adj)
4016 
4017                 -- update worksheet record
4018                 UPDATE cn_payment_worksheets
4019                    SET bb_prior_period_adj   = s_bb_prior_period_adj,
4020                        bb_pmt_recovery_plans = s_bb_pmt_recovery_plans,
4021                        current_earnings      = l_curr_earnings,
4022                        current_earnings_due  = s_curr_earnings_due,
4023                        last_update_date      = SYSDATE,
4024                        last_update_login     = fnd_global.login_id,
4025                        last_updated_by       = fnd_global.user_id,
4026                        object_version_number = l_wksht_sum_rec.object_version_number + 1
4027                  WHERE payment_worksheet_id = l_wksht_sum_rec.payment_worksheet_id;
4028             END LOOP;
4029 
4030             -- REMOVED cn_worksheet_qg_dtls code => re-create cn_worksheet_qg_dtls
4031             -- Bug 3140343 : Payee Design.
4032         END IF;
4033 
4034         -- End of API body.
4035         -- Standard check of p_commit.
4036         IF fnd_api.to_boolean(p_commit)
4037         THEN
4038             COMMIT WORK;
4039         END IF;
4040 
4041         --
4042         -- Standard call to get message count and if count is 1, get message info.
4043         fnd_msg_pub.count_and_get(p_count => x_msg_count, p_data => x_msg_data, p_encoded => fnd_api.g_false);
4044     EXCEPTION
4045         WHEN fnd_api.g_exc_error THEN
4046             ROLLBACK TO set_ced_and_bb;
4047             x_return_status := fnd_api.g_ret_sts_error;
4048             fnd_msg_pub.count_and_get(p_count => x_msg_count, p_data => x_msg_data, p_encoded => fnd_api.g_false);
4049         WHEN fnd_api.g_exc_unexpected_error THEN
4050             ROLLBACK TO set_ced_and_bb;
4051             x_return_status := fnd_api.g_ret_sts_unexp_error;
4052             fnd_msg_pub.count_and_get(p_count => x_msg_count, p_data => x_msg_data, p_encoded => fnd_api.g_false);
4053         WHEN OTHERS THEN
4054             ROLLBACK TO set_ced_and_bb;
4055             x_return_status := fnd_api.g_ret_sts_unexp_error;
4056 
4057             IF fnd_msg_pub.check_msg_level(fnd_msg_pub.g_msg_lvl_unexp_error)
4058             THEN
4059                 fnd_msg_pub.add_exc_msg(g_pkg_name, l_api_name);
4060             END IF;
4061 
4062             fnd_msg_pub.count_and_get(p_count => x_msg_count, p_data => x_msg_data, p_encoded => fnd_api.g_false);
4063     END set_ced_and_bb;
4064 
4065 
4066 
4067 PROCEDURE generic_conc_processor
4068     (
4069          p_payrun_id    IN NUMBER,
4070          p_params       IN  conc_params,
4071          p_org_id       cn_payment_worksheets.org_id%TYPE,
4072          p_salesrep_tbl IN salesrep_tab_typ,
4073          x_errbuf       OUT NOCOPY VARCHAR2,
4074          x_retcode      OUT NOCOPY NUMBER
4075     ) IS
4076         l_payrun_id         NUMBER;
4077         l_logical_batch_id  NUMBER;
4078         l_max_batch_id      NUMBER;
4079         l_physical_batch_id NUMBER;
4080         l_job_count         NUMBER := 0;
4081         l_conc_request_id   NUMBER(15) := fnd_global.conc_request_id;
4082         l_runner_count      NUMBER := 0;
4083         l_error_count       NUMBER := 0;
4084         l_warning_count     NUMBER := 0;
4085         mysysdate CONSTANT DATE := SYSDATE;
4086         l_request_id NUMBER := 0;
4087         l_sleep_time NUMBER := to_number(nvl(fnd_profile.VALUE('CN_SLEEP_TIME'), '20'));
4088         duration     NUMBER(7, 1);
4089         errmsg       VARCHAR2(4000) := '';
4090         err_num      NUMBER := NULL;
4091         l_org_id     cn_payruns.org_id%TYPE;
4092     BEGIN
4093         -- Standard Start of API savepoint
4094         SAVEPOINT generic_conc_processor;
4095         -- SUBMIT BATCHES
4096         fnd_file.put_line(fnd_file.LOG,'Start the batching process for payrun_id = ' || p_payrun_id);
4097         l_org_id := p_org_id;
4098         BEGIN
4099            -- lock payrun when when batching
4100             BEGIN
4101                 SELECT pr.PAYRUN_ID
4102                 INTO l_payrun_id
4103                 FROM cn_payruns pr
4104                 WHERE pr.PAYRUN_ID = p_payrun_id
4105                 FOR UPDATE NOWAIT;
4106 
4107             EXCEPTION
4108             WHEN NO_DATA_FOUND THEN
4109               fnd_file.put_line(fnd_file.LOG,'Invalid payrun. Could not find payrun with ID = ' || l_payrun_id);
4110               cn_message_pkg.debug('Invalid payrun. Could not find payrun with ID = ' || l_payrun_id);
4111               RAISE ;
4112             END;
4113 
4114             l_max_batch_id := p_salesrep_tbl(p_salesrep_tbl.COUNT).batch_id;
4115 
4116             -- Get logical batch ID
4117             SELECT cn_process_batches_s2.NEXTVAL
4118               INTO l_logical_batch_id
4119               FROM sys.dual;
4120 
4121             fnd_file.put_line(fnd_file.LOG,'Logical Batch ID in cn_process_batches_all = ' || l_logical_batch_id);
4122 
4123             FOR currbatch IN 1 .. l_max_batch_id
4124             LOOP
4125 
4126                 /* Load batches into cn_process_batches*/
4127                 -- sequence s1 is for Physical batch id
4128                 SELECT cn_process_batches_s3.NEXTVAL
4129                   INTO l_physical_batch_id
4130                   FROM sys.dual;
4131 
4132                FOR kk IN 1 .. p_salesrep_tbl.COUNT
4133                 LOOP
4134                     IF (p_salesrep_tbl(kk).batch_id = currbatch)
4135                     THEN
4136                     INSERT INTO cn_process_batches
4137                             (process_batch_id,
4138                              logical_batch_id,
4139                              physical_batch_id,
4140                              srp_period_id,
4141                              period_id,
4142                              salesrep_id,
4143                              status_code,
4144                              org_id,
4145                              process_batch_type,
4146                              creation_date,
4147                              created_by,
4148                              last_update_date,
4149                              last_updated_by,
4150                              last_update_login,
4151                              request_id,
4152                              program_application_id,
4153                              program_id,
4154                              program_update_date)
4155                         VALUES
4156                             (cn_process_batches_s1.NEXTVAL,
4157                              l_logical_batch_id,
4158                              l_physical_batch_id,
4159                              1,
4160                              1,
4161                              p_salesrep_tbl(kk).salesrep_id,
4162                              'VOID',
4163                              p_org_id,
4164                              p_params.conc_program_name,
4165                              mysysdate,
4166                              fnd_global.user_id,
4167                              mysysdate,
4168                              fnd_global.user_id,
4169                              fnd_global.login_id,
4170                              fnd_global.conc_request_id,
4171                              fnd_global.prog_appl_id,
4172                              fnd_global.conc_program_id,
4173                              mysysdate);
4174 
4175                     END IF;
4176 
4177                 END LOOP; -- kk
4178                 --COMMIT;
4179 
4180                 /***************** Launching Threads ***********************/
4181                 l_job_count := l_job_count + 1;
4182 
4183                 -- SUBMIT BATCHES
4184                 fnd_file.put_line(fnd_file.LOG,' Now submit physical batch id ' || l_physical_batch_id);
4185 
4186                 conc_submit(p_conc_program     => p_params.conc_program_name,
4187                             p_description      => 'Runner physical batch ID ' || l_physical_batch_id,
4188                             p_logical_batch_id => l_logical_batch_id,
4189                             p_batch_id         => l_physical_batch_id,
4190                             p_org_id           => l_org_id,
4191                             p_payrun_id        => l_payrun_id,
4192                             x_request_id       => l_request_id,
4193                             p_params           => p_params);
4194                 fnd_file.put_line(fnd_file.LOG,' Created child concurrent request. ID = ' || l_request_id);
4195 
4196             END LOOP; --currbatch
4197 
4198         EXCEPTION
4199             WHEN OTHERS THEN
4200                 ROLLBACK TO generic_conc_processor ;
4201                 x_retcode := 2;
4202                 x_errbuf  := 'Error occured when processing payrun = ' || l_payrun_id || '. Check the error log.';
4203 
4204                 err_num := SQLCODE;
4205                 IF err_num = -54
4206                 THEN
4207                     errmsg := 'This payrun is already involved in another process. Please try again later.';
4208                     fnd_file.put_line(fnd_file.log, errmsg);
4209                     x_errbuf := errmsg ;
4210                     raise_application_error(-20000, errmsg);
4211                 ELSE
4212                     RAISE;
4213                 END IF;
4214         END;
4215 
4216         -- commit the child requests and start waiting for the children to complete
4217         COMMIT ;
4218 
4219         -- Monitor batches
4220         LOOP
4221             SELECT COUNT(0)
4222               INTO l_runner_count
4223               FROM fnd_concurrent_requests fcr
4224              WHERE fcr.parent_request_id = l_conc_request_id
4225                AND fcr.phase_code <> 'C';
4226             EXIT WHEN l_runner_count = 0;
4227             dbms_lock.sleep(l_sleep_time);
4228         END LOOP;
4229 
4230         FOR rs_errors IN (SELECT fcr.request_id,
4231                                  fcr.actual_completion_date,
4232                                  fcr.completion_text
4233                             FROM fnd_concurrent_requests fcr
4234                            WHERE parent_request_id = l_conc_request_id
4235                              AND upper(status_code) = 'E')
4236         LOOP
4237             l_error_count := l_error_count + 1;
4238             IF l_error_count = 1
4239             THEN
4240                 fnd_file.put_line(fnd_file.log, 'ERRORED REQUESTS');
4241                 fnd_file.put_line(fnd_file.log, '================');
4242             END IF;
4243             fnd_file.put_line(fnd_file.LOG,'   ' || rs_errors.request_id || ' @ ' || rs_errors.actual_completion_date || ' due to ' || rs_errors.completion_text);
4244         END LOOP;
4245 
4246         -- Count the warning batches
4247         l_warning_count := 0;
4248         BEGIN
4249             SELECT COUNT(0)
4250               INTO l_warning_count
4251               FROM fnd_concurrent_requests fcr
4252              WHERE parent_request_id = l_conc_request_id
4253                AND upper(status_code) = 'G';
4254 
4255             fnd_file.put_line(fnd_file.log, 'WARNING REQUESTS: ' || l_warning_count);
4256         EXCEPTION
4257             WHEN no_data_found THEN
4258                 NULL;
4259             WHEN OTHERS THEN
4260                 fnd_file.put_line(fnd_file.log, 'Error getting warnings: ' || SQLERRM);
4261         END;
4262 
4263         duration := (SYSDATE - mysysdate) * 1440;
4264 
4265         IF l_error_count <> 0
4266         THEN
4267             x_retcode := 2;
4268             x_errbuf  := to_char(l_error_count) || ' batches in error';
4269         ELSIF l_warning_count <> 0
4270         THEN
4271             x_retcode := 1;
4272             x_errbuf  := 'WARNINGS: ' || to_char(l_warning_count);
4273         ELSE
4274             x_retcode := 0;
4275             x_errbuf  := 'SUCCESS: ';
4276         END IF;
4277 
4278         x_errbuf := x_errbuf || '.  Worksheet process completed in ' || to_char(duration) ||' minutes. ';
4279 
4280     EXCEPTION
4281     WHEN OTHERS THEN
4282         x_retcode := 2;
4283         x_errbuf  := x_errbuf || '. Error processing payrun ID = ' || l_payrun_id ;
4284         fnd_file.put_line(fnd_file.log, x_errbuf);
4285         RAISE ;
4286     END generic_conc_processor;
4287 
4288         --============================================================================
4289     -- This procedure is used as executable for the concurrent program
4290     -- REFRESH_WORKSHEET".This program will take payrun name as the input
4291     -- and then call the procedure "refresh_worksheet_child" which refreshes
4292     -- worksheets.
4293     --============================================================================
4294 
4295     PROCEDURE refresh_worksheet_parent
4296     (
4297         errbuf  OUT NOCOPY VARCHAR2,
4298         retcode OUT NOCOPY NUMBER,
4299         p_name  cn_payruns.NAME%TYPE
4300     ) IS
4301         salesrep_t   salesrep_tab_typ;
4302         l_batch_sz   NUMBER := 80;
4303         errmsg       VARCHAR2(4000) := '';
4304         l_min_period NUMBER;
4305         l_max_period NUMBER;
4306         l_payrun_id  NUMBER;
4307         x_reps_exist NUMBER := 0;
4308 
4309         l_status     VARCHAR2(30);
4310         --R12
4311         l_org_id cn_payruns.org_id%TYPE;
4312         l_conc_params conc_params ;
4313         l_has_access BOOLEAN;
4314 
4315         CURSOR get_payrun_id_curs IS
4316             SELECT payrun_id,
4317                    status
4318               FROM cn_payruns pr
4319              WHERE NAME = p_name
4320              AND org_id = mo_global.get_current_org_id;
4321     BEGIN
4322         fnd_file.put_line(fnd_file.log, 'Input Parameters Payrun_Name =' || p_name);
4323         l_has_access := cn_payment_security_pvt.get_security_access(cn_payment_security_pvt.g_type_wksht, cn_payment_security_pvt.g_access_payrun_refresh);
4324         --Get the salesrep batch size from profile option.
4325         l_batch_sz := nvl(fnd_profile.value('CN_PMT_SRP_BATCH_SIZE'),251);
4326         fnd_file.put_line(fnd_file.log, 'Batch Size =' || to_char(l_batch_sz));
4327 
4328         IF l_batch_sz < 1
4329         THEN
4330             errmsg := 'The batch size should be greater than zero.';
4331             fnd_file.put_line(fnd_file.log, errmsg);
4332             raise_application_error(-20000, errmsg);
4333         END IF;
4334 
4335         -- TODO Handle error message
4336         BEGIN
4337             OPEN get_payrun_id_curs;
4338             FETCH get_payrun_id_curs
4339                 INTO l_payrun_id, l_status;
4340             CLOSE get_payrun_id_curs;
4341         EXCEPTION
4342             WHEN NO_DATA_FOUND THEN
4343                 errmsg := 'Invalid payrun name. Could not find payrun with the name = ' || p_name;
4344                 fnd_file.put_line(fnd_file.log, errmsg);
4345                 raise_application_error(-20000, errmsg);
4346         END;
4347 
4348         IF l_status NOT IN ('UNPAID')
4349         THEN
4350             errmsg := 'Cannot perform worksheet refresh when paid is in status = ' || l_status;
4351             raise_application_error(-20000, errmsg);
4352         END IF;
4353 
4354         BEGIN
4355             SELECT salesrep_id,
4356                    ceil(rownum / l_batch_sz) BULK COLLECT
4357               INTO salesrep_t
4358               FROM (SELECT DISTINCT wk.salesrep_id
4359                       FROM cn_payment_worksheets wk
4360                      WHERE wk.worksheet_status = 'UNPAID'
4361                        AND wk.quota_id IS NULL
4362                        AND wk.payrun_id = l_payrun_id
4363                        AND wk.org_id = mo_global.get_current_org_id);
4364 
4365             l_conc_params.conc_program_name := 'CN_REFRESH_WKSHT_CHILD' ;
4366 
4367             -- batch
4368             generic_conc_processor(p_payrun_id    => l_payrun_id,
4369                                    p_salesrep_tbl => salesrep_t,
4370                                    p_params       => l_conc_params,
4371                                    p_org_id       => mo_global.get_current_org_id,
4372                                    x_errbuf       => errbuf,
4373                                    x_retcode      => retcode);
4374 
4375         EXCEPTION
4376         WHEN no_data_found THEN
4377             errmsg := 'No salesreps found that were eligible for worksheet creation in the payrun : ';
4378             fnd_file.put_line(fnd_file.log, errmsg);
4379             retcode := 2;
4380             errbuf  := errmsg;
4381             RAISE ;
4382         END;
4383 
4384         fnd_file.put_line(fnd_file.log, errbuf);
4385         fnd_file.put_line(fnd_file.LOG,'   Count of worksheets to be refreshed = ' || salesrep_t.COUNT);
4386         fnd_file.put_line(fnd_file.log,'   Completed refresh worksheet process....');
4387 
4388     EXCEPTION
4389         WHEN OTHERS THEN
4390             fnd_file.put_line(fnd_file.LOG,'Unexpected exception in cn_payment_worksheet_pvt.refresh_worksheet_parent');
4391             fnd_file.put_line(fnd_file.log, errmsg);
4392             fnd_file.put_line(fnd_file.log, SQLERRM);
4393             RAISE;
4394     END refresh_worksheet_parent;
4395 
4396   --============================================================================
4397     --  Name : refresh_worksheet_child
4398     --  Description : This procedure is used as executable for the concurrent program
4399     --   "CN_REFRESH_WKSHT_CHILD".This program will take payrun_id as the input
4400     --  and refresh worksheets for that payrun.
4401     --============================================================================
4402 
4403     PROCEDURE refresh_worksheet_child
4404     (
4405         errbuf             OUT NOCOPY VARCHAR2,
4406         retcode            OUT NOCOPY NUMBER,
4407         p_batch_id         IN NUMBER,
4408         p_payrun_id        IN NUMBER,
4409         p_logical_batch_id IN NUMBER,
4410         --R12
4411         p_org_id           IN       cn_payruns.org_id%TYPE
4412     ) IS
4413         x_return_status  VARCHAR2(10) := fnd_api.g_ret_sts_success;
4414         x_msg_count      NUMBER;
4415         x_msg_data       VARCHAR2(4000);
4416         l_worksheet_rec  cn_payment_worksheet_pvt.worksheet_rec_type;
4417         x_status         VARCHAR2(200);
4418         x_loading_status VARCHAR2(20) := 'CN_UPDATED';
4419         l_start_time     DATE;
4420         l_error_count    NUMBER := 0;
4421         l_ovn            cn_payment_worksheets.object_version_number%TYPE;
4422     BEGIN
4423         l_start_time := SYSDATE;
4424         fnd_file.put_line(fnd_file.log, '  Input Parameters Payrun_id = ' || p_payrun_id);
4425         fnd_file.put_line(fnd_file.log, '  Input Parameters Batch_id  = ' || p_batch_id);
4426         fnd_file.put_line(fnd_file.log, '  Current time               = ' || to_char(l_start_time, 'Dy DD-Mon-YYYY HH24:MI:SS'));
4427 
4428         l_worksheet_rec.payrun_id := p_payrun_id;
4429         l_worksheet_rec.org_id := p_org_id;
4430 
4431         FOR emp IN (SELECT salesrep_id
4432                       FROM cn_process_batches
4433                      WHERE logical_batch_id = p_logical_batch_id
4434                        AND physical_batch_id = p_batch_id)
4435         LOOP
4436             -- Run refresh worksheet for this salesrep.
4437             l_worksheet_rec.salesrep_id := emp.salesrep_id;
4438             l_worksheet_rec.call_from   := cn_payment_worksheet_pvt.concurrent_program_call;
4439 
4440             SELECT wk.payment_worksheet_id,wk.object_version_number
4441               INTO l_worksheet_rec.worksheet_id,l_ovn
4442               FROM cn_payment_worksheets_all wk
4443              WHERE wk.payrun_id = l_worksheet_rec.payrun_id
4444                AND wk.salesrep_id = l_worksheet_rec.salesrep_id
4445                AND quota_id IS NULL;
4446 
4447             fnd_file.put_line(fnd_file.log,'Refresh worksheet for  = ' || l_worksheet_rec.salesrep_id || ' salesrepID');
4448 
4449             cn_payment_worksheet_pvt.update_worksheet(p_api_version      => 1.0,
4450                                                       p_init_msg_list    => 'T',
4451                                                       p_commit           => 'F',
4452                                                       p_validation_level => fnd_api.g_valid_level_full,
4453                                                       x_return_status    => x_return_status,
4454                                                       x_msg_count        => x_msg_count,
4455                                                       x_msg_data         => x_msg_data,
4456                                                       p_worksheet_id     => l_worksheet_rec.worksheet_id,
4457                                                       p_operation        => 'REFRESH',
4458                                                       x_loading_status   => x_loading_status,
4459                                                       x_status           => x_status,
4460                                                       x_ovn              => l_ovn
4461                                                       );
4462 
4463         END LOOP;
4464 
4465         IF x_return_status <> fnd_api.g_ret_sts_success
4466         THEN
4467             l_error_count := l_error_count + 1;
4468 
4469             --ROLLBACK TO create_single_worksheet;
4470             cn_message_pkg.debug('Error when refreshing Worksheet for :  ' || l_worksheet_rec.salesrep_id);
4471             fnd_file.put_line(fnd_file.log,'Failed to refresh worksheet for ' || l_worksheet_rec.salesrep_id);
4472 
4473             FOR i IN 1 .. x_msg_count
4474             LOOP
4475                 fnd_file.put_line(fnd_file.log, 'msg: ' || fnd_msg_pub.get(i, 'F'));
4476             END LOOP;
4477             fnd_file.put_line(fnd_file.log, '+------------------------------+');
4478             ROLLBACK;
4479 
4480         ELSE
4481 
4482             COMMIT;
4483         END IF;
4484 
4485         IF l_error_count <> 0
4486         THEN
4487             retcode := 2;
4488             errbuf  := '  Batch# ' || p_batch_id || ' : Refresh of worksheets was not successful for some resources. Count = ' || to_char(l_error_count);
4489             fnd_file.put_line(fnd_file.log, errbuf);
4490         END IF;
4491 
4492         fnd_file.put_line(fnd_file.LOG,'  Finish time = ' || to_char(SYSDATE, 'Dy DD-Mon-YYYY HH24:MI:SS'));
4493         fnd_file.put_line(fnd_file.LOG, '  Batch time  = ' || (SYSDATE - l_start_time) * 1400 || ' minutes ');
4494 
4495     EXCEPTION
4496         WHEN OTHERS THEN
4497             fnd_file.put_line(fnd_file.LOG,'Unexpected exception in processing the (payrun_id,batch) = ' ||p_payrun_id || ',' || p_batch_id);
4498             fnd_file.put_line(fnd_file.log, SQLERRM);
4499             RAISE;
4500 
4501     END refresh_worksheet_child;
4502 
4503 
4504 
4505 END cn_payment_worksheet_pvt;