DBA Data[Home] [Help]

PACKAGE BODY: APPS.CN_PMT_TRANS_PVT

Source


1 PACKAGE BODY cn_pmt_trans_pvt AS
2 -- $Header: cnvpmtrb.pls 120.15 2006/01/20 18:51:53 fmburu ship $
3    g_pkg_name           CONSTANT VARCHAR2 (30) := 'CN_Pmt_Trans_PVT';
4    g_credit_type_id              NUMBER := -1000;
5 
6    CURSOR get_transactions_details(
7              c_payrun_id         NUMBER,
8              c_salesrep_id       NUMBER,
9              c_quota_id          NUMBER,
10              c_revenue_class_id  NUMBER,
11              c_invoice_number    VARCHAR2,
12              c_order_number      NUMBER,
13              c_customer_name     VARCHAR2,
14              c_hold_flag         VARCHAR2,
15              c_action            VARCHAR2)
16     IS
17     SELECT
18       pmttrxeo.payment_transaction_id,
19       pmttrxeo.quota_id quotaId,
20       pmttrxeo.hold_flag,
21       pmttrxeo.amount,
22       pmttrxeo.payment_amount,
23       pmttrxeo.payrun_id,
24       pmttrxeo.credited_salesrep_id,
25       pmttrxeo.org_id,
26       pmttrxeo.object_version_number,
27       pmttrxeo.incentive_type_code,
28       pmttrxeo.waive_flag,
29       pmttrxeo.recoverable_flag
30     FROM
31       cn_payment_transactions pmttrxeo,
32       cn_commission_headers ch,
33       (select cust_acct.cust_account_id customer_id,
34               party.party_name customer_name
35            from hz_parties party, hz_cust_accounts cust_acct
36            where cust_acct.party_id = party.party_id) cus
37     WHERE
38           pmttrxeo.payrun_id =            c_payrun_id
39       and pmttrxeo.credited_salesrep_id = c_salesrep_id
40       and pmttrxeo.incentive_type_code in ('COMMISSION','BONUS')
41       and pmttrxeo.commission_header_id = ch.commission_header_id
42       and pmttrxeo.quota_id =           NVL(c_quota_id, pmttrxeo.quota_id)
43       and (ch.revenue_class_id =   NVL(c_revenue_class_id, ch.revenue_class_id)
44           OR (ch.revenue_class_id IS NULL and c_revenue_class_id IS NULL))
45       and pmttrxeo.hold_flag LIKE NVL(c_hold_flag, pmttrxeo.hold_flag)
46       -- hold or release only when necessary
47       and pmttrxeo.hold_flag = DECODE(c_action, 'HOLD_ALL', 'N', 'RELEASE_ALL', 'Y', pmttrxeo.hold_flag)
48       and NVL(ch.invoice_number, '%') LIKE  NVL(c_invoice_number, NVL(ch.invoice_number, '%'))
49       and (ch.order_number = nvl(c_order_number,ch.order_number)
50            OR (c_order_number IS NULL and ch.order_number IS NULL))
51       and nvl(ch.customer_id,-0.9999) = cus.customer_id(+)
52       and NVL(cus.customer_name, '%') LIKE  NVL(c_customer_name,  NVL(cus.customer_name, '%')) ;
53 
54 --============================================================================
55 -- Procedure : DEBUG PROCEDURE
56 -- Description: To debug information
57 --============================================================================
58    PROCEDURE DEBUG( ID NUMBER, MSG VARCHAR2)
59    IS
60    BEGIN
61        --dbms_output.put_line('Msg:'|| id || ': Text : ' || msg ) ;
62        NULL ;
63    END ;
64 
65 --============================================================================
66 -- Procedure : Update_Pmt_Transactions
67 -- Description: To update Payment Transctions information
68 --============================================================================
69     PROCEDURE validate_hold_processing (
70           p_api_version              IN       NUMBER,
71           p_init_msg_list            IN       VARCHAR2 := fnd_api.g_false,
72           p_commit                   IN       VARCHAR2 := fnd_api.g_false,
73           p_validation_level         IN       NUMBER := fnd_api.g_valid_level_full,
74           p_rec                      IN OUT NOCOPY pmt_process_rec,
75           x_return_status            OUT NOCOPY VARCHAR2,
76           x_msg_count                OUT NOCOPY NUMBER,
77           x_msg_data                 OUT NOCOPY VARCHAR2 )
78      IS
79           l_api_name           CONSTANT VARCHAR2 (30) := 'validate_hold_processing';
80           l_api_version        CONSTANT NUMBER := 1.0;
81           l_request_id         NUMBER := NULL ;
82           l_org_id             NUMBER := NULL ;
83           l_worksheet_id       NUMBER := NULL;
84           l_status             cn_payment_worksheets.worksheet_status%TYPE ;
85           l_ovn                NUMBER := NULL ;
86           request_id NUMBER;
87           l_phase VARCHAR2(4000);
88           l_req_status VARCHAR2(4000);
89           l_dev_phase VARCHAR2(4000);
90           l_dev_status VARCHAR2(4000);
91           l_message VARCHAR2(4000);
92           l_ret_val BOOLEAN ;
93           pmt_trxn_rec get_transactions_details%ROWTYPE ;
94      BEGIN
95           -- Standard Start of API savepoint
96           SAVEPOINT validate_hold_processing;
97 
98           -- Standard call to check for call compatibility.
99           IF NOT fnd_api.compatible_api_call (l_api_version, p_api_version, l_api_name, g_pkg_name)
100           THEN
101              RAISE fnd_api.g_exc_unexpected_error;
102           END IF;
103 
104           -- Initialize message list if p_init_msg_list is set to TRUE.
105           IF fnd_api.to_boolean (p_init_msg_list)
106           THEN
107              fnd_msg_pub.initialize;
108           END IF;
109 
110           --  Initialize API return status to success
111           x_return_status := fnd_api.g_ret_sts_success;
112 
113           --debug(1, 'IN VALIDATE_HOLD_PROCESSING') ;
114 
115           BEGIN
116               SELECT worksheet_status,
117                      request_id,
118                      payment_worksheet_id,
119                      object_version_number,
120                      org_id
121               INTO  l_status, l_request_id, p_rec.worksheet_id,l_ovn, p_rec.org_id
122               FROM  cn_payment_worksheets
123               WHERE quota_id is null
124               AND   payrun_id =   p_rec.payrun_id
125               AND   salesrep_id = p_rec.salesrep_id ;
126 
127           EXCEPTION
128           WHEN NO_DATA_FOUND THEN
129                IF fnd_msg_pub.check_msg_level (fnd_msg_pub.g_msg_lvl_error)
130                THEN
131                   fnd_message.set_name ('CN', 'CN_WKSHT_DOES_NOT_EXIST');
132                   fnd_msg_pub.ADD;
133                END IF;
134                --debug(222, 'In the NO_DATA_FOUND') ;
135                RAISE fnd_api.g_exc_error;
136           END ;
137 
138           IF p_rec.object_version_number IS NOT NULL AND l_ovn <> p_rec.object_version_number THEN
139                -- record has changed
140                IF fnd_msg_pub.check_msg_level (fnd_msg_pub.g_msg_lvl_error)
141                THEN
142                   fnd_message.set_name ('CN', 'CN_RECORD_CHANGED');
143                   fnd_msg_pub.ADD;
144                END IF;
145                RAISE fnd_api.g_exc_error;
146           END IF ;
147 
148           IF NVL(p_rec.hold_flag, 'N') NOT IN ('N', 'Y') THEN
149               IF fnd_msg_pub.check_msg_level (fnd_msg_pub.g_msg_lvl_error)
150               THEN
151                 fnd_message.set_name ('CN', 'CN_INVALID_HOLD_PARAM');
152                 fnd_msg_pub.ADD;
153               END IF;
154               RAISE fnd_api.g_exc_error;
155           END IF ;
156 
157           IF p_rec.p_action IN (CN_PMT_TRANS_PVT.G_HOLD_ALL,CN_PMT_TRANS_PVT.G_RELEASE_ALL)
158           THEN
159                BEGIN
160                   OPEN get_transactions_details(
161                       p_rec.payrun_id,
162                       p_rec.salesrep_id,
163                       p_rec.quota_id,
164                       p_rec.revenue_class_id,
165                       p_rec.invoice_number,
166                       p_rec.order_number,
167                       p_rec.customer,
168                       p_rec.hold_flag,
169                       p_rec.p_action) ;
170 
171                   FETCH get_transactions_details INTO pmt_trxn_rec;
172                   IF get_transactions_details%NOTFOUND THEN
173                       IF fnd_msg_pub.check_msg_level (fnd_msg_pub.g_msg_lvl_error)
174                       THEN
175                         fnd_message.set_name ('CN', 'CN_NO_TRXNS_TO_PROCESS');
176                         fnd_msg_pub.ADD;
177                       END IF;
178                       RAISE fnd_api.g_exc_error;
179                   END IF;
180                   CLOSE get_transactions_details ;
181                EXCEPTION
182                WHEN OTHERS THEN
183                     CLOSE get_transactions_details ;
184                     RAISE ;
185                END ;
186           ELSIF p_rec.p_action = CN_PMT_TRANS_PVT.G_RESET_TO_UNPAID
187           THEN
188                NULL ;
189           ELSE
190                -- throw the error, should not be calling this procedure in this start
191               IF fnd_msg_pub.check_msg_level (fnd_msg_pub.g_msg_lvl_error)
192               THEN
193                 fnd_message.set_name ('CN', 'CN_WKSHT_ACTION_NOT_EXIST');
194                 fnd_msg_pub.ADD;
195               END IF;
196               RAISE fnd_api.g_exc_error;
197           END IF ;
198 
199          --debug(2, 'IF l_status = PROCESSING THEN') ;
200 
201           IF l_status = 'PROCESSING' AND nvl(p_rec.is_processing,'NO') <> 'YES' THEN
202              -- cannot resubmit a new request when worksheet is processing if the last request is not complete or cancelled
203              -- should send error message saying that another has already been submitted
204 
205              l_ret_val := fnd_concurrent.get_request_status( l_request_id,
206                                                 NULL,
207                                                 NULL,
208                                                 l_phase,
209                                                 l_req_status,
210                                                 l_dev_phase,
211                                                 l_dev_status,
212                                                 l_message);
213              IF l_phase = 'INACTIVE' THEN
214                  -- the previous request has not yet completed. Please check with system admin
215                  -- cannot submit another request.
216                  IF fnd_msg_pub.check_msg_level (fnd_msg_pub.g_msg_lvl_error)
217                  THEN
218                     fnd_message.set_name ('CN', 'CN_LAST_REQ_INACTIVE');
219                     fnd_msg_pub.ADD;
220                  END IF;
221                  RAISE fnd_api.g_exc_error;
222              ELSE
223                  IF fnd_msg_pub.check_msg_level (fnd_msg_pub.g_msg_lvl_error)
224                  THEN
225                     fnd_message.set_name ('CN', 'CN_LAST_REQ_NOT_COMPLETED');
226                     fnd_msg_pub.ADD;
227                  END IF;
228                  RAISE fnd_api.g_exc_error;
229              END IF ;
230 
231           ELSIF l_status IN ( 'FAILED', 'UNPAID' ) THEN
232              -- can resubmit the request but we need a new request id
233             NULL ;
234           END IF;
235 
236           cn_payment_security_pvt.worksheet_action(p_api_version           => p_api_version,
237                                                    p_init_msg_list         => p_init_msg_list,
238                                                    p_commit                => fnd_api.g_false,
239                                                    p_validation_level      => p_validation_level,
240                                                    x_return_status         => x_return_status,
241                                                    x_msg_count             => x_msg_count,
242                                                    x_msg_data              => x_msg_data,
243                                                    p_worksheet_id          => p_rec.worksheet_id,
244                                                    p_action                => p_rec.p_action,
245                                                    p_do_audit              => fnd_api.g_false
246                                                   );
247 
248         IF x_return_status <> fnd_api.g_ret_sts_success
249         THEN
250           --debug(4, 'raise expcetion cn_payment_security_pvt.worksaction' || x_return_status ) ;
251           RAISE fnd_api.g_exc_error;
252         END IF;
253 
254      EXCEPTION
255           WHEN fnd_api.g_exc_error
256           THEN
257              ROLLBACK TO validate_hold_processing;
258              x_return_status := fnd_api.g_ret_sts_error;
259              fnd_msg_pub.count_and_get (p_count => x_msg_count, p_data => x_msg_data, p_encoded => fnd_api.g_false);
260           WHEN fnd_api.g_exc_unexpected_error
261           THEN
262              ROLLBACK TO validate_hold_processing;
263              x_return_status := fnd_api.g_ret_sts_unexp_error;
264              fnd_msg_pub.count_and_get (p_count => x_msg_count, p_data => x_msg_data, p_encoded => fnd_api.g_false);
265           WHEN OTHERS
266           THEN
267              ROLLBACK TO validate_hold_processing;
268              x_return_status := fnd_api.g_ret_sts_unexp_error;
269 
270              IF fnd_msg_pub.check_msg_level (fnd_msg_pub.g_msg_lvl_unexp_error)
271              THEN
272                 fnd_msg_pub.add_exc_msg (g_pkg_name, l_api_name);
273              END IF;
274              fnd_msg_pub.count_and_get (p_count => x_msg_count, p_data => x_msg_data, p_encoded => fnd_api.g_false);
275     END validate_hold_processing;
276 
277 
278 
279 --============================================================================
280 -- Procedure : Update_Pmt_Transactions
281 -- Description: To update Payment Transctions information
282 --       1. Manual Adjustments
283 --    2. Manual Adjustments Recoverable or Non recoverable
284 --    3. Waive Recovery
285 --    4. Commission or Bonus Adjustments
286 --    5. Commission or Bonus Hold
287 --============================================================================
288    PROCEDURE update_pmt_transactions (
289       p_api_version              IN       NUMBER,
290       p_init_msg_list            IN       VARCHAR2,
291       p_commit                   IN       VARCHAR2,
292       p_validation_level         IN       NUMBER,
293       x_return_status            OUT NOCOPY VARCHAR2,
294       x_msg_count                OUT NOCOPY NUMBER,
295       x_msg_data                 OUT NOCOPY VARCHAR2,
296       p_payment_transaction_id   IN       cn_payment_transactions.payment_transaction_id%TYPE,
297       p_hold_flag                IN       cn_payment_transactions.hold_flag%TYPE,
298       p_recoverable_flag         IN       cn_payment_transactions.recoverable_flag%TYPE,
299       p_payment_amount           IN       cn_payment_transactions.payment_amount%TYPE,
300       p_waive_flag               IN       cn_payment_transactions.waive_flag%TYPE,
301       p_incentive_type_code      IN       cn_payment_transactions.incentive_type_code%TYPE,
302       p_payrun_id                IN       cn_payment_transactions.payrun_id%TYPE,
303       p_salesrep_id              IN       cn_payment_transactions.credited_salesrep_id%TYPE,
304       x_status                   OUT NOCOPY VARCHAR2,
305       x_loading_status           OUT NOCOPY VARCHAR2,
306       --R12
307       p_org_id                   IN       cn_payment_transactions.org_id%TYPE,
308       p_object_version_number    IN OUT NOCOPY cn_payment_transactions.object_version_number%TYPE
309    )
310    IS
311       l_api_name           CONSTANT VARCHAR2 (30) := 'Update_Pmt_Transactions';
312       l_api_version        CONSTANT NUMBER := 1.0;
313       l_counter                     NUMBER;
314       l_rec_amount                  NUMBER;
315       l_nrec_amount                 NUMBER;
316       l_calc_amount                 NUMBER;
317       l_adj_amount                  NUMBER;
318       l_old_amount                  NUMBER;
319       l_new_amount                  NUMBER;
320       l_pbt_profile_value           VARCHAR2 (01) := 'N';
321       l_count                       NUMBER;
322       l_earnings                    NUMBER;
323       l_pmt_trans_rec               cn_pmt_trans_pkg.pmt_trans_rec_type;
324       l_recovery_amount             NUMBER;
325       l_payment_amount              NUMBER;
326       l_wksht_ovn                   NUMBER;
327 
328       CURSOR get_pmt_trans
329       IS
330          SELECT payment_transaction_id,
331                 amount,
332                 payment_amount,
333                 hold_flag,
334                 recoverable_flag,
335                 quota_id,
336                 payrun_id,
337                 credited_salesrep_id,
338                 --R12
339                 org_id,
340                 object_version_number ovn
341            FROM cn_payment_transactions
342           WHERE payment_transaction_id = p_payment_transaction_id;
343 
344       -- clku, bug 2451907, fixed the Group by statement, adding waive_flag
345       CURSOR get_earnings (
346          p_quota_id                          cn_payment_transactions.quota_id%TYPE
347       )
348       IS
349          SELECT NVL (SUM (NVL (amount, 0)), 0) earn_amount
350            -- 12/25/02 RC bug 2710066
351            -- Commenting out waive_flag and quota_id from group by
352            -- quota_id
353            --, waive_flag
354          FROM   cn_payment_transactions
355           WHERE payrun_id = p_payrun_id
356             AND credited_salesrep_id = p_salesrep_id
357             AND NVL (paid_flag, 'N') = 'N'
358             AND NVL (hold_flag, 'N') = 'N'
359             AND incentive_type_code IN ('COMMISSION', 'BONUS')
360             AND quota_id = p_quota_id
361             --R12
362             AND org_id = p_org_id;
363 
364       l_earn                        NUMBER;
365 
366       -- 12/25/02 RC bug 2710066
367       CURSOR get_wksht_nullqid
368       IS
369          SELECT NVL (SUM (NVL (pmt_amount_calc, 0)), 0) earn_amount
370            FROM cn_payment_worksheets
371           WHERE payrun_id = p_payrun_id
372           AND salesrep_id = p_salesrep_id
373           AND quota_id IS NULL;
374 
375       l_wksht_null_earn             NUMBER;
376 
377       CURSOR get_wksht_notnullqid
378       IS
379          SELECT NVL (SUM (NVL (pmt_amount_calc, 0)), 0) earn_amount
380            FROM cn_payment_worksheets
381           WHERE payrun_id = p_payrun_id
382           AND salesrep_id = p_salesrep_id AND quota_id IS NOT NULL
383           AND org_id = p_org_id;
384 
385       l_wksht_not_null_earn         NUMBER;
386       l_delta_earn                  NUMBER;
387       pmt_trans_rec                 get_pmt_trans%ROWTYPE;
388 
389       -- get the worksheet when waive the recovery
390       CURSOR get_wksht (
391          p_payrun_id                         cn_payment_transactions.payrun_id%TYPE,
392          p_salesrep_id                       cn_payment_transactions.credited_salesrep_id%TYPE,
393          p_quota_id                          cn_payment_transactions.quota_id%TYPE
394       )
395       IS
396          SELECT *
397            FROM cn_payment_worksheets
398           WHERE payrun_id = p_payrun_id
399             AND salesrep_id = p_salesrep_id
400             AND quota_id = p_quota_id
401             AND EXISTS (
402                    SELECT 1
403                      FROM cn_payment_transactions
404                     WHERE payrun_id = p_payrun_id
405                       AND credited_salesrep_id = p_salesrep_id
406                       AND quota_id = p_quota_id
407                       AND NVL (waive_flag, 'N') = 'N'
408                       AND incentive_type_code <> 'PMTPLN');
409 
410       CURSOR get_payment_worksheet (
411          p_quota_id                          cn_payment_transactions.quota_id%TYPE
412       )
413       IS
414          SELECT *
415            FROM cn_payment_worksheets
416           WHERE salesrep_id = p_salesrep_id
417           AND quota_id = p_quota_id
418           AND payrun_id = p_payrun_id;
419 
420       -- Bug 2795606 : use amount since get_cp will handle adj amt
421       CURSOR get_mpa (
422          p_quota_id                          cn_payment_transactions.quota_id%TYPE
423       )
424       IS
425          SELECT NVL (SUM (NVL (amount, 0)), 0) mpa_amount
426            FROM cn_payment_transactions
427           WHERE credited_salesrep_id = p_salesrep_id
428             AND quota_id = p_quota_id
429             AND payrun_id = p_payrun_id
430             AND incentive_type_code = 'MANUAL_PAY_ADJ' ;
431 
432       l_mpa                         NUMBER;
433 
434       CURSOR get_cp (
435          p_quota_id                          cn_payment_transactions.quota_id%TYPE
436       )
437       IS
438          SELECT NVL (SUM (NVL (payment_amount, 0) - NVL (amount, 0)), 0) cp_amount
439            FROM cn_payment_transactions
440           WHERE credited_salesrep_id = p_salesrep_id
441             AND quota_id = p_quota_id
442             AND payrun_id = p_payrun_id
443             AND incentive_type_code NOT IN ('PMTPLN', 'PMTPLN_REC')
444             AND hold_flag <> 'Y'
445             ;
446 
447       l_cp                          NUMBER;
448 
449       -- (3) get payment holds
450       CURSOR get_ph (
451          p_quota_id                          cn_payment_transactions.quota_id%TYPE
452       )
453       IS
454          SELECT NVL (SUM (NVL (payment_amount, 0)), 0) ph_amount
455            FROM cn_payment_transactions
456           WHERE credited_salesrep_id = p_salesrep_id
457           AND quota_id = p_quota_id
458           AND payrun_id = p_payrun_id
459           AND hold_flag = 'Y'
460           ;
461 
462       l_ph                          NUMBER;
463 
464       -- (4) get waive = nrec
465       --bug 3114349, issue 3.  Added quota_id as a parameter.
466       CURSOR get_wv (
467          p_quota_id                          cn_payment_transactions.quota_id%TYPE
468       )
469       IS
470          SELECT -NVL (SUM (NVL (payment_amount, 0)), 0) wv_amount
471            FROM cn_payment_transactions
472           WHERE credited_salesrep_id = p_salesrep_id
473             -- AND quota_id is null
474             AND payrun_id = p_payrun_id
475             AND waive_flag = 'Y'
476             AND quota_id = p_quota_id
477             ;
478 
479       l_wv                          NUMBER;
480 
481       --fix for bug: 2848235
482       CURSOR get_pmt_trans_amt (
483          p_quota_id                          cn_payment_transactions.quota_id%TYPE
484       )
485       IS
486          SELECT NVL (SUM (NVL (amount, 0)), 0) amount,
487                 NVL (SUM (NVL (payment_amount, 0)), 0) payment_amount
488            FROM cn_payment_transactions
489           WHERE credited_salesrep_id = p_salesrep_id
490             AND quota_id = p_quota_id
491             AND payrun_id = p_payrun_id
492             AND (hold_flag = 'N' OR hold_flag IS NULL)
493             AND incentive_type_code IN ('COMMISSION', 'BONUS')
494             ;
495 
496       pmt_trans_rec_amount          get_pmt_trans_amt%ROWTYPE;
497 
498       --bug 3114349, issue 3.
499       CURSOR get_waive_quota_id (
500          p_payrun_id                         cn_payruns.payrun_id%TYPE,
501          p_salesrep_id                       cn_payment_transactions.credited_salesrep_id%TYPE
502       )
503       IS
504          SELECT   -NVL (SUM (NVL (payment_amount, 0)), 0) payment_amount,
505                   quota_id
506              FROM cn_payment_transactions
507             WHERE payrun_id = p_payrun_id
508               AND credited_salesrep_id = p_salesrep_id
509               AND credit_type_id = -1000
510               AND incentive_type_code = 'PMTPLN_REC'
511               GROUP BY quota_id;
512 
513       CURSOR get_waive_flag (
514          p_payrun_id                         cn_payruns.payrun_id%TYPE,
515          p_salesrep_id                       cn_payment_transactions.credited_salesrep_id%TYPE
516       )
517       IS
518          SELECT NVL (waive_flag, 'N') waive_flag,
519                 object_version_number ovn
520            FROM cn_payment_transactions
521           WHERE payrun_id = p_payrun_id
522             AND credited_salesrep_id = p_salesrep_id
523             AND credit_type_id = -1000
524             AND incentive_type_code = 'PMTPLN_REC'
525             AND ROWNUM < 2;
526 
527       l_waive_flag                  cn_payment_transactions.waive_flag%TYPE;
528       l_waive_flag_db               cn_payment_transactions.waive_flag%TYPE;
529       l_change_waive_flag           NUMBER;
530       l_waive_amount                NUMBER;
531       l_waive_amount_total          NUMBER;
532       l_waive_factor                NUMBER;
533    BEGIN
534       --
535       -- Standard Start of API savepoint
536       --
537       SAVEPOINT update_pmt_transactions;
538 
539       --
540       -- Standard call to check for call compatibility.
541       --
542       IF NOT fnd_api.compatible_api_call (l_api_version, p_api_version, l_api_name, g_pkg_name)
543       THEN
544          RAISE fnd_api.g_exc_unexpected_error;
545       END IF;
546 
547       --
548       -- Initialize message list if p_init_msg_list is set to TRUE.
549       --
550       IF fnd_api.to_boolean (p_init_msg_list)
551       THEN
552          fnd_msg_pub.initialize;
553       END IF;
554 
555       --
556       --  Initialize API return status to success
557       --
558       x_return_status := fnd_api.g_ret_sts_success;
559       x_loading_status := 'UPDATED';
560 
561       --
562       -- API body
563       --
564       -- check the payrun status and valid payrun
565       IF cn_api.chk_payrun_status_paid (
566              p_payrun_id => p_payrun_id,
567              p_loading_status => x_loading_status,
568              x_loading_status => x_loading_status) = fnd_api.g_true
569       THEN
570          RAISE fnd_api.g_exc_error;
571       END IF;
572 
573       -- check the salesrep id is valid and not on HOLD
574       IF cn_api.chk_srp_hold_status (p_salesrep_id         => p_salesrep_id,
575                                      --R12
576                                      p_org_id              => p_org_id,
577                                      p_loading_status      => x_loading_status,
578                                      x_loading_status      => x_loading_status
579                                     ) = fnd_api.g_true
580       THEN
581          RAISE fnd_api.g_exc_error;
582       END IF;
583 
584       -- Check worksheet status
585       IF cn_api.chk_worksheet_status (p_payrun_id           => p_payrun_id,
586                                       p_salesrep_id         => p_salesrep_id,
587                                       --R12
588                                       p_org_id              => p_org_id,
589                                       p_loading_status      => x_loading_status,
590                                       x_loading_status      => x_loading_status
591                                      ) = fnd_api.g_true
592       THEN
593          RAISE fnd_api.g_exc_error;
594       END IF;
595 
596       -- R12: obtain pay_by_mode from the payrun
597       l_pbt_profile_value := cn_payment_security_pvt.get_pay_by_mode(p_payrun_id) ;
598 
599 
600       -- Valid Flag Passed
601       -- Check Waive_flag Flag must be Y/N
602       IF p_waive_flag NOT IN ('Y', 'N') AND p_incentive_type_code = 'PMTPLN_REC'
603       THEN
604          IF fnd_msg_pub.check_msg_level (fnd_msg_pub.g_msg_lvl_error)
605          THEN
606             fnd_message.set_name ('CN', 'CN_INVALID_WAIVE_FLAG');
607             fnd_msg_pub.ADD;
608          END IF;
609 
610          x_loading_status := 'CN_INVALID_WAIVE_FLAG';
611          RAISE fnd_api.g_exc_error;
612       END IF;
613 
614       -- Check Recoverable Flag must be Y/N
615       IF p_recoverable_flag NOT IN ('Y', 'N') AND p_incentive_type_code = 'MANUAL_PAY_ADJ'
616       THEN
617          IF fnd_msg_pub.check_msg_level (fnd_msg_pub.g_msg_lvl_error)
618          THEN
619             fnd_message.set_name ('CN', 'CN_INVALID_RECOVERABLE_FLAG');
620             fnd_msg_pub.ADD;
621          END IF;
622 
623          x_loading_status := 'CN_INVALID_RECOVERABLE_FLAG';
624          RAISE fnd_api.g_exc_error;
625       END IF;
626 
627       --
628       -- Get worksheet earnings for NULL quota id
629       --
630       FOR earn IN get_wksht_notnullqid
631       LOOP
632          l_wksht_not_null_earn := earn.earn_amount;
633       END LOOP;
634 
635       --
636       -- Get worksheet earnings for NOT NULL quota id
637       --
638       FOR earn IN get_wksht_nullqid
639       LOOP
640          l_wksht_null_earn := earn.earn_amount;
641       END LOOP;
642 
643       l_delta_earn := l_wksht_null_earn - l_wksht_not_null_earn;
644 
645       --
646       -- Get Payment Transaction
647       --
648       IF p_payment_transaction_id IS NOT NULL
649       THEN
650          OPEN get_pmt_trans;
651 
652          FETCH get_pmt_trans
653           INTO pmt_trans_rec;
654 
655          CLOSE get_pmt_trans;
656 
657          IF pmt_trans_rec.ovn <> p_object_version_number
658          THEN
659             IF (fnd_msg_pub.check_msg_level (fnd_msg_pub.g_msg_lvl_error))
660             THEN
661                fnd_message.set_name ('CN', 'CN_RECORD_CHANGED');
662                fnd_msg_pub.ADD;
663             END IF;
664 
665             RAISE fnd_api.g_exc_error;
666          END IF;
667       END IF;
668 
669       UPDATE cn_payment_transactions
670          SET hold_flag = p_hold_flag,
671              recoverable_flag = DECODE (p_incentive_type_code, 'MANUAL_PAY_ADJ', p_recoverable_flag, 'N'),
672              -- bug 3146137
673              amount = DECODE (p_incentive_type_code, 'MANUAL_PAY_ADJ', p_payment_amount, amount),
674              payment_amount = p_payment_amount,
675              waive_flag = DECODE (p_incentive_type_code, 'PMTPLN_REC', p_waive_flag, 'N'),
676              -- bug 3080846
677              last_update_date = SYSDATE,
678              last_updated_by = fnd_global.user_id,
679              last_update_login = fnd_global.login_id,
680              object_version_number = nvl(object_version_number,1) + 1
681        WHERE payment_transaction_id = p_payment_transaction_id;
682 
683       --This if statement is for waive recovery.
684       IF p_payment_transaction_id IS NULL
685       THEN
686 
687          --bug 3114349, issue 3.
688          --Update detail waive records.
689          l_waive_amount := 0;
690          l_waive_amount_total := 0;
691 
692          --Find the value of waive flag in db.
693          FOR i IN get_waive_flag (p_payrun_id, p_salesrep_id)
694          LOOP
695             l_waive_flag_db := i.waive_flag;
696          END LOOP;
697 
698          l_change_waive_flag := 0;
699          l_waive_flag := NVL (p_waive_flag, 'N');
700 
701          IF l_waive_flag = 'Y' AND l_waive_flag_db = 'N'
702          THEN
703             l_waive_factor := 1;
704             l_change_waive_flag := 1;
705          ELSIF l_waive_flag = 'N' AND l_waive_flag_db = 'Y'
706          THEN
707             l_waive_factor := -1;
708             l_change_waive_flag := 1;
709          END IF;
710 
711          IF l_change_waive_flag = 1
712          THEN
713 
714             SELECT object_version_number
715             INTO l_wksht_ovn
716             FROM cn_payment_worksheets
717             WHERE payrun_id = p_payrun_id
718             AND salesrep_id = p_salesrep_id
719             AND quota_id IS NULL;
720 
721             IF l_wksht_ovn <> p_object_version_number
722             THEN
723                IF (fnd_msg_pub.check_msg_level (fnd_msg_pub.g_msg_lvl_error))
724                THEN
725                   fnd_message.set_name ('CN', 'CN_RECORD_CHANGED');
726                   fnd_msg_pub.ADD;
727                END IF;
728                RAISE fnd_api.g_exc_error;
729             END IF;
730 
731             FOR waive_per_quota IN get_waive_quota_id (p_payrun_id, p_salesrep_id)
732             LOOP
733                --l_waive_factor = 1 is for waive_flag changes from N to Y.
734                --l_waive_factor = -1 is for waive_flag changes from Y to N.
735                l_waive_amount := waive_per_quota.payment_amount * l_waive_factor;
736 
737                UPDATE cn_payment_worksheets
738                   SET pmt_amount_adj = NVL (pmt_amount_adj, 0) + l_waive_amount,
739                       object_version_number = object_version_number + 1,
740                       last_update_date = SYSDATE,
741                       last_updated_by = fnd_global.user_id,
742                       last_update_login = fnd_global.login_id
743                 WHERE payrun_id = p_payrun_id
744                 AND salesrep_id = p_salesrep_id
745                 AND quota_id = waive_per_quota.quota_id
746                 ;
747 
748                l_waive_amount_total := l_waive_amount_total + l_waive_amount;
749             END LOOP;
750 
751             --Update summary waive record.
752             UPDATE cn_payment_worksheets
753                SET pmt_amount_adj = NVL (pmt_amount_adj, 0) + l_waive_amount_total,
754                    object_version_number = nvl(object_version_number,0) + 1,
755                    last_update_date = SYSDATE,
756                    last_updated_by = fnd_global.user_id,
757                    last_update_login = fnd_global.login_id
758              WHERE payrun_id = p_payrun_id
759              AND salesrep_id = p_salesrep_id
760              AND quota_id IS NULL
761              ;
762          END IF;
763 
764          UPDATE cn_payment_transactions
765             SET waive_flag = p_waive_flag,
766                 object_version_number = nvl(object_version_number,0) + 1,
767                 -- bug 3080846
768                 last_update_date = SYSDATE,
769                 last_updated_by = fnd_global.user_id,
770                 last_update_login = fnd_global.login_id
771           WHERE incentive_type_code = 'PMTPLN_REC'
772           AND credited_salesrep_id = p_salesrep_id
773           AND payrun_id = p_payrun_id
774           ;
775 
776       END IF;
777 
778       --Bug Fix : 2848235
779       IF (l_pbt_profile_value = 'N' AND pmt_trans_rec.hold_flag = 'Y' AND (p_hold_flag = 'N' OR p_hold_flag IS NULL))
780       THEN
781          OPEN get_pmt_trans_amt (pmt_trans_rec.quota_id);
782 
783          FETCH get_pmt_trans_amt
784           INTO pmt_trans_rec_amount;
785 
786          CLOSE get_pmt_trans_amt;
787 
788          DELETE FROM cn_payment_transactions
789                WHERE payment_transaction_id IN (
790                         SELECT payment_transaction_id
791                           FROM cn_payment_transactions
792                          WHERE quota_id = pmt_trans_rec.quota_id
793                            AND payrun_id = p_payrun_id
794                            AND credited_salesrep_id = p_salesrep_id
795                            AND (hold_flag = 'N' OR hold_flag IS NULL)
796                            AND incentive_type_code IN ('COMMISSION', 'BONUS')
797                            )
798                  AND payment_transaction_id <> p_payment_transaction_id;
799 
800          UPDATE cn_payment_transactions
801             SET amount = pmt_trans_rec_amount.amount,
802                 payment_amount = pmt_trans_rec_amount.payment_amount,
803                 object_version_number = object_version_number + 1,
804                 -- bug 3080846
805                 last_update_date = SYSDATE,
806                 last_updated_by = fnd_global.user_id,
807                 last_update_login = fnd_global.login_id
808           WHERE payment_transaction_id = p_payment_transaction_id
809             AND payrun_id = p_payrun_id
810             AND credited_salesrep_id = p_salesrep_id
811             AND (hold_flag = 'N' OR hold_flag IS NULL) ;
812 
813       END IF;
814 
815       --end of Bug fix 2848235
816       FOR worksheet IN get_payment_worksheet (pmt_trans_rec.quota_id)
817       LOOP
818          -- (1) get manual pay adjustments
819          FOR mpa IN get_mpa (worksheet.quota_id)
820          LOOP
821             l_mpa := mpa.mpa_amount;
822          END LOOP;
823 
824          -- (2) get control payments
825          FOR cp IN get_cp (worksheet.quota_id)
826          LOOP
827             l_cp := cp.cp_amount;
828          END LOOP;
829 
830          -- (3) get payment holds
831          FOR ph IN get_ph (worksheet.quota_id)
832          LOOP
833             l_ph := ph.ph_amount;
834          END LOOP;
835 
836          -- (4) get waive = nrec
837          --bug 3114349, issue 3. Added quota_id.
838          FOR wv IN get_wv (worksheet.quota_id)
839          LOOP
840             l_wv := wv.wv_amount;
841          END LOOP;
842 
843          -- (5) get worksheet earnings
844          FOR earn IN get_earnings (worksheet.quota_id)
845          LOOP
846             l_earn := earn.earn_amount;
847          END LOOP;
848 
849          -- 12/25/02 RC bug 2710066
850          UPDATE cn_payment_worksheets
851             SET pmt_amount_adj = l_wv + l_cp + l_mpa,
852                 held_amount = l_ph,
853                 pmt_amount_calc = l_earn,
854                 object_version_number = object_version_number + 1,
855                 -- bug 3080846
856                 last_update_date = SYSDATE,
857                 last_updated_by = fnd_global.user_id,
858                 last_update_login = fnd_global.login_id
859           WHERE payment_worksheet_id = worksheet.payment_worksheet_id;
860       END LOOP;
861 
862       -- updating the summary record with totals
863       UPDATE cn_payment_worksheets
864          SET pmt_amount_adj =
865                 (SELECT NVL (SUM (NVL (pmt_amount_adj, 0)), 0)
866                    FROM cn_payment_worksheets
867                   WHERE quota_id IS NOT NULL
868                     AND salesrep_id = pmt_trans_rec.credited_salesrep_id
869                     AND payrun_id = pmt_trans_rec.payrun_id
870                     ),
871              held_amount =
872                 (SELECT NVL (SUM (NVL (held_amount, 0)), 0)
873                    FROM cn_payment_worksheets
874                   WHERE quota_id IS NOT NULL
875                     AND salesrep_id = pmt_trans_rec.credited_salesrep_id
876                     AND payrun_id = pmt_trans_rec.payrun_id
877                     ),
878              pmt_amount_calc =
879                 (SELECT l_delta_earn + NVL (SUM (NVL (pmt_amount_calc, 0)), 0)
880                    FROM cn_payment_worksheets
881                   WHERE quota_id IS NOT NULL
882                     AND salesrep_id = pmt_trans_rec.credited_salesrep_id
883                     AND payrun_id = pmt_trans_rec.payrun_id
884                     ),
885              object_version_number = object_version_number + 1,
886              -- bug 3080846
887              last_update_date = SYSDATE,
888              last_updated_by = fnd_global.user_id,
889              last_update_login = fnd_global.login_id
890        WHERE quota_id IS NULL
891          AND salesrep_id = pmt_trans_rec.credited_salesrep_id
892          AND payrun_id = pmt_trans_rec.payrun_id
893          AND org_id = p_org_id;
894 
895       --Need to pass back the ovn.
896       IF p_payment_transaction_id IS NOT NULL
897       THEN
898          SELECT object_version_number
899            INTO p_object_version_number
900            FROM cn_payment_transactions
901           WHERE payment_transaction_id = p_payment_transaction_id;
902 
903       -- when waiving recovery on all trxns
904       ELSIF p_payment_transaction_id IS NULL
905       THEN
906          SELECT object_version_number
907            INTO p_object_version_number
908            FROM cn_payment_worksheets
909           WHERE payrun_id = p_payrun_id
910             AND salesrep_id = p_salesrep_id
911             AND quota_id IS NULL;
912       END IF;
913 
914       -- End of API body.
915       -- Standard check of p_commit.
916       IF fnd_api.to_boolean (p_commit)
917       THEN
918          COMMIT WORK;
919       END IF;
920 
921       -- Standard call to get message count and if count is 1, get message info.
922       fnd_msg_pub.count_and_get (p_count => x_msg_count, p_data => x_msg_data, p_encoded => fnd_api.g_false);
923    EXCEPTION
924       WHEN fnd_api.g_exc_error
925       THEN
926          ROLLBACK TO update_pmt_transactions;
927          x_return_status := fnd_api.g_ret_sts_error;
928          fnd_msg_pub.count_and_get (p_count => x_msg_count, p_data => x_msg_data, p_encoded => fnd_api.g_false);
929       WHEN fnd_api.g_exc_unexpected_error
930       THEN
931          ROLLBACK TO update_pmt_transactions;
932          x_loading_status := 'UNEXPECTED_ERR';
933          x_return_status := fnd_api.g_ret_sts_unexp_error;
934          fnd_msg_pub.count_and_get (p_count => x_msg_count, p_data => x_msg_data, p_encoded => fnd_api.g_false);
935       WHEN OTHERS
936       THEN
937          ROLLBACK TO update_pmt_transactions;
938          x_loading_status := 'UNEXPECTED_ERR';
939          x_return_status := fnd_api.g_ret_sts_unexp_error;
940 
941          IF fnd_msg_pub.check_msg_level (fnd_msg_pub.g_msg_lvl_unexp_error)
942          THEN
943             fnd_msg_pub.add_exc_msg (g_pkg_name, l_api_name);
944          END IF;
945 
946          fnd_msg_pub.count_and_get (p_count => x_msg_count, p_data => x_msg_data, p_encoded => fnd_api.g_false);
947    END update_pmt_transactions;
948 
949 
950 --=====================================================================
951 --Procedure Name:Create_Pmt_Transaction
952 --Description: used to Create the Manual Payment Transaction Record
953 --=====================================================================
954    PROCEDURE create_pmt_transactions (
955       p_api_version              IN       NUMBER,
956       p_init_msg_list            IN       VARCHAR2,
957       p_commit                   IN       VARCHAR2,
958       p_validation_level         IN       NUMBER,
959       p_payrun_id                IN       NUMBER,
960       p_salesrep_id              IN       NUMBER,
961       p_incentive_type_code      IN       VARCHAR2,
962       p_recoverable_flag         IN       VARCHAR2,
963       p_payment_amount           IN       NUMBER,
964       p_quota_id                 IN       NUMBER,
965       p_org_id                   IN       cn_payment_transactions.org_id%TYPE,
966       p_object_version_number    IN       cn_payment_transactions.object_version_number%TYPE,
967       x_pmt_transaction_id       OUT NOCOPY NUMBER,
968       x_status                   OUT NOCOPY VARCHAR2,
969       x_loading_status           OUT NOCOPY VARCHAR2,
970       x_return_status            OUT NOCOPY VARCHAR2,
971       x_msg_count                OUT NOCOPY NUMBER,
972       x_msg_data                 OUT NOCOPY VARCHAR2
973    )
974    IS
975       l_api_name           CONSTANT VARCHAR2 (30) := 'Create_Payment_Transaction';
976       l_api_version        CONSTANT NUMBER := 1.0;
977       l_exist                       VARCHAR2 (02);
978       l_incentive_type              cn_lookups.meaning%TYPE;
979       l_pay_period_id               NUMBER;
980       l_posting_batch_id            NUMBER;
981       l_rec_amount                  NUMBER := 0;
982       l_nrec_amount                 NUMBER := 0;
983       l_pay_date                    DATE;
984       l_pay_element_type_id         cn_payment_transactions.pay_element_type_id%TYPE;
985       l_rowid                       VARCHAR2 (100);
986       l_quota_id                    NUMBER;
987       l_pmt_trans_rec               cn_pmt_trans_pkg.pmt_trans_rec_type;
988       l_batch_rec                   cn_prepostbatches.posting_batch_rec_type;
989       --Bug 3866089 (the same as 11.5.8 bug 3841926, 11.5.10 3866116) by Julia Huang on 9/1/04.
990       l_payables_flag               cn_repositories.payables_flag%TYPE;
991       l_pmt_tran_id                 cn_payment_transactions.payment_transaction_id%TYPE;
992 
993       CURSOR get_apps
994       IS
995          SELECT payables_flag
996            FROM cn_repositories
997           --R12
998          WHERE  org_id = p_org_id;
999 
1000       -- Payrun Curs
1001       CURSOR get_payrun
1002       IS
1003          SELECT pay_period_id,
1004                 pay_date
1005            FROM cn_payruns
1006           WHERE payrun_id = p_payrun_id
1007           AND status = 'UNPAID';
1008 
1009    BEGIN
1010       --
1011       -- Standard Start of API savepoint
1012       --
1013       SAVEPOINT create_pmt_transactions;
1014 
1015       --
1016       -- Standard call to check for call compatibility.
1017       --
1018       IF NOT fnd_api.compatible_api_call (l_api_version, p_api_version, l_api_name, g_pkg_name)
1019       THEN
1020          RAISE fnd_api.g_exc_unexpected_error;
1021       END IF;
1022 
1023       --
1024       -- Initialize message list if p_init_msg_list is set to TRUE.
1025       --
1026       IF fnd_api.to_boolean (p_init_msg_list)
1027       THEN
1028          fnd_msg_pub.initialize;
1029       END IF;
1030 
1031       --
1032       --  Initialize API return status to success
1033       --
1034       x_return_status := fnd_api.g_ret_sts_success;
1035       x_loading_status := 'CN_INSERTED';
1036 
1037       -- Mandatory parameters check for payrun_id, salesrep_id
1038       IF ((cn_api.chk_miss_null_num_para (p_num_para            => p_payrun_id,
1039                                           p_obj_name            => cn_api.get_lkup_meaning ('PAY_RUN_NAME', 'PAY_RUN_VALIDATION_TYPE'),
1040                                           p_loading_status      => x_loading_status,
1041                                           x_loading_status      => x_loading_status
1042                                          )
1043           ) = fnd_api.g_true
1044          )
1045       THEN
1046          RAISE fnd_api.g_exc_error;
1047       END IF;
1048 
1049       IF ((cn_api.chk_miss_null_num_para (p_num_para            => p_salesrep_id,
1050                                           p_obj_name            => cn_api.get_lkup_meaning ('SALES_PERSON', 'PAY_RUN_VALIDATION_TYPE'),
1051                                           p_loading_status      => x_loading_status,
1052                                           x_loading_status      => x_loading_status
1053                                          )
1054           ) = fnd_api.g_true
1055          )
1056       THEN
1057          RAISE fnd_api.g_exc_error;
1058       END IF;
1059 
1060       -- check Incentive Type Code
1061       IF ((cn_api.chk_null_char_para (p_char_para           => p_incentive_type_code,
1062                                       p_obj_name            => cn_api.get_lkup_meaning ('INCENTIVE_TYPE', 'PAY_RUN_VALIDATION_TYPE'),
1063                                       p_loading_status      => x_loading_status,
1064                                       x_loading_status      => x_loading_status
1065                                      )
1066           ) = fnd_api.g_true
1067          )
1068       THEN
1069          RAISE fnd_api.g_exc_error;
1070       END IF;
1071 
1072       -- Check Recoverable Flag must be Y/N
1073       IF p_recoverable_flag NOT IN ('Y', 'N')
1074       THEN
1075          IF fnd_msg_pub.check_msg_level (fnd_msg_pub.g_msg_lvl_error)
1076          THEN
1077             fnd_message.set_name ('CN', 'CN_INVALID_RECOVERABLE_FLAG');
1078             fnd_msg_pub.ADD;
1079          END IF;
1080 
1081          x_loading_status := 'CN_INVALID_RECOVERABLE_FLAG';
1082          RAISE fnd_api.g_exc_error;
1083       END IF;
1084 
1085       -- Check/Valid Incentive Type
1086       IF (p_incentive_type_code NOT IN ('MANUAL_PAY_ADJ'))
1087       THEN
1088          IF fnd_msg_pub.check_msg_level (fnd_msg_pub.g_msg_lvl_error)
1089          THEN
1090             fnd_message.set_name ('CN', 'CN_INVALID_INCENTIVE_TYPE');
1091             fnd_msg_pub.ADD;
1092          END IF;
1093 
1094          x_loading_status := 'CN_INVALID_INCENTIVE_TYPE';
1095          RAISE fnd_api.g_exc_error;
1096       END IF;
1097 
1098       -- check the payrun status and valid payrun
1099       IF cn_api.chk_payrun_status_paid (
1100               p_payrun_id      => p_payrun_id,
1101               p_loading_status => x_loading_status,
1102               x_loading_status => x_loading_status) =  fnd_api.g_true
1103       THEN
1104          RAISE fnd_api.g_exc_error;
1105       END IF;
1106 
1107       -- check the salesrep id is valid and not on HOLD
1108       IF cn_api.chk_srp_hold_status (p_salesrep_id         => p_salesrep_id,
1109                                      --R12
1110                                      p_org_id              => p_org_id,
1111                                      p_loading_status      => x_loading_status,
1112                                      x_loading_status      => x_loading_status
1113                                     ) = fnd_api.g_true
1114       THEN
1115          RAISE fnd_api.g_exc_error;
1116       END IF;
1117 
1118       -- Check Worksheet Status
1119       IF cn_api.chk_worksheet_status (p_payrun_id           => p_payrun_id,
1120                                       p_salesrep_id         => p_salesrep_id,
1121                                       --R12
1122                                       p_org_id              => p_org_id,
1123                                       p_loading_status      => x_loading_status,
1124                                       x_loading_status      => x_loading_status
1125                                      ) = fnd_api.g_true
1126       THEN
1127          RAISE fnd_api.g_exc_error;
1128       END IF;
1129 
1130       -- Check Quota ID
1131       IF p_quota_id IS NULL
1132       THEN
1133          IF fnd_msg_pub.check_msg_level (fnd_msg_pub.g_msg_lvl_error)
1134          THEN
1135             fnd_message.set_name ('CN', 'CN_QUOTA_NOT_EXISTS');
1136             fnd_msg_pub.ADD;
1137          END IF;
1138 
1139          x_loading_status := 'CN_QUOTA_NOT_EXISTS';
1140          RAISE fnd_api.g_exc_error;
1141       END IF;
1142 
1143       -- Check Valid Quota ID
1144       BEGIN
1145          SELECT quota_id
1146            INTO l_quota_id
1147            FROM cn_quotas_v
1148           WHERE quota_id = p_quota_id;
1149       EXCEPTION
1150          WHEN NO_DATA_FOUND
1151          THEN
1152             IF fnd_msg_pub.check_msg_level (fnd_msg_pub.g_msg_lvl_error)
1153             THEN
1154                fnd_message.set_name ('CN', 'CN_QUOTA_NOT_EXISTS');
1155                fnd_msg_pub.ADD;
1156             END IF;
1157 
1158             x_loading_status := 'CN_QUOTA_NOT_EXISTS';
1159             RAISE fnd_api.g_exc_error;
1160       END;
1161 
1162       -- get pay period id and Pay Date
1163       OPEN get_payrun;
1164 
1165       FETCH get_payrun
1166        INTO l_pay_period_id,
1167             l_pay_date;
1168 
1169       CLOSE get_payrun;
1170 
1171       -- Bug 2880233: manual adj has quota_id, use assigned quota_id
1172       l_pay_element_type_id := cn_api.get_pay_element_id (p_quota_id, p_salesrep_id, p_org_id, l_pay_date);
1173       -- Create the Record in cn_posting_batches
1174       cn_prepostbatches.get_uid (l_posting_batch_id);
1175       l_batch_rec.posting_batch_id := l_posting_batch_id;
1176       l_batch_rec.NAME := 'MANUAL_PAY_ADJ batch number:' || p_payrun_id || ':' || p_salesrep_id || ':' || l_posting_batch_id;
1177       l_batch_rec.created_by := fnd_global.user_id;
1178       l_batch_rec.creation_date := SYSDATE;
1179       l_batch_rec.last_updated_by := fnd_global.user_id;
1180       l_batch_rec.last_update_date := SYSDATE;
1181       l_batch_rec.last_update_login := fnd_global.login_id;
1182       -- call table handler
1183       cn_prepostbatches.begin_record (x_operation              => 'INSERT',
1184                                       x_rowid                  => l_rowid,
1185                                       x_posting_batch_rec      => l_batch_rec,
1186                                       x_program_type           => NULL,
1187                                       p_org_id                 => p_org_id
1188                                      );
1189       l_pmt_trans_rec.posting_batch_id := l_posting_batch_id;
1190       l_pmt_trans_rec.incentive_type_code := 'MANUAL_PAY_ADJ';
1191       l_pmt_trans_rec.credit_type_id := g_credit_type_id;
1192       l_pmt_trans_rec.payrun_id := p_payrun_id;
1193       l_pmt_trans_rec.credited_salesrep_id := p_salesrep_id;
1194       l_pmt_trans_rec.payee_salesrep_id := p_salesrep_id;
1195       l_pmt_trans_rec.quota_id := p_quota_id;
1196       l_pmt_trans_rec.pay_period_id := l_pay_period_id;
1197       l_pmt_trans_rec.hold_flag := 'N';
1198       l_pmt_trans_rec.waive_flag := 'N';
1199       l_pmt_trans_rec.paid_flag := 'N';
1200       l_pmt_trans_rec.recoverable_flag := NVL (p_recoverable_flag, 'N');
1201       l_pmt_trans_rec.pay_element_type_id := l_pay_element_type_id;
1202       l_pmt_trans_rec.amount := p_payment_amount;
1203       l_pmt_trans_rec.payment_amount := p_payment_amount;
1204       --R12
1205       l_pmt_trans_rec.org_id := p_org_id;
1206       l_pmt_trans_rec.object_version_number := 1;
1207       -- Call Table hander to Insert Payment Transactions
1208       cn_pmt_trans_pkg.INSERT_RECORD (p_tran_rec => l_pmt_trans_rec);
1209       --  Bug 3866089 (the same as 11.5.8 bug 3841926, 11.5.10 3866116) by jjhuang on 11/1/04
1210       l_pmt_tran_id := cn_pmt_trans_pkg.get_pmt_tran_id;
1211       x_pmt_transaction_id := l_pmt_tran_id ;
1212 
1213       -- Update the payment Worksheets based on the recoverable flag
1214       IF NVL (p_recoverable_flag, 'N') = 'N'
1215       THEN
1216          l_nrec_amount := NVL (p_payment_amount, 0);
1217       ELSE
1218          l_rec_amount := NVL (p_payment_amount, 0);
1219       END IF;
1220 
1221       -- Update the Worksheet
1222       UPDATE cn_payment_worksheets
1223          SET pmt_amount_adj = NVL (pmt_amount_adj, 0) + NVL (l_rec_amount, 0) + NVL (l_nrec_amount, 0),
1224              last_updated_by = fnd_global.user_id,
1225              last_update_date = SYSDATE,
1226              last_update_login = fnd_global.login_id,
1227              object_version_number = NVL(object_version_number+1,1)
1228        WHERE salesrep_id = p_salesrep_id
1229          AND payrun_id = p_payrun_id
1230          AND quota_id = p_quota_id
1231          ;
1232 
1233       IF SQL%NOTFOUND
1234       THEN
1235          cn_payment_worksheets_pkg.INSERT_RECORD (x_payrun_id                  => p_payrun_id,
1236                                                   x_salesrep_id                => p_salesrep_id,
1237                                                   x_quota_id                   => p_quota_id,
1238                                                   x_credit_type_id             => g_credit_type_id,
1239                                                   x_calc_pmt_amount            => 0,
1240                                                   x_adj_pmt_amount_rec         => 0,
1241                                                   x_adj_pmt_amount_nrec        => 0,
1242                                                   x_adj_pmt_amount             => l_rec_amount + l_nrec_amount,
1243                                                   x_pmt_amount_recovery        => 0,
1244                                                   x_worksheet_status           => 'UNPAID',
1245                                                   x_created_by                 => fnd_global.user_id,
1246                                                   x_creation_date              => SYSDATE,
1247                                                   p_org_id                     => p_org_id,
1248                                                   p_object_version_number      => 1
1249                                                  );
1250       END IF;
1251 
1252       -- Update the Summary Record.
1253       UPDATE cn_payment_worksheets
1254          SET pmt_amount_adj = NVL (pmt_amount_adj, 0) + NVL (l_rec_amount, 0) + NVL (l_nrec_amount, 0),
1255              last_updated_by = fnd_global.user_id,
1256              last_update_date = SYSDATE,
1257              last_update_login = fnd_global.login_id,
1258              object_version_number = NVL(object_version_number+1,1)
1259        WHERE salesrep_id = p_salesrep_id
1260        AND payrun_id = p_payrun_id
1261        AND quota_id IS NULL
1262        ;
1263 
1264       --Bug 3866089 (the same as 11.5.8 bug 3841926, 11.5.10 3866116) by Julia Huang on 9/1/04.
1265       --For AP integration population of account
1266       OPEN get_apps;
1267 
1268       FETCH get_apps
1269        INTO l_payables_flag;
1270 
1271       CLOSE get_apps;
1272 
1273       IF l_payables_flag = 'Y'
1274       THEN
1275          -- Populate ccid's in payment worksheets
1276          -- Bug 3866089 (the same as 11.5.8 bug 3841926, 11.5.10 3866116) by jjhuang on 11/1/04
1277          IF (cn_payrun_pvt.populate_ccids
1278                                (p_payrun_id           => p_payrun_id,
1279                                 p_salesrep_id         => p_salesrep_id,
1280                                 p_pmt_tran_id         => l_pmt_tran_id,
1281                                 p_loading_status      => x_loading_status,
1282                                 x_loading_status      => x_loading_status
1283                                )
1284             ) = fnd_api.g_true
1285          THEN
1286             RAISE fnd_api.g_exc_unexpected_error;
1287          END IF;
1288       END IF;
1289 
1290       -- End of API body.
1291       -- Standard check of p_commit.
1292       IF fnd_api.to_boolean (p_commit)
1293       THEN
1294          COMMIT WORK;
1295       END IF;
1296 
1297       -- Standard call to get message count and if count is 1, get message info.
1298       fnd_msg_pub.count_and_get (p_count => x_msg_count, p_data => x_msg_data, p_encoded => fnd_api.g_false);
1299    EXCEPTION
1300       WHEN fnd_api.g_exc_error
1301       THEN
1302          ROLLBACK TO create_pmt_transactions;
1303          x_return_status := fnd_api.g_ret_sts_error;
1304          fnd_msg_pub.count_and_get (p_count => x_msg_count, p_data => x_msg_data, p_encoded => fnd_api.g_false);
1305       WHEN fnd_api.g_exc_unexpected_error
1306       THEN
1307          ROLLBACK TO create_pmt_transactions;
1308          x_loading_status := 'UNEXPECTED_ERR';
1309          x_return_status := fnd_api.g_ret_sts_unexp_error;
1310          fnd_msg_pub.count_and_get (p_count => x_msg_count, p_data => x_msg_data, p_encoded => fnd_api.g_false);
1311       WHEN OTHERS
1312       THEN
1313          ROLLBACK TO create_pmt_transactions;
1314          x_loading_status := 'UNEXPECTED_ERR';
1315          x_return_status := fnd_api.g_ret_sts_unexp_error;
1316 
1317          IF fnd_msg_pub.check_msg_level (fnd_msg_pub.g_msg_lvl_unexp_error)
1318          THEN
1319             fnd_msg_pub.add_exc_msg (g_pkg_name, l_api_name);
1320          END IF;
1321 
1322          fnd_msg_pub.count_and_get (p_count => x_msg_count, p_data => x_msg_data, p_encoded => fnd_api.g_false);
1323    END create_pmt_transactions;
1324 
1325 --=====================================================================
1326 --Procedure Name:Delete_Pmt_Transactions
1327 --Description: Used to delete the Manual Payment Transaction Record
1328 --=====================================================================
1329    PROCEDURE delete_pmt_transactions (
1330       p_api_version              IN       NUMBER,
1331       p_init_msg_list            IN       VARCHAR2,
1332       p_commit                   IN       VARCHAR2,
1333       p_validation_level         IN       NUMBER,
1334       x_return_status            OUT NOCOPY VARCHAR2,
1335       x_msg_count                OUT NOCOPY NUMBER,
1336       x_msg_data                 OUT NOCOPY VARCHAR2,
1337       p_payment_transaction_id   IN       NUMBER,
1338       p_validation_only          IN       VARCHAR2,
1339       x_status                   OUT NOCOPY VARCHAR2,
1340       x_loading_status           OUT NOCOPY VARCHAR2,
1341       p_ovn                      IN       NUMBER
1342    )
1343    IS
1344       l_api_name           CONSTANT VARCHAR2 (30) := 'Delete_Pmt_Transactions';
1345       l_api_version        CONSTANT NUMBER := 1.0;
1346 
1347       -- cursor to get the payment transaction to
1348       -- update the payment worksheets
1349       CURSOR get_pmt_trans
1350       IS
1351          SELECT payrun_id,
1352                 credited_salesrep_id,
1353                 payment_amount,
1354                 incentive_type_code,
1355                 recoverable_flag,
1356                 posting_batch_id,
1357                 quota_id,
1358                 org_id,
1359                 object_version_number ovn
1360            FROM cn_payment_transactions
1361           WHERE payment_transaction_id = p_payment_transaction_id;
1362 
1363       trans_rec                     get_pmt_trans%ROWTYPE;
1364       l_adj_rec                     NUMBER := 0;
1365       l_adj_nrec                    NUMBER := 0;
1366       --R12 for OA.
1367       l_validation_only             VARCHAR2 (1);
1368    BEGIN
1369       --
1370       -- Standard Start of API savepoint
1371       --
1372       SAVEPOINT delete_pmt_transactions;
1373 
1374       --
1375       -- Standard call to check for call compatibility.
1376       --
1377       IF NOT fnd_api.compatible_api_call (l_api_version, p_api_version, l_api_name, g_pkg_name)
1378       THEN
1379          RAISE fnd_api.g_exc_unexpected_error;
1380       END IF;
1381 
1382       --
1383       -- Initialize message list if p_init_msg_list is set to TRUE.
1384       --
1385       IF fnd_api.to_boolean (p_init_msg_list)
1386       THEN
1387          fnd_msg_pub.initialize;
1388       END IF;
1389 
1390       --
1391       --  Initialize API return status to success
1392       --
1393       x_return_status := fnd_api.g_ret_sts_success;
1394       x_loading_status := 'CN_DELETED';
1395       --R12 for OA.  When p_validation_only = 'Y', only do validation for delete from OA.
1396       --Otherwise, do delete_pmt_transactions.
1397       l_validation_only := NVL (p_validation_only, 'N');
1398 
1399       --
1400       -- get the Payment Transactions
1401       --
1402       OPEN get_pmt_trans;
1403 
1404       FETCH get_pmt_trans
1405        INTO trans_rec;
1406 
1407       CLOSE get_pmt_trans;
1408 
1409       -- check deleting Allowed.
1410       -- Delete allowed only on Manual Transactions
1411       IF trans_rec.incentive_type_code <> 'MANUAL_PAY_ADJ'
1412       THEN
1413          IF fnd_msg_pub.check_msg_level (fnd_msg_pub.g_msg_lvl_error)
1414          THEN
1415             fnd_message.set_name ('CN', 'CN_PMT_TRAN_DEL_NOT_ALLOWED');
1416             fnd_msg_pub.ADD;
1417          END IF;
1418 
1419          x_loading_status := 'CN_PMT_TRAN_DEL_NOT_ALLOWED';
1420          RAISE fnd_api.g_exc_error;
1421       END IF;
1422 
1423       -- check the payrun status
1424       -- check the payrun ID is valid
1425       -- if payrun status <> UNPAID you cannot delete Transactions
1426       IF cn_api.chk_payrun_status_paid (p_payrun_id           => trans_rec.payrun_id, p_loading_status => x_loading_status,
1427                                         x_loading_status      => x_loading_status) = fnd_api.g_true
1428       THEN
1429          RAISE fnd_api.g_exc_error;
1430       END IF;
1431 
1432       IF cn_api.chk_worksheet_status (p_payrun_id           => trans_rec.payrun_id,
1433                                       p_salesrep_id         => trans_rec.credited_salesrep_id,
1434                                       p_org_id              => trans_rec.org_id,
1435                                       p_loading_status      => x_loading_status,
1436                                       x_loading_status      => x_loading_status
1437                                      ) = fnd_api.g_true
1438       THEN
1439          RAISE fnd_api.g_exc_error;
1440       END IF;
1441 
1442       --R12
1443       IF l_validation_only = 'Y'
1444       THEN
1445          RETURN;
1446       END IF;
1447 
1448       -- Delete the Trasaction batches
1449       DELETE FROM cn_posting_batches cnpb
1450             WHERE cnpb.posting_batch_id = trans_rec.posting_batch_id;
1451 
1452       -- Delete the payment Transactions
1453       cn_pmt_trans_pkg.DELETE_RECORD (p_payment_transaction_id);
1454 
1455       -- assign to a variable to get the payment transaction amounts
1456       IF NVL (trans_rec.recoverable_flag, 'N') = 'N'
1457       THEN
1458          l_adj_rec := NVL (trans_rec.payment_amount, 0);
1459          l_adj_nrec := 0;
1460       ELSE
1461          l_adj_nrec := NVL (trans_rec.payment_amount, 0);
1462          l_adj_rec := 0;
1463       END IF;
1464 
1465       -- Update the Payment Worksheets
1466       UPDATE cn_payment_worksheets
1467          SET pmt_amount_adj = NVL (pmt_amount_adj, 0) - NVL (l_adj_rec, 0) - NVL (l_adj_nrec, 0),
1468              object_version_number = object_version_number + 1,
1469              last_updated_by = fnd_global.user_id,
1470              last_update_date = SYSDATE,
1471              -- bug 3080846
1472              last_update_login = fnd_global.login_id
1473        WHERE salesrep_id = trans_rec.credited_salesrep_id
1474          AND payrun_id = trans_rec.payrun_id
1475          AND (quota_id = trans_rec.quota_id OR quota_id IS NULL)
1476          ;
1477 
1478       -- End of API body.
1479       -- Standard check of p_commit.
1480       IF fnd_api.to_boolean (p_commit)
1481       THEN
1482          COMMIT WORK;
1483       END IF;
1484 
1485       -- Standard call to get message count and if count is 1, get message info.
1486       fnd_msg_pub.count_and_get (p_count => x_msg_count, p_data => x_msg_data, p_encoded => fnd_api.g_false);
1487    EXCEPTION
1488       WHEN fnd_api.g_exc_error
1489       THEN
1490          ROLLBACK TO delete_pmt_transactions;
1491          x_return_status := fnd_api.g_ret_sts_error;
1492          fnd_msg_pub.count_and_get (p_count => x_msg_count, p_data => x_msg_data, p_encoded => fnd_api.g_false);
1493       WHEN fnd_api.g_exc_unexpected_error
1494       THEN
1495          ROLLBACK TO delete_pmt_transactions;
1496          x_loading_status := 'UNEXPECTED_ERR';
1497          x_return_status := fnd_api.g_ret_sts_unexp_error;
1498          fnd_msg_pub.count_and_get (p_count => x_msg_count, p_data => x_msg_data, p_encoded => fnd_api.g_false);
1499       WHEN OTHERS
1500       THEN
1501          ROLLBACK TO delete_pmt_transactions;
1502          x_loading_status := 'UNEXPECTED_ERR';
1503          x_return_status := fnd_api.g_ret_sts_unexp_error;
1504 
1505          IF fnd_msg_pub.check_msg_level (fnd_msg_pub.g_msg_lvl_unexp_error)
1506          THEN
1507             fnd_msg_pub.add_exc_msg (g_pkg_name, l_api_name);
1508          END IF;
1509 
1510          fnd_msg_pub.count_and_get (p_count => x_msg_count, p_data => x_msg_data, p_encoded => fnd_api.g_false);
1511    END delete_pmt_transactions;
1512 
1513 --=====================================================================
1514 --Procedure Name:release_wksht_hold
1515 --Description: Used to release the payment holds at worksheet level.
1516 --11.5.10
1517 --=====================================================================
1518    PROCEDURE release_wksht_hold (
1519       p_api_version              IN       NUMBER,
1520       p_init_msg_list            IN       VARCHAR2,
1521       p_commit                   IN       VARCHAR2,
1522       p_validation_level         IN       NUMBER,
1523       x_return_status            OUT NOCOPY VARCHAR2,
1524       x_msg_count                OUT NOCOPY NUMBER,
1525       x_msg_data                 OUT NOCOPY VARCHAR2,
1526       p_payment_worksheet_id     IN       NUMBER
1527    )
1528    IS
1529       l_api_name           CONSTANT VARCHAR2 (30) := 'release_wksht_hold';
1530       l_api_version        CONSTANT NUMBER := 1.0;
1531       l_status                      VARCHAR2 (30) := 'RELEASE_WKSHT_HOLD';
1532       l_loading_status              VARCHAR2 (100);
1533 
1534       -- cursor to get the hold payment transactions
1535       CURSOR get_hold_pmt_trans (
1536          p_payment_worksheet_id              cn_payment_worksheets.payment_worksheet_id%TYPE
1537       )
1538       IS
1539          SELECT cpt.payment_transaction_id,
1540                 cpt.hold_flag,
1541                 cpt.recoverable_flag,
1542                 cpt.payment_amount,
1543                 cpt.waive_flag,
1544                 cpt.incentive_type_code,
1545                 cp.payrun_id,
1546                 cpw.salesrep_id,
1547                 --R12
1548                 cpw.org_id,
1549                 cpt.object_version_number ovn
1550            FROM cn_payruns cp,
1551                 cn_payment_worksheets cpw,
1552                 cn_payment_transactions cpt
1553           WHERE cpw.payment_worksheet_id = p_payment_worksheet_id
1554             AND cp.payrun_id = cpw.payrun_id
1555             AND cp.payrun_id = cpt.payrun_id
1556             AND cpw.salesrep_id = cpt.credited_salesrep_id
1557             AND cpt.hold_flag = 'Y'
1558             --R12
1559             AND cpw.org_id = cp.org_id
1560             AND cpw.org_id = cpt.org_id;
1561    BEGIN
1562       --
1563       -- Standard Start of API savepoint
1564       --
1565       SAVEPOINT release_wksht_hold;
1566 
1567       --
1568       -- Standard call to check for call compatibility.
1569       --
1570       IF NOT fnd_api.compatible_api_call (l_api_version, p_api_version, l_api_name, g_pkg_name)
1571       THEN
1572          RAISE fnd_api.g_exc_unexpected_error;
1573       END IF;
1574 
1575       --
1576       -- Initialize message list if p_init_msg_list is set to TRUE.
1577       --
1578       IF fnd_api.to_boolean (p_init_msg_list)
1579       THEN
1580          fnd_msg_pub.initialize;
1581       END IF;
1582 
1583       --
1584       --  Initialize API return status to success
1585       --
1586       x_return_status := fnd_api.g_ret_sts_success;
1587 
1588       FOR i IN get_hold_pmt_trans (p_payment_worksheet_id)
1589       LOOP
1590          update_pmt_transactions (p_api_version                 => p_api_version,
1591                                   p_init_msg_list               => p_init_msg_list,
1592                                   p_commit                      => p_commit,
1593                                   p_validation_level            => p_validation_level,
1594                                   x_return_status               => x_return_status,
1595                                   x_msg_count                   => x_msg_count,
1596                                   x_msg_data                    => x_msg_data,
1597                                   p_payment_transaction_id      => i.payment_transaction_id,
1598                                   p_hold_flag                   => 'N',
1599                                   p_recoverable_flag            => i.recoverable_flag,
1600                                   p_payment_amount              => i.payment_amount,
1601                                   p_waive_flag                  => i.waive_flag,
1602                                   p_incentive_type_code         => i.incentive_type_code,
1603                                   p_payrun_id                   => i.payrun_id,
1604                                   p_salesrep_id                 => i.salesrep_id,
1605                                   x_status                      => l_status,                                              --Not used by caller anymore
1606                                   x_loading_status              => l_loading_status,                                      --Not used by caller anymore
1607                                   --R12
1608                                   p_org_id                      => i.org_id,
1609                                   p_object_version_number       => i.ovn
1610                                  );
1611       END LOOP;
1612 
1613       -- End of API body.
1614       -- Standard check of p_commit.
1615       IF fnd_api.to_boolean (p_commit)
1616       THEN
1617          COMMIT WORK;
1618       END IF;
1619 
1620       -- Standard call to get message count and if count is 1, get message info.
1621       fnd_msg_pub.count_and_get (p_count => x_msg_count, p_data => x_msg_data, p_encoded => fnd_api.g_false);
1622    EXCEPTION
1623       WHEN fnd_api.g_exc_error
1624       THEN
1625          ROLLBACK TO release_wksht_hold;
1626          x_return_status := fnd_api.g_ret_sts_error;
1627          fnd_msg_pub.count_and_get (p_count => x_msg_count, p_data => x_msg_data, p_encoded => fnd_api.g_false);
1628       WHEN fnd_api.g_exc_unexpected_error
1629       THEN
1630          ROLLBACK TO release_wksht_hold;
1631          x_return_status := fnd_api.g_ret_sts_unexp_error;
1632          fnd_msg_pub.count_and_get (p_count => x_msg_count, p_data => x_msg_data, p_encoded => fnd_api.g_false);
1633       WHEN OTHERS
1634       THEN
1635          ROLLBACK TO release_wksht_hold;
1636          x_return_status := fnd_api.g_ret_sts_unexp_error;
1637 
1638          IF fnd_msg_pub.check_msg_level (fnd_msg_pub.g_msg_lvl_unexp_error)
1639          THEN
1640             fnd_msg_pub.add_exc_msg (g_pkg_name, l_api_name);
1641          END IF;
1642 
1643          fnd_msg_pub.count_and_get (p_count => x_msg_count, p_data => x_msg_data, p_encoded => fnd_api.g_false);
1644    END release_wksht_hold;
1645 
1646 --=====================================================================
1647 --Procedure Name:hold_multiple_trans_conc
1648 --Description: Exceutable for the hold all the transactions.
1649 --=====================================================================
1650 PROCEDURE hold_multiple_trans_conc (
1651       errbuf                     OUT NOCOPY VARCHAR2,
1652       retcode                    OUT NOCOPY NUMBER,
1653       p_payrun_id                IN       NUMBER,
1654       p_salesrep_id              IN       NUMBER,
1655       p_quota_id                 IN       NUMBER,
1656       p_revenue_class_id         IN       NUMBER,
1657       p_invoice_number           IN       VARCHAR2,
1658       p_order_number             IN       NUMBER,
1659       p_customer                 IN       VARCHAR2,
1660       p_hold_flag                IN       VARCHAR2,
1661       p_action                   IN       VARCHAR2
1662    )
1663    IS
1664       l_return_status               VARCHAR2 (1000);
1665       l_msg_data                    VARCHAR2 (2000);
1666       l_msg_count                   NUMBER;
1667       l_loading_status              VARCHAR2 (1000);
1668       l_status                      VARCHAR2 (2000);
1669       l_worksheet_id                NUMBER;
1670       l_ovn                         NUMBER;
1671       l_msg_name                   VARCHAR2(200);
1672       l_note_msg                 VARCHAR2(240);
1673       l_note_id                  NUMBER;
1674       l_transaction_id              NUMBER;
1675       l_errNum                      NUMBER;
1676       l_errText                     VARCHAR2(200);
1677       l_processed                   VARCHAR2(20);
1678       l_flag                        varchar2(1);
1679 
1680 
1681       l_pmt_process_rec            cn_pmt_trans_pvt.pmt_process_rec;
1682 
1683     CURSOR get_paysheet_details IS
1684     SELECT
1685         payment_worksheet_id,object_version_number, name
1686     FROM
1687         cn_payment_worksheets wk, cn_salesreps srp
1688     WHERE
1689         quota_id is null
1690     AND wk.payrun_id   = p_payrun_id
1691     AND wk.salesrep_id = p_salesrep_id
1692     AND wk.salesrep_id = srp.salesrep_id ;
1693 
1694     l_new_status cn_payment_worksheets.worksheet_status%type ;
1695     l_srp_name   cn_salesreps.name%type ;
1696 
1697 BEGIN
1698     SAVEPOINT hold_multiple_trans_conc;
1699     retcode := 0;
1700     -- Initial message list
1701     fnd_msg_pub.initialize;
1702 
1703     OPEN get_paysheet_details;
1704     FETCH get_paysheet_details
1705     INTO l_worksheet_id,l_ovn,l_srp_name;
1706 
1707     CLOSE get_paysheet_details;
1708 
1709     l_pmt_process_rec.payrun_id     := p_payrun_id;
1710     l_pmt_process_rec.salesrep_id   := p_salesrep_id;
1711     l_pmt_process_rec.p_action      :=  p_action;
1712     l_pmt_process_rec.is_processing := 'YES' ;
1713     l_pmt_process_rec.hold_flag     := p_hold_flag ;
1714 
1715     BEGIN
1716           IF p_action = 'HOLD_ALL' THEN
1717              l_flag := 'Y' ;
1718           ELSE
1719              l_flag := 'N' ;
1720           END IF ;
1721           --debug(2, 'begin validate_hold_processing') ;
1722 
1723           validate_hold_processing (
1724                 p_api_version              =>       1.0,
1725                 p_init_msg_list            =>       fnd_api.g_true,
1726                 p_commit                   =>       fnd_api.g_false,
1727                 p_validation_level         =>       fnd_api.g_valid_level_full,
1728                 p_rec                      =>       l_pmt_process_rec,
1729                 x_return_status            =>       l_return_status,
1730                 x_msg_count                =>       l_msg_count,
1731                 x_msg_data                 =>       l_msg_data );
1732 
1733           IF l_return_status <> fnd_api.g_ret_sts_success THEN
1734               --debug(2.1, 'error @ validate_hold_processing') ;
1735               RAISE fnd_api.g_exc_error;
1736           END IF;
1737 
1738           FOR transactions_details_rec IN get_transactions_details(p_payrun_id,
1739                                                                    p_salesrep_id,
1740                                                                    p_quota_id,
1741                                                                    p_revenue_class_id,
1742                                                                    p_invoice_number,
1743                                                                    p_order_number,
1744                                                                    p_customer,
1745                                                                    p_hold_flag,
1746                                                                    p_action)
1747           LOOP
1748               update_pmt_transactions(
1749                   p_api_version              =>       1.0,
1750                   p_init_msg_list            =>       fnd_api.g_true,
1751                   p_commit                   =>       fnd_api.g_false,--changed to false
1752                   p_validation_level         =>       fnd_api.g_valid_level_full,
1753                   x_return_status            =>       l_return_status,
1754                   x_msg_count                =>       l_msg_count,
1755                   x_msg_data                 =>       l_msg_data,
1756                   p_payment_transaction_id   =>       transactions_details_rec.payment_transaction_id,
1757                   p_hold_flag                =>       l_flag,
1758                   p_recoverable_flag         =>       transactions_details_rec.recoverable_flag,
1759                   p_payment_amount           =>       transactions_details_rec.payment_amount,
1760                   p_waive_flag               =>       transactions_details_rec.waive_flag,
1761                   p_incentive_type_code      =>       transactions_details_rec.incentive_type_code,
1762                   p_payrun_id                =>       p_payrun_id,
1763                   p_salesrep_id              =>       p_salesrep_id,
1764                   x_status                   =>       l_status,
1765                   x_loading_status           =>       l_loading_status,
1766                   p_org_id                   =>       transactions_details_rec.org_id,
1767                   p_object_version_number    =>       transactions_details_rec.object_version_number);
1768 
1769              IF l_return_status <> fnd_api.g_ret_sts_success THEN
1770                 l_errText := fnd_msg_pub.get (p_msg_index => fnd_msg_pub.g_last, p_encoded => fnd_api.g_false);
1771                 IF fnd_msg_pub.check_msg_level (fnd_msg_pub.g_msg_lvl_error) THEN
1772                       fnd_message.set_name ('CN', 'CN_PROCESS_UPD_TRANS_NOTE');
1773                       fnd_message.set_token ('TRX_ID', transactions_details_rec.payment_transaction_id );
1774                       fnd_message.set_token('MESSAGE_TEXT', l_errText);
1775                       fnd_msg_pub.ADD;
1776                 END IF;
1777                 RAISE fnd_api.g_exc_error;
1778              END IF;
1779           END LOOP;
1780 
1781           --debug(5, 'end end for update_pmt_transactions') ;
1782 
1783           l_new_status := 'UNPAID' ;
1784           fnd_message.set_name('CN', 'CN_PROCESS_TRANS_NOTE');
1785           l_note_msg := fnd_message.get;
1786 
1787     EXCEPTION
1788     WHEN fnd_api.g_exc_error  THEN
1789          ROLLBACK TO hold_multiple_trans_conc;
1790          retcode := 2;
1791          errbuf := fnd_msg_pub.get (p_msg_index => fnd_msg_pub.g_last, p_encoded => fnd_api.g_false);
1792          l_note_msg := fnd_message.get;
1793          l_new_status := 'FAILED' ;
1794 
1795     WHEN fnd_api.g_exc_unexpected_error THEN
1796          ROLLBACK TO hold_multiple_trans_conc;
1797          retcode := 2;
1798          errbuf := fnd_msg_pub.get (p_msg_index => fnd_msg_pub.g_last, p_encoded => fnd_api.g_false);
1799          l_note_msg := fnd_message.get;
1800          l_new_status := 'FAILED' ;
1801     END ;
1802 
1803     cn_payment_worksheets_pkg.update_status(p_salesrep_id,p_payrun_id,l_new_status) ;
1804 
1805     BEGIN
1806         jtf_notes_pub.create_note (
1807             p_api_version         => 1.0,
1808             x_return_status       => l_return_status,
1809             x_msg_count           => l_msg_count,
1810             x_msg_data            => l_msg_data,
1811             p_source_object_id    => l_worksheet_id,
1812             p_source_object_code  => 'CN_PAYMENT_WORKSHEETS',
1813             p_notes               => l_note_msg,
1814             p_notes_detail        => l_note_msg,
1815             p_note_type           => 'CN_SYSGEN', -- for system generated
1816             x_jtf_note_id         => l_note_id   -- returned
1817             );
1818     EXCEPTION
1819     WHEN OTHERS THEN
1820          retcode := 2;
1821          errbuf := fnd_msg_pub.get (p_msg_index => fnd_msg_pub.g_last, p_encoded => fnd_api.g_false);
1822     END ;
1823 
1824     COMMIT ;
1825 EXCEPTION
1826 WHEN OTHERS THEN
1827     ROLLBACK;
1828     l_errNum  := SQLCODE;
1829     l_errText := SUBSTR(SQLERRM,1,200);
1830     fnd_message.set_name ('CN', 'CN_PROCESS_WKSHT_FAIL_NOTE');
1831     fnd_message.set_token('SRP_NAME', l_srp_name );
1832     fnd_message.set_token('MESSAGE_TEXT', l_errText);
1833     fnd_msg_pub.ADD;
1834 
1835     cn_payment_worksheets_pkg.update_status(p_salesrep_id,p_payrun_id, 'FAILED') ;
1836 
1837     retcode := 2;
1838     errbuf := fnd_msg_pub.get (p_msg_index => fnd_msg_pub.g_last, p_encoded => fnd_api.g_false);
1839     COMMIT ;
1840 END  hold_multiple_trans_conc;
1841 
1842 
1843 --============================================================================
1844 -- Start of Comments
1845 --
1846 -- API name  : process_pmt_transactions
1847 -- Type     : Private.
1848 -- Pre-reqs : None.
1849 -- Usage :    submits the hold all concurrent program.
1850 -- Parameters  :
1851 -- IN    :  p_api_version       IN NUMBER      Require
1852 --          p_init_msg_list     IN VARCHAR2    Optional
1853 --             Default = FND_API.G_FALSE
1854 --          p_commit        IN VARCHAR2    Optional
1855 --                Default = FND_API.G_FALSE
1856 --          p_validation_level  IN NUMBER      Optional
1857 --                Default = FND_API.G_VALID_LEVEL_FULL
1858 -- IN    :  p_payrun_id          IN       NUMBER
1859 -- IN    :  p_salesrep_id        IN          VARCHAR2(01)
1860 -- IN    :  p_quota_id           IN          NUMBER
1861 -- IN    :  p_revenue_class_id   IN          Varchar2(01)
1862 -- IN    :  p_invoice_number     IN       Varchar2(01)
1863 -- IN    :  p_customer           IN         Varchar2
1864 -- IN    :  p_hold_flag          IN         Varchar2
1865 -- IN    :  p_action             IN         Varchar2
1866 --          Detailed Error Message
1867 -- Version  : Current version 1.0
1868 --      Initial version    1.0
1869 --
1870 -- End of comments
1871 --============================================================================
1872     PROCEDURE process_pmt_transactions (
1873           p_api_version              IN       NUMBER,
1874           p_init_msg_list            IN       VARCHAR2 := fnd_api.g_false,
1875           p_commit                   IN       VARCHAR2 := fnd_api.g_false,
1876           p_validation_level         IN       NUMBER := fnd_api.g_valid_level_full,
1877           p_rec                      IN OUT NOCOPY pmt_process_rec,
1878           x_return_status            OUT NOCOPY VARCHAR2,
1879           x_msg_count                OUT NOCOPY NUMBER,
1880           x_msg_data                 OUT NOCOPY VARCHAR2
1881     )
1882      IS
1883           l_api_name           CONSTANT VARCHAR2 (30) := 'process_pmt_transactions';
1884           l_api_version        CONSTANT NUMBER := 1.0;
1885           l_request_id         NUMBER := NULL ;
1886           l_return_status      VARCHAR2 (1000);
1887           l_msg_data           VARCHAR2 (2000);
1888           l_msg_count          NUMBER;
1889           l_status             VARCHAR2(100)  ;
1890      BEGIN
1891         -- Standard Start of API savepoint
1892         SAVEPOINT process_pmt_transactions;
1893 
1894         -- Standard call to check for call compatibility.
1895         IF NOT fnd_api.compatible_api_call (l_api_version, p_api_version, l_api_name, g_pkg_name)
1896         THEN
1897            RAISE fnd_api.g_exc_unexpected_error;
1898         END IF;
1899 
1900         -- Initialize message list if p_init_msg_list is set to TRUE.
1901         IF fnd_api.to_boolean (p_init_msg_list)
1902         THEN
1903            fnd_msg_pub.initialize;
1904         END IF;
1905 
1906         --  Initialize API return status to success
1907         x_return_status := fnd_api.g_ret_sts_success;
1908 
1909         validate_hold_processing (
1910            p_api_version        => p_api_version ,
1911            p_init_msg_list      => p_init_msg_list,
1912            p_commit             => p_commit,
1913            p_validation_level   => p_validation_level,
1914            p_rec                => p_rec,
1915            x_return_status      => l_return_status,
1916            x_msg_count          => l_msg_count,
1917            x_msg_data           => l_msg_data
1918         ) ;
1919 
1920         IF l_return_status <> fnd_api.g_ret_sts_success
1921         THEN
1922           RAISE fnd_api.g_exc_error;
1923         END IF;
1924 
1925         IF p_rec.p_action IN (CN_PMT_TRANS_PVT.G_HOLD_ALL, CN_PMT_TRANS_PVT.G_RELEASE_ALL) THEN
1926 
1927               -- init the org_id
1928               fnd_request.set_org_id(p_rec.org_id);
1929 
1930               --- create the request
1931               l_request_id := fnd_request.submit_request(
1932                    application    => 'CN'
1933                   ,program        => 'PROCESS_PMT_TRANSACTIONS'
1934                   ,description    => 'Process Payment Transactions'
1935                   ,start_time     => NULL
1936                   ,sub_request    => NULL
1937                   ,argument1      => p_rec.payrun_id
1938                   ,argument2      => p_rec.salesrep_id
1939                   ,argument3      => p_rec.quota_id
1940                   ,argument4      => p_rec.revenue_class_id
1941                   ,argument5      => p_rec.invoice_number
1942                   ,argument6      => p_rec.order_number
1943                   ,argument7      => p_rec.customer
1944                   ,argument8      => p_rec.hold_flag
1945                   ,argument9      => p_rec.p_action
1946                   );
1947 
1948               IF l_request_id = 0 THEN
1949                  cn_message_pkg.debug('Main : unable to submit batch conc program ');
1950                  cn_message_pkg.debug('Main : ' || fnd_message.get);
1951 
1952                  IF (FND_LOG.LEVEL_UNEXPECTED >= FND_LOG.G_CURRENT_RUNTIME_LEVEL ) THEN
1953                      FND_LOG.STRING(FND_LOG.LEVEL_UNEXPECTED,'cn.plsql.cn_pmt_trans_pvt.pmt_process.exception','Failed to submit request for BATCH_PROCESSOR.');
1954                  END IF;
1955                  RAISE fnd_api.g_exc_error;
1956               END IF ;
1957               p_rec.request_id := l_request_id ;
1958 
1959               UPDATE cn_payment_worksheets
1960               SET request_id = p_rec.request_id,
1961                   last_update_date = SYSDATE,
1962                   last_updated_by = fnd_global.user_id,
1963                   last_update_login = fnd_global.login_id
1964               WHERE payrun_id = p_rec.payrun_id
1965               AND salesrep_id = p_rec.salesrep_id
1966               AND quota_id IS NULL ;
1967 
1968         ELSIF p_rec.p_action = CN_PMT_TRANS_PVT.G_RESET_TO_UNPAID THEN
1969               NULL ;
1970         ELSE
1971               IF fnd_msg_pub.check_msg_level (fnd_msg_pub.g_msg_lvl_error)
1972               THEN
1973                 fnd_message.set_name ('CN', 'CN_WKSHT_ACTION_NOT_EXIST');
1974                 fnd_msg_pub.ADD;
1975               END IF;
1976               RAISE fnd_api.g_exc_error;
1977         END IF;
1978 
1979         cn_payment_worksheet_pvt.update_worksheet (
1980            p_api_version         =>   p_api_version,
1981            p_init_msg_list       =>   p_init_msg_list,
1982            p_commit              =>   p_commit,
1983            p_validation_level    =>   p_validation_level,
1984            x_return_status       =>   l_return_status,
1985            x_msg_count           =>   l_msg_count,
1986            x_msg_data            =>   l_msg_data,
1987            p_worksheet_id        =>   p_rec.worksheet_id,
1988            p_operation           =>   p_rec.p_action,
1989            x_status              =>   l_status,
1990            x_loading_status      =>   l_status,
1991            x_ovn                 =>   p_rec.object_version_number
1992         ) ;
1993 
1994         IF l_return_status <> fnd_api.g_ret_sts_success
1995         THEN
1996           RAISE fnd_api.g_exc_error;
1997         END IF;
1998 
1999      EXCEPTION
2000           WHEN fnd_api.g_exc_error
2001           THEN
2002              ROLLBACK TO process_pmt_transactions;
2003              x_return_status := fnd_api.g_ret_sts_error;
2004              fnd_msg_pub.count_and_get (p_count => x_msg_count, p_data => x_msg_data, p_encoded => fnd_api.g_false);
2005           WHEN fnd_api.g_exc_unexpected_error
2006           THEN
2007              ROLLBACK TO process_pmt_transactions;
2008              x_return_status := fnd_api.g_ret_sts_unexp_error;
2009              fnd_msg_pub.count_and_get (p_count => x_msg_count, p_data => x_msg_data, p_encoded => fnd_api.g_false);
2010           WHEN OTHERS
2011           THEN
2012              ROLLBACK TO process_pmt_transactions;
2013              x_return_status := fnd_api.g_ret_sts_unexp_error;
2014 
2015              IF fnd_msg_pub.check_msg_level (fnd_msg_pub.g_msg_lvl_unexp_error)
2016              THEN
2017                 fnd_msg_pub.add_exc_msg (g_pkg_name, l_api_name);
2018              END IF;
2019              fnd_msg_pub.count_and_get (p_count => x_msg_count, p_data => x_msg_data, p_encoded => fnd_api.g_false);
2020     END process_pmt_transactions;
2021 
2022 
2023 END cn_pmt_trans_pvt;