DBA Data[Home] [Help]

PACKAGE BODY: APPS.OKL_CURE_CALC_PVT

Source


1 PACKAGE BODY OKL_CURE_CALC_PVT AS
2 /* $Header: OKLRCURB.pls 120.9 2007/10/17 17:39:20 vdamerla noship $ */
3 
4 ---------------------------------------------------------------------------
5 -- PROCEDURE POPULATE_QTE_TABLE
6 -- This procedue populates the necessary PL/SQL table for quote
7 -- mandatory fields. It also populates the contract ID, quote type and
8 -- quote reason.
9 ---------------------------------------------------------------------------
10 PROCEDURE populate_qte_rec( p_contract_id   IN NUMBER
11                            ,p_quot_rec_type IN OUT NOCOPY okl_trx_quotes_pub.qtev_rec_type )
12 IS
13 cursor c_get_quote_type (p_contract_id IN NUMBER ) is
14 select  RULE_INFORMATION3
15 from okc_rules_b rul,
16       okl_k_headers khr
17 where rul.dnz_chr_id =khr.khr_id
18 and khr.id =p_contract_id
19 and  RULE_INFORMATION_CATEGORY ='CORPUR';
20 l_type okl_trx_quotes_b.qtp_code%TYPE;
21 
22 BEGIN
23 
24   okl_debug_pub.logmessage('populate_qte_rec : START ');
25 
26   p_quot_rec_type.khr_id                     := p_contract_id;
27 
28   -- QUOTE Type from vendor agreement
29   -- cannot use okl_contract_info.get_rule value, since it returns
30   -- the description for the quote type
31   --09/17/03
32 
33   OPEN  c_get_quote_type (p_contract_id);
34   FETCH c_get_quote_type INTO l_type;
35   CLOSE c_get_quote_type;
36 
37   p_quot_rec_type.qtp_code := nvl(l_type,'TER_RECOURSE');
38 
39 
40   p_quot_rec_type.qrs_code                   := 'RES_DELINQUENCY';
41   p_quot_rec_type.comments                   := 'Requesting Repurchase Amount'||
42                                                 'From Collections for Vendor Cure Request';
43 
44   okl_debug_pub.logmessage('populate_qte_rec : l_type : '|| l_type);
45 
46   okl_debug_pub.logmessage('populate_qte_rec : END ');
47 
48 END populate_qte_rec;
49 
50 ---------------------------------------------------------------------------
51 -- PROCEDURE POPULATE_ASSET_TABLE
52 -- Populate the asset PL/SQL table, this is required for getting the
53 -- quote amount for individual asset, the Repurhcase amount procedure
54 -- will add up the values for obtaining repurchase amount for the entire
55 -- contract.
56 ---------------------------------------------------------------------------
57 PROCEDURE populate_asset_table(
58        p_contract_id     IN NUMBER
59        ,p_assn_tbl       IN OUT NOCOPY OKL_AM_CREATE_QUOTE_PUB.assn_tbl_type)
60 IS
61 
62   CURSOR asset_line_dur (p_contract_id IN NUMBER) IS
63   --  SELECT asset_id, asset_number
64   -- according to ravi M , we have to pass ID1 as the assest ID
65   --also the line sts_code should be same as contract sts_code
66   -- and should be from TOP lines
67   --01/21/03
68   SELECT kle.id kle_id, kle.name asset_number
69   FROM okc_k_lines_v kle, okc_k_headers_v khr,
70        OKC_LINE_STYLES_V LSE
71   WHERE kle.chr_id = khr.id
72   AND kle.lse_id = LSE.id
73   AND lse.lty_code = 'FREE_FORM1' --This is the TOP LINE for Financial Assets
74   AND khr.sts_code = kle.sts_code
75   AND khr.id = p_contract_id;
76 
77 l_counter Number :=1;
78 BEGIN
79 
80   okl_debug_pub.logmessage('populate_asset_table : START ');
81 
82   FOR i IN asset_line_dur (p_contract_id)
83   LOOP
84     p_assn_tbl(l_counter).p_asset_id      := i.kle_id;
85     p_assn_tbl(l_counter).p_asset_number  := i.asset_number;
86     l_counter :=l_counter + 1;
87 
88   END LOOP;
89 
90   okl_debug_pub.logmessage('populate_asset_table : END ');
91 
92 END populate_asset_table;
93 
94 PROCEDURE get_error_message(p_all_message
95                OUT nocopy error_message_type)
96   IS
97     l_msg_text VARCHAR2(32627);
98     l_msg_count NUMBER ;
99   BEGIN
100     l_msg_count := fnd_msg_pub.count_msg;
101     FOR i IN 1..l_msg_count
102 	LOOP
103       fnd_msg_pub.get
104         (p_data => p_all_message(i),
105         p_msg_index_out => l_msg_count,
106 	    p_encoded => fnd_api.g_false,
107 	    p_msg_index => fnd_msg_pub.g_next
108         );
109     END LOOP;
110  EXCEPTION
111     WHEN OTHERS THEN
112 	  NULL;
113  END get_error_message;
114 
115  Procedure Update_cure_amounts(
116                 p_contract_id     IN NUMBER
117                ,x_return_status  OUT NOCOPY VARCHAR2
118                ,x_msg_count      OUT NOCOPY NUMBER
119                ,x_msg_data       OUT NOCOPY VARCHAR2 ) IS
120 
121 Cursor c_get_cure_amts (p_contract_id IN NUMBER) IS
122 Select cure_amount_id,object_version_number,negotiated_amount
123 from okl_cure_amounts
124 where chr_id =p_contract_id
125 and SHOW_ON_REQUEST ='Y';
126 
127 -- while creating cure invoices, it should show only the details of a
128 --cure request, if a new contract is created, we should null out the crt id
129 --of the previous contract if negotiated amount is zero or null
130 --otherwise, okl_cure_invoices_uv will show all the contracts.
131 
132  l_camv_tbl                 OKL_cure_amounts_pub.camv_tbl_type;
133  x_camv_tbl                 OKL_cure_amounts_pub.camv_tbl_type;
134  l_msg_count                NUMBER;
135  l_msg_data                 VARCHAR2(32627);
136  l_return_status            VARCHAR2(1) :=FND_API.G_RET_STS_SUCCESS;
137  next_row                   INTEGER;
138  l_error_msg_tbl error_message_type;
139 
140 
141 -- ASHIM CHANGE - START
142 
143 
144 
145  /*cursor c_get_received_amounts (p_cure_amount_id IN NUMBER) is
146  select sum(ara.amount_applied)
147  from ar_payment_schedules ps1,
148       okl_cnsld_ar_strms_b st1
149      ,ar_receivable_applications ara
150      ,okl_xtl_sell_invs_v  xls
151      ,okl_txl_ar_inv_lns_v til
152      ,okl_trx_ar_invoices_v tai
153 where st1.receivables_invoice_id = ps1.customer_trx_id
154      and ara.applied_payment_schedule_id = ps1.payment_schedule_id
155      and st1.id =xls.lsm_id
156      and tai.id = til.tai_id
157      and til.id = xls.til_id
158      and tai.cpy_id =p_cure_amount_id
159      and st1.khr_id =tai.khr_id;*/
160 
161  cursor c_get_received_amounts (p_cure_amount_id IN NUMBER) is
162  select sum(ara.amount_applied)
163  from ar_payment_schedules ps1,
164       okl_bpd_tld_ar_lines_v st1
165      ,ar_receivable_applications ara
166      --,okl_xtl_sell_invs_v  xls
167      ,okl_txl_ar_inv_lns_v til
168      ,okl_trx_ar_invoices_v tai
169 where st1.customer_trx_id = ps1.customer_trx_id
170      and ara.applied_payment_schedule_id = ps1.payment_schedule_id
171      --and st1.id =xls.lsm_id
172      and tai.id = til.tai_id
173      --and til.id = xls.til_id
174      and tai.cpy_id =p_cure_amount_id
175      and st1.khr_id =tai.khr_id
176      and st1.til_id_details = til.id
177      and til.tai_id = tai.id;
178 
179 
180 -- ASHIM CHANGE - END
181 
182 
183  BEGIN
184 
185 
186          SAVEPOINT UPDATE_CURE_AMOUNTS;
187          FND_MSG_PUB.initialize;
188          x_return_status := FND_API.G_RET_STS_SUCCESS;
189          write_log(FND_MSG_PUB.G_MSG_LVL_DEBUG_LOW, 'Calling Cure Amount Update Api');
190 
191          okl_debug_pub.logmessage('Update_cure_amounts : START ');
192 
193         --update cure amounts table
194          FOR i in c_get_cure_amts (p_contract_id)
195          LOOP
196              next_row := nvl(l_camv_tbl.LAST,0) +1;
197              l_camv_tbl(next_row).cure_amount_id        :=i.cure_amount_id;
198              l_camv_tbl(next_row).object_version_number :=i.object_version_number;
199              l_camv_tbl(next_row).SHOW_ON_REQUEST :='N';
200              OPEN c_get_received_amounts(i.cure_amount_id);
201              FETCH c_get_received_amounts INTO
202                     l_camv_tbl(next_row).received_amount;
203                    write_log(FND_MSG_PUB.G_MSG_LVL_DEBUG_LOW,
204                   'cure_amount id '||i.cure_amount_id ||
205                   'recevied_amount '||l_camv_tbl(next_row).received_amount);
206 
207                okl_debug_pub.logmessage('Update_cure_amounts : i.cure_amount_id '|| i.cure_amount_id);
208                okl_debug_pub.logmessage('Update_cure_amounts : l_camv_tbl(next_row).received_amount '|| l_camv_tbl(next_row).received_amount);
209              CLOSE c_get_received_amounts;
210 
211              --commented out on 09/23 , requested by pdeveraj
212             /* If nvl(i.negotiated_amount,0) = 0 THEN
213                 l_camv_tbl(next_row).crt_id :=NULL;
214              END if;
215             */
216 
217          END LOOP;
218 
219          write_log(FND_MSG_PUB.G_MSG_LVL_DEBUG_LOW,
220                   'no of records to be updated in Cure amounts '||
221                    l_camv_tbl.COUNT);
222         IF l_camv_tbl.COUNT > 0 THEN
223            OKL_cure_amounts_pub.update_cure_amounts
224                          (  p_api_version    => 1
225                            ,p_init_msg_list  => 'T'
226                            ,x_return_status  => l_return_status
227                            ,x_msg_count      => l_msg_count
228                            ,x_msg_data       => l_msg_data
229                            ,p_camv_tbl       => l_camv_tbl
230                            ,x_camv_tbl       => x_camv_tbl
231                          );
232 
233          okl_debug_pub.logmessage('Update_cure_amounts : OKL_cure_amounts_pub.update_cure_amounts : '||l_return_status);
234 
235           IF (l_return_status  <> FND_Api.G_RET_STS_SUCCESS ) THEN
236              RAISE Fnd_Api.G_EXC_ERROR;
237           ELSE
238              write_log(FND_MSG_PUB.G_MSG_LVL_DEBUG_MEDIUM,
239                'Updation of cure amounts is Successful');
240          END IF;
241          x_return_status  := l_return_status;
242          FND_MSG_PUB.Count_And_Get ( p_count =>   x_msg_count,
243                                      p_data   =>   x_msg_data );
244       END IF;
245 
246       okl_debug_pub.logmessage('Update_cure_amounts : END ');
247 
248 EXCEPTION
249 
250     WHEN Fnd_Api.G_EXC_ERROR THEN
251       ROLLBACK TO UPDATE_CURE_AMOUNTS;
252       x_return_status := Fnd_Api.G_RET_STS_ERROR;
253       x_msg_count := l_msg_count ;
254       x_msg_data := l_msg_data ;
255       Fnd_Msg_Pub.count_and_get(
256              p_count   => x_msg_count
257             ,p_data    => x_msg_data);
258     WHEN Fnd_Api.G_EXC_UNEXPECTED_ERROR THEN
259       ROLLBACK TO UPDATE_CURE_AMOUNTS;
260       x_return_status := Fnd_Api.G_RET_STS_UNEXP_ERROR;
261       x_msg_count := l_msg_count ;
262       x_msg_data := l_msg_data ;
263       Fnd_Msg_Pub.count_and_get(
264              p_count   => x_msg_count
265             ,p_data    => x_msg_data);
266     WHEN OTHERS THEN
267       ROLLBACK TO UPDATE_CURE_AMOUNTS;
268       x_return_status := Fnd_Api.G_RET_STS_UNEXP_ERROR;
269       x_msg_count := l_msg_count ;
270       x_msg_data := l_msg_data ;
271       Fnd_Msg_Pub.ADD_EXC_MSG('OKL_CURE_CALC_PVT','UPDATE_CURE_AMOUNTS');
272       Fnd_Msg_Pub.count_and_get(
273              p_count   => x_msg_count
274             ,p_data    => x_msg_data);
275 
276 
277 End update_cure_amounts;
278 
279 
280 
281   ---------------------------------------------------------------------------
282   -- PROCEDURE GET_REPURCHASE_AMT
283   ---------------------------------------------------------------------------
284   PROCEDURE GET_REPURCHASE_AMT(
285 	 p_contract_id	       IN NUMBER
286 	 ,x_repurchase_amt       OUT NOCOPY NUMBER
287 	 ,x_return_status        OUT NOCOPY VARCHAR2
288 	 ,x_msg_count            OUT NOCOPY NUMBER
289 	 ,x_msg_data             OUT NOCOPY VARCHAR2
290      ,x_qte_id               OUT NOCOPY NUMBER )
291   IS
292 
293   l_repurchase_amount		NUMBER;
294   l_api_version               CONSTANT NUMBER := 1;
295   l_api_name                  CONSTANT VARCHAR2(30) := 'OKL_CURE_CALC_PVT';
296   l_return_status             VARCHAR2(1) := fnd_api.G_RET_STS_SUCCESS;
297 
298   l_quot_rec              OKL_AM_CREATE_QUOTE_PUB.quot_rec_type;
299   l_assn_tbl		      OKL_AM_CREATE_QUOTE_PUB.assn_tbl_type;
300   l_qpyv_tbl              OKL_AM_CREATE_QUOTE_Pub.qpyv_tbl_type;
301 
302 
303   l_qtev_rec OKL_AM_PARTIES_PVT.qtev_rec_type;
304   x_q_party_uv_tbl OKL_AM_PARTIES_PVT.q_party_uv_tbl_type;
305   l_record_count NUMBER;
306 
307 
308   x_quot_rec              OKL_AM_CREATE_QUOTE_PUB.quot_rec_type;
309   x_tqlv_tbl		      OKL_AM_CREATE_QUOTE_PUB.tqlv_tbl_type;
310   x_assn_tbl	          OKL_AM_CREATE_QUOTE_PUB.assn_tbl_type;
311 
312   l_counter 			NUMBER := 1;
313   l_msg_count           NUMBER;
314   l_msg_data            VARCHAR2(32627);
315   l_error_msg_tbl error_message_type;
316   l_msg_index_out number;
317 
318   l_cpl_id    NUMBER;
319   l_qtp_code  okl_trx_quotes_b.qtp_code%TYPE;
320 
321    Cursor c_get_cpl_id(p_contract_id IN NUMBER) is
322     SELECT  party.id
323       FROM okl_am_k_party_roles_uv party,
324            okl_k_headers khr
325       WHERE party.dnz_chr_id =khr.khr_id
326       and khr.id=p_contract_id
327       AND party.rle_code = 'OKL_VENDOR';
328 
329 /*
330 REVERTING back to the previous correct query
331 Performance issue will be addressed later
332 
333 --Updated the cursor sql statement for performance issue - bug#5484903
334    Cursor c_get_cpl_id(p_contract_id IN NUMBER) is
335    select CPLB.ID id
336    FROM OKC_K_PARTY_ROLES_B CPLB
337    where CPLB.DNZ_CHR_ID=p_contract_id
338    and CPLB.RLE_CODE= 'OKL_VENDOR';
339 */
340 
341   BEGIN
342 
343        SAVEPOINT GET_REPURCHASE_AMT;
344 
345        okl_debug_pub.logmessage('GET_REPURCHASE_AMT : START ');
346 
347        populate_qte_rec( p_contract_id
348                         ,l_quot_rec );
349 
350        populate_asset_table( p_contract_id
351                          ,l_assn_tbl );
352 
353 
354  -- Populate receipent table
355 /*    l_qtev_rec.KHR_ID :=p_contract_id;
356     l_qtev_rec.QTP_CODE :=l_quot_rec.qtp_code;
357 
358 
359   OKL_AM_PARTIES_PVT.fetch_rule_quote_parties
360                                 (p_api_version =>1.0
361                                  ,p_init_msg_list  =>FND_API.G_TRUE
362                                  ,x_return_status  =>l_return_status
363                                  ,x_msg_count      =>l_msg_count
364                                  ,x_msg_data       =>l_msg_data
365                              	 ,p_qtev_rec	   =>L_qtev_rec
366 	                             ,x_qpyv_tbl	   =>l_qpyv_tbl
367                              	,x_q_party_uv_tbl  =>x_q_party_uv_tbl
368                              	,x_record_count	   =>l_record_count
369                                 );
370 
371 */
372 
373       OPEN c_get_cpl_id (p_contract_id);
374       FETCH c_get_cpl_id INTO l_cpl_id;
375       CLOSE c_get_cpl_id;
376 
377       l_qpyv_tbl(1).cpl_id   := l_cpl_id;
378       l_qpyv_tbl(1).qpt_code := 'RECIPIENT';
379 
380 
381       write_log(FND_MSG_PUB.G_MSG_LVL_DEBUG_LOW, 'CPL ID' ||  l_cpl_id );
382 
383       okl_debug_pub.logmessage('GET_REPURCHASE_AMT : l_cpl_id : '|| l_cpl_id);
384 
385       -- Call the Asset Management Quote Creation API to get
386       -- Repurchase amount for the contract
387 
388       OKL_AM_CREATE_QUOTE_PUB.create_terminate_quote(
389 					 p_api_version 	=> 1.0
390 			   	     ,p_init_msg_list  => 'T'
391 			    	 ,x_return_status  => l_return_status
392 					,x_msg_count      => l_msg_count
393 					,x_msg_data       => l_msg_data
394 					,p_quot_rec       => l_quot_rec
395 					,p_assn_tbl		  => l_assn_tbl
396                    ,p_qpyv_tbl		  => l_qpyv_tbl
397 					,x_quot_rec       => x_quot_rec
398 					,x_tqlv_tbl		=> x_tqlv_tbl
399 					,x_assn_tbl		=> x_assn_tbl);
400 
401     okl_debug_pub.logmessage('GET_REPURCHASE_AMT : OKL_AM_CREATE_QUOTE_PUB.create_terminate_quote : '|| l_return_status);
402 
403     if l_return_status <> FND_Api.G_RET_STS_SUCCESS THEN
404        fnd_msg_pub.get (p_msg_index => 1,
405                       p_encoded => 'F',
406                       p_data => l_msg_data,
407                       p_msg_index_out => l_msg_index_out);
408        write_log(FND_MSG_PUB.G_MSG_LVL_DEBUG_HIGH,'error after calling create terminate quote '||
409                         ' is ' || l_msg_data);
410        RAISE Fnd_Api.G_EXC_ERROR;
411     END IF;
412 
413     l_repurchase_amount := 0;
414     FOR i in x_tqlv_tbl.FIRST..x_tqlv_tbl.LAST LOOP
415         l_repurchase_amount := l_repurchase_amount + x_tqlv_tbl(i).amount;
416     END LOOP;
417 
418    -- get quote id
419    --09/17/2003
420 
421     x_qte_id :=x_quot_rec.id;
422     x_repurchase_amt := l_repurchase_amount;
423     x_return_status  := l_return_status;
424     x_msg_count := l_msg_count ;
425     x_msg_data := l_msg_data ;
426 
427 
428     write_log(FND_MSG_PUB.G_MSG_LVL_DEBUG_LOW, 'Repurchase Amount is '
429                       ||l_repurchase_amount
430                       || 'and Quote id is '||x_qte_id);
431 
432 
433 
434       FND_MSG_PUB.Count_And_Get
435       (  p_count          =>   x_msg_count,
436          p_data           =>   x_msg_data
437       );
438        okl_debug_pub.logmessage('GET_REPURCHASE_AMT : l_repurchase_amount : '|| l_repurchase_amount);
439        okl_debug_pub.logmessage('GET_REPURCHASE_AMT : END ');
440 
441     EXCEPTION
442       WHEN Fnd_Api.G_EXC_ERROR THEN
443       ROLLBACK TO GET_REPURCHASE_AMT;
444       x_return_status := Fnd_Api.G_RET_STS_ERROR;
445       x_msg_count := l_msg_count ;
446       x_msg_data := l_msg_data ;
447       Fnd_Msg_Pub.count_and_get(
448              p_count   => x_msg_count
449             ,p_data    => x_msg_data);
450 
451     WHEN OTHERS THEN
452       ROLLBACK TO GET_REPURCHASE_AMT;
453       x_return_status := Fnd_Api.G_RET_STS_UNEXP_ERROR;
454       x_msg_count := l_msg_count ;
455       x_msg_data := l_msg_data ;
456       Fnd_Msg_Pub.ADD_EXC_MSG('OKL_CURE_CALC_PVT','GET_REPURCHASE_AMT');
457       Fnd_Msg_Pub.count_and_get(
458              p_count   => x_msg_count
459             ,p_data    => x_msg_data);
460   END GET_REPURCHASE_AMT;
461 
462   ---------------------------------------------------------------------------
463   -- FUNCTION GET_CURE_AMT
464   -- This function calculates and returns the cure amount for a contract
465   -- It accepts contract ID and cure type as parameters
466   -- cure types may be FULL or INTEREST.
467   -- currently the formula for FULL CURE is:
468   -- (net rent past due excluding current months due and any cures received
469   -- thus far for the contract)
470   -- The formula for INTEREST CURE is:
471   -- (net investment * contract rate)/12 * no of months requiring cures
472   ---------------------------------------------------------------------------
473 PROCEDURE    GET_CURE_AMT( p_contract_id    IN  NUMBER
474                           ,p_program_id     IN  NUMBER
475                           ,p_cure_type	    IN  VARCHAR2
476                           ,x_cure_amount    OUT NOCOPY NUMBER
477                           ,x_return_status  OUT NOCOPY VARCHAR2
478                           ,x_msg_count      OUT NOCOPY NUMBER
479                           ,x_msg_data       OUT NOCOPY VARCHAR2 )
480 
481 IS
482 
483   l_current_due_amount          NUMBER := 0;
484   l_days_past_due               NUMBER;
485   l_current_due_date            DATE;
486   l_contract_rate               NUMBER;
487   l_months_requiring_cure       NUMBER := 0;
488   l_net_investment              NUMBER := 0;
489   l_return_status               VARCHAR2(1) := FND_Api.G_RET_STS_SUCCESS;
490   l_last_due_date               DATE;
491   l_sysdate                     DATE := TRUNC(SYSDATE);
492   l_id1                         VARCHAR2(40);
493   l_id2                         VARCHAR2(200);
494   l_rule_value                  VARCHAR2(2000);
495 
496  cursor c_cures_in_possession (p_contract_id IN NUMBER ) IS
497  select refund_amount_due
498  from okl_cure_refunds_dtls_uv
499  where contract_id =p_contract_id;
500 
501   l_contract_number okc_k_headers_b.contract_number%TYPE;
502 
503 
504 -- ASHIM CHANGE - START
505 
506 
507   /*CURSOR c_amount_past_due(p_contract_id IN NUMBER,
508                            p_grace_days  IN NUMBER) IS
509     SELECT SUM(NVL(aps.amount_due_remaining, 0)) past_due_amount
510     FROM   okl_cnsld_ar_strms_b ocas
511            ,ar_payment_schedules aps
512     WHERE  ocas.khr_id = p_contract_id
513     AND    ocas.receivables_invoice_id = aps.customer_trx_id
514     AND    aps.class ='INV'
515     AND    (aps.due_date + p_grace_days) < sysdate
516     AND    NVL(aps.amount_due_remaining, 0) > 0
517     and not exists
518           (select xls1.lsm_id from
519               okl_xtl_sell_invs_v xls1
520               ,okl_txl_ar_inv_lns_v til1
521               ,okl_trx_ar_invoices_v tai1 where
522               tai1.id = til1.tai_id and
523               til1.id = xls1.til_id and
524               tai1.cpy_id IS NOT NULL and
525               xls1.lsm_id =ocas.id
526            ); */
527 
528   CURSOR c_amount_past_due(p_contract_id IN NUMBER,
529                            p_grace_days  IN NUMBER) IS
530     SELECT SUM(NVL(aps.amount_due_remaining, 0)) past_due_amount
531     FROM   okl_bpd_tld_ar_lines_v ocas
532            ,ar_payment_schedules aps
533     WHERE  ocas.khr_id = p_contract_id
534     AND    ocas.customer_trx_id = aps.customer_trx_id
535     AND    aps.class ='INV'
536     AND    (aps.due_date + p_grace_days) < sysdate
537     AND    NVL(aps.amount_due_remaining, 0) > 0
538     and not exists
539           (select tld.id from
540               --okl_xtl_sell_invs_v xls1
541                okl_txd_ar_ln_dtls_b tld
542               ,okl_txl_ar_inv_lns_v til1
543               ,okl_trx_ar_invoices_v tai1 where
544               tai1.id = til1.tai_id and
545               --til1.id = xls1.til_id and
546               til1.id = tld.til_id_details and
547               tai1.cpy_id IS NOT NULL and
548               --xls1.lsm_id =ocas.id
549               tld.id =ocas.tld_id
550            );
551 
552 
553 -- ASHIM CHANGE - END
554 
555 
556 
557   l_cures_in_possession  NUMBER := 0;
558   l_amount_past_due      NUMBER   :=0;
559   l_days_allowed         NUMBER   :=0;
560 
561   BEGIN
562 
563     -- Process Full Cure Payment
564     write_log(FND_MSG_PUB.G_MSG_LVL_DEBUG_LOW,
565      'Getting cure amounts' || ' and cure_type is ' ||p_cure_type);
566 
567     okl_debug_pub.logmessage('GET_CURE_AMT : START ');
568 
569     IF (p_cure_type = 'Full Cure') THEN
570       -- Get Contract allowed value for days past due from rules
571       l_return_status := okl_contract_info.get_rule_value(
572                               p_contract_id     => p_program_id
573                              ,p_rule_group_code => 'COCURP'
574                              ,p_rule_code		=> 'COCURE'
575                              ,p_segment_number	=> 3
576                              ,x_id1             => l_id1
577                              ,x_id2             => l_id2
578                              ,x_value           => l_rule_value);
579 
580      okl_debug_pub.logmessage('GET_CURE_AMT : okl_contract_info.get_rule_value : '||l_return_status);
581 
582       IF l_return_status =FND_Api.G_RET_STS_SUCCESS THEN
583         l_days_allowed :=nvl(l_rule_value,0);
584         write_log(FND_MSG_PUB.G_MSG_LVL_DEBUG_LOW,
585                  'l_days allowed for days past due ' || l_days_allowed);
586       END IF;
587 
588       okl_debug_pub.logmessage('GET_CURE_AMT : l_days_allowed : '||l_days_allowed);
589 
590       -- Get Past Due Amount
591       OPEN  c_amount_past_due (p_contract_id,l_days_allowed);
592       FETCH c_amount_past_due INTO l_amount_past_due;
593       CLOSE c_amount_past_due;
594 
595       okl_debug_pub.logmessage('GET_CURE_AMT : l_amount_past_due : '||l_amount_past_due);
596 
597       -- cures in possession
598       OPEN  c_cures_in_possession (p_contract_id);
599       FETCH c_cures_in_possession INTO l_cures_in_possession;
600       CLOSE c_cures_in_possession;
601       x_cure_amount :=nvl(l_amount_past_due,0)-nvl(l_cures_in_possession,0);
602 
603     ELSIF  (p_cure_type = 'Interest Cure') THEN
604       x_cure_amount := OKL_seeded_functions_pvt.contract_interest_cure (p_contract_id);
605     END IF;
606 
607     okl_debug_pub.logmessage('GET_CURE_AMT : x_cure_amount : '||x_cure_amount);
608     okl_debug_pub.logmessage('GET_CURE_AMT : END ');
609 
610 EXCEPTION
611   WHEN OTHERS THEN
612     x_return_status := Fnd_Api.G_RET_STS_UNEXP_ERROR;
613     Fnd_Msg_Pub.ADD_EXC_MSG('OKL_CURE_CALC_PVT','GET_CURE_AMT');
614     Fnd_Msg_Pub.count_and_get( p_count   => x_msg_count
615                               ,p_data    => x_msg_data);
616 END GET_CURE_AMT;
617 
618 
619 Procedure Calculate_CAM_COLUMNS ( p_contract_id IN NUMBER,
620                                   p_program_id  IN NUMBER,
621                                   x_cures_in_possession OUT NOCOPY NUMBER,
622                                   x_effective_date      OUT NOCOPY DATE,
623                                   x_payments_remaining  OUT NOCOPY NUMBER,
624                                   x_outstanding_amount  OUT NOCOPY NUMBER,
625                                   x_delinquent_amount   OUT NOCOPY NUMBER)IS
626 
627 
628  cursor c_cures_in_possession (p_contract_id IN NUMBER ) IS
629   select refund_amount_due
630   from okl_cure_refunds_dtls_uv
631   where contract_id =p_contract_id;
632 
633 
634 -- ASHIM CHANGE - START
635 
636 
637   /*CURSOR c_amount_past_due(p_contract_id IN NUMBER,
638                            p_grace_days  IN NUMBER) IS
639     SELECT SUM(NVL(aps.amount_due_remaining, 0)) past_due_amount
640     FROM   okl_cnsld_ar_strms_b ocas
641            ,ar_payment_schedules aps
642     WHERE  ocas.khr_id = p_contract_id
643     AND    ocas.receivables_invoice_id = aps.customer_trx_id
644     AND    aps.class ='INV'
645     AND    (aps.due_date + p_grace_days) < sysdate
646     AND    NVL(aps.amount_due_remaining, 0) > 0
647     and not exists
648           (select xls1.lsm_id from
649               okl_xtl_sell_invs_v xls1
650               ,okl_txl_ar_inv_lns_v til1
651               ,okl_trx_ar_invoices_v tai1 where
652               tai1.id = til1.tai_id and
653               til1.id = xls1.til_id and
654               tai1.cpy_id IS NOT NULL and
655               xls1.lsm_id =ocas.id
656            ); */
657 
658   CURSOR c_amount_past_due(p_contract_id IN NUMBER,
659                            p_grace_days  IN NUMBER) IS
660     SELECT SUM(NVL(aps.amount_due_remaining, 0)) past_due_amount
661     FROM   okl_bpd_tld_ar_lines_v ocas
662            ,ar_payment_schedules aps
663     WHERE  ocas.khr_id = p_contract_id
664     AND    ocas.customer_trx_id = aps.customer_trx_id
665     AND    aps.class ='INV'
666     AND    (aps.due_date + p_grace_days) < sysdate
667     AND    NVL(aps.amount_due_remaining, 0) > 0
668     and not exists
669           (select tld.id from
670               okl_txd_ar_ln_dtls_b tld
671               ,okl_txl_ar_inv_lns_v til1
672               ,okl_trx_ar_invoices_v tai1 where
673               tai1.id = til1.tai_id and
674               til1.id = tld.til_id_details and
675               tai1.cpy_id IS NOT NULL and
676               tld.id =ocas.tld_id
677            );
678 
679 
680 -- ASHIM CHANGE - END
681 
682 
683   l_contract_number okc_k_headers_b.contract_number%TYPE;
684   l_rule_name     VARCHAR2(200);
685   l_rule_value    VARCHAR2(2000);
686   l_return_Status VARCHAR2(1):=FND_Api.G_RET_STS_SUCCESS;
687   l_id1           VARCHAR2(40);
688   l_id2           VARCHAR2(200);
689   l_days_allowed  NUMBER :=0;
690 
691 BEGIN
692 
693       ----------------------------------------------------------
694       -- Get Effective Date for the Vendor Program
695       -- Used to caculate the Cure Amount
696       ----------------------------------------------------------
697 
698 /*       l_rule_value :=NULL;
699        l_return_status := okl_contract_info.get_rule_value(
700                             p_contract_id     => p_program_id
701                            ,p_rule_group_code => 'COCURP'
702                            ,p_rule_code		  => 'COCURE'
703                            ,p_segment_number  => 5
704                            ,x_id1             => l_id1
705                            ,x_id2             => l_id2
706                            ,x_value           => l_rule_value );
707 
708 
709        IF l_rule_value is NOT NULL  THEN
710           x_effective_date := to_date(l_rule_value ||
711                   to_char(SYSDATE,'-MM-RRRR'),'DD-MM-RRRR');
712        ELSE
713            x_effective_date := last_day(sysdate);
714        END IF;
715      */
716 
717        x_effective_date :=SYSDATE;
718 
719        write_log(FND_MSG_PUB.G_MSG_LVL_DEBUG_LOW, ' Effective Day ' ||
720                        ' is ' ||x_effective_date );
721 
722        okl_debug_pub.logmessage('Calculate_CAM_COLUMNS : START ');
723 
724        -- Get remaining payments
725         l_return_status := okl_contract_info.get_remaining_payments
726                                              (  p_contract_id
727                                                ,x_payments_remaining );
728 
729        okl_debug_pub.logmessage('Calculate_CAM_COLUMNS : okl_contract_info.get_remaining_payments : '||l_return_status);
730 
731        IF (l_return_status  <> FND_Api.G_RET_STS_SUCCESS ) THEN
732            x_payments_remaining :=0;
733       END IF;
734       write_log(FND_MSG_PUB.G_MSG_LVL_DEBUG_LOW, 'Remaining_payments is '
735                                                ||x_payments_remaining);
736 
737      -- cures in possession
738      OPEN  c_cures_in_possession (p_contract_id);
739      FETCH c_cures_in_possession INTO x_cures_in_possession;
740      CLOSE c_cures_in_possession;
741 
742      write_log(FND_MSG_PUB.G_MSG_LVL_DEBUG_LOW, 'Cures in possession is '
743                                                 ||x_cures_in_possession);
744 
745      okl_debug_pub.logmessage('Calculate_CAM_COLUMNS : x_cures_in_possession : '||x_cures_in_possession);
746 
747      l_return_status := okl_contract_info.get_rule_value(
748                               p_contract_id     => p_program_id
749                              ,p_rule_group_code => 'COCURP'
750                              ,p_rule_code		=> 'COCURE'
751                              ,p_segment_number	=> 3
752                              ,x_id1             => l_id1
753                              ,x_id2             => l_id2
754                              ,x_value           => l_rule_value);
755 
756      IF l_return_status =FND_Api.G_RET_STS_SUCCESS THEN
757          l_days_allowed :=nvl(l_rule_value,0);
758          write_log(FND_MSG_PUB.G_MSG_LVL_DEBUG_LOW,
759                  'days allowed for days past due ' || l_days_allowed);
760     END IF;
761 
762     okl_debug_pub.logmessage('Calculate_CAM_COLUMNS : l_days_allowed : '||l_days_allowed);
763 
764         -- Get Past Due Amount
765     OPEN  c_amount_past_due (p_contract_id,0);
766     FETCH c_amount_past_due INTO x_outstanding_amount;
767     CLOSE c_amount_past_due;
768 
769     okl_debug_pub.logmessage('Calculate_CAM_COLUMNS : x_outstanding_amount : '||x_outstanding_amount);
770 
771     -- Get Past Due Amount with maximium days allowed
772     OPEN  c_amount_past_due (p_contract_id,l_days_allowed);
773     FETCH c_amount_past_due INTO x_delinquent_amount;
774     CLOSE c_amount_past_due;
775 
776     write_log(FND_MSG_PUB.G_MSG_LVL_DEBUG_LOW, 'Amount past due '
777                                   || ' is ' ||x_outstanding_amount);
778 
779     write_log(FND_MSG_PUB.G_MSG_LVL_DEBUG_LOW, 'Amount past due with maximum day allowed'
780                                   || ' is ' ||x_delinquent_amount);
781     okl_debug_pub.logmessage('Calculate_CAM_COLUMNS : x_delinquent_amount : '||x_delinquent_amount);
782     okl_debug_pub.logmessage('Calculate_CAM_COLUMNS : END ');
783 
784 END Calculate_CAM_COLUMNS;
785 
786 
787 
788 ---------------------------------------------------------------------------
789 -- PROCEDURE CALC_CURE_REPURCHASE
790 ---------------------------------------------------------------------------
791 PROCEDURE CALC_CURE_REPURCHASE(
792   p_api_version               IN NUMBER,
793   p_init_msg_list             IN VARCHAR2 DEFAULT FND_api.G_FALSE,
794   p_contract_id			      IN NUMBER,
795   p_contract_number           IN VARCHAR2,
796   p_program_id                IN NUMBER,
797   p_rule_group_code           IN VARCHAR2,
798   p_cure_calc_flag            IN VARCHAR2,
799   p_process                   IN VARCHAR2,
800   x_repurchase_amount         OUT NOCOPY NUMBER,
801   x_cure_amount               OUT NOCOPY NUMBER,
802   x_return_status             OUT NOCOPY VARCHAR2,
803   x_msg_count                 OUT NOCOPY NUMBER,
804   x_msg_data                  OUT NOCOPY VARCHAR2
805 )
806 IS
807 
808 
809   l_return_status             VARCHAR2(1)  := FND_Api.G_RET_STS_SUCCESS;
810   l_repurchase_amount         NUMBER := 0;
811   l_cure_amount               NUMBER := 0;
812   l_payments_remaining        NUMBER := 0;
813   l_effective_date            DATE;
814   l_negotiated_amount         NUMBER := 0;
815   l_outstanding_amount        NUMBER := 0;
816   l_delinquent_amount         NUMBER := 0;
817   l_cures_in_possession       NUMBER := 0;
818   l_camv_rec                 OKL_cure_amounts_pub.camv_rec_type;
819   x_camv_rec                 OKL_cure_amounts_pub.camv_rec_type;
820   l_msg_count                NUMBER;
821   l_msg_data                 VARCHAR2(32627);
822   l_error_msg_tbl error_message_type;
823 
824   Cursor c_get_negoiated_amt (p_contract_id IN NUMBER) is
825   select nvl(sum(negotiated_amount),0)+ nvl(sum(short_fund_amount),0)
826   from  okl_cure_amounts
827   where chr_id =p_contract_id
828   and   status ='CURESINPROGRESS';
829 
830   --dkagrawa added following cursor to get the org_id MOAC Issue
831   CURSOR c_get_org_id (p_contract_id IN NUMBER) IS
832   SELECT org_id
833   FROM okc_k_headers_b
834   WHERE id = p_contract_id;
835 
836   l_qte_id okl_cure_amounts.qte_id%TYPE;
837 
838 BEGIN
839 
840       SAVEPOINT CALC_CURE_REPURCHASE;
841 
842       okl_debug_pub.logmessage('CALC_CURE_REPURCHASE : START ');
843       okl_debug_pub.logmessage('CALC_CURE_REPURCHASE : p_cure_calc_flag : '||p_cure_calc_flag);
844       okl_debug_pub.logmessage('CALC_CURE_REPURCHASE : p_process : '||p_process);
845 
846       write_log(FND_MSG_PUB.G_MSG_LVL_DEBUG_LOW,
847               'Calc repurchase started for ' || p_contract_number);
848 
849       Calculate_CAM_COLUMNS ( p_contract_id       =>p_contract_id,
850                             p_program_id          =>p_program_id,
851                             x_effective_date      =>l_effective_date,
852                             x_payments_remaining  =>l_payments_remaining,
853                             x_cures_in_possession =>l_cures_in_possession,
854                             x_outstanding_amount  =>l_outstanding_amount,
855                             x_delinquent_amount   =>l_delinquent_amount);
856 
857      SELECT DECODE(Fnd_Global.CONC_REQUEST_ID, -1, NULL, Fnd_Global.CONC_REQUEST_ID),
858           DECODE(Fnd_Global.PROG_APPL_ID, -1, NULL, Fnd_Global.PROG_APPL_ID),
859           DECODE(Fnd_Global.CONC_PROGRAM_ID, -1, NULL, Fnd_Global.CONC_PROGRAM_ID),
860           DECODE(Fnd_Global.CONC_REQUEST_ID, -1, NULL, SYSDATE)
861     INTO l_camv_rec.request_id,
862          l_camv_rec.program_application_id,
863          l_camv_rec.program_id,
864          l_camv_rec.program_update_date
865     FROM DUAL;
866 
867 
868    --09/26
869    -- calculate both cure
870    -- and repurchase
871 
872    IF p_process IN ( 'BOTH', 'REPURCHASE') THEN
873        -- Get Repurchase Amount
874        GET_REPURCHASE_AMT( p_contract_id	=> p_contract_id,
875  	                       x_repurchase_amt => l_repurchase_amount,
876                    	       x_return_status  => l_return_status,
877                    	       x_msg_count      => l_msg_count,
878                    	       x_msg_data       => l_msg_data
879                           ,x_qte_id         => l_qte_id );
880 
881       okl_debug_pub.logmessage('CALC_CURE_REPURCHASE : GET_REPURCHASE_AMT : '||l_return_status);
882 
883       IF (l_return_status  <> FND_Api.G_RET_STS_SUCCESS ) THEN
884           RAISE Fnd_Api.G_EXC_ERROR;
885       ELSE
886            x_repurchase_amount :=l_repurchase_amount;
887       END IF;
888 
889       write_log(FND_MSG_PUB.G_MSG_LVL_DEBUG_LOW, 'Repurchase  amount Is '
890                     ||l_repurchase_amount);
891 
892       okl_debug_pub.logmessage('CALC_CURE_REPURCHASE : GET_REPURCHASE_AMT : l_repurchase_amount : '||l_repurchase_amount);
893 
894     END IF;
895 
896     IF p_process IN ('CURE','BOTH') AND p_cure_calc_flag = 'Interest Cure' THEN
897         l_cure_amount := OKL_seeded_functions_pvt.contract_interest_cure(p_contract_id);
898         x_cure_amount := l_cure_amount;
899 
900         write_log(FND_MSG_PUB.G_MSG_LVL_DEBUG_LOW, 'Interest Cure Amount Is '
901                       ||l_cure_amount);
902 
903         okl_debug_pub.logmessage('CALC_CURE_REPURCHASE : Interest Cure Amount : '||l_cure_amount);
904 
905     END IF;
906 
907     IF p_process IN('CURE','BOTH') AND p_cure_calc_flag = 'Full Cure' THEN
908          -- for full cure
909          --formula is Delinquent_amount -Sum (negotiated_Amount) + Short_Fund_amount)
910          -- for records from cure amounts where chr_id =p_contract_id
911          -- and status ='CURESINPROGRESS''
912             Okl_Execute_Formula_Pub.EXECUTE(p_api_version =>1.0
913                                  ,p_init_msg_list       =>p_init_msg_list
914                                  ,x_return_status       =>l_return_status
915                                  ,x_msg_count           =>l_msg_count
916                                  ,x_msg_data            =>l_msg_data
917                                  ,p_formula_name        => 'CONTRACT_FULL_CURE_AMOUNT'
918                                 ,p_contract_id          => p_contract_id
919                                 ,x_value                => l_cure_amount
920                                 );
921 
922           okl_debug_pub.logmessage('CALC_CURE_REPURCHASE : Okl_Execute_Formula_Pub : '||l_return_status);
923 
924          IF (l_return_status  <> FND_Api.G_RET_STS_SUCCESS ) THEN
925             RAISE Fnd_Api.G_EXC_ERROR;
926          END IF;
927          x_cure_amount := l_cure_amount;  -- Bug 6487958
928 
929         write_log(FND_MSG_PUB.G_MSG_LVL_DEBUG_LOW, 'Cure Amount Is '
930                       ||l_cure_amount);
931 
932         okl_debug_pub.logmessage('CALC_CURE_REPURCHASE : Full Cure : l_cure_amount : '||l_cure_amount);
933 
934   END IF; -- p_process ='CURE'
935 
936 
937   -- Populate the data in OKL_cure_amounts entity for the contract.
938   l_camv_rec.chr_id                := p_contract_id;
939 
940   IF p_process <> 'BOTH' THEN
941     l_camv_rec.cure_type             := p_Process;
942   END IF;
943   l_camv_rec.cure_type             :=p_cure_calc_flag;
944   l_camv_rec.cure_amount           := l_cure_amount;
945   l_camv_rec.repurchase_amount     := l_repurchase_amount;
946   l_camv_rec.effective_date        := l_effective_date;
947   l_camv_rec.cures_in_possession   := l_cures_in_possession;
948   l_camv_rec.status                := 'CURESINPROGRESS';
949   l_camv_rec.object_version_number := 1.0;
950   l_camv_rec.show_on_request       := 'Y';
951   l_camv_rec.selected_on_request   := 'Y';
952   --this is the lessee invoice amount
953   --past due amount <sysdate
954    l_camv_rec.outstanding_amount    := l_outstanding_amount;
955   --this is the delinquent amount after maximium due days allowed
956    l_camv_rec.delinquent_amount  := l_delinquent_amount;
957    l_camv_rec.qte_id             :=l_qte_id;
958    --dkagrawa added following for MOAC Issue
959    OPEN c_get_org_id(p_contract_id);
960    FETCH c_get_org_id INTO l_camv_rec.org_id;
961    CLOSE c_get_org_id;
962 
963    write_log(FND_MSG_PUB.G_MSG_LVL_DEBUG_LOW, 'Before updating Cure Amounts');
964 --   IF (l_negotiated_amount > 0)  THEN
965 
966 
967      IF (l_cure_amount > 0 or l_repurchase_amount > 0) THEN
968        -- Update SHOW_ON_REQUEST to 'N' FOR previous contracts.
969            Update_cure_amounts(
970                                  p_contract_id    =>p_contract_id,
971                                  x_return_status  =>l_return_status,
972                                  x_msg_count      =>l_msg_count,
973                                  x_msg_data       =>l_msg_data );
974 
975            okl_debug_pub.logmessage('CALC_CURE_REPURCHASE : Update_cure_amounts : '||l_return_status);
976 
977             IF l_return_status <> FND_API.G_RET_STS_SUCCESS  THEN
978                 write_log(FND_MSG_PUB.G_MSG_LVL_DEBUG_LOW ,
979                      'Error Updating Cure amounts Table for contract '
980                       || p_contract_number );
981                 GET_ERROR_MESSAGE(l_error_msg_tbl);
982                 IF (l_error_msg_tbl.COUNT > 0) THEN
983                    FOR i IN l_error_msg_tbl.FIRST..l_error_msg_tbl.LAST
984                    LOOP
985                        write_log(FND_MSG_PUB.G_MSG_LVL_DEBUG_HIGH,
986                                    l_error_msg_tbl(i));
987                    END LOOP;
988                END IF; --end of l_error_msg_tbl
989             END IF; --  update_cure_amounts
990  --   END IF; --negotiated _amount;
991 
992      write_log(FND_MSG_PUB.G_MSG_LVL_DEBUG_LOW, 'Before Inserting Cure Amounts');
993 
994      -- Populate null for repurchase amount and cure amount if =0
995      --requested by pdevaraj for UI purposes
996      --09/17/2003
997        IF l_cure_amount = 0 THEN
998           l_camv_rec.cure_amount :=NULL;
999        ELSIF l_camv_rec.repurchase_amount =0 THEN
1000           l_camv_rec.repurchase_amount :=NULL;
1001        END IF;
1002 
1003        OKL_cure_amounts_pub.insert_cure_amounts
1004                          (
1005                             p_api_version    => p_api_version
1006                            ,p_init_msg_list  => p_init_msg_list
1007                            ,x_return_status  => l_return_status
1008                            ,x_msg_count      => l_msg_count
1009                            ,x_msg_data       => l_msg_data
1010                            ,p_camv_rec       => l_camv_rec
1011                            ,x_camv_rec       => x_camv_rec
1012                          );
1013 
1014        okl_debug_pub.logmessage('CALC_CURE_REPURCHASE : OKL_cure_amounts_pub.insert_cure_amounts : '||l_return_status);
1015 
1016         IF (l_return_status  <> FND_Api.G_RET_STS_SUCCESS ) THEN
1017             RAISE Fnd_Api.G_EXC_ERROR;
1018         ELSE
1019               write_log(FND_MSG_PUB.G_MSG_LVL_DEBUG_MEDIUM,
1020               ' Cure amount  is '||x_cure_amount ||
1021               ' Repurchase Amount is '||x_repurchase_amount);
1022         END IF;
1023   ELSE
1024        write_log(FND_MSG_PUB.G_MSG_LVL_DEBUG_MEDIUM,
1025           ' Cure amount or repurchase amount= 0 , so cure amount record is not created');
1026   END IF;
1027 
1028 
1029   x_return_status  := l_return_status;
1030   FND_MSG_PUB.Count_And_Get ( p_count =>   x_msg_count,
1031                              p_data   =>   x_msg_data );
1032 
1033   okl_debug_pub.logmessage('CALC_CURE_REPURCHASE : END ');
1034 
1035 EXCEPTION
1036 
1037     WHEN Fnd_Api.G_EXC_ERROR THEN
1038       ROLLBACK TO CALC_CURE_REPURCHASE;
1039       x_return_status := Fnd_Api.G_RET_STS_ERROR;
1040       x_msg_count := l_msg_count ;
1041       x_msg_data := l_msg_data ;
1042       Fnd_Msg_Pub.count_and_get(
1043              p_count   => x_msg_count
1044             ,p_data    => x_msg_data);
1045     WHEN Fnd_Api.G_EXC_UNEXPECTED_ERROR THEN
1046       ROLLBACK TO CALC_CURE_REPURCHASE;
1047       x_return_status := Fnd_Api.G_RET_STS_UNEXP_ERROR;
1048       x_msg_count := l_msg_count ;
1049       x_msg_data := l_msg_data ;
1050       Fnd_Msg_Pub.count_and_get(
1051              p_count   => x_msg_count
1052             ,p_data    => x_msg_data);
1053     WHEN OTHERS THEN
1054       ROLLBACK TO CALC_CURE_REPURCHASE;
1055       x_return_status := Fnd_Api.G_RET_STS_UNEXP_ERROR;
1056       x_msg_count := l_msg_count ;
1057       x_msg_data := l_msg_data ;
1058       Fnd_Msg_Pub.ADD_EXC_MSG('OKL_CURE_CALC_PVT','CALC_CURE_REPURCHASE');
1059       Fnd_Msg_Pub.count_and_get(
1060              p_count   => x_msg_count
1061             ,p_data    => x_msg_data);
1062 
1063 END CALC_CURE_REPURCHASE ;
1064 
1065 PROCEDURE POPULATE_LOG_TBL(
1066                    p_contract_number IN VARCHAR2,
1067                    p_cure_flag       IN VARCHAR2,
1068                    p_cure_amount     IN NUMBER,
1069                    P_type            IN VARCHAR2) IS
1070 
1071 BEGIN
1072 
1073       If p_type = 'ERROR' THEN
1074          l_error_idx := nvl(l_error_tbl.LAST,0) + 1;
1075          l_error_tbl(l_error_idx).contract_number :=p_contract_number;
1076          l_error_tbl(l_error_idx).cure_type   :=p_cure_flag;
1077          l_error_tbl(l_error_idx).cure_amount := p_cure_amount;
1078       ELSE
1079           l_success_idx := nvl(l_success_tbl.LAST,0) + 1;
1080           l_success_tbl(l_success_idx).contract_number :=p_contract_number;
1081           l_success_tbl(l_success_idx).cure_type   :=p_cure_flag;
1082           l_success_tbl(l_success_idx).cure_amount := p_cure_amount;
1083       END IF;
1084 
1085 
1086 END POPULATE_LOG_TBL;
1087 
1088 PROCEDURE write_log(mesg_level IN NUMBER, mesg IN VARCHAR2) is
1089 BEGIN
1090      if (mesg_level >= l_msgLevel) then
1091         fnd_file.put_line(FND_FILE.LOG, mesg);
1092     end if;
1093 
1094 
1095 END;
1096 
1097 Procedure print_log
1098                 (p_contract_number VARCHAR2) IS
1099 BEGIN
1100 
1101           FND_FILE.PUT_LINE (FND_FILE.OUTPUT, 'OKL Generate Cure Amounts');
1102           FND_FILE.PUT_LINE (FND_FILE.OUTPUT, 'Program Run Date:'||SYSDATE);
1103           FND_FILE.PUT_LINE (FND_FILE.OUTPUT, '***********************************************');
1104           FND_FILE.PUT_LINE (FND_FILE.OUTPUT, 'PARAMETERS');
1105           FND_FILE.PUT_LINE (FND_FILE.OUTPUT, 'Contract Number = ' ||p_contract_number);
1106           FND_FILE.PUT_LINE (FND_FILE.OUTPUT, '***********************************************');
1107 
1108        IF l_success_tbl.COUNT > 0 THEN
1109           FND_FILE.PUT_LINE (FND_FILE.OUTPUT, 'Cure Amounts Generated for '||
1110                                                 l_success_tbl.COUNT || ' Contracts ');
1111           FND_FILE.PUT_LINE (FND_FILE.OUTPUT, '***********************************************');
1112           FOR i in l_success_tbl.FIRST..l_success_tbl.LAST LOOP
1113               FND_FILE.PUT_LINE (FND_FILE.OUTPUT ,'Contract Number ' ||
1114                   l_success_tbl(i).contract_number  || ' Cure Type is '||
1115                   l_success_tbl(i).cure_type        || ' Cure Amount '||
1116                   l_success_tbl(i).cure_amount       );
1117           END LOOP;
1118         END IF;
1119 
1120         IF l_error_tbl.COUNT > 0 THEN
1121           FND_FILE.PUT_LINE (FND_FILE.OUTPUT, 'Cure Amounts Not Generated For '||
1122                                                  l_error_tbl.COUNT || ' Contracts ');
1123           FND_FILE.PUT_LINE (FND_FILE.OUTPUT, '***********************************************');
1124           FOR i in l_error_tbl.FIRST..l_error_tbl.LAST LOOP
1125               FND_FILE.PUT_LINE (FND_FILE.OUTPUT ,'  Contract Number  ' ||
1126                   l_error_tbl(i).contract_number  );
1127 
1128           END LOOP;
1129        END IF;
1130 
1131 END print_log;
1132 
1133 PROCEDURE check_contract(p_contract_id       IN NUMBER
1134                          ,p_program_id       IN NUMBER
1135                          ,p_contract_number  IN VARCHAR2
1136                         ,x_return_status     OUT NOCOPY VARCHAR2) IS
1137 
1138 
1139 l_id1                  VARCHAR2(40);
1140 l_id2                  VARCHAR2(200);
1141 l_rule_value           VARCHAR2(2000);
1142 l_days_allowed         NUMBER   :=0;
1143 l_return_status VARCHAR2(1):= FND_API.G_RET_STS_SUCCESS;
1144 
1145 
1146 
1147 -- ASHIM CHANGE - START
1148 
1149 
1150 /*CURSOR c_amount_past_due(p_contract_id IN NUMBER,
1151                          p_grace_days  IN NUMBER) IS
1152     SELECT SUM(NVL(aps.amount_due_remaining, 0)) past_due_amount
1153     FROM   okl_cnsld_ar_strms_b ocas
1154           ,ar_payment_schedules aps
1155     WHERE  ocas.khr_id = p_contract_id
1156     AND    ocas.receivables_invoice_id = aps.customer_trx_id
1157     AND    aps.class ='INV'
1158     AND    (aps.due_date + p_grace_days) < sysdate
1159     AND    NVL(aps.amount_due_remaining, 0) > 0
1160     AND  not exists
1161           (select xls1.lsm_id from
1162               okl_xtl_sell_invs_v xls1
1163               ,okl_txl_ar_inv_lns_v til1
1164               ,okl_trx_ar_invoices_v tai1 where
1165               tai1.id = til1.tai_id and
1166               til1.id = xls1.til_id and
1167               tai1.cpy_id IS NOT NULL and
1168               xls1.lsm_id =ocas.id);*/
1169 
1170 
1171 CURSOR c_amount_past_due(p_contract_id IN NUMBER,
1172                          p_grace_days  IN NUMBER) IS
1173     SELECT SUM(NVL(aps.amount_due_remaining, 0)) past_due_amount
1174     FROM   okl_bpd_tld_ar_lines_v ocas
1175           ,ar_payment_schedules aps
1176     WHERE  ocas.khr_id = p_contract_id
1177     AND    ocas.customer_trx_id = aps.customer_trx_id
1178     AND    aps.class ='INV'
1179     AND    (aps.due_date + p_grace_days) < sysdate
1180     AND    NVL(aps.amount_due_remaining, 0) > 0
1181     AND  not exists
1182           --(select xls1.lsm_id from
1183           (select tld.id from
1184               --okl_xtl_sell_invs_v xls1
1185               okl_txd_ar_ln_dtls_b tld
1186               ,okl_txl_ar_inv_lns_v til1
1187               ,okl_trx_ar_invoices_v tai1 where
1188               tai1.id = til1.tai_id and
1189               --til1.id = xls1.til_id and
1190               til1.id = tld.til_id_details and
1191               tai1.cpy_id IS NOT NULL and
1192               --xls1.lsm_id =ocas.id);
1193               tld.id =ocas.tld_id);
1194 
1195 -- ASHIM CHANGE - END
1196 
1197 
1198 l_idx INTEGER;
1199 l_amount_past_due NUMBER :=0;
1200 
1201 BEGIN
1202 
1203        x_return_status := FND_API.G_RET_STS_SUCCESS;
1204        write_log(FND_MSG_PUB.G_MSG_LVL_DEBUG_LOW, 'Start of check_contract Procedure' );
1205 
1206        okl_debug_pub.logmessage('check_contract : START ');
1207 
1208        -- Get Contract allowed value for days past due from rules
1209           l_return_status := okl_contract_info.get_rule_value(
1210                               p_contract_id     => p_program_id
1211                              ,p_rule_group_code => 'COCURP'
1212                              ,p_rule_code		=> 'COCURE'
1213                              ,p_segment_number	=> 3
1214                              ,x_id1             => l_id1
1215                              ,x_id2             => l_id2
1216                              ,x_value           => l_rule_value);
1217 
1218        okl_debug_pub.logmessage('check_contract : okl_contract_info.get_rule_value : '||l_return_status);
1219 
1220         IF l_return_status =FND_Api.G_RET_STS_SUCCESS THEN
1221            l_days_allowed :=nvl(l_rule_value,0);
1222            write_log(FND_MSG_PUB.G_MSG_LVL_DEBUG_LOW,
1223                  'No of Past due days allowed from Rule is ' || l_days_allowed);
1224         END IF;
1225 
1226          okl_debug_pub.logmessage('check_contract : l_days_allowed : '||l_days_allowed);
1227 
1228          -- Get Past Due Amount
1229          OPEN  c_amount_past_due (p_contract_id,l_days_allowed);
1230          FETCH c_amount_past_due INTO l_amount_past_due;
1231          CLOSE c_amount_past_due;
1232          write_log(FND_MSG_PUB.G_MSG_LVL_DEBUG_LOW,
1233                  'Amount Past due with grace days is ' || nvl(l_days_allowed,0));
1234 
1235          IF nvl(l_amount_past_due,0) > 0 THEN
1236              write_log(FND_MSG_PUB.G_MSG_LVL_DEBUG_LOW, 'Contract'
1237                          ||p_contract_number || ' is delinquent');
1238             x_return_status  := FND_API.G_RET_STS_ERROR;
1239         END IF;
1240 
1241        okl_debug_pub.logmessage('check_contract : l_amount_past_due : '||l_amount_past_due);
1242        okl_debug_pub.logmessage('check_contract : END ');
1243 
1244 END check_contract;
1245 
1246 
1247 
1248 ---------------------------------------------------------------------------
1249 -- PROCEDURE GENERATE_CURE_AMOUNT
1250 -- This procedure starts the process for all contracts. It starts off by
1251 -- validating if the contract has cure applicable and call populates cure
1252 -- amount. If the contract does not have applicable cure, it is ignored
1253 ---------------------------------------------------------------------------
1254 PROCEDURE GENERATE_CURE_AMOUNT(
1255    errbuf              OUT NOCOPY VARCHAR2,
1256    retcode             OUT NOCOPY NUMBER,
1257    p_contract_number     IN VARCHAR2
1258 )
1259 IS
1260   l_api_version               CONSTANT NUMBER := 1.0;
1261   l_api_name                  CONSTANT VARCHAR2(30) := 'OKL_CURE_CALC_PVT';
1262   l_return_status             VARCHAR2(1) := fnd_api.G_RET_STS_SUCCESS;
1263   l_msg_count                 NUMBER ;
1264   l_msg_data                  VARCHAR2(32627);
1265   l_init_msg_list             VARCHAR2(1) DEFAULT fnd_api.g_false;
1266 
1267   l_cure_flag 			VARCHAR2(1);
1268   l_rule_group_code           VARCHAR2(30) := 'COCURP';
1269   l_rule_code                 VARCHAR2(30) := 'COCURE';
1270   l_rule_name                 VARCHAR2(200);
1271   l_rule_value                VARCHAR2(2000);
1272   l_cure_past_due_allowed     NUMBER ;
1273   l_days_past_due             NUMBER ;
1274   l_no_of_cures               NUMBER :=0;
1275   l_no_of_cures_allowed       NUMBER :=0;
1276   l_repurchase_days_past_allowed NUMBER := -999;
1277   l_cure_calc_flag            VARCHAR2(30);
1278 
1279   l_id1                      VARCHAR2(40);
1280   l_id2                      VARCHAR2(200);
1281 
1282   -- Cursor fetches the contracts for processing
1283   CURSOR contract_csr( p_contract_number IN VARCHAR2) IS
1284     SELECT   prog.id program_id
1285             ,prog.contract_number program_number
1286             ,lease.id contract_id
1287             ,lease.contract_number contract_number
1288             ,rgp.rgd_code
1289     FROM    okc_k_headers_b prog,
1290             okc_k_headers_b lease,
1291             okl_k_headers   khr,
1292             okc_rule_groups_b rgp
1293     WHERE   khr.id = lease.id
1294     AND     khr.khr_id = prog.id
1295     AND     prog.scs_code = 'PROGRAM'
1296     AND     lease.scs_code in ('LEASE','LOAN')
1297     AND     rgp.rgd_code = 'COCURP'
1298     AND     rgp.dnz_chr_id = prog.id
1299     AND     lease.contract_number =nvl(p_contract_number,lease.contract_number) ;
1300 
1301    l_cure_amount okl_cure_amounts.cure_amount%type;
1302 
1303 
1304 
1305 /*if the cure invoice is paid in full (i.e remaining_amount =0)
1306  then it is considered to be cured */
1307 
1308 -- ASHIM CHANGE - START
1309 
1310 
1311  /*cursor c_get_noof_cures(p_contract_id IN NUMBER) is
1312  select count( ps.payment_schedule_id)
1313  from ar_payment_schedules ps
1314      ,okl_cnsld_ar_strms_b stream
1315      ,okl_xtl_sell_invs_v  xls
1316      ,okl_txl_ar_inv_lns_v til
1317      ,okl_trx_ar_invoices_v tai
1318  where ps.class ='INV'
1319       and ps.amount_due_remaining = 0
1320       and stream.receivables_invoice_id = ps.customer_trx_id
1321       and stream.id =xls.lsm_id
1322       and tai.id    = til.tai_id
1323       and til.id    = xls.til_id
1324       and tai.cpy_id IS NOT NULL
1325       and tai.khr_id =p_contract_id;*/
1326 
1327  cursor c_get_noof_cures(p_contract_id IN NUMBER)
1328  is
1329  select count( ps.payment_schedule_id)
1330  from   ar_payment_schedules ps
1331         ,okl_bpd_tld_ar_lines_v stream
1332         --,okl_xtl_sell_invs_v  xls
1333         ,okl_txd_ar_ln_dtls_b  tld
1334         ,okl_txl_ar_inv_lns_v til
1335         ,okl_trx_ar_invoices_v tai
1336  where  ps.class ='INV'
1337  and    ps.amount_due_remaining = 0
1338  and    stream.customer_trx_id = ps.customer_trx_id
1339  --and stream.id =xls.lsm_id
1340  and    stream.tld_id =tld.id
1341  and    tai.id    = til.tai_id
1342  --and til.id    = xls.til_id
1343  and    til.id    = tld.til_id_details
1344  and    tai.cpy_id IS NOT NULL
1345  and    tai.khr_id =p_contract_id;
1346 
1347 -- ASHIM CHANGE - END
1348 
1349 
1350   l_error_msg_tbl error_message_type;
1351 
1352  /* Get min due date for the contract */
1353 
1354 -- ASHIM CHANGE - START
1355 
1356 
1357   /*cursor  l_days_past_due_cur (p_contract_id IN NUMBER) is
1358         SELECT  min(aps.due_date)
1359         FROM    okl_cnsld_ar_strms_b ocas
1360                ,ar_payment_schedules aps
1361                ,okc_k_headers_b chr
1362                ,OKL_STRM_TYPE_TL SM
1363         WHERE
1364                ocas.khr_id = p_contract_id
1365           AND  ocas.receivables_invoice_id = aps.customer_trx_id
1366           AND  aps.class = 'INV'
1367           AND  aps.due_date < sysdate
1368           AND  NVL(aps.amount_due_remaining, 0) > 0
1369           AND  ocas.khr_id=chr.id
1370           AND sm.ID = ocas.STY_ID and sm.name <> 'CURE'    ;*/
1371 
1372   cursor  l_days_past_due_cur (p_contract_id IN NUMBER)
1373   is
1374   SELECT  min(aps.due_date)
1375   FROM    okl_bpd_tld_ar_lines_v ocas
1376           ,ar_payment_schedules aps
1377           ,okc_k_headers_b chr
1378           ,OKL_STRM_TYPE_TL SM
1379   WHERE   ocas.khr_id = p_contract_id
1380   AND     ocas.customer_trx_id = aps.customer_trx_id
1381   AND     aps.class = 'INV'
1382   AND     aps.due_date < sysdate
1383   AND     NVL(aps.amount_due_remaining, 0) > 0
1384   AND     ocas.khr_id=chr.id
1385   AND     sm.ID = ocas.STY_ID and sm.name <> 'CURE'    ;
1386 
1387 -- ASHIM CHANGE - END
1388 
1389 
1390 
1391 x_contract_number okc_k_headers_b.contract_number%TYPE;
1392 
1393 l_default_date DATE :=TRUNC(SYSDATE);
1394 l_days_past    DATE ;
1395 
1396 l_process VARCHAR2(50);
1397 l_process1 VARCHAR2(50);
1398 l_process2 VARCHAR2(50);
1399 l_repurchase_amount NUMBER;
1400 
1401 BEGIN
1402 
1403   okl_debug_pub.logmessage('GENERATE_CURE_AMOUNT: START');
1404   okl_debug_pub.logmessage('GENERATE_CURE_AMOUNT: p_contract_number : ' || p_contract_number);
1405 
1406         write_log(FND_MSG_PUB.G_MSG_LVL_DEBUG_HIGH, 'OKL Generate Cure Amounts');
1407         write_log(FND_MSG_PUB.G_MSG_LVL_DEBUG_HIGH, 'Program Run Date:'||SYSDATE);
1408         write_log(FND_MSG_PUB.G_MSG_LVL_DEBUG_HIGH, '***********************************************');
1409         write_log(FND_MSG_PUB.G_MSG_LVL_DEBUG_HIGH, 'PARAMETERS');
1410         write_log(FND_MSG_PUB.G_MSG_LVL_DEBUG_HIGH, 'Contract Number = ' ||p_contract_number);
1411         write_log(FND_MSG_PUB.G_MSG_LVL_DEBUG_HIGH, '***********************************************');
1412 
1413     -- Open the contract cursor for process
1414     FOR i IN contract_csr(p_contract_number)
1415     LOOP
1416          write_log(FND_MSG_PUB.G_MSG_LVL_DEBUG_MEDIUM, '***********************************************');
1417          write_log(FND_MSG_PUB.G_MSG_LVL_DEBUG_MEDIUM,' Processing: Contract Number=> '
1418                                 ||i.contract_number);
1419          write_log(FND_MSG_PUB.G_MSG_LVL_DEBUG_MEDIUM, ' Program number is ' ||i.program_number);
1420          write_log(FND_MSG_PUB.G_MSG_LVL_DEBUG_MEDIUM, ' Contract Id    is ' ||i.contract_id);
1421 
1422       okl_debug_pub.logmessage('GENERATE_CURE_AMOUNT: p_contract_number : ' || i.program_number);
1423       okl_debug_pub.logmessage('GENERATE_CURE_AMOUNT: p_contract_number : ' || i.contract_id);
1424 
1425       --need to process other contract if the first one errors out
1426       --so introducing this while loop
1427 
1428       WHILE TRUE LOOP
1429          -- Initialize the variables
1430          l_rule_value := NULL;
1431          l_cure_past_due_allowed := 0;
1432          l_days_past_due := 0;
1433          l_no_of_cures := 0;
1434          l_no_of_cures_allowed := 0;
1435          l_repurchase_days_past_allowed := 0;
1436          l_cure_calc_flag := NULL;
1437          l_return_status :=FND_Api.G_RET_STS_SUCCESS;
1438          l_days_past :=SYSDATE;
1439         -----------------------------------------------------------------
1440         -- CHECK IF THE CONTRACT HAS CURE RULE - WE DO NOT GENERATE CURES
1441         -- FOR CONTRACT THAT DOES NOT HAVE CURE AGREEMENT
1442         -- we need to the pass the vendor program id to get the
1443         -- cure rule values.
1444         -----------------------------------------------------------------
1445          l_return_status := okl_contract_info.get_rule_value(
1446                               p_contract_id     => i.program_id
1447                              ,p_rule_group_code => l_rule_group_code
1448                              ,p_rule_code		=> l_rule_code
1449                              ,p_segment_number	=> 1
1450                              ,x_id1             => l_id1
1451                              ,x_id2             => l_id2
1452                              ,x_value           => l_rule_value);
1453 
1454          IF (l_return_status <> FND_API.G_RET_STS_SUCCESS) THEN
1455             write_log(FND_MSG_PUB.G_MSG_LVL_DEBUG_LOW ,
1456                'Did not return a value for cure applicable Rule ');
1457              POPULATE_LOG_TBL(
1458                   p_contract_number =>i.contract_number,
1459                   p_cure_flag       =>NULL,
1460                   p_cure_amount     =>NULL,
1461                   P_type            =>'ERROR');
1462              EXIT;
1463           ELSE
1464               write_log(FND_MSG_PUB.G_MSG_LVL_DEBUG_LOW ,
1465                      'Is Cure Applicable and rule value is ' || l_rule_value);
1466           END IF;
1467 
1468           okl_debug_pub.logmessage('GENERATE_CURE_AMOUNT: Cure Applicable rule value : ' || l_rule_value);
1469 
1470           IF (l_rule_value <> 'Yes') THEN
1471               write_log(FND_MSG_PUB.G_MSG_LVL_DEBUG_LOW ,
1472                        'Is not cure applicable ');
1473              POPULATE_LOG_TBL(
1474                   p_contract_number =>i.contract_number,
1475                   p_cure_flag       =>NULL,
1476                   p_cure_amount     =>NULL,
1477                   P_type            =>'ERROR');
1478              EXIT;
1479           END IF;
1480 
1481           ------------------------------------------------------------------
1482           --check if the contract is come out of delinquency
1483           --if so, update cure amounts table SHOW_ON_REQUEST 'N' for the given
1484           --contract.
1485           --Check if any of the contracts are in delinquency
1486           --We are going to check if the contract has any delinquent
1487           --invoices.(due_date + gracedays(from rule) < SYSDATE )
1488          --Alternate way was to check if the case with the contract
1489          --is in was in Delinquency or not. ( this would not consider
1490          --                                    the grace days)
1491          ------------------------------------------------------------------
1492 
1493          CHECK_CONTRACT(i.contract_id,
1494                         i.program_id,
1495                         i.contract_number,
1496                         l_return_status);
1497 
1498 
1499          IF l_return_status = FND_API.G_RET_STS_SUCCESS  THEN
1500 
1501              write_log(FND_MSG_PUB.G_MSG_LVL_DEBUG_LOW ,
1502                       'Contract  ' || i.contract_number ||
1503                       'is Not Delinquent ');
1504 
1505              okl_debug_pub.logmessage('GENERATE_CURE_AMOUNT: Contract ' || i.contract_number || ' is Not Delinquent');
1506 
1507              Update_cure_amounts(
1508                                  p_contract_id    =>i.contract_id,
1509                                  x_return_status  =>l_return_status,
1510                                  x_msg_count      =>l_msg_count,
1511                                  x_msg_data       =>l_msg_data );
1512 
1513              IF l_return_status <> FND_API.G_RET_STS_SUCCESS  THEN
1514                 write_log(FND_MSG_PUB.G_MSG_LVL_DEBUG_LOW ,
1515                      'Error Updating Cure amounts Table for contract '
1516                       || i.contract_number );
1517                 GET_ERROR_MESSAGE(l_error_msg_tbl);
1518                 IF (l_error_msg_tbl.COUNT > 0) THEN
1519                    FOR i IN l_error_msg_tbl.FIRST..l_error_msg_tbl.LAST
1520                    LOOP
1521                        write_log(FND_MSG_PUB.G_MSG_LVL_DEBUG_HIGH,
1522                                    l_error_msg_tbl(i));
1523                    END LOOP;
1524                END IF; --end of l_error_msg_tbl
1525             END IF; --  update_cure_amounts
1526             POPULATE_LOG_TBL(
1527                   p_contract_number =>i.contract_number,
1528                   p_cure_flag       =>NULL,
1529                   p_cure_amount     =>NULL,
1530                   P_type            =>'ERROR');
1531             EXIT;
1532          END IF; -- end of check_contract
1533 
1534           ------------------------------------------------------------------
1535           --check if the contract is already there in the cure amount table
1536           -- and also the negotiated amount is populated
1537           --(this indicates that a cure invoice was created for that contract)
1538           -- and status ='CURESINPROGRESS'
1539           --this is because the concurrent program can be run more than once
1540           -- in a month.
1541          ------------------------------------------------------------------
1542 
1543 
1544            OPEN  l_days_past_due_cur(i.contract_id);
1545            FETCH l_days_past_due_cur INTO l_days_past;
1546            CLOSE l_days_past_due_cur;
1547 
1548          l_days_past_due := l_default_date - nvl(TRUNC(l_days_past),
1549                                                    l_default_date);
1550 
1551          write_log(FND_MSG_PUB.G_MSG_LVL_DEBUG_LOW,
1552                    'Days past due  is ' ||l_days_past_due);
1553 
1554          okl_debug_pub.logmessage('GENERATE_CURE_AMOUNT: Days past due : ' || l_days_past_due);
1555           ----------------------------------------------------------
1556           -- Get Contract allowed value for days past due from rules
1557           --For Cure
1558           ----------------------------------------------------------
1559           l_rule_value := NULL;
1560           l_return_status := okl_contract_info.get_rule_value(
1561                               p_contract_id     => i.program_id
1562                              ,p_rule_group_code => l_rule_group_code
1563                              ,p_rule_code		=> l_rule_code
1564                              ,p_segment_number		=> 3
1565                              ,x_id1             => l_id1
1566                              ,x_id2             => l_id2
1567                              ,x_value           => l_rule_value);
1568 
1569          IF (l_return_status <> fnd_api.G_RET_STS_SUCCESS) THEN
1570             write_log(FND_MSG_PUB.G_MSG_LVL_DEBUG_LOW ,
1571                      'Did not return a value for days past due ');
1572 
1573              POPULATE_LOG_TBL(
1574                   p_contract_number =>i.contract_number,
1575                   p_cure_flag       =>NULL,
1576                   p_cure_amount     =>NULL,
1577                   P_type            =>'ERROR');
1578              EXIT;
1579           ELSE
1580               write_log(FND_MSG_PUB.G_MSG_LVL_DEBUG_LOW ,'Days past '||
1581                       'due allowed from rule is '
1582                                     || l_rule_value);
1583                l_cure_past_due_allowed :=nvl(l_rule_value,0);
1584           END IF;
1585 
1586          okl_debug_pub.logmessage('GENERATE_CURE_AMOUNT: Days past due allowed for Cure : ' || l_cure_past_due_allowed);
1587 
1588           ----------------------------------------------------------
1589           -- Get Contract allowed value for days past due from rules
1590           -- For repurchase
1591           ----------------------------------------------------------
1592 
1593             l_rule_value := NULL;
1594             l_return_status := okl_contract_info.get_rule_value(
1595                               p_contract_id     => i.program_id
1596                              ,p_rule_group_code => l_rule_group_code
1597                              ,p_rule_code		=> 'CORPUR'
1598                              ,p_segment_number  => 1
1599                              ,x_id1             => l_id1
1600                              ,x_id2             => l_id2
1601                              ,x_value           => l_rule_value);
1602 
1603             IF (l_return_status <> fnd_api.G_RET_STS_SUCCESS) THEN
1604               write_log(FND_MSG_PUB.G_MSG_LVL_DEBUG_LOW ,
1605                 'Did not return a value for days past due allowed for Repurchase'  );
1606               POPULATE_LOG_TBL(
1607                   p_contract_number =>i.contract_number,
1608                   p_cure_flag       =>NULL,
1609                   p_cure_amount     =>NULL,
1610                   P_type            =>'ERROR');
1611               EXIT;
1612             ELSE
1613               write_log(FND_MSG_PUB.G_MSG_LVL_DEBUG_LOW,
1614                  'Days_past due_allowed for repurchase is  ' || l_rule_value);
1615                  l_repurchase_days_past_allowed := nvl(l_rule_value,0);
1616            END IF;
1617 
1618            okl_debug_pub.logmessage('GENERATE_CURE_AMOUNT: Days past due allowed for repurchase : ' || l_repurchase_days_past_allowed);
1619 
1620           ----------------------------------------------------------
1621           -- Get no of cures made against contract
1622           -- For repurchase
1623           ----------------------------------------------------------
1624 
1625             l_no_of_cures := 0;
1626             OPEN  c_get_noof_cures(i.contract_id);
1627             FETCH c_get_noof_cures INTO l_no_of_cures;
1628             CLOSE c_get_noof_cures;
1629 
1630             write_log(FND_MSG_PUB.G_MSG_LVL_DEBUG_LOW, ' No of cures  is '
1631                                                           ||l_no_of_cures);
1632 
1633             okl_debug_pub.logmessage('GENERATE_CURE_AMOUNT: No of cures from cursor : ' || l_no_of_cures);
1634 
1635             -- Now get the no of cures allowed value from Rule
1636             l_rule_value := NULL;
1637             l_return_status := okl_contract_info.get_rule_value(
1638                               p_contract_id     => i.program_id
1639                              ,p_rule_group_code => l_rule_group_code
1640                              ,p_rule_code		=> 'CORPUR'
1641                              ,p_segment_number	=> 2
1642                              ,x_id1             => l_id1
1643                              ,x_id2             => l_id2
1644                              ,x_value           => l_rule_value);
1645 
1646             IF (l_return_status <> fnd_api.G_RET_STS_SUCCESS) THEN
1647               write_log(FND_MSG_PUB.G_MSG_LVL_DEBUG_LOW ,
1648                         'Did not return a value for no of cures allowed ');
1649               POPULATE_LOG_TBL(
1650                   p_contract_number =>i.contract_number,
1651                   p_cure_flag       =>NULL,
1652                   p_cure_amount     =>NULL,
1653                   P_type            =>'ERROR');
1654               EXIT;
1655             ELSE
1656               write_log(FND_MSG_PUB.G_MSG_LVL_DEBUG_LOW ,
1657                       'No of cures allowed before Repurchase is ' || l_rule_value);
1658               l_no_of_cures_allowed := nvl(l_rule_value,0);
1659             END IF;
1660 
1661             okl_debug_pub.logmessage('GENERATE_CURE_AMOUNT: No of cures from rule : ' || l_no_of_cures_allowed);
1662 
1663             /* If days past due is more than days past due allowed
1664                and number of cures received is more than number of
1665                cures allowed for repurchase, ask for repurchase, else
1666                cure
1667                --09/26 logic has been changed ,we could have CURE and repurchase
1668                -- for the same record, so introducing a new field -Process
1669             */
1670 
1671 
1672            --1) if   l_days_past_due  > l_cure_past_due_allowed -- CURE
1673            --2) if    l_days_past_due  > l_repurchase_days_past_allowed
1674                       --and l_no_of_cures > l_no_of_cures_allowed -- REPURCHASE
1675 
1676 
1677             IF  l_days_past_due >  l_cure_past_due_allowed THEN
1678                 l_process1 := 'CURE';
1679             END IF;
1680 
1681             IF  l_days_past_due >  l_repurchase_days_past_allowed
1682                  and l_no_of_cures > l_no_of_cures_allowed THEN
1683                  l_process2 := 'REPURCHASE';
1684             END IF;
1685 
1686             IF  l_process1 IS NOT NULL and l_process2 is NOT NULL  THEN
1687                   l_process  := 'BOTH' ;
1688             ELSIF l_process1 IS NOT NULL THEN
1689                   l_process  := l_process1;
1690             ELSIF  l_process2 IS NOT NULL THEN
1691                   l_process  := l_process2;
1692             ELSE
1693                  write_log(FND_MSG_PUB.G_MSG_LVL_DEBUG_LOW ,
1694                          'Did not Satisfy The Rule Values ');
1695                  POPULATE_LOG_TBL(
1696                   p_contract_number =>i.contract_number,
1697                   p_cure_flag       =>NULL,
1698                   p_cure_amount     =>NULL,
1699                   P_type            =>'ERROR');
1700               EXIT;
1701           END IF;
1702 
1703            write_log(FND_MSG_PUB.G_MSG_LVL_DEBUG_MEDIUM, ' Contract '||
1704                    i.contract_number || ' will be in ' ||l_process);
1705 
1706            okl_debug_pub.logmessage('GENERATE_CURE_AMOUNT: Contract '||  i.contract_number || ' is processed for ' ||l_process);
1707 
1708             /* Check if the contract is in litigation
1709                The code will be added once the source is finalized
1710                The code will check if the contract is in litigation,
1711                if so, we will utilize the cure type set up for contract
1712                under litigation otherwise use the default cure type
1713                (FULL, INTEREST)
1714             */
1715 
1716             IF l_process IN ('CURE','BOTH')THEN
1717 
1718                   -- add litigation check here
1719                    ----------------------------------------------------------
1720                   -- Get Contract cure type from rules
1721                   ----------------------------------------------------------
1722                   l_rule_value := NULL;
1723                   l_return_status := okl_contract_info.get_rule_value(
1724                                    p_contract_id     => i.program_id
1725                                   ,p_rule_group_code => l_rule_group_code
1726                                   ,p_rule_code	     => l_rule_code
1727                                   ,p_segment_number  => 2
1728                                   ,x_id1             => l_id1
1729                                   ,x_id2             => l_id2
1730                                   ,x_value           => l_rule_value );
1731 
1732                  IF (l_return_status <> fnd_api.G_RET_STS_SUCCESS) THEN
1733                      write_log(FND_MSG_PUB.G_MSG_LVL_DEBUG_LOW ,
1734                        'Did not return a value for Type of Cure '  );
1735                      POPULATE_LOG_TBL(
1736                        p_contract_number =>i.contract_number,
1737                        p_cure_flag       =>NULL,
1738                        p_cure_amount     =>NULL,
1739                        P_type            =>'ERROR');
1740                     EXIT;
1741                  ELSE
1742                      write_log(FND_MSG_PUB.G_MSG_LVL_DEBUG_LOW ,
1743                        'Type of Cure is ' || l_rule_value);
1744                  END IF;
1745                  l_cure_calc_flag := l_rule_value;
1746 
1747             END IF; --(l_cure_calc_flag = 'CURE')
1748 
1749 
1750             CALC_CURE_REPURCHASE( p_api_version       =>l_api_version,
1751                                   p_init_msg_list     =>l_init_msg_list,
1752  				                  p_contract_id       =>i.contract_id,
1753                                   p_contract_number   =>i.contract_number,
1754                                   p_program_id        =>i.program_id,
1755                                   p_rule_group_code   =>l_rule_group_code,
1756                                   p_cure_calc_flag    =>l_cure_calc_flag,
1757                                   p_process           =>l_process,
1758                                   x_repurchase_amount =>l_repurchase_amount,
1759                                   x_cure_amount       =>l_cure_amount,
1760                                   x_return_status     =>l_return_status,
1761                                   x_msg_count         =>l_msg_count,
1762                                   x_msg_data          =>l_msg_data );
1763 
1764               okl_debug_pub.logmessage('GENERATE_CURE_AMOUNT: after CALC_CURE_REPURCHASE : '|| l_return_status);
1765 
1766               write_log(FND_MSG_PUB.G_MSG_LVL_DEBUG_MEDIUM,
1767               'Result of Cure or Repurchase for contract_number '||
1768                 i.contract_number || ' is ' ||l_return_status);
1769 
1770             IF (l_return_status <> fnd_api.G_RET_STS_SUCCESS) THEN
1771               GET_ERROR_MESSAGE(l_error_msg_tbl);
1772               IF (l_error_msg_tbl.COUNT > 0) THEN
1773                  write_log(FND_MSG_PUB.G_MSG_LVL_DEBUG_HIGH,' Error in calculating repurchase');
1774                 FOR i IN l_error_msg_tbl.FIRST..l_error_msg_tbl.LAST
1775                 LOOP
1776                   write_log(FND_MSG_PUB.G_MSG_LVL_DEBUG_HIGH,
1777                                    l_error_msg_tbl(i));
1778                 END LOOP;
1779               END IF;
1780               POPULATE_LOG_TBL(
1781                      p_contract_number =>i.contract_number,
1782                      p_cure_flag       =>l_cure_calc_flag,
1783                      p_cure_amount     =>l_cure_amount,
1784                      P_type            =>'ERROR');
1785             ELSE
1786                   POPULATE_LOG_TBL(
1787                      p_contract_number =>i.contract_number,
1788                      p_cure_flag       =>l_cure_calc_flag,
1789                      p_cure_amount     =>l_cure_amount,
1790                      P_type            =>'SUCCESS');
1791             END IF;
1792 
1793           EXIT; --for while loop
1794        END LOOP; --end of while loop
1795     END LOOP;
1796     Print_log (p_contract_number);
1797     retcode :=0; --success
1798 
1799   okl_debug_pub.logmessage('GENERATE_CURE_AMOUNT: END');
1800 
1801   EXCEPTION
1802   WHEN OTHERS THEN
1803         FND_FILE.PUT_LINE (FND_FILE.OUTPUT, 'Error (OTHERS)IN OKL_CURE_CALC_PVT => '||SQLERRM);
1804         retcode :=2;
1805         errbuf :=SQLERRM;
1806 
1807 END GENERATE_CURE_AMOUNT;
1808 
1809 END OKL_CURE_CALC_PVT;