DBA Data[Home] [Help]

PACKAGE BODY: APPS.XTR_MM_COVERS

Source


1 PACKAGE BODY XTR_MM_COVERS AS
2 /* $Header: xtrmmcvb.pls 120.29.12010000.2 2008/08/06 10:43:40 srsampat ship $ */
3 
4 ----------------------------------------------------------------------------------------------------------------
5 -- This is just a cover function that determines whether CALC_DAYS_RUN or
6 -- CALC_DAYS_RUN_B should be called
7 -- use this procedure instead of CALC_DAYS_RUN if ACT/ACT-BOND day count basis
8 -- is used
9 -- When this procedure is called, and if the method is ACT/ACT-BOND,be aware of
10 -- the fact that year_basis will be
11 -- calculated incorrectly if start_date and end_date combined do not form a
12 -- coupon period. So, if year_basis are needed, make sure that, coupon periods
13 -- are sent in as parameters. num_days are calculated correctly all the time
14 PROCEDURE CALC_DAYS_RUN_C(start_date IN DATE,
15                           end_date   IN DATE,
16                           method     IN VARCHAR2,
17                           frequency  IN NUMBER,
18                           num_days   IN OUT NOCOPY NUMBER,
19                           year_basis IN OUT NOCOPY NUMBER,
20                           fwd_adjust IN NUMBER,
21 			  day_count_type IN VARCHAR2,
22 			  first_trans_flag IN VARCHAR2) is
23 --
24 begin
25    if method = 'ACT/ACT-BOND' then
26       CALC_DAYS_RUN_B(start_date,end_date,method,frequency, num_days,
27                       year_basis);
28    else
29       -- Added the day_count_type and first_trans_flag paramters
30       -- for Interest override feature.
31 
32       CALC_DAYS_RUN(start_date,end_date,method, num_days,year_basis, fwd_adjust,
33 		    day_count_type, first_trans_flag);
34    end if;
35 end CALC_DAYS_RUN_C;
36 
37 
38 -- This calculates the number of days and year basis for bond only day count
39 -- basis(ACT/ACT-BOND)
40 -- For ACT/ACT-BOND day count basis, this procedure must be used or preferably
41 -- through CALC_DAYS_RUN_C. CALC_DAYS_RUN must not be used for the day count
42 -- basis
43 -- When this procedure is called, be aware of the fact that year_basis will be
44 -- calculated incorrectly if start_date and end_date combined do not form a
45 -- coupon period. So, if year_basis are needed, make sure that, coupon periods
46 -- are sent in as parameters. num_days are calculated correctly all the time
47 PROCEDURE CALC_DAYS_RUN_B(start_date IN DATE,
48                           end_date   IN DATE,
49                           method     IN VARCHAR2,
50                           frequency  IN NUMBER,
51                           num_days   IN OUT NOCOPY NUMBER,
52                           year_basis IN OUT NOCOPY NUMBER) is
53 --
54    l_start_date DATE := start_date;
55    l_end_date   DATE := end_date;
56 
57    l_start_year NUMBER := to_number(to_char(start_date,'YYYY'));
58    l_end_year NUMBER := to_number(to_char(end_date,'YYYY'));
59 
60 --
61 begin
62    if start_date is not null and end_date is not null and method is not null then
63       if l_end_date <l_start_date then
64          FND_MESSAGE.Set_Name('XTR', 'XTR_1059');
65          APP_EXCEPTION.raise_exception;
66       else
67          num_days := l_end_date - l_start_date;
68          if method = 'ACT/ACT-BOND' then
69             year_basis:=(l_end_date-l_start_date) * frequency;
70          else
71             APP_EXCEPTION.raise_exception;
72          end if;
73       end if;
74    end if;
75 end CALC_DAYS_RUN_B;
76 
77 
78 -- Calculate over a Year Basis and Number of Days ased on different calc
79 -- methods.  Note that this procedure now supports ACTUAL/365L day count basis,
80 -- but it does not support ACT/ACT-BOND day count basis. In order to use the day
81 -- count basis, CALC_DAYS_RUN_C must be used
82 PROCEDURE CALC_DAYS_RUN(start_date IN DATE,
83                         end_date   IN DATE,
84                         method     IN VARCHAR2,
85                         num_days   IN OUT NOCOPY NUMBER,
86                         year_basis IN OUT NOCOPY NUMBER,
87                         fwd_adjust IN NUMBER DEFAULT NULL,
88                         day_count_type IN VARCHAR2 DEFAULT NULL,
89                         first_trans_flag IN VARCHAR2 DEFAULT NULL) is
90 -- Bug 3511403 start Used the same code of calc_days_run_ig in xtr_calc_p package to make it generic fix
91 --
92    l_start_date DATE := start_date;
93    l_end_date   DATE := end_date;
94    l_start_year NUMBER := to_number(to_char(start_date,'YYYY'));
95    l_end_year NUMBER := to_number(to_char(end_date,'YYYY'));
96    start_year_basis     NUMBER;
97    end_year_basis       NUMBER;
98    l_total_days         NUMBER;
99    l_total_year NUMBER:= l_end_year - l_start_year;
100 --
101 begin
102    -- Bug 6743063 start commented below code
103  /* if day_count_type = 'L' or day_count_type = 'B' then
104      l_start_date :=l_start_date +1;
105      l_end_date := l_end_date +1 ;
106    end if; */
107    -- Bug 6743063 end
108    if start_date is not null and end_date is not null and method is not null then
109 
110       if l_end_date <l_start_date then
111          FND_MESSAGE.Set_Name('XTR', 'XTR_1059');
112          APP_EXCEPTION.raise_exception;
113 
114       else
115 
116          -------------------------------
117          -- For all ACTUAL year basis --
118          -------------------------------
119          if substr(method,1,6) = 'ACTUAL' then
120             num_days := l_end_date - l_start_date;
121             year_basis := 365;
122 
123             if method = 'ACTUAL360' then
124                year_basis := 360;
125             elsif method = 'ACTUAL365' then
126                year_basis := 365;
127             elsif method = 'ACTUAL365L' then
128                -- if the "to year" is a leap year use 366 day count basis. Otherwise, use 365
129                if to_char(last_day(to_date('01/02'||to_char(l_end_date,'YYYY'),'DD/MM/YYYY')),'DD') = '29' then
130                   year_basis:=366;
131                else
132                   year_basis:=365;
133                end if;
134             elsif method = 'ACTUAL/ACTUAL' then
135               -- Bug 3511403 start
136 	      -- Bug 6880961 start added condition start year not equal to end year
137                if (day_count_type = 'L' or day_count_type = 'B') and (l_end_year <> l_start_year ) then
138                  l_start_date :=l_start_date +1;
139                  l_end_date := l_end_date +1 ;
140                end if;
141              -- Bug 3511403 end
142             /***************************************************************/
143             /* Bug 3511403 Correct Actual/Actual calculation  */
144             /***************************************************************/
145                If l_end_year = l_start_year then -- same year. Determine whether it's leap year.
146                   if to_char(last_day(to_date('01/02'||to_char(l_end_date,'YYYY'),
147                      'DD/MM/YYYY')),'DD') = '29' then
148                      year_basis := 366;
149                   else
150                      year_basis := 365;
151                   end if;
152                else
153                   if to_char(last_day(to_date('01/02'||to_char(l_start_date,'YYYY'),
154                      'DD/MM/YYYY')),'DD') = '29' then
155                      IF day_count_type='B' AND first_trans_flag ='Y' THEN
156                         start_year_basis := (to_date('1/1/'||to_char(l_start_year+1),'DD/MM/YYYY')                                - l_start_date + 1) /366;
157                      else
158                         start_year_basis := (to_date('1/1/'||to_char(l_start_year+1),'DD/MM/YYYY')
159                                 - l_start_date) /366;
160                      end if;
161                   else
162                      IF day_count_type='B' AND first_trans_flag ='Y' THEN
163                         start_year_basis := (to_date('1/1/'||to_char(l_start_year+1),'DD/MM/YYYY')                                    - l_start_date + 1) / 365;
164                      else
165                         start_year_basis := (to_date('1/1/'||to_char(l_start_year+1),'DD/MM/YYYY')                                    - l_start_date) / 365;
166                      end if;
167                   end if;
168 
169                   if to_char(last_day(to_date('01/02'||to_char(l_end_date,'YYYY'),
170                      'DD/MM/YYYY')),'DD') = '29' then
171                      end_year_basis := (l_end_date - to_date('1/1/'||to_char(l_end_year),
172                                         'DD/MM/YYYY')) / 366;
173                   else
174                      end_year_basis := (l_end_date - to_date('1/1/'||to_char(l_end_year),
175                                         'DD/MM/YYYY')) / 365;
176                   end if;
177 
178                   IF day_count_type='B' AND first_trans_flag ='Y' THEN
179                       l_total_days := num_days +1;
180                   else
181                       l_total_days := num_days;
182                   END IF;
183 
184                    Year_basis := l_total_days / (start_year_basis + (l_total_year -1)
185                                  + end_year_basis);
186                 End if;
187 	    End if;
188 
189             -------------------------------
190             -- Interest Override feature --
191             -- Adde Day count type logic --
192             -------------------------------
193             IF day_count_type='B' AND first_trans_flag ='Y' THEN
194                num_days := num_days +1;
195             END IF;
196          ------------------------------
197          -- For all other year basis --
198          ------------------------------
199          else
200 
201             /*-------------------------------------------------------------------------------------------*/
202             /* AW 2113171       This date is adjusted when called in CALCULATE_ACCRUAL_AMORTISATION.     */
203             /* Need to add one day back to it for FORWARD, and then adjust later in num_days
204 (see below).*/
205             /* The 'fwd_adjust' parameter is used 30/360, 30E/360, 30E+/360 calculations.
206             */
207             /* If it is 1, then it is Forward, if it is 0, then it is Arrear.
208             */
209             /*-------------------------------------------------------------------------------------------*/
210                l_start_date := start_date + nvl(fwd_adjust,0);
211             /*-------------------------------------------------------------------------------------------*/
212 
213             -- Calculate over a 360 basis based on different calc methods
214             year_basis :=360;
215 
216             if method = '30/' then
217                if to_number(to_char(start_date + nvl(fwd_adjust,0),'DD')) = 31 then
218 -- AW 2113171
219                   -- make start date = 30th ie add 1 day
220                   l_start_date := start_date + nvl(fwd_adjust,0) - 1;
221 -- AW 2113171
222                end if;
223                if to_number(to_char(end_date,'DD')) = 31 then
224                   if to_number(to_char(start_date + nvl(fwd_adjust,0),'DD')) in(30,31) then
225 -- AW 2113171
226                      -- make end date = 30th if end date = 31st
227                      -- only if start date is 30th or 31st ie minus 1 day from calc
228                      l_end_date := end_date  - 1;
229                   end if;
230                end if;
231             elsif method = '30E/' then
232                if to_number(to_char(start_date + nvl(fwd_adjust,0),'DD')) = 31 then
233 -- AW 2113171
234                   -- make start date = 30th ie add 1 day
235                   l_start_date := start_date + nvl(fwd_adjust,0)  - 1;
236 -- AW 2113171
237                end if;
238                if to_number(to_char(end_date,'DD')) = 31 then
239                   -- make end date = 30th ie minus 1 day
240                   l_end_date := end_date - 1;
241                end if;
242             elsif method = '30E+/' then
243                if to_number(to_char(start_date + nvl(fwd_adjust,0),'DD')) = 31 then
244 -- AW 2113171
245                   -- make start date = 30th ie add 1 day
246                   l_start_date := start_date + nvl(fwd_adjust,0)  - 1;
247 -- AW 2113171
248                end if;
249                if to_number(to_char(end_date,'DD')) = 31 then
250                   -- make end date = 1st of the next month
251                   l_end_date := end_date + 1;
252                end if;
253             end if;
254 
255             -- Calculate based on basic 30/360 method
256             --with the above modifications
257             num_days := to_number(to_char(l_end_date,'DD')) -
258                         to_number(to_char(l_start_date,'DD')) +
259                         (30 * (
260                         to_number(to_char(l_end_date,'MM')) -
261                         to_number(to_char(l_start_date,'MM')))) +
262                         (360 * (
263                         to_number(to_char(l_end_date,'YYYY')) -
264                         to_number(to_char(l_start_date,'YYYY'))));
265 
266             /*-----------------------------------------------*/
267             /* AW 2113171                                    */
268             /*-----------------------------------------------*/
269              num_days := num_days + nvl(fwd_adjust,0);
270             /*-----------------------------------------------*/
271 
272          end if;
273 
274       end if;
275 
276    end if;
277 -- Bug 3511403 End
278 end CALC_DAYS_RUN;
279 /*----------------------------------------------------------------------------
280  Calculates the future value given either the yield or discount rate as
281  the input.
282 
283  IMPORTANT: There are two ways to use this API, the first one is passing in
284 	the p_DAY_COUNT and p_ANNUAL_BASIS, the second one is passing in the
285 	Present Value date (p_PV_DATE), Future Value date (p_FV_DATE),
286 	p_DAY_COUNT_BASIS, p_RATE_TYPE, and p_COMPOUND_FREQ.
287 	The second method is the one that should be used due to some
288 	complications in determining whether a period is less or greater
289 	than a year (refer to Bug 2295869) and whether a rate should be a
290 	simple rate (period is less than a year) or annually compounding rate
291 	(period is greater than or equal to a year).
292 
293  RECORD Data Type:
294    IN:    P_INDICATOR varchar2
295           P_PRESENT_VALUE num
296           P_RATE num
297           P_DAY_COUNT num
298           P_ANNUAL_BASIS num
299           P_PV_DATE date
300           P_FV_DATE date
301           P_DAY_COUNT_BASIS varchar2
302  	  P_RATE_TYPE varchar2
303 	  P_COMPOUND_FREQ number
304    OUT:   P_FUTURE_VAL num
305 
306  * P_INDICATOR is to differentiate whether the rate is a discount rate or a
307    yield rate.(Y=Yield Rate, DR=Discount Rate).
308  * P_FUTURE_VAL = the amount at maturity .
309  * P_PRESENT_VAL  = the fair value of the discounted security.
310  * P_RATE = Yield Rate or Discount Rate (annualized)
311  * P_DAY_COUNT = number of days between the PRESENT_VALUE date and
312    FUTURE_VALUE date. This parameter must be NULL if want
313    (For example: DAY_COUNT = Maturity Date -
314    Settlement Date in Discounted Securities Calculator HLD).
315  * P_ANNUAL_BASIS = number of days in a year where the RATE and the
316    DAY_COUNT are based on.
317  * P_PV_DATE = the PRESENT_VALUE date (For example: p_PV_DATE =  Settlement
318 	Date in Discounted Securities Calculator HLD).
319  * P_FV_DATE = the FUTURE_VALUE date (For example: p_FV_DATE =  Maturity
320 	Date in Discounted Securities Calculator HLD).
321  * P_DAY_COUNT_BASIS = the day count basis of p_RATE.
322  * P_RATE_TYPE = the rate type of p_RATE. Possible values are: (S)imple,
323 	com(P)ounded, and (C)ontinuous.
324  * P_COMPOUND_FREQ = the compounding frequency of P_RATE, only necessary if
325 	p_RATE_TYPE='P'.
326 ----------------------------------------------------------------------------*/
327 PROCEDURE future_value(p_in_rec  IN futureValue_in_rec_type,
328 		       p_out_rec IN OUT NOCOPY futureValue_out_rec_type) IS
329 
330   v_in_rec xtr_rate_conversion.df_in_rec_type;
331   v_out_rec xtr_rate_conversion.df_out_rec_type;
332   v_rate NUMBER;
333   v_cf_necessary BOOLEAN := FALSE;
334   v_extensive BOOLEAN := FALSE;
335   v_ann_basis NUMBER;
336   v_day_count NUMBER;
337 BEGIN
338 --  xtr_risk_debug_pkg.dpush('XTR_MM_COVERS.FUTURE_VALUE');
339 
340   --Determine whether p_compounding_freq is necessary
341   IF p_in_rec.p_rate_type='P' THEN
342     v_cf_necessary := TRUE;
343   END IF;
344 
345   --Determine whether we need to calc using p_RATE_TYPE,
346   --p_COMPOUND_FREQ(if p_RATE_TYPE='P'), p_FUTURE_DATE,
347   --p_SPOT_DATE, and p_DAY_COUNT_BASIS
348   IF p_in_rec.p_fv_date IS NOT NULL AND p_in_rec.p_pv_date IS NOT NULL
349   AND p_in_rec.p_day_count_basis IS NOT NULL AND p_in_rec.p_rate_type IS NOT
350   NULL AND ((v_cf_necessary AND p_in_rec.p_compound_freq IS NOT NULL)
351   OR NOT v_cf_necessary) THEN
352     --Calculate the annual basis and day count based on ACT/ACT to get
353     --fair comparison
354     v_extensive := TRUE;
355   END IF;
356 
357   IF (p_in_rec.p_indicator = 'Y') THEN
358      IF v_extensive THEN
359        --use discount factor method
360        v_in_rec.p_indicator:='T';
361        v_in_rec.p_spot_date:=p_in_rec.p_pv_date;
362        v_in_rec.p_future_date:=p_in_rec.p_fv_date;
363        v_in_rec.p_rate:=p_in_rec.p_rate;
364        v_in_rec.p_rate_type:=p_in_rec.p_rate_type;
365        v_in_rec.p_compound_freq:=p_in_rec.p_compound_freq;
366        v_in_rec.p_day_count_basis:=p_in_rec.p_day_count_basis;
367        xtr_rate_conversion.discount_factor_conv(v_in_rec,v_out_rec);
368        v_rate:=v_out_rec.p_result;
369        p_out_rec.p_future_val:=p_in_rec.p_present_val/v_rate;
370      ELSIF (p_in_rec.p_day_count<=p_in_rec.p_annual_basis) THEN
371        xtr_mm_formulas.future_value_yield_rate(p_in_rec.p_present_val,
372 					      p_in_rec.p_rate,
373 				 	      p_in_rec.p_day_count,
374 					      p_in_rec.p_annual_basis,
375 					      p_out_rec.p_future_val);
376      ELSE
377        --use discount factor method
378        v_in_rec.p_indicator:='T';
379        v_in_rec.p_day_count:=p_in_rec.p_day_count;
380        v_in_rec.p_annual_basis:=p_in_rec.p_annual_basis;
381        v_in_rec.p_rate:=p_in_rec.p_rate;
382        xtr_rate_conversion.discount_factor_conv(v_in_rec,v_out_rec);
383        v_rate:=v_out_rec.p_result;
384        p_out_rec.p_future_val:=p_in_rec.p_present_val/v_rate;
385      END IF;
386   ELSIF (p_in_rec.p_indicator = 'DR') THEN
387      IF v_extensive THEN
388        -- use discount factor method, but first find the yield rate to be
389        --able to convert to discount factor
390        calc_days_run_c(p_in_rec.p_pv_date, p_in_rec.p_fv_date,
391 	p_in_rec.p_day_count_basis, null, v_day_count, v_ann_basis);
392 
393        xtr_rate_conversion.discount_to_yield_rate(p_in_rec.p_rate,
394 						v_day_count,
395 						v_ann_basis,
396 						v_rate);
397        --use discount factor method
398        v_in_rec.p_indicator:='T';
399        v_in_rec.p_spot_date:=p_in_rec.p_pv_date;
400        v_in_rec.p_future_date:=p_in_rec.p_fv_date;
401        v_in_rec.p_rate:=v_rate;
402        v_in_rec.p_rate_type:=p_in_rec.p_rate_type;
403        v_in_rec.p_compound_freq:=p_in_rec.p_compound_freq;
404        v_in_rec.p_day_count_basis:=p_in_rec.p_day_count_basis;
405        xtr_rate_conversion.discount_factor_conv(v_in_rec,v_out_rec);
406        v_rate:=v_out_rec.p_result;
407        p_out_rec.p_future_val:=p_in_rec.p_present_val/v_rate;
408      ELSIF (p_in_rec.p_day_count<=p_in_rec.p_annual_basis) THEN
409         xtr_mm_formulas.future_value_discount_rate(p_in_rec.p_present_val,
410 						 p_in_rec.p_rate,
411 						 p_in_rec.p_day_count,
412 						 p_in_rec.p_annual_basis,
413 						 p_out_rec.p_future_val);
414      ELSE
415        -- use discount factor method, but first find the yield rate to be
416        --able to convert to discount factor
417        xtr_rate_conversion.discount_to_yield_rate(p_in_rec.p_rate,
418 						p_in_rec.p_day_count,
419 						p_in_rec.p_annual_basis,
420 						v_rate);
421        --convert to disc. factor
422        v_in_rec.p_indicator:='T';
423        v_in_rec.p_day_count:=p_in_rec.p_day_count;
424        v_in_rec.p_annual_basis:=p_in_rec.p_annual_basis;
425        v_in_rec.p_rate:=v_rate;
426        xtr_rate_conversion.discount_factor_conv(v_in_rec,v_out_rec);
427        v_rate:=v_out_rec.p_result;
428 
429        --FV with disc. factor
430        p_out_rec.p_future_val:=p_in_rec.p_present_val/v_rate;
431 
432      END IF;
433   ELSE
434      --
435      -- error message!!!!!!!!!!!!!!!!!!!!!
436      --
437      RAISE_APPLICATION_ERROR(-20001, 'The indicator should be either ''Y'' '||
438 				'or ''D'' or ''DR''.');
439 
440   END IF;
441 
442 --  xtr_risk_debug_pkg.dpop('XTR_MM_COVERS.FUTURE_VALUE');
443 
444 END future_value;
445 
446 
447 
448 /*----------------------------------------------------------------------------
449  Calculates the present value given either the yield rate, discount rate,
450  or discount factor as the input.
451 
452  IMPORTANT: There are two ways to use this API, the first one is passing in
453 	the p_DAY_COUNT and p_ANNUAL_BASIS, the second one is passing in the
454 	Present Value date (p_PV_DATE), Future Value date (p_FV_DATE),
455 	p_DAY_COUNT_BASIS, p_RATE_TYPE, and p_COMPOUND_FREQ.
456 	The second method is the one that should be used due to some
457 	complications in determining whether a period is less or greater
458 	than a year (refer to Bug 2295869) and whether a rate should be a
459 	simple rate (period is less than a year) or annually compounding rate
460 	(period is greater than or equal to a year).
461 
462  RECORD Data Type:
463     IN:     P_INDICATOR char
464             P_FUTURE_VALUE num
465             P_RATE nu
466             P_DAY_COUNT date default
467             P_ANNUAL_BASIS num default
468     OUT:    P_PRESENT_VALUE num
469 
470  * P_INDICATOR is to differentiate whether the rate is a discount rate,
471    a yield rate, or a disocunt factor.(Y=Yield Rate, DR=Discount Rate,
472    D=Disount Factor).
473  * P_FUTURE_VAL = the amount at maturity .
474  * P_PRESENT_VAL  = the fair value of the discounted security.
475  * P_RATE = Yield Rate, Discount Rate, or Discount Factor (annualized)
476  * P_DAY_COUNT = number of days between the PRESENT_VALUE date and
477    FUTURE_VALUE date. (For example: DAY_COUNT = Maturity Date -
478    Settlement Date in Discounted Securities Calculator HLD).
479  * P_ANNUAL_BASIS = number of days in a year where the RATE and the
480    DAY_COUNT are based on.
481  * P_PV_DATE = the PRESENT_VALUE date (For example: p_PV_DATE =  Settlement
482 	Date in Discounted Securities Calculator HLD).
483  * P_FV_DATE = the FUTURE_VALUE date (For example: p_FV_DATE =  Maturity
484 	Date in Discounted Securities Calculator HLD).
485  * P_DAY_COUNT_BASIS = the day count basis of p_RATE.
486  * P_RATE_TYPE = the rate type of p_RATE. Possible values are: (S)imple,
487 	com(P)ounded, and (C)ontinuous.
488  * P_COMPOUND_FREQ = the compounding frequency of P_RATE, only necessary if
489 	p_RATE_TYPE='P'.
490 ----------------------------------------------------------------------------*/
491 PROCEDURE present_value(p_in_rec  IN presentValue_in_rec_type,
492 		        p_out_rec IN OUT NOCOPY presentValue_out_rec_type) IS
493   v_rate NUMBER;
494   v_in_rec xtr_rate_conversion.df_in_rec_type;
495   v_out_rec xtr_rate_conversion.df_out_rec_type;
496   v_cf_necessary BOOLEAN := FALSE;
497   v_extensive BOOLEAN := FALSE;
498   v_day_count NUMBER;
499   v_ann_basis NUMBER;
500 BEGIN
501   IF xtr_risk_debug_pkg.g_Debug THEN
502      xtr_risk_debug_pkg.dpush('XTR_MM_COVERS.PRESENT_VALUE');
503   END IF;
504 
505   --Determine whether p_compounding_freq is necessary
506   IF p_in_rec.p_rate_type='P' THEN
507     v_cf_necessary := TRUE;
508   END IF;
509 
510   --Determine whether we need to calc using p_RATE_TYPE,
511   --p_COMPOUND_FREQ(if p_RATE_TYPE='P'), p_FUTURE_DATE,
512   --p_SPOT_DATE, and p_DAY_COUNT_BASIS
513   IF p_in_rec.p_fv_date IS NOT NULL AND p_in_rec.p_pv_date IS NOT NULL
514   AND p_in_rec.p_day_count_basis IS NOT NULL AND p_in_rec.p_rate_type IS NOT
515   NULL  AND ((v_cf_necessary AND p_in_rec.p_compound_freq IS NOT NULL)
516   OR NOT v_cf_necessary) THEN
517     --Calculate the annual basis and day count based on ACT/ACT to get
518     --fair comparison
519     v_extensive := TRUE;
520   END IF;
521 
522   IF (p_in_rec.p_indicator = 'Y') THEN
523      IF v_extensive THEN
524        --use discount factor method
525        v_in_rec.p_indicator:='T';
526        v_in_rec.p_spot_date:=p_in_rec.p_pv_date;
527        v_in_rec.p_future_date:=p_in_rec.p_fv_date;
528        v_in_rec.p_rate:=p_in_rec.p_rate;
529        v_in_rec.p_rate_type:=p_in_rec.p_rate_type;
530        v_in_rec.p_compound_freq:=p_in_rec.p_compound_freq;
531        v_in_rec.p_day_count_basis:=p_in_rec.p_day_count_basis;
532        xtr_rate_conversion.discount_factor_conv(v_in_rec,v_out_rec);
533        v_rate:=v_out_rec.p_result;
534        xtr_mm_formulas.present_value_discount_factor(v_rate,
535 						   p_in_rec.p_future_val,
536 						   p_out_rec.p_present_val);
537      ELSIF (p_in_rec.p_day_count<=p_in_rec.p_annual_basis) THEN
538        xtr_mm_formulas.present_value_yield_rate(p_in_rec.p_future_val,
539 				 	      p_in_rec.p_rate,
540 				 	      p_in_rec.p_day_count,
541 				 	      p_in_rec.p_annual_basis,
542 				 	      p_out_rec.p_present_val);
543      ELSE
544        --use discount factor method
545        v_in_rec.p_indicator:='T';
546        v_in_rec.p_day_count:=p_in_rec.p_day_count;
547        v_in_rec.p_annual_basis:=p_in_rec.p_annual_basis;
548        v_in_rec.p_rate:=p_in_rec.p_rate;
549        xtr_rate_conversion.discount_factor_conv(v_in_rec,v_out_rec);
550        v_rate:=v_out_rec.p_result;
551 
552        xtr_mm_formulas.present_value_discount_factor(v_rate,
553 						   p_in_rec.p_future_val,
554 						   p_out_rec.p_present_val);
555      END IF;
556   ELSIF (p_in_rec.p_indicator = 'DR') THEN
557      IF v_extensive THEN
558        -- use discount factor method, but first find the yield rate to be
559        --able to convert to discount factor
560        calc_days_run_c(p_in_rec.p_pv_date, p_in_rec.p_fv_date,
561 	p_in_rec.p_day_count_basis, null, v_day_count, v_ann_basis);
562 
563        xtr_rate_conversion.discount_to_yield_rate(p_in_rec.p_rate,
564 						v_day_count,
565 						v_ann_basis,
566 						v_rate);
567        --use discount factor method
568        v_in_rec.p_indicator:='T';
569        v_in_rec.p_spot_date:=p_in_rec.p_pv_date;
570        v_in_rec.p_future_date:=p_in_rec.p_fv_date;
571        v_in_rec.p_rate:=v_rate;
572        v_in_rec.p_rate_type:=p_in_rec.p_rate_type;
573        v_in_rec.p_compound_freq:=p_in_rec.p_compound_freq;
574        v_in_rec.p_day_count_basis:=p_in_rec.p_day_count_basis;
575        xtr_rate_conversion.discount_factor_conv(v_in_rec,v_out_rec);
576        v_rate:=v_out_rec.p_result;
577        xtr_mm_formulas.present_value_discount_factor(v_rate,
578 						   p_in_rec.p_future_val,
579 						   p_out_rec.p_present_val);
580      ELSIF (p_in_rec.p_day_count<=p_in_rec.p_annual_basis) THEN
581        xtr_mm_formulas.present_value_discount_rate(p_in_rec.p_future_val,
582 				    		 p_in_rec.p_rate,
583 						 p_in_rec.p_day_count,
584 				    		 p_in_rec.p_annual_basis,
585 				    		 p_out_rec.p_present_val);
586      ELSE
587        -- use discount factor method, but first find the yield rate to be
588        --able to convert to discount factor
589        xtr_rate_conversion.discount_to_yield_rate(p_in_rec.p_rate,
590 						p_in_rec.p_day_count,
591 						p_in_rec.p_annual_basis,
592 						v_rate);
593 
594        --convert to disc. factor
595        v_in_rec.p_indicator:='T';
596        v_in_rec.p_day_count:=p_in_rec.p_day_count;
597        v_in_rec.p_annual_basis:=p_in_rec.p_annual_basis;
598        v_in_rec.p_rate:=v_rate;
599        xtr_rate_conversion.discount_factor_conv(v_in_rec,v_out_rec);
600        v_rate:=v_out_rec.p_result;
601 
602        --PV with disc. factor
603        xtr_mm_formulas.present_value_discount_factor(v_rate,
604 						   p_in_rec.p_future_val,
605 						   p_out_rec.p_present_val);
606 
607      END IF;
608 
609   ELSIF (p_in_rec.p_indicator = 'D') THEN
610        xtr_mm_formulas.present_value_discount_factor(p_in_rec.p_rate,
611 						   p_in_rec.p_future_val,
612 						   p_out_rec.p_present_val);
613   ELSE
614      --
615      -- error message!!!!!!!!!!!!!!!!!!!!
616      --
617      RAISE_APPLICATION_ERROR(-20001, 'The indicator should be either ''Y'' '||
618 				'or ''D'' or ''DR''.');
619   END IF;
620 
621   IF xtr_risk_debug_pkg.g_Debug THEN
622      xtr_risk_debug_pkg.dpop('XTR_MM_COVERS.PRESENT_VALUE');
623   END IF;
624 
625 END present_value;
626 
627 
628 
629 --
630 -- Calculates the FRA Settlement Amount in FRA Calculator when the input
631 -- parameter is set to 'Yield'.
632 --
633 -- RECORD Data Type:
634 --    IN:     P_INDICATOR char
635 --            P_FRA_PRICE num
636 --            P_SETTLEMENT_RATE num
637 --            P_FACE_VALUE num
638 --            P_DAY_COUNT num
639 --            P_ANNUAL_BASIS num
640 --    OUT:    P_SETTLEMENT_AMOUNT num
641 --
642 -- * P_INDICATOR is to differentiate whether the settlement rate parameter
643 --   is a discount rate or a yield rate.(Y=Yield Rate, DR=Discount Rate).
644 -- * P_A_PRICE = fra_rate = fair contract rate of FRA (forward interest
645 --   rate covering from the Start Date to the Maturity Date of the contract).
646 -- * P_SETTLEMENT_RATE = current market annual interest rate.
647 -- * P_FACE_VALUE  = notional principal amount of FRA.
648 -- * P_DAY_COUNT = number of days between the Settlement Date to Maturity Date.
649 -- * P_ANNUAL_BASIS = number of days in a year the SETTLEMENT_RATE and
650 --   DAY_COUNT are based on.
651 -- * P_SETTLEMENT_AMOUNT = absolute profit or loss amount
652 -- * p_DEAL_TYPE = an indicator whether the deal subtype is fund ('FUND') or
653 --   invest ('INVEST'). This affects whether one pay/loss (-) or receive/gain (+)
654 --   in the settlement.
655 --
656 PROCEDURE fra_settlement_amount(p_in_rec  IN fra_settlement_in_rec_type,
657 			       p_out_rec IN OUT NOCOPY fra_settlement_out_rec_type) IS
658 
659 BEGIN
660 
661   IF (p_in_rec.p_indicator = 'Y') THEN
662     xtr_mm_formulas.fra_settlement_amount_yield(p_in_rec.p_fra_price,
663 					   p_in_rec.p_settlement_rate,
664 					   p_in_rec.p_face_value,
665 					   p_in_rec.p_day_count,
666 					   p_in_rec.p_annual_basis,
667 					   p_out_rec.p_settlement_amount);
668 
669   ELSIF (p_in_rec.p_indicator = 'DR') THEN
670     xtr_mm_formulas.fra_settlement_amount_discount(p_in_rec.p_fra_price,
671 				   	   p_in_rec.p_settlement_rate,
672 				   	   p_in_rec.p_face_value,
673 				   	   p_in_rec.p_day_count,
674 				   	   p_in_rec.p_annual_basis,
675 				   	   p_out_rec.p_settlement_amount);
676   ELSE
677 
678      --
679      -- error !!!!!!!!!!!!!!!!!!!!!!
680      --
681      RAISE_APPLICATION_ERROR(-20001, 'The indicator should be either ''Y'' '||
682 				'or ''D''.');
683   END IF;
684 
685   --determine the sign of the settlement amount base on the deal subtype
686   IF (p_in_rec.p_deal_subtype IS NOT NULL) THEN
687     IF (UPPER(p_in_rec.p_deal_subtype) = 'FUND') THEN
688       IF (p_in_rec.p_fra_price > p_in_rec.p_settlement_rate) THEN
689         p_out_rec.p_settlement_amount := -p_out_rec.p_settlement_amount;
690       END IF;
691     ELSIF (UPPER(p_in_rec.p_deal_subtype) = 'INVEST') THEN
692       IF (p_in_rec.p_fra_price < p_in_rec.p_settlement_rate) THEN
693         p_out_rec.p_settlement_amount := -p_out_rec.p_settlement_amount;
694       END IF;
695     ELSE
696       RAISE_APPLICATION_ERROR(-20001, 'The indicator should be either ''FUND'' '||
697 				'or ''INVEST''.');
698     END IF;
699   END IF;
700 
701 END fra_settlement_amount;
702 
703 
704 /*----------------------------------------------------------------------------
705 INTEREST_FORWARD_RATE
706 
707 Calculates the FRA Price (Interest Forward Rate) given either yield rates or
708 discount factors as input.
709 
710 INT_FORW_RATE_IN_REC_TYPE
711 IN:     p_indicator
712 	p_t num
713 	p_T1 num
714 	p_Rt num
715 	p_RT1 num
716 	p_year_basis num
717 INT_FORW_RATE_OUT_REC_TYPE
718 OUT: 	p_fra_rate num
719 
720 Assumption:  all interest rates (p_Rt and p_Rt1)  have the same day count
721 basis.
722 p_t = number of days from today to start date
723 p_T1 = number of days from today to maturity date
724 p_Rt = if p_indicator = 'Y' : annualized interest rate for maturity in
725   p_t days, if p_indicator = 'D': discount factor for maturity in p_t days.
726 p_RT1 = if p_indicator = 'Y' : annualized interest rate for maturity in p_T1
727   days, if p_indicator = 'D': discount factor for maturity in p_T1 days.
728 p_year_basis = number of days in a year the interest rate is based on.
729 p_fra_rate = fair contract rate of FRA (forward interest rate covering from
730   the Start Date to the Maturity Date).
731 p_indicator = an indicator whether the input rates are yield rates ('Y') or
732   discount factors ('D').
733 ----------------------------------------------------------------------------*/
734 PROCEDURE interest_forward_rate (p_in_rec IN int_forw_rate_in_rec_type,
735 				p_out_rec OUT NOCOPY int_forw_rate_out_rec_type) AS
736 
737   v_rate_short NUMBER;
738   v_rate_long NUMBER;
739   v_rc_in xtr_rate_conversion.rate_conv_in_rec_type;
740   v_rc_out xtr_rate_conversion.rate_conv_out_rec_type;
741   v_df_in xtr_rate_conversion.df_in_rec_type;
742   v_df_out xtr_rate_conversion.df_out_rec_type;
743 
744 BEGIN
745   IF xtr_risk_debug_pkg.g_Debug THEN
746      xtr_risk_debug_pkg.dpush('XTR_MM_COVERS.INTEREST_FORWARD_RATE');
747   END IF;
748 
749   IF (p_in_rec.p_indicator IN ('D','d')) THEN
750     xtr_mm_formulas.fra_price_df(p_in_rec.p_t, p_in_rec.p_T1,
751 				p_in_rec.p_Rt, p_in_rec.p_Rt1,
752 				p_in_rec.p_year_basis, p_out_rec.p_fra_rate);
753   ELSIF (p_in_rec.p_indicator IN ('Y','y')) THEN
754   --also use FRA Price from DF formula
755     v_df_in.p_indicator := 'T';
756     --convert the first rate: spot to start date rate
757     v_df_in.p_rate := p_in_rec.p_Rt;
758     v_df_in.p_day_count := p_in_rec.p_t;
759     v_df_in.p_annual_basis := p_in_rec.p_year_basis;
760     xtr_rate_conversion.discount_factor_conv(v_df_in, v_df_out);
761     v_rate_short := v_df_out.p_result;
762 IF xtr_risk_debug_pkg.g_Debug THEN
763    xtr_risk_debug_pkg.dlog('interest_forward_rate: ' || 'v_rate_short',v_rate_short);
764 END IF;
765     --convert the second rate: spot to maturity date rate
766     v_df_in.p_rate := p_in_rec.p_RT1;
767     v_df_in.p_day_count := p_in_rec.p_T1;
768     v_df_in.p_annual_basis := p_in_rec.p_year_basis;
769     xtr_rate_conversion.discount_factor_conv(v_df_in, v_df_out);
770     v_rate_long := v_df_out.p_result;
771 IF xtr_risk_debug_pkg.g_Debug THEN
772    xtr_risk_debug_pkg.dlog('interest_forward_rate: ' || 'v_rate_long',v_rate_long);
773 END IF;
774     xtr_mm_formulas.fra_price_df(p_in_rec.p_t, p_in_rec.p_T1,
775 				v_rate_short, v_rate_long,
776 				p_in_rec.p_year_basis, p_out_rec.p_fra_rate);
777 
778   ELSE
779     RAISE_APPLICATION_ERROR(-20001, 'The indicator should be either ''Y'' '||
780 				'or ''D''.');
781   END IF;
782 
783   IF xtr_risk_debug_pkg.g_Debug THEN
784      xtr_risk_debug_pkg.dpop('XTR_MM_COVERS.INTEREST_FORWARD_RATE');
785   END IF;
786 END interest_forward_rate;
787 
788 
789 /*----------------------------------------------------------------------------
790 BLACK_OPTION_PRICE_CV
791 
792 Calculates the price of the interest rate option price using Black's Formula.
793 Record Data Type
794 BLACK_OPT_CV_IN_REC_TYPE
795 IN:
796 p_PRINCIPAL num
797 p_STRIKE_RATE num
798 p_IR_SHORT num
799 p_RATE_TYPE_SHORT varchar2 DEFAULT 'S'
800 p_COMPOUND_FREQ_SHORT num
801 p_DAY_COUNT_BASIS_SHORT varchar2
802 p_IR_LONG num
803 p_RATE_TYPE_LONG varchar2 DEFAULT 'S'
804 p_COMPOUND_FREQ_LONG num
805 p_DAY_COUNT_BASIS_LONG varchar2
806 p_SPOT_DATE date
807 p_START_DATE date
808 p_MATURITY_DATE date
809 p_VOLATILITY num
810 
811 BLACK_OPT_CV_OUT_REC_TYPE
812 OUT:
813 p_CAPLET_PRICE num
814 p_FLOORLET_PRICE num
815 p_Nd1 num
816 p_Nd2 num
817 p_Nd1_A num
818 p_Nd2_A num
819 
820 p_PRINCIPAL = the principal amount from which the interest rate is calculated
821 p_STRIKE_RATE = Rx = simple interest rate for the deal
822 p_IR_SHORT = market simple interest rate for the period between the spot date
823   and the start date
824 p_RATE_TYPE_SHORT = the p_IR_SHORT rate's type. 'S' for Simple Rate.
825   'C' for Continuous Rate, and 'P' for Compounding Rate.
826   Default value = 'S' (Simple IR).
827 p_DAY_COUNT_BASIS_SHORT = day count basis for p_IR_SHORT
828 p_IR_LONG = market simple interest rate for the period between the spot date and
829   the maturity date
830 p_RATE_TYPE_LONG = the p_IR_LONG rate's type. 'S' for Simple Rate. 'C' for
831   Continuous Rate, and 'P' for Compounding Rate. Default value = 'S' (Simple IR)
832 p_DAY_COUNT_BASIS_LONG = day count basis for p_IR_LONG
833 p_SPOT_DATE = the date when the evaluation/calculation is done
834 p_START_DATE = the date when the deal becomes effective.
835 p_END_DATE = the date when the deal matures.
836 p_VOLATILITY = volatility of interest rate per annum
837 p_CAPLET_PRICE = interest rate collars
838 p_FLOORLET_PRICE = interest rate floors (CAPLET_PRICE = FLOORLET_PRICE + SWAP_VALUE)
839 p_Nd1/2 = cumulative distribution value given limit probability values in
840   Black's formula = N(x) (refer to Hull's Fourth Edition p.252)
841 p_Nd1/2_A = N'(x) in Black's formula (refer to Hull's Fourth Edition p.252)
842 p_COMPOUND_FREQ_SHORT/LONG = frequencies of discretely compounded input/output rate.
843 This is only necessary if either p_RATE_TYPE_SHORT or p_RATE_TYPE_LONG is 'P'.
844 p_FORWARD_RATE = forward rate from start date to maturity date with compound frequency equivalent to the time span between start date and maturity date (=simple rate).
845 ----------------------------------------------------------------------------*/
846 PROCEDURE black_option_price_cv (p_in_rec IN black_opt_cv_in_rec_type,
847 				p_out_rec OUT NOCOPY black_opt_cv_out_rec_type) IS
848 
849   v_rc_in xtr_rate_conversion.rate_conv_in_rec_type;
850   v_rc_out xtr_rate_conversion.rate_conv_out_rec_type;
851   v_fr_in int_forw_rate_in_rec_type;
852   v_fr_out int_forw_rate_out_rec_type;
853   v_bo_in xtr_mm_formulas.black_opt_in_rec_type;
854   v_bo_out xtr_mm_formulas.black_opt_out_rec_type;
855   v_temp NUMBER;
856   v_dummy NUMBER;
857   v_strike NUMBER;
858 
859 BEGIN
860   IF xtr_risk_debug_pkg.g_Debug THEN
861      xtr_risk_debug_pkg.dpush('XTR_MM_COVERS.BLACK_OPTION_PRICE_CV');
862   END IF;
863 
864   --we want all rates to be Actual/365 output to find the forward rate
865   v_rc_in.p_day_count_basis_out := 'ACTUAL365';  -- bug 3509267
866 
867   --first, convert short rate to Actual/365
868   v_rc_in.p_rate_type_in := p_in_rec.p_rate_type_short;
869   v_rc_in.p_day_count_basis_in := p_in_rec.p_day_count_basis_short;
870   v_rc_in.p_rate_in := p_in_rec.p_ir_short;
871   v_rc_in.p_start_date := p_in_rec.p_spot_date;
872   v_rc_in.p_end_date := p_in_rec.p_start_date;
873   v_rc_in.p_compound_freq_in := p_in_rec.p_compound_freq_short;
874 
875 IF xtr_risk_debug_pkg.g_Debug THEN
876    xtr_risk_debug_pkg.dlog('black_option_price_cv: ' || 'Short Start Date',v_rc_in.p_start_date);
877    xtr_risk_debug_pkg.dlog('black_option_price_cv: ' || 'Short End Date',v_rc_in.p_end_date);
878    xtr_risk_debug_pkg.dlog('black_option_price_cv: ' || 'Short DCB IN',v_rc_in.p_day_count_basis_in);
879    xtr_risk_debug_pkg.dlog('black_option_price_cv: ' || 'Short DCB OUT',v_rc_in.p_day_count_basis_out);
880    xtr_risk_debug_pkg.dlog('black_option_price_cv: ' || 'Short Rate Type IN',v_rc_in.p_rate_type_in);
881    xtr_risk_debug_pkg.dlog('black_option_price_cv: ' || 'Short Rate Type OUT',v_rc_in.p_rate_type_out);
882    xtr_risk_debug_pkg.dlog('black_option_price_cv: ' || 'Short Compound Freq IN',v_rc_in.p_compound_freq_in);
883    xtr_risk_debug_pkg.dlog('black_option_price_cv: ' || 'Short Compound Freq OUT',v_rc_in.p_compound_freq_out);
884    xtr_risk_debug_pkg.dlog('black_option_price_cv: ' || 'Short Rate IN',v_rc_in.p_rate_in);
885 END IF;
886 
887   xtr_rate_conversion.rate_conv_simple_annualized(v_rc_in, v_rc_out);
888   v_fr_in.p_Rt := v_rc_out.p_rate_out;
889 
890   --second, convert long rate to Actual/365
891   v_rc_in.p_rate_type_in := p_in_rec.p_rate_type_long;
892   v_rc_in.p_day_count_basis_in := p_in_rec.p_day_count_basis_long;
893   v_rc_in.p_rate_in := p_in_rec.p_ir_long;
894   v_rc_in.p_start_date := p_in_rec.p_spot_date;
895   v_rc_in.p_end_date := p_in_rec.p_maturity_date;
896   v_rc_in.p_compound_freq_in := p_in_rec.p_compound_freq_long;
897 
898 IF xtr_risk_debug_pkg.g_Debug THEN
899    xtr_risk_debug_pkg.dlog('black_option_price_cv: ' || 'Long Start Date',v_rc_in.p_start_date);
900    xtr_risk_debug_pkg.dlog('black_option_price_cv: ' || 'Long End Date',v_rc_in.p_end_date);
901    xtr_risk_debug_pkg.dlog('black_option_price_cv: ' || 'Long DCB IN',v_rc_in.p_day_count_basis_in);
902    xtr_risk_debug_pkg.dlog('black_option_price_cv: ' || 'Long DCB OUT',v_rc_in.p_day_count_basis_out);
903    xtr_risk_debug_pkg.dlog('black_option_price_cv: ' || 'Long Rate Type IN',v_rc_in.p_rate_type_in);
904    xtr_risk_debug_pkg.dlog('black_option_price_cv: ' || 'Long Rate Type OUT',v_rc_in.p_rate_type_out);
905    xtr_risk_debug_pkg.dlog('black_option_price_cv: ' || 'Long Compound Freq IN',v_rc_in.p_compound_freq_in);
906    xtr_risk_debug_pkg.dlog('black_option_price_cv: ' || 'Long Compound Freq OUT',v_rc_in.p_compound_freq_out);
907    xtr_risk_debug_pkg.dlog('black_option_price_cv: ' || 'Long Rate IN',v_rc_in.p_rate_in);
908 END IF;
909 
910   xtr_rate_conversion.rate_conv_simple_annualized(v_rc_in, v_rc_out);
911   v_fr_in.p_RT1 := v_rc_out.p_rate_out;
912 
913   --third, convert strike rate to Actual/365 (has to be the same basis as
914   --the forward rate
915   v_rc_in.p_day_count_basis_out := 'ACTUAL365';
916   v_rc_in.p_rate_type_in := p_in_rec.p_rate_type_strike;
917   v_rc_in.p_day_count_basis_in := p_in_rec.p_day_count_basis_strike;
918   v_rc_in.p_rate_in := p_in_rec.p_strike_rate;
919   v_rc_in.p_start_date := p_in_rec.p_start_date;
920   v_rc_in.p_end_date := p_in_rec.p_maturity_date;
921   v_rc_in.p_compound_freq_in := p_in_rec.p_compound_freq_strike;
922 
923 IF xtr_risk_debug_pkg.g_Debug THEN
924    xtr_risk_debug_pkg.dlog('black_option_price_cv: ' || 'Strike Start Date',v_rc_in.p_start_date);
925    xtr_risk_debug_pkg.dlog('black_option_price_cv: ' || 'Strike End Date',v_rc_in.p_end_date);
926    xtr_risk_debug_pkg.dlog('black_option_price_cv: ' || 'Strike DCB IN',v_rc_in.p_day_count_basis_in);
927    xtr_risk_debug_pkg.dlog('black_option_price_cv: ' || 'Strike DCB OUT',v_rc_in.p_day_count_basis_out);
928    xtr_risk_debug_pkg.dlog('black_option_price_cv: ' || 'Strike Rate Type IN',v_rc_in.p_rate_type_in);
929    xtr_risk_debug_pkg.dlog('black_option_price_cv: ' || 'Strike Rate Type OUT',v_rc_in.p_rate_type_out);
930    xtr_risk_debug_pkg.dlog('black_option_price_cv: ' || 'Strike Compound Freq IN',v_rc_in.p_compound_freq_in);
931    xtr_risk_debug_pkg.dlog('black_option_price_cv: ' || 'Strike Compound Freq OUT',v_rc_in.p_compound_freq_out);
932    xtr_risk_debug_pkg.dlog('black_option_price_cv: ' || 'Strike Rate IN',v_rc_in.p_rate_in);
933 END IF;
934 
935   xtr_rate_conversion.rate_conv_simple_annualized(v_rc_in, v_rc_out);
936   v_strike := v_rc_out.p_rate_out;
937 
938   --get t
939   calc_days_run_c(p_in_rec.p_spot_date, p_in_rec.p_start_date,
940 			'ACTUAL365', null, v_fr_in.p_t, v_dummy); -- bug 3509267
941   --get T1
942   calc_days_run_c(p_in_rec.p_spot_date, p_in_rec.p_maturity_date,
943 			'ACTUAL365', null, v_fr_in.p_T1, v_dummy); -- bug 3509267
944   --get forward rate
945   v_fr_in.p_indicator := 'Y'; --we're supplying yield rate
946   v_fr_in.p_year_basis := 365;  -- bug 3509267
947 
948 IF xtr_risk_debug_pkg.g_Debug THEN
949    xtr_risk_debug_pkg.dlog('black_option_price_cv: ' || 'Forw Conv Short Rate',v_fr_in.p_Rt);
950    xtr_risk_debug_pkg.dlog('black_option_price_cv: ' || 'Forw Conv Long Rate',v_fr_in.p_RT1);
951    xtr_risk_debug_pkg.dlog('black_option_price_cv: ' || 'Forw Conv Time Short',v_fr_in.p_t);
952    xtr_risk_debug_pkg.dlog('black_option_price_cv: ' || 'Forw Conv Time Long',v_fr_in.p_T1);
953 END IF;
954 
955   interest_forward_rate(v_fr_in,v_fr_out);
956   v_bo_in.p_forward_rate := v_fr_out.p_fra_rate;
957 
958   --convert long rate to continuous Actual/365
959   IF NOT (p_in_rec.p_rate_type_long IN ('C','c') AND
960 	p_in_rec.p_day_count_basis_long = 'ACTUAL365') THEN
961     v_rc_in.p_rate_type_out := 'C';
962     v_rc_in.p_day_count_basis_out := 'ACTUAL365';
963     v_rc_in.p_rate_type_in := p_in_rec.p_rate_type_long;
964     v_rc_in.p_day_count_basis_in := p_in_rec.p_day_count_basis_long;
965     v_rc_in.p_rate_in := p_in_rec.p_ir_long;
966     v_rc_in.p_start_date := p_in_rec.p_spot_date;
967     v_rc_in.p_end_date := p_in_rec.p_maturity_date;
968     v_rc_in.p_compound_freq_in := p_in_rec.p_compound_freq_long;
969     xtr_rate_conversion.rate_conversion(v_rc_in, v_rc_out);
970     v_bo_in.p_T2_INT_RATE := v_rc_out.p_rate_out;
971   ELSE
972     v_bo_in.p_T2_INT_RATE := p_in_rec.p_ir_long;
973   END IF;
974 
975 IF xtr_risk_debug_pkg.g_Debug THEN
976    xtr_risk_debug_pkg.dlog('black_option_price_cv: ' || 'BO v_strike',v_strike);
977    xtr_risk_debug_pkg.dlog('black_option_price_cv: ' || 'BO p_forward_rate',v_fr_out.p_fra_rate);
978    xtr_risk_debug_pkg.dlog('black_option_price_cv: ' || 'BO Conv. forward_rate',v_bo_in.p_forward_rate);
979    xtr_risk_debug_pkg.dlog('black_option_price_cv: ' || 'BO Conv. Long Rate ',v_bo_in.p_t2_int_rate);
980 END IF;
981 
982   --call black option pricing engine
983   v_bo_in.p_principal := p_in_rec.p_principal;
984   v_bo_in.p_int_rate := v_strike;
985   v_bo_in.p_T1 := v_fr_in.p_t;
986   v_bo_in.p_T2 := v_fr_in.p_T1;
987   v_bo_in.p_VOLATILITY := p_in_rec.p_VOLATILITY;
988   xtr_mm_formulas.black_option_price(v_bo_in, v_bo_out);
989   p_out_rec.p_CAPLET_PRICE := v_bo_out.p_CAPLET_PRICE;
990   p_out_rec.p_FLOORLET_PRICE := v_bo_out.p_FLOORLET_PRICE;
991   p_out_rec.p_FORWARD_FORWARD_RATE := v_bo_in.p_forward_rate;
992   p_out_rec.p_Nd1 := v_bo_out.p_Nd1;
993   p_out_rec.p_Nd2 := v_bo_out.p_Nd2;
994   p_out_rec.p_Nd1_a := v_bo_out.p_Nd1_a;
995   p_out_rec.p_Nd2_a := v_bo_out.p_Nd2_a;
996 
997   IF xtr_risk_debug_pkg.g_Debug THEN
998      xtr_risk_debug_pkg.dpop('XTR_MM_COVERS.BLACK_OPTION_PRICE_CV');
999   END IF;
1000 END black_option_price_cv;
1001 
1002 
1003 -------------------------------------------------------------------
1004 -- COMPOUND COUPON
1005 -- To find the first coupon's Start Date or Maturity Date based on
1006 -- the bond's Frequency, Commence Date and Maturity Date, so that
1007 -- Start Date and Maturity Date gives a full coupon.
1008 --
1009 -- If p_odd_date_ind = 'S', then return Start Date.
1010 -- If p_odd_date_ind = 'M', then return Maturity Date.
1011 -------------------------------------------------------------------
1012 FUNCTION  ODD_COUPON_DATE  (p_commence_date IN  DATE,
1013                             p_maturity_date IN  DATE,
1014                             p_frequency     IN  NUMBER,
1015                             p_odd_date_ind  IN  VARCHAR2) return DATE is
1016    l_coupon_date      DATE;
1017    l_prev_coupon_date DATE;
1018    l_counter          NUMBER := 0;
1019 --
1020 BEGIN
1021 
1022    l_prev_coupon_date := p_maturity_date;
1023 
1024    if nvl(p_frequency,0) <> 0 then
1025 
1026       l_coupon_date := add_months(p_maturity_date,(-12 / p_frequency)-l_counter);
1027       l_counter     := l_counter + (12 / p_frequency);
1028 
1029       LOOP
1030          EXIT WHEN l_coupon_date <= p_commence_date;
1031 
1032          l_prev_coupon_date := l_coupon_date;
1033          l_coupon_date      := add_months(p_maturity_date,(-12 / p_frequency)-l_counter);
1034          l_counter          := l_counter + (12 / p_frequency);
1035 
1036       END LOOP;
1037 
1038       if p_odd_date_ind = 'S' then
1039          return(l_coupon_date);         -- Start Date
1040       else
1041          return(l_prev_coupon_date);    -- Maturity Date
1042       end if;
1043 
1044    else
1045       return(p_maturity_date);
1046    end if;
1047 
1048 END;
1049 
1050 -------------------------------------------------------------------
1051 -- COMPOUND COUPON
1052 -- To find the number of Full coupons
1053 -------------------------------------------------------------------
1054 FUNCTION  FULL_COUPONS(p_commence_date IN  DATE,
1055                        p_maturity_date IN  DATE,
1056                        p_frequency     IN  NUMBER) return NUMBER is
1057 
1058  l_coupon_date      DATE;
1059  l_counter          NUMBER := 0;
1060  l_num_full         NUMBER := 0;
1061 
1062 --
1063 begin
1064 
1065    if nvl(p_frequency,0) <> 0 then
1066 
1067       l_coupon_date := add_months(p_maturity_date,(-12 / p_frequency)-l_counter);
1068       l_counter     := l_counter + (12 / p_frequency);
1069 
1070       LOOP
1071          EXIT WHEN l_coupon_date <= p_commence_date;
1072 
1073          l_coupon_date := add_months(p_maturity_date,(-12 / p_frequency)-l_counter);
1074          l_counter     := l_counter + (12 / p_frequency);
1075          l_num_full    := l_num_full + 1;
1076 
1077       END LOOP;
1078 
1079    end if;
1080 
1081    return(l_num_full);
1082 
1083 END;
1084 
1085 -------------------------------------------------------------------
1086 -- COMPOUND COUPON
1087 -- To find the number of Previous Full coupons
1088 -------------------------------------------------------------------
1089 FUNCTION  PREVIOUS_FULL_COUPONS(p_commence_date   IN  DATE,
1090                                 p_maturity_date   IN  DATE,
1091                                 p_settlement_date IN  DATE,
1092                                 p_frequency       IN  NUMBER) return NUMBER is
1093 
1094  l_coupon_date      DATE;
1095  l_prev_coupon_date DATE;
1096  l_counter          NUMBER := 0;
1097  l_num_full         NUMBER := 0;
1098 
1099 --
1100 begin
1101 
1102    l_prev_coupon_date := p_maturity_date;
1103 
1104    if nvl(p_frequency,0) <> 0 then
1105 
1106       l_coupon_date := add_months(p_maturity_date,(-12 / p_frequency)-l_counter);
1107       l_counter     := l_counter + (12 / p_frequency);
1108 
1109       LOOP
1110          EXIT WHEN l_coupon_date <= p_commence_date;
1111 
1112          l_prev_coupon_date := l_coupon_date;
1113          l_coupon_date      := add_months(p_maturity_date,(-12 / p_frequency)-l_counter);
1114          l_counter          := l_counter + (12 / p_frequency);
1115 
1116          if l_prev_coupon_date <= p_settlement_date and l_coupon_date > p_commence_date then
1117             l_num_full := l_num_full + 1;
1118          end if;
1119 
1120       END LOOP;
1121 
1122    end if;
1123 
1124    return(l_num_full);
1125 
1126 END;
1127 
1128 -------------------------------------------------------------------
1129 -- COMPOUND COUPON
1130 -- To calculate the coupon amount
1131 -------------------------------------------------------------------
1132 FUNCTION  CALC_COMPOUND_COUPON_AMT(p_compound_rec   IN  COMPOUND_CPN_REC_TYPE) return NUMBER is
1133 
1134    l_year_basis           NUMBER;
1135    l_nbr_days_in_period   NUMBER;
1136    l_total_coupon_days    NUMBER;
1137    l_full_quasi_coupon    NUMBER;
1138    l_amount               NUMBER;
1139 
1140 BEGIN
1141 
1142    ----------------------------------------------
1143    -- To return the total coupon amount
1144    ----------------------------------------------
1145 
1146    l_full_quasi_coupon := p_compound_rec.p_full_coupon;
1147 
1148    if p_compound_rec.p_odd_coupon_start = p_compound_rec.p_bond_start_date then
1149       l_full_quasi_coupon := l_full_quasi_coupon + 1;
1150    else
1151       XTR_CALC_P.Calc_Days_Run_C (p_compound_rec.p_bond_start_date,
1152                                   p_compound_rec.p_odd_coupon_maturity,
1153                                   p_compound_rec.p_year_calc_type,
1154                                   p_compound_rec.p_frequency,
1155                                   l_nbr_days_in_period,
1156                                   l_year_basis,
1157                                   NULL,
1158                                   p_compound_rec.p_day_count_type,
1159                                   'N');
1160       XTR_CALC_P.Calc_Days_Run_C (p_compound_rec.p_odd_coupon_start,
1161                                   p_compound_rec.p_odd_coupon_maturity,
1162                                   p_compound_rec.p_year_calc_type,
1163                                   p_compound_rec.p_frequency,
1164                                   l_total_coupon_days,
1165                                   l_year_basis,
1166                                   NULL,
1167                                   p_compound_rec.p_day_count_type,
1168                                   'N');
1169       if nvl(l_nbr_days_in_period,0) <> 0 and nvl(l_total_coupon_days,0) <> 0 then
1170          l_full_quasi_coupon := l_full_quasi_coupon + nvl(l_nbr_days_in_period,0)/nvl(l_total_coupon_days,1);
1171       end if;
1172    end if;
1173 
1174    l_amount := (power(1+(p_compound_rec.p_coupon_rate/100)/
1175                       nvl(p_compound_rec.p_frequency,2),l_full_quasi_coupon))*
1176                       p_compound_rec.p_maturity_amount - p_compound_rec.p_maturity_amount;
1177 
1178    ----------------------------------------------------------------------------
1179    -- Currency rounding needed for Coupon Amount, but not for Redemption Value.
1180    ----------------------------------------------------------------------------
1181    if nvl(p_compound_rec.p_amount_redemption_ind,'R') = 'A' then
1182       return( xtr_fps2_p.interest_round(l_amount,
1183                                         p_compound_rec.p_precision,p_compound_rec.p_rounding_type));
1184    else
1185       return( l_amount );
1186    end if;
1187 
1188 END;
1189 
1190 
1191 ---------------------------------------------------------------------------
1192 -- COMPOUND COUPON
1193 -- To calculate the total number of previous quasi coupon
1194 ---------------------------------------------------------------------------
1195 FUNCTION  CALC_TOTAL_PREVIOUS_COUPON(p_bond_rec     IN   BOND_INFO_REC_TYPE) return NUMBER is
1196 
1197    l_odd_coupon_days        NUMBER;
1198    l_odd_coupon_length      NUMBER;
1199    l_yr_basis               NUMBER;
1200    l_no_previous_coupon     NUMBER;
1201    l_no_current_coupon      NUMBER;
1202 
1203 BEGIN
1204 
1205    l_no_current_coupon := p_bond_rec.p_curr_coupon;
1206 
1207    CALC_DAYS_RUN_C(p_bond_rec.p_odd_coupon_start,
1208                    p_bond_rec.p_odd_coupon_maturity,
1209                    p_bond_rec.p_yr_calc_type,
1210                    p_bond_rec.p_frequency,
1211                    l_odd_coupon_length,
1212                    l_yr_basis,
1213                    NULL,
1214                    p_bond_rec.p_day_count_type,     -- Added for Interest Override
1215                    'N');                            -- Added for Interest Override
1216 
1217    if p_bond_rec.p_calc_date < p_bond_rec.p_odd_coupon_maturity then
1218       ------------------------ Determine the number of previous coupon ----------------------------
1219       -------------( Settlement date is within first coupon, previous coupon is zero )-------------
1220       ---------------------------------------------------------------------------------------------
1221       l_no_previous_coupon := 0;
1222 
1223    else
1224       ------------------------ Determine the number of previous coupon ----------------------------
1225       CALC_DAYS_RUN_C(p_bond_rec.p_bond_commence,
1226                       p_bond_rec.p_odd_coupon_maturity,
1227                       p_bond_rec.p_yr_calc_type,
1228                       p_bond_rec.p_frequency,
1229                       l_odd_coupon_days,
1230                       l_yr_basis,
1231                       NULL,
1232                       p_bond_rec.p_day_count_type,     -- Added for Interest Override
1233                       'N');                            -- Added for Interest Override
1234       if nvl(l_odd_coupon_days,0) <> 0 and nvl(l_odd_coupon_length,0) <> 0 then
1235          l_no_previous_coupon := l_odd_coupon_days/l_odd_coupon_length + p_bond_rec.p_prv_full_coupon;
1236       else
1237          l_no_previous_coupon := p_bond_rec.p_prv_full_coupon;           -- AW: or zero
1238       end if;
1239 
1240 
1241       if p_bond_rec.p_calc_date = p_bond_rec.p_odd_coupon_maturity then
1242          l_no_current_coupon := 0;
1243       end if;
1244 
1245    end if;
1246 
1247    return( l_no_previous_coupon + l_no_current_coupon);
1248 
1249 END;
1250 
1251 
1252 -- added fhu 5/3/02
1253 /* bug 2358592 merged various changes from xtr_calc_package
1254 For Floating Rate Bond: p_yield becomes the Discount Margin.
1255 	When it's passed in its unit is assumed to be in Percent, hence the
1256 	caller need to make sure about the unit.
1257 	When it's passed out its unit will be in Percent, hence the caller need to
1258 	adjust the unit for display purposes. This is to avoid bug 31315424.
1259 */
1260 
1261 PROCEDURE CALCULATE_BOND_PRICE_YIELD(
1262 	p_py_in		IN		BOND_PRICE_YIELD_IN_REC_TYPE,
1263 	p_py_out	IN OUT NOCOPY		BOND_PRICE_YIELD_OUT_REC_TYPE) IS
1264 
1265 p_bond_issue_code    		VARCHAR2(7) := p_py_in.p_bond_issue_code;
1266 p_settlement_date		DATE := p_py_in.p_settlement_date;
1267 p_ex_cum_next_coupon		VARCHAR2(3) := p_py_in.p_ex_cum_next_coupon;
1268 p_calculate_yield_or_price	VARCHAR2(1) := p_py_in.p_calculate_yield_or_price;
1269 p_yield				NUMBER := p_py_in.p_yield;
1270 p_yield_temp			NUMBER;--bug 3135424
1271 p_accrued_interest		NUMBER := p_py_in.p_accrued_interest;
1272 p_clean_price			NUMBER := p_py_in.p_clean_price;
1273 p_dirty_price			NUMBER := p_py_in.p_dirty_price;
1274 p_input_or_calculator		VARCHAR2(1) := p_py_in.p_input_or_calculator;
1275 p_commence_date			DATE := p_py_in.p_commence_date;
1276 p_maturity_date			DATE := p_py_in.p_maturity_date;
1277 p_prev_coupon_date		DATE := p_py_in.p_prev_coupon_date;
1278 p_next_coupon_date		DATE := p_py_in.p_next_coupon_date;
1279 p_calc_type			VARCHAR2(15) := p_py_in.p_calc_type;
1280 p_year_calc_type		VARCHAR2(15) := p_py_in.p_year_calc_type;
1281 p_accrued_int_calc_basis	VARCHAR2(15) := p_py_in.p_accrued_int_calc_basis;
1282 p_coupon_freq			NUMBER := p_py_in.p_coupon_freq;
1283 p_calc_rounding			NUMBER := p_py_in.p_calc_rounding;
1284 p_price_rounding		NUMBER := p_py_in.p_price_rounding;
1285 p_price_round_type		VARCHAR2(2) := p_py_in.p_price_round_type;
1286 p_yield_rounding		NUMBER := p_py_in.p_yield_rounding;
1287 p_yield_round_type		VARCHAR2(2) := p_py_in.p_yield_round_type;
1288 p_coupon_rate			NUMBER := p_py_in.p_coupon_rate;
1289 p_num_coupons_remain		NUMBER := p_py_in.p_num_coupons_remain;
1290 p_day_count_type                VARCHAR2(1) := p_py_in.p_day_count_type;
1291 p_first_trans_flag              VARCHAR2(1) := p_py_in.p_first_trans_flag;
1292 p_deal_subtype                  VARCHAR2(7) := p_py_in.p_deal_subtype;
1293 
1294 -------------------------------------------------------------------------
1295 -- Variables added for COMPOUND COUPON
1296 -------------------------------------------------------------------------
1297 -- need this from calculator
1298 l_currency                      VARCHAR2(15):= p_py_in.p_currency;
1299 l_face_value                    NUMBER      := p_py_in.p_face_value;
1300 l_consideration                 NUMBER      := p_py_in.p_consideration;
1301 l_full_quasi_coupon             NUMBER;
1302 
1303 l_num_current_coupon      	NUMBER;
1304 l_num_full_cpn_previous   	NUMBER;
1305 l_prv_quasi_coupon        	NUMBER;
1306 l_odd_coupon_start      	DATE;
1307 l_odd_coupon_maturity   	DATE;
1308 l_days_settle_to_next_cpn 	NUMBER;
1309 l_days_in_current_cpn           NUMBER;
1310 l_coupon_amount                 NUMBER;
1311 l_redemption_value              NUMBER;
1312 l_precision                     NUMBER;
1313 l_ext_precision                 NUMBER;
1314 l_min_acct_unit                 NUMBER;
1315 l_rounding_type                 VARCHAR2(1) := 'R';
1316 l_comp_coupon                   XTR_MM_COVERS.COMPOUND_CPN_REC_TYPE;
1317 l_bond_rec                      XTR_MM_COVERS.BOND_INFO_REC_TYPE;
1318 l_amt1                          number;
1319 l_amt2                          number;
1320 l_amt3                          number;
1321 -------------------------------------------------------------------------
1322 
1323 
1324 l_count				NUMBER;
1325 l_num_full_cpn_remain   	NUMBER;
1326 l_prev_coupon_date       	DATE;
1327 l_next_coupon_date    		DATE;
1328 l_days_settle_to_nxt_cpn	NUMBER;
1329 l_days_last_cpn_to_nxt_cpn 	NUMBER;
1330 l_days_last_cpn_to_settle 	NUMBER;
1331 l_yr_calc_type   		VARCHAR2(15);
1332 l_coupon_rate            	NUMBER;
1333 l_calc_type			VARCHAR2(15);
1334 l_bond_commence        		DATE;
1335 l_accrued_int_calc_basis        VARCHAR2(15);
1336 l_coupon_freq   		NUMBER;
1337 l_calc_dirty_price    		NUMBER;
1338 yr_basis			NUMBER;
1339 l_dummy_num			NUMBER;
1340 l_yield_inc			NUMBER :=0.5;
1341 l_inc_flag			VARCHAR2(1) :='+';
1342 l_maturity_date			DATE;
1343 l_nbr_full_months_to_maturity	NUMBER;
1344 l_nbr_months_bwt_cpn		NUMBER;
1345 l_settle_to_nxt_cpn_ratio	NUMBER;
1346 l_calc_precision                NUMBER;
1347 l_price_precision		NUMBER;
1348 l_price_round_type              VARCHAR2(1);
1349 l_yield_precision		NUMBER;
1350 l_yield_round_type              VARCHAR2(1);
1351 -- bug2536590
1352 l_days_settle_to_maturity       NUMBER;
1353 l_settle_to_maturity_years      NUMBER;
1354 l_fast_yield                    NUMBER;
1355 
1356 l_dirty_px_1			number;
1357 l_dirty_px_2			number;
1358 l_dirty_px_3			number;
1359 l_dirty_px_4			number;
1360 l_dirty_px_5			number;
1361 l_temp                          number;
1362 l_temp2                         number;
1363 l_temp3                         number;
1364 l_acc_cum                       number;
1365 l_dirty_price_cum		NUMBER;
1366 -- Added for Interest Override feature
1367 l_first_trans_flag              VARCHAR2(1);
1368 --
1369 v_benchmark_rate		NUMBER; --bug 2804548
1370 v_float_margin			NUMBER; --bug 2804548
1371 l_coupon_rate_fl		NUMBER; --bug 2804548
1372 v_actual_ytm                    NUMBER; --bug 2804548 needed for QRM BPV
1373 
1374 cursor ISSUE_DETAILS is
1375  select YEAR_CALC_TYPE,COUPON_RATE,CURRENCY,CALC_TYPE,
1376         COMMENCE_DATE,nvl(NO_OF_COUPONS_PER_YEAR,0),
1377         nvl(ACCRUED_INT_YEAR_CALC_BASIS,YEAR_CALC_TYPE),MATURITY_DATE,
1378         price_rounding,price_round_type,yield_rounding,yield_round_type,
1379         calc_rounding, rounding_type
1380   from XTR_BOND_ISSUES_V
1381   where BOND_ISSUE_CODE = p_bond_issue_code;
1382 --
1383 cursor PRV_COUPON_DATES is
1384  select max(COUPON_DATE),                        --------------------------------------------------------
1385         min(COUPON_DATE), greatest(count(*)-1,0) -- COMPOUND COUPON: first coupon date, prev full coupon
1386   from  XTR_BOND_COUPON_DATES                    --------------------------------------------------------
1387   where BOND_ISSUE_CODE = p_bond_issue_code
1388   and   COUPON_DATE    <= p_settlement_date;
1389 
1390 cursor NXT_COUPON_DATES is
1391  select min(COUPON_DATE),nvl(count(COUPON_DATE),0)
1392   from XTR_BOND_COUPON_DATES
1393   where BOND_ISSUE_CODE = p_bond_issue_code
1394   and COUPON_DATE > p_settlement_date;
1395 
1396 -----------------------------------------------------------------------------------------------------
1397 cursor TOTAL_FULL_COUPONS (p_issue_code VARCHAR2) is -- COMPOUND COUPON: Count number of full coupons
1398 select count(*)-1
1399 from   xtr_bond_coupon_dates
1400 where  bond_issue_code = p_issue_code;
1401 -----------------------------------------------------------------------------------------------------
1402 --bug 2804548
1403 cursor get_benchmark_rate(p_settlement_date DATE,p_bond_issue_code VARCHAR2) is
1404 select c.rate, i.float_margin
1405   from xtr_bond_coupon_dates c, xtr_bond_issues i
1406   where c.bond_issue_code=p_bond_issue_code
1407   and c.bond_issue_code=i.bond_issue_code
1408   and c.coupon_date=(select min(COUPON_DATE)
1409   	from XTR_BOND_COUPON_DATES
1410   	where BOND_ISSUE_CODE = p_bond_issue_code
1411   	and COUPON_DATE > p_settlement_date);
1412 
1413 FUNCTION ROUND_P(p_num IN NUMBER) RETURN NUMBER IS
1414 BEGIN
1415    IF CALCULATE_BOND_PRICE_YIELD.l_yield_round_type = 'T' then
1416      RETURN trunc(p_num,CALCULATE_BOND_PRICE_YIELD.l_calc_precision);
1417    ELSE
1418      RETURN round(p_num,CALCULATE_BOND_PRICE_YIELD.l_calc_precision);
1419    END IF;
1420 END ROUND_P;
1421 
1422 FUNCTION ROUND_Y(p_num IN NUMBER) RETURN NUMBER IS
1423 BEGIN
1424   IF CALCULATE_BOND_PRICE_YIELD.l_price_round_type = 'T' then
1425     RETURN trunc(p_num,CALCULATE_BOND_PRICE_YIELD.l_calc_precision);
1426   ELSE
1427     RETURN round(p_num,CALCULATE_BOND_PRICE_YIELD.l_calc_precision);
1428   END IF;
1429 END ROUND_Y;
1430 --
1431 begin
1432 /*
1433 XTR_RISK_DEBUG_PKG.start_debug('/sqlcom/out/findv115', 'fhpatest.dbg');
1434 IF xtr_risk_debug_pkg.g_Debug THEN
1435    XTR_RISK_DEBUG_PKG.dpush('calculate_bond_price_yield');
1436    XTR_RISK_DEBUG_PKG.dlog('CALCULATE_BOND_PRICE_YIELD: ' || 'p_bond_issue_code',p_bond_issue_code);
1437    XTR_RISK_DEBUG_PKG.dlog('CALCULATE_BOND_PRICE_YIELD: ' || 'p_settlement_date',p_settlement_date);
1438    XTR_RISK_DEBUG_PKG.dlog('CALCULATE_BOND_PRICE_YIELD: ' || 'p_ex_cum_next_coupon',p_ex_cum_next_coupon);
1439    XTR_RISK_DEBUG_PKG.dlog('CALCULATE_BOND_PRICE_YIELD: ' || 'p_calculate_yield_or_price',p_calculate_yield_or_price);
1440    XTR_RISK_DEBUG_PKG.dlog('CALCULATE_BOND_PRICE_YIELD: ' || 'p_yield',p_yield);
1441    XTR_RISK_DEBUG_PKG.dlog('CALCULATE_BOND_PRICE_YIELD: ' || 'p_accrued_interest',p_accrued_interest);
1442    XTR_RISK_DEBUG_PKG.dlog('CALCULATE_BOND_PRICE_YIELD: ' || 'p_clean_price',p_clean_price);
1443    XTR_RISK_DEBUG_PKG.dlog('CALCULATE_BOND_PRICE_YIELD: ' || 'p_dirty_price',p_dirty_price);
1444    XTR_RISK_DEBUG_PKG.dlog('CALCULATE_BOND_PRICE_YIELD: ' || 'p_input_or_calculator',p_input_or_calculator);
1445    XTR_RISK_DEBUG_PKG.dlog('CALCULATE_BOND_PRICE_YIELD: ' || 'p_commence_date',p_commence_date);
1446    XTR_RISK_DEBUG_PKG.dlog('CALCULATE_BOND_PRICE_YIELD: ' || 'p_maturity_date',p_maturity_date);
1447    XTR_RISK_DEBUG_PKG.dlog('CALCULATE_BOND_PRICE_YIELD: ' || 'p_prev_coupon_date',p_prev_coupon_date);
1448    XTR_RISK_DEBUG_PKG.dlog('CALCULATE_BOND_PRICE_YIELD: ' || 'p_next_coupon_date',p_next_coupon_date);
1449    XTR_RISK_DEBUG_PKG.dlog('CALCULATE_BOND_PRICE_YIELD: ' || 'p_calc_type',p_calc_type);
1450    XTR_RISK_DEBUG_PKG.dlog('CALCULATE_BOND_PRICE_YIELD: ' || 'p_year_calc_type',p_year_calc_type);
1451    XTR_RISK_DEBUG_PKG.dlog('CALCULATE_BOND_PRICE_YIELD: ' || 'p_accrued_int_calc_basis',p_accrued_int_calc_basis);
1452    XTR_RISK_DEBUG_PKG.dlog('CALCULATE_BOND_PRICE_YIELD: ' || 'p_coupon_freq',p_coupon_freq);
1453    XTR_RISK_DEBUG_PKG.dlog('CALCULATE_BOND_PRICE_YIELD: ' || 'p_calc_rounding',p_calc_rounding);
1454    XTR_RISK_DEBUG_PKG.dlog('CALCULATE_BOND_PRICE_YIELD: ' || 'p_price_rounding',p_price_rounding);
1455    XTR_RISK_DEBUG_PKG.dlog('CALCULATE_BOND_PRICE_YIELD: ' || 'p_price_round_type',p_price_round_type);
1456    XTR_RISK_DEBUG_PKG.dlog('CALCULATE_BOND_PRICE_YIELD: ' || 'p_yield_rounding',p_yield_rounding);
1457    XTR_RISK_DEBUG_PKG.dlog('CALCULATE_BOND_PRICE_YIELD: ' || 'p_yield_round_type',p_yield_round_type);
1458    XTR_RISK_DEBUG_PKG.dlog('CALCULATE_BOND_PRICE_YIELD: ' || 'p_coupon_rate',p_coupon_rate);
1459    XTR_RISK_DEBUG_PKG.dlog('CALCULATE_BOND_PRICE_YIELD: ' || 'p_num_coupons_remain',p_num_coupons_remain);
1460    XTR_RISK_DEBUG_PKG.dlog('CALCULATE_BOND_PRICE_YIELD: ' || 'p_day_count_type',p_day_count_type);
1461    XTR_RISK_DEBUG_PKG.dlog('CALCULATE_BOND_PRICE_YIELD: ' || 'p_first_trans_flag',p_first_trans_flag);
1462    XTR_RISK_DEBUG_PKG.dlog('CALCULATE_BOND_PRICE_YIELD: ' || 'p_deal_subtype',p_deal_subtype);
1463    XTR_RISK_DEBUG_PKG.dpop('calculate_bond_price_yield');
1464 END IF;
1465 XTR_RISK_DEBUG_PKG.stop_debug;
1466 */
1467 
1468    -- Added for Interest Override
1469    l_first_trans_flag := p_first_trans_flag;
1470    --
1471 
1472    IF (nvl(p_input_or_calculator,'I') = 'I') THEN
1473     open   ISSUE_DETAILS;
1474     fetch  ISSUE_DETAILS INTO l_yr_calc_type,l_coupon_rate,l_currency,
1475                            l_calc_type,l_bond_commence,l_coupon_freq,
1476                            l_accrued_int_calc_basis,l_maturity_date,
1477                            l_price_precision,l_price_round_type,
1478                            l_yield_precision,l_yield_round_type,
1479                            l_calc_precision, l_rounding_type;
1480     close ISSUE_DETAILS;
1481   ELSE
1482     l_yr_calc_type	:= p_year_calc_type;
1483     l_coupon_rate	:= p_coupon_rate;
1484     l_calc_type		:= p_calc_type;
1485     l_bond_commence	:= p_commence_date;
1486     l_maturity_date	:= p_maturity_date;
1487     l_coupon_freq	:= p_coupon_freq;
1488     l_accrued_int_calc_basis := p_accrued_int_calc_basis;
1489     l_yield_precision	:= p_yield_rounding;
1490     l_yield_round_type  := p_yield_round_type;
1491     l_price_precision	:= p_price_rounding;
1492     l_price_round_type  := p_price_round_type;
1493     l_calc_precision    := p_calc_rounding;
1494     l_rounding_type     := p_py_in.p_rounding_type;  -- 2737823
1495   END IF;
1496 
1497   --start bug 2804548
1498   IF (l_calc_type in ('FL IRREGULAR','FL REGULAR')) then
1499      open get_benchmark_rate(p_settlement_date,p_bond_issue_code);
1500      fetch get_benchmark_rate into l_coupon_rate,v_float_margin;
1501      close get_benchmark_rate;
1502      v_float_margin := nvl(v_float_margin,0);
1503   END IF;
1504   --end bug 2804548
1505 
1506   --
1507   IF ((nvl(p_input_or_calculator,'I') = 'I') or
1508       (nvl(p_input_or_calculator,'I') = 'C' and p_bond_issue_code is not null and
1509        p_ex_cum_next_coupon = 'CUM' and l_calc_type = 'COMPOUND COUPON')) then
1510      -- Calculate for Coupon Bonds (non-zero coupon bond)
1511 
1512      ----------------------------------------------------------------------------------
1513      -- COMPOUND COUPON: also fetch the first coupon date, and previous full coupons
1514      ----------------------------------------------------------------------------------
1515      open  PRV_COUPON_DATES;
1516      fetch PRV_COUPON_DATES INTO l_prev_coupon_date, l_odd_coupon_maturity, l_num_full_cpn_previous;
1517      close PRV_COUPON_DATES;
1518 
1519      --------------------------------------
1520      -- COMPOUND COUPON
1521      --------------------------------------
1522      if l_odd_coupon_maturity is null and l_calc_type = 'COMPOUND COUPON' then
1523         select min(COUPON_DATE)
1524         into   l_odd_coupon_maturity
1525         from   xtr_bond_coupon_dates
1526         where  bond_issue_code = p_bond_issue_code;
1527      end if;
1528 
1529      ----------------------------------------------------------------------------------
1530      -- Note.  COMPOUND COUPON : If Settlement Date falls in the first coupon,
1531      --                          l_next_coupon_date is the first coupon's maturity date
1532      ----------------------------------------------------------------------------------
1533      open  NXT_COUPON_DATES;
1534      fetch NXT_COUPON_DATES INTO l_next_coupon_date, l_num_full_cpn_remain;
1535      close NXT_COUPON_DATES;
1536 
1537   ELSE  -- from calculator without issue code
1538 
1539      l_prev_coupon_date := p_prev_coupon_date;
1540      l_next_coupon_date := p_next_coupon_date;
1541 
1542      IF p_ex_cum_next_coupon = 'EX' then
1543         -- correct the next coupon date when called from calculator form for the
1544         -- calculation
1545         IF p_bond_issue_code is null then
1546            l_next_coupon_date:=add_months(l_prev_coupon_date,12/l_coupon_freq);
1547         ELSE
1548            open  NXT_COUPON_DATES;
1549            fetch NXT_COUPON_DATES INTO l_next_coupon_date,l_dummy_num;
1550            close NXT_COUPON_DATES;
1551         END IF;
1552 
1553      ------------------------------------------------------------------------------------
1554      -- COMPOUND COUPON
1555      ------------------------------------------------------------------------------------
1556      ELSIF p_ex_cum_next_coupon = 'CUM' and l_calc_type = 'COMPOUND COUPON' then
1557 
1558         IF p_bond_issue_code is null then
1559 
1560            --------------------------------------------------------------------------------------
1561            -- COMPOUND COUPON: l_num_full_cpn_remain := p_num_coupons_remain;  -- from calculator
1562            --------------------------------------------------------------------------------------
1563            l_odd_coupon_maturity    := ODD_COUPON_DATE(l_bond_commence,l_maturity_date,l_coupon_freq,'M');
1564            l_num_full_cpn_previous  := PREVIOUS_FULL_COUPONS(l_bond_commence,  l_maturity_date,
1565                                                              p_settlement_date,l_coupon_freq);
1566            ----------------------------------------------------------------------------------
1567 
1568         END IF;
1569      END IF;
1570      l_num_full_cpn_remain := p_num_coupons_remain;
1571 
1572   END IF;
1573 
1574   ---------------------------------------------------------------------------------------
1575   IF l_prev_coupon_date is null or
1576     (l_prev_coupon_date is not null and l_prev_coupon_date < l_odd_coupon_maturity and
1577      l_calc_type = 'COMPOUND COUPON') THEN
1578      l_prev_coupon_date := l_bond_commence;
1579   END IF;
1580 
1581   if l_next_coupon_date is null and l_calc_type = 'COMPOUND COUPON' then
1582      l_next_coupon_date := p_settlement_date;
1583   end if;
1584   ---------------------------------------------------------------------------------------
1585 
1586   IF (l_calc_type <> 'ZERO COUPON') then
1587     -- calculate days run within coupon preiod
1588     -- note that CALC_DAYS_RUN_C is used insatead of CALC_DAYS_RUN because the day
1589     -- count basis could be ACT/ACT-BOND
1590 
1591     --  Bug 2358500.
1592     --  Re-arranged the order of the calls to the "calc_days_run_c" procedure
1593     --  so that the year basis is based on the entire related coupon period
1594     --  instead of for a subperiod from/to the settlement date.
1595     --  The year basis will be needed to calculate the purchase accrued
1596     --  interest for a variable bond.
1597 
1598     --====================================================================================
1599     --  Added for Interest Override feature
1600     -- (The following result is not used by COMPOUND COUPON.)
1601     --====================================================================================
1602     IF p_day_count_type='B' AND p_ex_cum_next_coupon='EX' THEN
1603        l_first_trans_flag := NULL;
1604     ELSE
1605        l_first_trans_flag := p_first_trans_flag;
1606     END IF;
1607 
1608     CALC_DAYS_RUN_C(p_settlement_date,
1609                     l_next_coupon_date,
1610                     l_accrued_int_calc_basis,
1611                     l_coupon_freq,
1612                     l_days_settle_to_nxt_cpn,
1613                     yr_basis,
1614                     NULL,
1615                     p_day_count_type,      -- Added for Interest Override
1616                     l_first_trans_flag);   -- Added for Interest Override
1617 
1618     --====================================================================================
1619     -- Added for Interest Override feature
1620     -- Added 'SHORT' for COMPOUND COUPON - need to consider "Both" for SELL and SHORT only
1621     --====================================================================================
1622     IF p_day_count_type='B' and nvl(p_deal_subtype,'BUY') not in ('SELL','SHORT') THEN
1623        l_first_trans_flag := NULL;
1624     ELSE
1625        l_first_trans_flag := p_first_trans_flag;
1626     END IF;
1627 
1628     -------------------------------------------------------------------------------------------
1629     -- If Settlement Date is within first coupon, then l_prev_coupon_date = Bond Start
1630     -- If Settlement Date is after first coupon,  then l_prev_coupon_date = Previous Coupon Date
1631     -- If Settlement Date is on a Coupon Date,    then l_prev_coupon_date = Settlement Date
1632     --                      (from PRV_COUPON_DATE cursor, and l_days_last_cpn_to_settle = 0)
1633     -------------------------------------------------------------------------------------------
1634 
1635     CALC_DAYS_RUN_C(l_prev_coupon_date,
1636                     p_settlement_date,
1637                     l_accrued_int_calc_basis,
1638                     l_coupon_freq,
1639                     l_days_last_cpn_to_settle,
1640                     yr_basis,
1641                     NULL,
1642                     p_day_count_type,
1643                     l_first_trans_flag);
1644 
1645 
1646     --====================================================================================
1647     -- For Compound Coupon, find odd coupon date for subsequent calculations.
1648     --====================================================================================
1649     if l_calc_type = 'COMPOUND COUPON' then
1650        l_odd_coupon_start := ODD_COUPON_DATE(l_bond_commence, l_maturity_date, l_coupon_freq,'S');
1651     end if;
1652 
1653     --====================================================================================
1654     -- Number of days in Current coupon - need to consider "Both" for all subtypes
1655     --====================================================================================
1656     l_first_trans_flag := p_first_trans_flag;
1657 
1658     if l_calc_type = 'COMPOUND COUPON' and p_settlement_date < l_odd_coupon_maturity then
1659        --------------------------------------------------
1660        -- Settlement date is in the first coupon
1661        --------------------------------------------------
1662        CALC_DAYS_RUN_C(l_odd_coupon_start,
1663                        l_odd_coupon_maturity,
1664                        l_accrued_int_calc_basis,
1665                        l_coupon_freq,
1666                        l_days_last_cpn_to_nxt_cpn,
1667                        yr_basis,
1668                        NULL,
1669                        p_day_count_type,    -- Added for Interest Override
1670                        l_first_trans_flag); -- Added for Interest Override
1671     else
1672        --------------------------------------------------
1673        -- Settlement date is on or after the first coupon
1674        --------------------------------------------------
1675        CALC_DAYS_RUN_C(l_prev_coupon_date,
1676                        l_next_coupon_date,
1677                        l_accrued_int_calc_basis,
1678                        l_coupon_freq,
1679                        l_days_last_cpn_to_nxt_cpn,
1680                        yr_basis,
1681                        NULL,
1682                        p_day_count_type,    -- Added for Interest Override
1683                        l_first_trans_flag); -- Added for Interest Override
1684 
1685     end if;
1686 
1687     --=================================================================================================
1688     -- COMPOUND COUPON - Find Number of Previous Quasi Coupon
1689     --=================================================================================================
1690     if l_calc_type = 'COMPOUND COUPON' then
1691 
1692        if nvl(l_days_last_cpn_to_settle,0) <> 0 and nvl(l_days_last_cpn_to_nxt_cpn,0) <> 0 then
1693           l_num_current_coupon := l_days_last_cpn_to_settle/l_days_last_cpn_to_nxt_cpn;
1694        else
1695           ---------------------------------------------------------------------------
1696           -- If Settlement Date is on Coupon Date, then l_days_last_cpn_to_settle = 0
1697           ---------------------------------------------------------------------------
1698           l_num_current_coupon := 0;
1699        end if;
1700 
1701        l_bond_rec.p_bond_commence         := l_bond_commence;
1702        l_bond_rec.p_odd_coupon_start      := l_odd_coupon_start;
1703        l_bond_rec.p_odd_coupon_maturity   := l_odd_coupon_maturity;
1704        l_bond_rec.p_calc_date             := p_settlement_date;
1705        l_bond_rec.p_yr_calc_type          := l_accrued_int_calc_basis;
1706        l_bond_rec.p_frequency             := l_coupon_freq;
1707        l_bond_rec.p_curr_coupon           := l_num_current_coupon;
1708        l_bond_rec.p_prv_full_coupon       := l_num_full_cpn_previous;
1709        l_bond_rec.p_day_count_type        := p_day_count_type;
1710        l_prv_quasi_coupon                 := 0;
1711 
1712        l_prv_quasi_coupon := CALC_TOTAL_PREVIOUS_COUPON(l_bond_rec);
1713 
1714     end if;
1715     --=================================================================================================
1716 
1717 
1718     --  Bug 2358500.
1719     --  Re-worked previous code for purchase accrued interest calculations.
1720     --  Added back purchase accrued interest formula for variable bonds
1721     --  removed for patchset C enhancements where the new day count basis
1722     --  'Actual/Actual-Bond' was introduced.
1723 
1724     --  The formula for fixed coupon deals is:
1725     --  (nbr of interest days * cpn rate) / (cpn frequency * nbr of days in coupon period)
1726     --
1727     --  The formula for variable coupon deals is:
1728     --  (nbr of interest days * cpn rate) / year basis
1729     --
1730     --  where, the nbr of interest days is dependent on the coupon status of the deal.
1731     --  CUM vs EX.
1732     --  CUM - number of days between last cpn or deal start and deal settlement.
1733     --  EX  - number of days between deal settlement and cpn maturity.
1734 
1735     --  NOTE: This newly added formula for variable coupon deals will not work properly
1736     --        for "odd" coupon periods (ie.  frequency setup as 4, but only 1st coupon
1737     --        is due 3 months after bond issue start, the remaining coupons are semi-annual)
1738     --        However, none of the current logic will work for these "odd" coupon periods,
1739     --        regardless of day count basis or coupon type (flat vs. variable).
1740     --        This issue has been logged and a decision will have to be made to address it or not.
1741 
1742     l_coupon_rate := ROUND_P(l_coupon_rate);
1743 
1744     --====================================================================================
1745     if l_calc_type = 'COMPOUND COUPON' then
1746     --====================================================================================
1747 
1748        if l_coupon_freq = 0 then
1749           l_temp := 0;
1750        else
1751           l_temp  := ROUND_P( ROUND_P(l_coupon_rate / 100) / nvl(l_coupon_freq,2));
1752        end if;
1753 
1754        p_accrued_interest := ROUND_P( 100 * POWER ( 1 + l_temp, l_prv_quasi_coupon) - 100);
1755 
1756     --====================================================================================
1757     else  -- FLAT or VARIABLE
1758     --====================================================================================
1759        -- Always calculate accrued price for cum to get correct price later.
1760 
1761        l_temp := ROUND_P(l_days_last_cpn_to_settle * l_coupon_rate);
1762 
1763        If (l_calc_type in ('FLAT COUPON','FL REGULAR')) then --bug 2804548
1764           l_temp2 := ROUND_P(l_coupon_freq * l_days_last_cpn_to_nxt_cpn);
1765        Else
1766           l_temp2 := yr_basis;
1767        End If;
1768 
1769        l_acc_cum := ROUND_P(l_temp / l_temp2);
1770 
1771        -- If EX coupon, then calculate true accrued price.
1772 
1773        If (p_ex_cum_next_coupon = 'CUM') then
1774           p_accrued_interest := l_acc_cum;
1775        Else
1776           l_temp := ROUND_P(-(l_days_settle_to_nxt_cpn) * l_coupon_rate);
1777           p_accrued_interest :=  ROUND_P(l_temp / l_temp2);
1778        End If;
1779 
1780     end if;
1781 
1782   END IF;
1783 
1784 
1785 --
1786 -- note that CALC_DAYS_RUN_C is used insatead of CALC_DAYS_RUN because the day
1787 --count basis could be ACT/ACT-BOND
1788   CALC_DAYS_RUN_C(l_prev_coupon_date,
1789                             l_next_coupon_date,
1790                             l_yr_calc_type,
1791                             l_coupon_freq,
1792                             l_days_last_cpn_to_nxt_cpn,
1793                             yr_basis,
1794                             NULL,
1795                             p_day_count_type,
1796                             l_first_trans_flag);
1797 
1798   -- Added for Interest Override feature
1799   IF p_day_count_type='B' AND p_ex_cum_next_coupon='EX' THEN
1800        l_first_trans_flag := NULL;
1801    ELSE
1802        l_first_trans_flag := p_first_trans_flag;
1803   END IF;
1804 
1805   CALC_DAYS_RUN_C(p_settlement_date,
1806                             l_next_coupon_date,
1807                             l_yr_calc_type,
1808                             l_coupon_freq,
1809                             l_days_settle_to_nxt_cpn,
1810                             yr_basis,
1811                             NULL,
1812                             p_day_count_type,
1813                             l_first_trans_flag);
1814 
1815   -- Added for Interest Override feature
1816   IF p_day_count_type='B' and nvl(p_deal_subtype,'BUY') <> 'SELL' THEN
1817        l_first_trans_flag := NULL;
1818    ELSE
1819        l_first_trans_flag := p_first_trans_flag;
1820   END IF;
1821 
1822   CALC_DAYS_RUN_C(l_prev_coupon_date,
1823                             p_settlement_date,
1824                             l_yr_calc_type,
1825                             l_coupon_freq,
1826                             l_days_last_cpn_to_settle,
1827                             yr_basis,
1828                             NULL,
1829                             p_day_count_type,
1830                             l_first_trans_flag);
1831   l_days_last_cpn_to_nxt_cpn := nvl(l_days_last_cpn_to_nxt_cpn,0);
1832    --
1833 --
1834   IF (l_calc_type in ('FLAT COUPON','VARIABLE COUPON','FL REGULAR','FL IRREGULAR')) then
1835     IF p_calculate_yield_or_price = 'P' then
1836     -- Calculate Price (already have yield passed in as p_yield)
1837       --start bug 2804548
1838       IF (l_calc_type in ('FLAT COUPON','VARIABLE COUPON')) then
1839          l_coupon_rate_fl := l_coupon_rate;
1840          p_yield := ROUND_P(p_yield);
1841       ELSE --FLOATING BOND
1842          l_coupon_rate_fl := l_coupon_rate;
1843 	 p_yield_temp:=p_yield;--bug 3135424
1844          --p_yield := ROUND_P(l_coupon_rate_fl-(v_float_margin/100)+(p_yield/100));
1845 	 p_yield := ROUND_P(l_coupon_rate_fl-(v_float_margin/100)+(p_yield));
1846       END IF;
1847       --end bug 2804548
1848       If (l_days_last_cpn_to_nxt_cpn <> 0 and l_coupon_freq <> 0) then
1849         l_temp := ROUND_P(p_yield / 100);
1850         l_temp := ROUND_P(l_temp/l_coupon_freq);
1851         l_temp2:= ROUND_P(l_days_settle_to_nxt_cpn /
1852                           l_days_last_cpn_to_nxt_cpn);
1853         l_temp:= ROUND_P(power((1+l_temp),l_temp2));
1854         l_dirty_px_1 := ROUND_P(100/l_temp);
1855       ELSE
1856         l_dirty_px_1 := 0;
1857       End If;
1858       If (l_coupon_freq <> 0) then
1859         l_coupon_rate_fl:= ROUND_P(l_coupon_rate_fl);
1860         l_temp := ROUND_P(l_coupon_rate_fl/100);
1861         l_dirty_px_2 := ROUND_P(l_temp / l_coupon_freq);
1862         l_temp := ROUND_P(p_yield / 100);
1863         l_temp := ROUND_P(l_temp/l_coupon_freq);
1864         l_temp := ROUND_P(power((l_temp+1),l_num_full_cpn_remain));
1865         l_temp:= ROUND_P(1/l_temp);
1866         l_dirty_px_3 := 1 - l_temp;
1867         l_temp := ROUND_P(p_yield / 100);
1868         l_temp := ROUND_P(l_temp/l_coupon_freq);
1869         l_temp:= ROUND_P(1/(1+l_temp));
1870         l_dirty_px_4 := 1 - l_temp;
1871         l_temp := ROUND_P(p_yield / 100);
1872         l_temp := ROUND_P(l_temp/l_coupon_freq);
1873         l_temp := ROUND_P(power((1+l_temp),l_num_full_cpn_remain - 1));
1874         l_dirty_px_5 := ROUND_P(1 /l_temp);
1875       Else
1876         l_dirty_px_2 := 0;
1877         l_dirty_px_3 := 0;
1878         l_dirty_px_4 := 0;
1879         l_dirty_px_5 := 0;
1880       End If;
1881       If (l_dirty_px_4 <> 0) then
1882         l_temp:= ROUND_P(l_dirty_px_3 / l_dirty_px_4);
1883         l_temp:= ROUND_P(l_dirty_px_2 * l_temp);
1884         p_dirty_price := ROUND_P(l_dirty_px_1 *(l_temp+l_dirty_px_5));
1885         -- if coupon status is EX, then adjust dirty price to be correct
1886         -- dirty_ex = acc_ex +dirty_cum - acc_cum
1887         IF p_ex_cum_next_coupon = 'EX' then
1888           IF (l_price_round_type = 'T') THEN
1889             l_temp:=  trunc(p_dirty_price, l_price_precision);
1890             l_temp2 := trunc(nvl(p_accrued_interest,0), l_price_precision);
1891             l_temp3 := trunc(l_acc_cum, l_price_precision);
1892           ELSE
1893             l_temp := round(p_dirty_price, l_price_precision);
1894             l_temp2 := round(nvl(p_accrued_interest,0), l_price_precision);
1895             l_temp3 := round(l_acc_cum,l_price_precision);
1896           END IF;
1897           p_dirty_price:= l_temp2+l_temp-l_temp3;
1898         END IF;
1899       Else
1900         p_dirty_price := null;
1901       End If;
1902    --
1903       If (p_dirty_price is not NULL) then
1904         IF (l_price_round_type = 'T') THEN
1905           l_temp:=  trunc(p_dirty_price, l_price_precision);
1906           l_temp2 := trunc(nvl(p_accrued_interest,0), l_price_precision);
1907         ELSE
1908           l_temp := round(p_dirty_price, l_price_precision);
1909           l_temp2 := round(nvl(p_accrued_interest,0), l_price_precision);
1910         END IF;
1911         p_clean_price := l_temp-l_temp2;
1912       Else
1913         p_clean_price := null;
1914       End If;
1915     --
1916       --bug 3135424 return the Discount Margin in percent point
1917       if l_calc_type in ('FL REGULAR','FL IRREGULAR') then
1918          p_yield:=p_yield_temp;
1919       END IF;
1920     --
1921     ELSE   -- Calculate Yield (already have dirty price passed in
1922            -- as p_dirty_price)
1923       --
1924       -- Calculate the missing price info
1925       IF (p_clean_price IS NULL) THEN
1926 	-- Need to calculate "CUM" dirty price to find yield
1927         IF p_ex_cum_next_coupon = 'EX' THEN
1928           l_dirty_price_cum := p_dirty_price - p_accrued_interest + l_acc_cum;
1929         ELSE
1930     	  l_dirty_price_cum := p_dirty_price;
1931         END IF;
1932 	--
1933         IF (l_price_round_type = 'T') THEN
1934           l_temp:=  trunc(p_dirty_price, l_price_precision);
1935           l_temp2 := trunc(nvl(p_accrued_interest,0), l_price_precision);
1936         ELSE
1937           l_temp := round(p_dirty_price, l_price_precision);
1938           l_temp2 := round(nvl(p_accrued_interest,0), l_price_precision);
1939         END IF;
1940         p_clean_price:= l_temp - l_temp2;
1941       ELSE
1942 	-- Need to calculate "CUM" dirty price to find yield
1943         IF p_ex_cum_next_coupon = 'EX' THEN
1944           l_dirty_price_cum := p_clean_price + l_acc_cum;
1945         ELSE
1946           l_dirty_price_cum := p_clean_price + p_accrued_interest;
1947         END IF;
1948 	--
1949         IF (l_price_round_type = 'T') THEN
1950           l_temp:=  trunc(p_clean_price, l_price_precision);
1951           l_temp2 := trunc(nvl(p_accrued_interest,0), l_price_precision);
1952         ELSE
1953           l_temp := round(p_clean_price, l_price_precision);
1954           l_temp2 := round(nvl(p_accrued_interest,0), l_price_precision);
1955         END IF;
1956         p_dirty_price := l_temp + l_temp2;
1957       END IF;
1958       If (p_dirty_price is NULL) then
1959         p_yield := null;
1960       Else
1961       -- initially set yield to Coupon Rate
1962         --start bug 2804548
1963         IF (l_calc_type in ('FLAT COUPON','VARIABLE COUPON')) then
1964            l_coupon_rate_fl:= ROUND_Y(l_coupon_rate);
1965            p_yield := l_coupon_rate_fl;
1966         ELSE --FLOATING BOND
1967            l_coupon_rate_fl := ROUND_Y(l_coupon_rate);
1968            --bug 3145424 p_yield := l_coupon_rate_fl-(v_float_margin/100);
1969 	   p_yield := l_coupon_rate_fl-(v_float_margin);
1970         END IF;
1971         --end bug 2804548
1972         l_count := 0;
1973         l_days_last_cpn_to_nxt_cpn := nvl(l_days_last_cpn_to_nxt_cpn,0);
1974         LOOP
1975           l_count := l_count + 1;
1976           If (l_days_last_cpn_to_nxt_cpn <> 0 and l_coupon_freq <> 0) then
1977             l_dirty_px_1 := 100 / power((1 + (p_yield / 100 / l_coupon_freq)),
1978                (l_days_settle_to_nxt_cpn / l_days_last_cpn_to_nxt_cpn));
1979           Else
1980             l_dirty_px_1 := 0;
1981           End If;
1982           If (l_coupon_freq <> 0) then
1983             l_dirty_px_2 := ((l_coupon_rate_fl / 100) / l_coupon_freq);
1984             l_dirty_px_3 := 1 - (1 / power((1 + ((p_yield / 100) /
1985               l_coupon_freq)), l_num_full_cpn_remain));
1986             l_dirty_px_4 := 1 - (1 / (1 + ((p_yield / 100) / l_coupon_freq)));
1987             l_dirty_px_5 := 1 / power((1 + ((p_yield / 100) / l_coupon_freq)),
1988             (l_num_full_cpn_remain - 1));
1989           Else
1990             l_dirty_px_2 := 0;
1991             l_dirty_px_3 := 0;
1992             l_dirty_px_4 := 0;
1993             l_dirty_px_5 := 0;
1994           End If;
1995           If (l_dirty_px_4 <> 0) then
1996             l_calc_dirty_price := l_dirty_px_1 * (l_dirty_px_2 * (l_dirty_px_3
1997               /l_dirty_px_4) + l_dirty_px_5);
1998           Else
1999             l_calc_dirty_price := 0;
2000           End If;
2001           EXIT WHEN ((abs(l_calc_dirty_price - nvl(l_dirty_price_cum,0)) <=
2002             0.0000002) or (l_count >= 15000));
2003           IF l_calc_dirty_price > nvl(l_dirty_price_cum,0) then
2004             IF l_inc_flag='-' then
2005               l_inc_flag :='+';
2006               l_yield_inc:=ROUND_Y(l_yield_inc/2);
2007             END IF;
2008             p_yield :=p_yield + l_yield_inc;
2009           ELSE
2010             IF l_inc_flag='+' then
2011               l_inc_flag :='-';
2012               l_yield_inc:=ROUND_Y(l_yield_inc/2);
2013             END IF;
2014             p_yield :=p_yield - l_yield_inc;
2015           END IF;
2016         END LOOP;
2017         --start bug 2804548
2018         if l_calc_type in ('FL REGULAR','FL IRREGULAR') then
2019           v_actual_ytm := p_yield; --for QRM BPV
2020           --bug 3135424 p_yield := (p_yield-ROUND_Y(l_coupon_rate-(v_float_margin/100)))*100;
2021           p_yield := (p_yield-ROUND_Y(l_coupon_rate-(v_float_margin/100)));
2022         end if;
2023         --end bug 2804548
2024       End If;
2025     END IF;
2026 
2027   ELSIF l_calc_type = 'COMPOUND COUPON' then
2028 
2029      --=================================================================================================
2030      --  Calculate Number of Remaining Quasi Coupon
2031      --=================================================================================================
2032      l_num_full_cpn_remain := nvl(l_num_full_cpn_remain, 0);
2033 
2034      CALC_DAYS_RUN_C(p_settlement_date,
2035                      l_next_coupon_date,
2036                      l_yr_calc_type,
2037                      l_coupon_freq,
2038                      l_days_settle_to_nxt_cpn,
2039                      yr_basis,
2040                      NULL,
2041                      p_day_count_type,
2042                      'N');
2043 
2044      if p_settlement_date < l_odd_coupon_maturity then
2045         CALC_DAYS_RUN_C(l_odd_coupon_start,
2046                         l_odd_coupon_maturity,
2047                         l_yr_calc_type,
2048                         l_coupon_freq,
2049                         l_days_in_current_cpn,
2050                         yr_basis,
2051                         NULL,
2052                         p_day_count_type,    -- Added for Interest Override
2053                         'N');                -- Added for Interest Override
2054      else
2055         CALC_DAYS_RUN_C(l_prev_coupon_date,
2056                         l_next_coupon_date,
2057                         l_yr_calc_type,
2058                         l_coupon_freq,
2059                         l_days_in_current_cpn,
2060                         yr_basis,
2061                         NULL,
2062                         p_day_count_type,
2063                         'N');
2064      end if;
2065 
2066      IF (nvl(l_num_full_cpn_remain, 0) <= 0) THEN
2067         if nvl(l_days_settle_to_nxt_cpn,0) <> 0 and nvl(l_days_in_current_cpn,0) <> 0 then
2068            l_num_full_cpn_remain := l_days_settle_to_nxt_cpn/l_days_in_current_cpn;
2069         else
2070            l_num_full_cpn_remain := 0;
2071         end if;
2072      ELSE
2073         if nvl(l_days_settle_to_nxt_cpn,0) <> 0 and nvl(l_days_in_current_cpn,0) <> 0 then
2074            l_num_full_cpn_remain := (l_num_full_cpn_remain - 1) + l_days_settle_to_nxt_cpn/l_days_in_current_cpn;
2075         else
2076            l_num_full_cpn_remain := (l_num_full_cpn_remain - 1);
2077         end if;
2078      END IF;
2079 
2080      --=================================================================================================
2081 
2082      FND_CURRENCY.Get_Info ( l_currency,
2083                              l_precision,
2084                              l_ext_precision,
2085                              l_min_acct_unit);
2086 
2087      l_full_quasi_coupon := 0;
2088 
2089      if p_bond_issue_code is not null then
2090         open  TOTAL_FULL_COUPONS (p_bond_issue_code);
2091         fetch TOTAL_FULL_COUPONS into l_full_quasi_coupon;
2092         close TOTAL_FULL_COUPONS;
2093      else
2094         ------------------------------------
2095         -- COMPOUND COUPON - for calculator
2096         ------------------------------------
2097         l_full_quasi_coupon := FULL_COUPONS(l_bond_commence, l_maturity_date, l_coupon_freq);
2098      end if;
2099 
2100      --------------------------------------------------------------------------------------------
2101      -- Calculate Price
2102      --------------------------------------------------------------------------------------------
2103      IF p_calculate_yield_or_price = 'P' then
2104 
2105         if p_yield is null then
2106            if p_dirty_price is not null then
2107               p_clean_price := p_dirty_price - p_accrued_interest;
2108            else
2109               p_clean_price := null;
2110            end if;
2111         else
2112            l_temp := ROUND_P(p_yield);
2113            l_temp := ROUND_P(p_yield / 100);
2114 
2115            ----------------------------------------------------------------------
2116            -- Calculate Redemption Value
2117            ----------------------------------------------------------------------
2118            l_comp_coupon.p_bond_start_date       := l_bond_commence;
2119            l_comp_coupon.p_odd_coupon_start      := l_odd_coupon_start;
2120            l_comp_coupon.p_odd_coupon_maturity   := l_odd_coupon_maturity;
2121            l_comp_coupon.p_full_coupon           := l_full_quasi_coupon;
2122            l_comp_coupon.p_coupon_rate           := l_coupon_rate;
2123            l_comp_coupon.p_maturity_amount       := 100;
2124            l_comp_coupon.p_precision             := l_precision;
2125            l_comp_coupon.p_rounding_type         := l_rounding_type;
2126            l_comp_coupon.p_year_calc_type        := l_yr_calc_type;
2127            l_comp_coupon.p_frequency             := l_coupon_freq;
2128            l_comp_coupon.p_day_count_type        := p_day_count_type;
2129            l_comp_coupon.p_amount_redemption_ind := 'R';
2130 
2131            l_redemption_value := CALC_COMPOUND_COUPON_AMT(l_comp_coupon);
2132            --------------------------------------------------------------------------
2133 
2134            if POWER(1+l_temp,l_num_full_cpn_remain) <> 0 then
2135               p_clean_price := ((100+l_redemption_value)/POWER(1+(l_temp/l_coupon_freq),l_num_full_cpn_remain))
2136                                - p_accrued_interest;
2137            else
2138               p_clean_price := 0;
2139            end if;
2140 
2141            ------------------------------------------------------
2142            -- should this be reset everytime  ????????????????
2143            ------------------------------------------------------
2144            p_dirty_price := p_clean_price + p_accrued_interest;
2145            ------------------------------------------------------
2146 
2147         end if;
2148 
2149      --------------------------------------------------------------------------------------------
2150      -- Calculate Yield
2151      --------------------------------------------------------------------------------------------
2152      ELSE
2153 
2154         if p_clean_price is null then
2155            if p_dirty_price is not null then
2156               p_clean_price := p_dirty_price - p_accrued_interest;
2157            end if;
2158         else
2159            if p_dirty_price is null then
2160               p_dirty_price := p_clean_price + p_accrued_interest;
2161            end if;
2162         end if;
2163 
2164         if p_clean_price is not null then
2165 
2166            ----------------------------------------------------------------------
2167            -- Calculate Coupon Amount
2168            ----------------------------------------------------------------------
2169            l_comp_coupon.p_bond_start_date       := l_bond_commence;
2170            l_comp_coupon.p_odd_coupon_start      := l_odd_coupon_start;
2171            l_comp_coupon.p_odd_coupon_maturity   := l_odd_coupon_maturity;
2172            l_comp_coupon.p_full_coupon           := l_full_quasi_coupon;
2173            l_comp_coupon.p_coupon_rate           := l_coupon_rate;
2174            l_comp_coupon.p_maturity_amount       := l_face_value;
2175            l_comp_coupon.p_precision             := l_precision;
2176            l_comp_coupon.p_rounding_type         := l_rounding_type;
2177            l_comp_coupon.p_year_calc_type        := l_yr_calc_type;
2178            l_comp_coupon.p_frequency             := l_coupon_freq;
2179            l_comp_coupon.p_day_count_type        := p_day_count_type;
2180            l_comp_coupon.p_amount_redemption_ind := 'A';
2181 
2182            l_coupon_amount := CALC_COMPOUND_COUPON_AMT(l_comp_coupon);
2183            --------------------------------------------------------------------------
2184            l_dummy_num := l_face_value + l_coupon_amount;
2185 
2186            if p_dirty_price is not null and (nvl(p_input_or_calculator,'I') = 'C' or l_consideration is null) then
2187                -- bug 2617512: change way consideration is calculated
2188                l_amt1 := round(l_face_value, nvl(l_precision,2));
2189                l_amt2 := round(p_clean_price, nvl(p_price_rounding,4)) / 100;
2190                l_amt3 := round(p_accrued_interest, nvl(p_price_rounding, 4)) / 100;
2191                l_consideration := round(l_amt1 * l_amt2 + xtr_fps2_p.interest_round(l_amt1 * l_amt3, nvl(l_precision,2), l_rounding_type));
2192            end if;
2193 
2194            if nvl(l_num_full_cpn_remain,0) <> 0 and l_consideration <> 0 then
2195               p_yield:= (POWER(l_dummy_num/l_consideration,1/l_num_full_cpn_remain)-1)*l_coupon_freq*100;
2196            else
2197               p_yield:= 0;
2198            end if;
2199 
2200         else
2201            p_yield := null;
2202         end if;
2203 
2204      END IF;
2205 
2206 
2207   ELSE
2208   -- Calculate for Zero Coupon Bonds
2209     --bug2536590
2210     l_num_full_cpn_remain := nvl(l_num_full_cpn_remain, 0);
2211     CALC_DAYS_RUN_C(p_settlement_date,
2212                               l_maturity_date,
2213                               l_yr_calc_type,
2214                               l_coupon_freq,
2215                               l_days_settle_to_maturity,
2216                               yr_basis,
2217                               NULL,
2218                               p_day_count_type,
2219                               l_first_trans_flag);
2220     l_settle_to_maturity_years := ROUND_P(l_days_settle_to_maturity/yr_basis);
2221 
2222     IF (nvl(l_num_full_cpn_remain, 0) <= 0) THEN
2223       l_num_full_cpn_remain := 0;
2224     ELSE
2225       l_num_full_cpn_remain := l_num_full_cpn_remain - 1;
2226     END IF;
2227     /* commented out for bug2536590
2228     If (l_days_last_cpn_to_nxt_cpn <> 0) then
2229       IF xtr_risk_debug_pkg.g_Debug THEN
2230          XTR_RISK_DEBUG_PKG.dlog('CALCULATE_BOND_PRICE_YIELD: ' || 'BOND year basis', yr_basis);
2231       END IF;
2232       l_settle_to_nxt_cpn_ratio := ROUND_P(l_days_settle_to_nxt_cpn/yr_basis);
2233     Else
2234       l_settle_to_nxt_cpn_ratio := 0;
2235     End If;
2236     */
2237 
2238     IF p_calculate_yield_or_price = 'P' then
2239    -- Calculate Price
2240    -- Zero Coupon Bonds
2241       If (l_coupon_freq <> 0) then
2242 --        p_yield:= ROUND_P(p_yield);
2243 --        l_temp:= ROUND_P(p_yield/100);
2244 --        l_temp:= ROUND_P(l_temp/l_coupon_freq);
2245 --        p_dirty_price:=ROUND_P(100/(power(1+l_temp,
2246 --				l_settle_to_nxt_cpn_ratio*l_coupon_freq)));
2247 --
2248 --        p_dirty_price:=ROUND_P(100/(power(1+l_temp,
2249 --				l_settle_to_maturity_years*l_coupon_freq)));
2250 
2251           p_dirty_price:=ROUND_P(100 / power((1 + ((p_yield / 100) /
2252             l_coupon_freq)),( l_num_full_cpn_remain + (l_days_settle_to_nxt_cpn / l_days_last_cpn_to_nxt_cpn) )));
2253 --
2254       Else
2255         p_dirty_price := null;
2256       End If;
2257       p_clean_price := p_dirty_price;
2258     ELSE
2259    -- Calculate Yield (already have dirty price passed in as p_dirty_price)
2260    --
2261       -- Calculate the missing price info
2262       IF (p_dirty_price is NULL) THEN
2263         p_dirty_price := p_clean_price;
2264       ELSE
2265         p_clean_price:= p_dirty_price;
2266       END IF;
2267       --
2268       If (p_dirty_price is NULL) then
2269         p_yield := null;
2270       Else
2271    -- approximate yield.
2272         If ((l_maturity_date - p_settlement_date)/365 <> 0) then
2273           l_coupon_rate:=ROUND_Y(l_coupon_rate);
2274           p_yield := l_coupon_rate;
2275          -- (100 - nvl(p_dirty_price,0)) / ((l_maturity_date - p_settlement_date)/365) / 100;
2276         Else
2277           p_yield := 0;
2278         End If;
2279         -- Performance BUG - inordinately SLOW
2280 /*
2281         l_count := 0;
2282         LOOP
2283           l_count := l_count + 1;
2284 ----          l_calc_dirty_price := 100 / power((1 + ((p_yield / 100) /
2285 ----            l_coupon_freq)),(l_settle_to_nxt_cpn_ratio*l_coupon_freq));
2286 
2287 --          l_calc_dirty_price := 100 / power((1 + ((p_yield / 100) /
2288 --            l_coupon_freq)),(l_settle_to_maturity_years*l_coupon_freq));
2289 
2290           l_calc_dirty_price := 100 / power((1 + ((p_yield / 100) /
2291             l_coupon_freq)),( l_num_full_cpn_remain + (l_days_settle_to_nxt_cpn / l_days_last_cpn_to_nxt_cpn) ));
2292           EXIT WHEN ((abs(l_calc_dirty_price - nvl(p_dirty_price,0)) <=
2293           0.00002) or (l_count >= 15000));
2294           If (l_calc_dirty_price > nvl(p_dirty_price,0)) then
2295             If (l_inc_flag='-') then
2296               l_inc_flag :='+';
2297               l_yield_inc:=ROUND_Y(l_yield_inc/2);
2298             End If;
2299             p_yield:=p_yield + l_yield_inc;
2300           Else
2301             If (l_inc_flag='+') then
2302               l_inc_flag :='-';
2303               l_yield_inc:=ROUND_Y(l_yield_inc/2);
2304             End If;
2305             p_yield:=p_yield - l_yield_inc;
2306           End If;
2307         END LOOP;
2308 */
2309         -- Fast closed form solution
2310         --p_yield:=(power((100/p_dirty_price),(1/(l_settle_to_maturity_years*l_coupon_freq)))-1)*l_coupon_freq*100;
2311         p_yield:=(power((100/p_dirty_price),(1/( l_num_full_cpn_remain + (l_days_settle_to_nxt_cpn / l_days_last_cpn_to_nxt_cpn) )))-1)*l_coupon_freq*100;
2312 
2313       END IF;
2314     END IF;
2315   END IF;
2316   IF (l_yield_round_type = 'T') THEN
2317     p_yield :=trunc(p_yield,l_yield_precision);
2318   ELSE
2319     p_yield :=round(p_yield,l_yield_precision);
2320   END IF;
2321   IF (l_price_round_type = 'T') THEN
2322     p_accrued_interest := trunc(p_accrued_interest, l_price_precision);
2323     p_dirty_price := trunc(p_dirty_price, l_price_precision);
2324     p_clean_price := trunc(p_clean_price,l_price_precision);
2325   ELSE
2326     p_dirty_price := round(p_dirty_price, l_price_precision);
2327     p_accrued_interest := round(p_accrued_interest, l_price_precision);
2328     p_clean_price := round(p_clean_price,l_price_precision);
2329   END IF;
2330   p_py_out.p_yield := p_yield;
2331   p_py_out.p_accrued_interest := p_accrued_interest;
2332   p_py_out.p_clean_price := p_clean_price;
2333   p_py_out.p_dirty_price := p_dirty_price;
2334   p_py_out.p_actual_ytm := v_actual_ytm;
2335 
2336 END CALCULATE_BOND_PRICE_YIELD;
2337 
2338 
2339 
2340 --Bug 2804548
2341 --This procedure calculates the Bond Rate Fixing date
2342 --
2343 PROCEDURE bond_rate_fixing_date_calc(p_in_rec IN BndRateFixDate_in_rec,
2344 				 p_out_rec IN OUT NOCOPY BndRateFixDate_out_rec) IS
2345    v_date DATE;
2346    v_err_code        number(8);
2347    v_level           varchar2(2) := ' ';
2348 
2349 BEGIN
2350    if p_in_rec.date_in is not null and p_in_rec.rate_fixing_day is not null
2351    and p_in_rec.ccy is not null then
2352       v_date := p_in_rec.date_in;
2353       FOR i in 1..p_in_rec.rate_fixing_day LOOP
2354          v_date := v_date-1;
2355          XTR_fps3_P.CHK_HOLIDAY (v_date,
2356                              p_in_rec.ccy,
2357                              v_err_code,
2358                              v_level);
2359          if v_err_code is not null then --is holiday
2360             v_date := xtr_fps3_p.PREVIOUS_BUS_DAY(v_date,
2361 			p_in_rec.ccy);
2362          end if;
2363       end loop;
2364       p_out_rec.rate_fixing_date := v_date;
2365    else
2366      RAISE_APPLICATION_ERROR(-20001, 'One or more of the required parameters are missing.');
2367    end if;
2368 END bond_rate_fixing_date_calc;
2369 
2370 
2371 
2372 --Bug 2804548
2373 --This procedure calculates Bond Coupon Amount.
2374 --Copied some of the logic from xtr_calc_p.calc_bond_coupon_amounts
2375 --
2376 PROCEDURE calc_bond_coupon_amt(p_in_rec IN CalcBondCpnAmt_in_rec,
2377 				 p_out_rec IN OUT NOCOPY CalcBondCpnAmt_out_rec) IS
2378 
2379    p_maturity_amount NUMBER;
2380    p_day_count_type xtr_deals.day_count_type%TYPE;
2381    p_settlement_date DATE;
2382    p_rounding_type xtr_deals.rounding_type%TYPE;
2383    p_deal_date DATE;
2384    p_income_tax_ref NUMBER;
2385    p_income_tax_rate NUMBER;
2386    p_coupon_tax_code xtr_rollover_transactions.tax_code%TYPE;
2387    p_bond_issue_code xtr_deals.bond_issue%TYPE;
2388 	l_last_coupon_date	date;
2389         l_coupon_date 		date;
2390 	l_bond_start_date	date;
2391 	l_bond_maturity_date	date;
2392 	l_precision		number;
2393 	l_ext_precision		number;
2394 	l_min_acct_unit		number;
2395 	l_coupon_amt		number;
2396 	l_currency		varchar2(15);
2397 	l_coupon_rate		number;
2398 	l_frequency		number;
2399 	l_year_calc_type	varchar2(15);
2400 	l_year_basis		number;
2401 	l_nbr_days_in_period	number;
2402 	l_calc_type		varchar2(15);
2403 	-- Added for Interest Override
2404 	l_original_amount       NUMBER;
2405 	l_first_trans_flag      VARCHAR2(1);
2406 	--
2407 	l_income_tax_out	NUMBER;
2408 	l_dummy_num		NUMBER;
2409 	l_dummy_char		VARCHAR2(20);
2410 --
2411       --The rate for FLoating BOND will be different for each COUPON,
2412       --while it's the same for non-FLoating BOND.
2413    cursor BOND_DETAILS(p_bond_issue_code VARCHAR2,
2414 			p_coupon_date DATE) is
2415 	select i.currency,
2416 	       c.rate,
2417 	       i.no_of_coupons_per_year,
2418 	       i.maturity_date,
2419 	       i.year_calc_type,
2420 	       i.commence_date,
2421 	       i.calc_type
2422 	from xtr_bond_issues i, xtr_bond_coupon_dates c
2423 	where i.bond_issue_code = p_bond_issue_code
2424         and c.bond_issue_code=i.bond_issue_code
2425         and c.coupon_date=p_coupon_date;
2426 --
2427    cursor GET_LAST_COUPON_DATE(p_bond_issue_code VARCHAR2,
2428 				p_next_coupon_date DATE) is
2429 	select max(coupon_date)
2430 	from xtr_bond_coupon_dates
2431 	where bond_issue_code = p_bond_issue_code
2432 	and coupon_date < p_next_coupon_date;
2433 --
2434    cursor get_deal_info(p_deal_no NUMBER,p_trans_no NUMBER) is
2435         select d.start_date,d.maturity_balance_amount,d.day_count_type,
2436         d.rounding_type,
2437 	d.deal_date,rt.tax_settled_reference,rt.tax_rate,d.bond_issue,
2438 	rt.tax_code,rt.maturity_date
2439         from xtr_deals d, xtr_rollover_transactions rt
2440         where d.deal_no=p_deal_no
2441         and rt.deal_number=d.deal_no
2442         and rt.transaction_number=p_trans_no;
2443 --
2444    cursor GET_SETTLE_METHOD(p_tax_code VARCHAR2) is
2445 	select TAX_SETTLE_METHOD
2446   	from   XTR_TAX_BROKERAGE_SETUP
2447   	where  REFERENCE_CODE = p_tax_code;
2448 --
2449    v_tax_settle_method xtr_tax_brokerage_setup.tax_settle_method%TYPE;
2450 --
2451 
2452 -- Added for Bug 4731954
2453 Cursor C_ADD_RESALE_AMOUNT (p_deal_no NUMBER,l_curr_cpn_date date) is
2454    Select sum(face_value)
2455      from xtr_bond_alloc_details
2456     where deal_no = p_deal_no
2457       and cross_ref_start_date >= l_curr_cpn_date;
2458 
2459       p_resold_amount NUMBER; -- Added for Bug 4731954
2460 
2461 
2462 BEGIN
2463 
2464    if p_in_rec.transaction_no is not null and p_in_rec.deal_no is not null then
2465 
2466       open get_deal_info(p_in_rec.deal_no,p_in_rec.transaction_no);
2467       fetch get_deal_info into p_settlement_date,p_maturity_amount,
2468 		p_day_count_type,p_rounding_type,p_deal_date,p_income_tax_ref,
2469 		p_income_tax_rate,p_bond_issue_code,p_coupon_tax_code,
2470 		l_coupon_date;
2471       close get_deal_info;
2472 
2473       /* Obtain pertinent info on bond. */
2474       Open  BOND_DETAILS(p_bond_issue_code,
2475 			l_coupon_date);
2476       Fetch BOND_DETAILS into l_currency, l_coupon_rate, l_frequency, l_bond_maturity_date,
2477                            l_year_calc_type, l_bond_start_date, l_calc_type;
2478       If (BOND_DETAILS%NOTFOUND) then
2479          Close BOND_DETAILS;
2480          FND_MESSAGE.Set_Name('XTR','XTR_2171');
2481          APP_EXCEPTION.Raise_Exception;
2482       End If;
2483       Close BOND_DETAILS;
2484 
2485       /* Obtain currency precision for bond. */
2486 
2487       FND_CURRENCY.Get_Info (
2488    			l_currency,
2489    			l_precision,
2490    			l_ext_precision,
2491    			l_min_acct_unit);
2492 
2493       /* Obtain last coupon date before the next coupon date.
2494       In the case of an 'EX' status bond, this last coupon date is > the settlement date.
2495       In the case of an 'CUM' status bond, this last coupon date is <= the settlement date.
2496       We need to determine this date in order to compute the 'nbr of days' between the coupon
2497       period, with consideration given for the days calc method. */
2498 
2499       Open  GET_LAST_COUPON_DATE(p_bond_issue_code,
2500 				l_coupon_date);
2501       Fetch GET_LAST_COUPON_DATE into l_last_coupon_date;
2502       If (l_last_coupon_date is NULL) then
2503 
2504       -- NOTE:  Can't check for cursor %NOTFOUND since the 'max' will return a NULL row,
2505       --        which is considered a 'found' case.
2506 
2507          Close GET_LAST_COUPON_DATE;
2508          l_last_coupon_date := nvl(l_bond_start_date,p_settlement_date);
2509       Else
2510          Close GET_LAST_COUPON_DATE;
2511       End If;
2512 
2513       -- Added for Interest Override
2514       IF p_in_rec.transaction_no = 2 and l_calc_type <> 'COMPOUND COUPON' THEN
2515 	 l_first_trans_flag :='Y';
2516       ELSE
2517 	 l_first_trans_flag := NULL;
2518       END IF;
2519 
2520      -- Calculate the correct maturity amount by adding the balance amount with the amount
2521       -- sold after the maturity date of the transaction
2522       --  Added for Bug 4731954
2523       OPEN C_ADD_RESALE_AMOUNT(p_in_rec.deal_no,l_coupon_date);
2524       FETCH C_ADD_RESALE_AMOUNT INTO p_resold_amount;
2525       CLOSE C_ADD_RESALE_AMOUNT;
2526 
2527       p_maturity_amount := p_maturity_amount + nvl(p_resold_amount,0);
2528 
2529       --Calculate coupon amount
2530       If l_calc_type in ('VARIABLE COUPON','FL IRREGULAR') then
2531 
2532          /* Need to compute # of days between the coupon period and determine # of days in the year
2533             (l_year_basis) based on the year_calc_type. */
2534 
2535          -- Bug 2358549.
2536          -- Changed call to Calc_Days_Run_C from Calc_Days_Run in order
2537          -- to properly handle the year calc type of 'Actual/Actual-Bond'
2538          -- which was introduced in patchset C.
2539 
2540          XTR_CALC_P.Calc_Days_Run_C (
2541    			l_last_coupon_date,
2542 	   		l_coupon_date,
2543    			l_year_calc_type,
2544    			l_frequency,
2545    			l_nbr_days_in_period,
2546 			l_year_basis,
2547 			NULL,
2548 		        p_day_count_type,  -- Added for Override feature
2549 			l_first_trans_flag --  Added for Override feature
2550 				   );
2551 
2552 	 -- Changed for Interest Override
2553          -- l_coupon_amt := round((p_maturity_amount * (l_coupon_rate / 100) * (l_nbr_days_in_period / l_year_basis)), l_precision);
2554          l_original_amount := xtr_fps2_p.interest_round((p_maturity_amount * (l_coupon_rate / 100) * (l_nbr_days_in_period / l_year_basis)), l_precision,p_rounding_type);
2555 	  l_coupon_amt := l_original_amount;
2556       Elsif l_calc_type in ('FLAT COUPON','FL REGULAR') then
2557          --Flat coupons do not need to take day count basis into consideration.
2558          --We need to call this to calculate NO_OF_DAYS even though we are not using
2559          -- in coupon calculation.
2560 
2561          -- Bug 2358549.
2562          -- Changed call from Calc_Days_Run to Calc_Days_Run_C in order
2563          -- to properly handle the year calc type of 'Actual/Actual-Bond'
2564          -- which was introduced in patchset C.
2565 
2566          XTR_CALC_P.Calc_Days_Run_C (
2567    			l_last_coupon_date,
2568 	   		l_coupon_date,
2569    			l_year_calc_type,
2570    			l_frequency,
2571    			l_nbr_days_in_period,
2572 			l_year_basis,
2573 			NULL,
2574 		        p_day_count_type,  -- Added for Override feature
2575 			l_first_trans_flag --  Added for Override feature
2576 			);
2577 	 -- Changed for Interest Override
2578          -- l_coupon_amt := round((p_maturity_amount * (l_coupon_rate / 100) / nvl(l_frequency,2)), l_precision);
2579 	 l_original_amount := xtr_fps2_p.interest_round((p_maturity_amount * (l_coupon_rate / 100) / nvl(l_frequency,2)),
2580 					     l_precision,p_rounding_type);
2581 	 l_coupon_amt := l_original_amount;
2582       End If;
2583 
2584       -- calculate taxes
2585       IF (p_coupon_tax_code IS NOT NULL) THEN
2586            XTR_FPS1_P.calc_tax_amount('BOND',
2587 				 p_deal_date,
2588 				 null,
2589 				 p_coupon_tax_code,
2590 				 l_currency,
2591 				 null,
2592 				 0,
2593 				 0,
2594 				 null,
2595 				 l_dummy_num,
2596 				 l_coupon_amt,
2597 				 p_income_tax_rate,
2598 				 l_dummy_num,
2599 				 l_income_tax_out,
2600 				 l_dummy_num,
2601 				 l_dummy_char);
2602          --bug 2919154 round 3 issue 1
2603          --OPEN get_settle_method(p_coupon_tax_code);
2604          --FETCH get_settle_method INTO v_tax_settle_method;
2605          --CLOSE get_settle_method;
2606       END IF;
2607    else
2608       RAISE_APPLICATION_ERROR(-20001, 'One or more of the required parameters are missing.');
2609    end if;
2610    p_out_rec.coupon_amt:=l_coupon_amt;
2611    p_out_rec.coupon_tax_amt:=l_income_tax_out;
2612 END calc_bond_coupon_amt;
2613 
2614 
2615 
2616 --Bug 2804548
2617 --This procedure check whether the coupon or its tax has been reset.
2618 --This is called during settlement authorization, coupon amount override
2619 --Can be passed in with or w/o bond_issue_code and coupon_date.
2620 --If the coupon has been reset the value OUT will be TRUE, else FALSE.
2621 --
2622 PROCEDURE check_coupon_rate_reset(p_in_rec IN ChkCpnRateReset_in_rec,
2623 				 p_out_rec IN OUT NOCOPY ChkCpnRateReset_out_rec) IS
2624 
2625    cursor check_coupon_rate_reset(p_deal_no NUMBER,
2626 				p_trans_no NUMBER) is
2627       select count(*)
2628       from xtr_bond_coupon_dates bc, xtr_deals d, xtr_rollover_transactions rt
2629       where rt.deal_number=p_deal_no
2630       and rt.transaction_number=p_trans_no
2631       and d.deal_no=rt.deal_number
2632       and bc.bond_issue_code=d.bond_issue
2633       and bc.coupon_date=rt.maturity_date
2634       and bc.rate_update_on<bc.rate_fixing_date;
2635 
2636    cursor check_coupon_rate_reset_all(p_deal_no NUMBER) is
2637       select count(*)
2638       from xtr_bond_coupon_dates bc, xtr_deals d, xtr_rollover_transactions rt
2639       where d.deal_no=p_deal_no
2640       and d.deal_no=rt.deal_number
2641       and bc.bond_issue_code=d.bond_issue
2642       and bc.coupon_date=rt.maturity_date
2643       and bc.rate_update_on<bc.rate_fixing_date;
2644 
2645    cursor get_coupon_info(p_settled_ref NUMBER) is
2646       select deal_number,transaction_number
2647       from xtr_rollover_transactions
2648       where tax_settled_reference=p_settled_ref;
2649 
2650    v_deal_no NUMBER;
2651    v_transaction_no NUMBER;
2652    v_dummy NUMBER;
2653 BEGIN
2654    p_out_rec.yes := TRUE;
2655    if p_in_rec.deal_type is not null or p_in_rec.transaction_no is not null then
2656       if p_in_rec.deal_type='EXP' then
2657          open get_coupon_info(p_in_rec.transaction_no);
2658          fetch get_coupon_info into v_deal_no,v_transaction_no;
2659          close get_coupon_info;
2660       else
2661          v_deal_no := p_in_rec.deal_no;
2662          v_transaction_no := p_in_rec.transaction_no;
2663       end if;
2664       if v_transaction_no is null then
2665          open check_coupon_rate_reset_all(v_deal_no);
2666          fetch check_coupon_rate_reset_all into v_dummy;
2667          close check_coupon_rate_reset_all;
2668       else
2669          open check_coupon_rate_reset(v_deal_no,v_transaction_no);
2670          fetch check_coupon_rate_reset into v_dummy;
2671          close check_coupon_rate_reset;
2672       end if;
2673       if v_dummy>0 then
2674           p_out_rec.yes := FALSE;
2675       else
2676           p_out_rec.yes := TRUE;
2677       end if;
2678    else
2679       RAISE_APPLICATION_ERROR(-20001, 'One or more of the required parameters are missing.');
2680    end if;
2681    p_out_rec.deal_no:=v_deal_no;
2682 END check_coupon_rate_reset;
2683 
2684 END;
2685