DBA Data[Home] [Help]

PACKAGE BODY: APPS.XTR_FPS1_P

Source


1 PACKAGE BODY XTR_FPS1_P as
2 /* $Header: xtrfps1b.pls 120.3 2005/06/29 07:26:44 badiredd ship $ */
3 ----------------------------------------------------------------------------------------------------------------
4 PROCEDURE ADVICE_LETTERS (l_deal_type  IN VARCHAR2,
5 					    l_product    IN VARCHAR2,
6 					    l_cparty     IN VARCHAR2,
7 					    l_client     IN VARCHAR2,
8 					    l_cparty_adv IN OUT NOCOPY VARCHAR2,
9 					    l_client_adv IN OUT NOCOPY VARCHAR2) as
10       --
11        l_cparty_prod CHAR(1);
12        l_client_prod CHAR(1);
13       --
14        cursor PROD_LEVEL_ADV is
15 	select nvl(a.CPARTY_ADVICE,'Y'),nvl(a.CLIENT_ADVICE,'Y')
16 	 from XTR_PRODUCT_TYPES a
17 	 where a.DEAL_TYPE = l_deal_type
18 	 and   a.PRODUCT_TYPE = l_product;
19       --
20        cursor CPARTY_LEVEL_ADV is
21 	select a.CLIENT_ADVICE
22 	 from XTR_PARTY_INFO_V a
23 	 where a.PARTY_CODE = l_cparty;
24       --
25        cursor CLIENT_LEVEL_ADV is
26 	select a.CLIENT_ADVICE
27 	 from XTR_PARTY_INFO_V a
28 	 where a.PARTY_CODE = l_client;
29       --
30       begin
31        open PROD_LEVEL_ADV;
32 	fetch PROD_LEVEL_ADV INTO l_cparty_prod,l_client_prod;
33        close PROD_LEVEL_ADV;
34        --
35        if l_cparty is NOT NULL then
36 	open CPARTY_LEVEL_ADV;
37 	 fetch CPARTY_LEVEL_ADV INTO l_cparty_adv;
38 	 if l_cparty_adv is NULL then
39 	  l_cparty_adv := l_cparty_prod;
40 	 end if;
41 	close CPARTY_LEVEL_ADV;
42        else
43 	l_cparty_adv := 'N';
44        end if;
45        --
46        if l_client is NOT NULL then
47 	open CLIENT_LEVEL_ADV;
48 	 fetch CLIENT_LEVEL_ADV INTO l_client_adv;
49 	 if l_client_adv is NULL then
50 	  l_client_adv := l_client_prod;
51 	 end if;
52 	close CLIENT_LEVEL_ADV;
53        else
54 	l_client_adv := 'N';
55        end if;
56 end ADVICE_LETTERS ;
57 ----------------------------------------------------------------------------------------------------------------
58 PROCEDURE CAL_BOND_PRICE (num_full_cpn_remain      IN NUMBER,
59 				 annual_yield             IN NUMBER,
60 				 days_settle_to_nxt_cpn   IN NUMBER,
61 				 days_last_cpn_to_nxt_cpn IN NUMBER,
62 				 annual_cpn               IN NUMBER,
63 				 l_vol_chg_ann_yield      IN NUMBER,
64 				 cum_price                IN OUT NOCOPY NUMBER,
65 				 ex_price                 IN OUT NOCOPY NUMBER,
66 				 vol_price                IN OUT NOCOPY NUMBER) as
67 --
68  controlnum NUMBER;
69 --
70 begin
71 	controlnum := 0;
72 	if num_full_cpn_remain > 0 then
73 	    ex_price :=
74 		    (((1 / (power(1 + annual_yield,num_full_cpn_remain))) +
75 		     (annual_cpn * ((1 - (1 / power(1 + annual_yield,num_full_cpn_remain))) / annual_yield))) /
76 		     power(1 + annual_yield,(days_settle_to_nxt_cpn / days_last_cpn_to_nxt_cpn)) * 100);
77 	else
78 	    ex_price :=
79 		    (100 / (1 + ((days_settle_to_nxt_cpn * annual_yield) /
80 					days_last_cpn_to_nxt_cpn)));
81 	end if;
82 	controlnum := 1;
83 	if num_full_cpn_remain > 0 then
84 	    cum_price :=
85 		    (((1 / power(1 + annual_yield,num_full_cpn_remain)) +
86 		     (annual_cpn * (controlnum + ((1 - (1/(power(1 +
87 		     annual_yield,num_full_cpn_remain)))) / annual_yield)))) /
88 		      power(1 + annual_yield,days_settle_to_nxt_cpn /
89 		      days_last_cpn_to_nxt_cpn)) * 100;
90 	else
91 	    cum_price :=
92 		    (100 + (100 * annual_cpn))/(1 + days_settle_to_nxt_cpn *
93 		     annual_yield / days_last_cpn_to_nxt_cpn);
94 	end if;
95 	if num_full_cpn_remain > 0 then
96 	    vol_price :=
97 		    (((1 / power(1 + l_vol_chg_ann_yield,num_full_cpn_remain))
98 		     + (annual_cpn * (controlnum + ((1 - (1 / (power(1 +
99 		     l_vol_chg_ann_yield,num_full_cpn_remain)))) /
100 		     l_vol_chg_ann_yield)))) / power(1 + l_vol_chg_ann_yield,
101 		     days_settle_to_nxt_cpn / days_last_cpn_to_nxt_cpn))* 100;
102 	else
103 	   vol_price :=
104 		    (100 + (100 * annual_cpn))/(1 + days_settle_to_nxt_cpn *
105 		     l_vol_chg_ann_yield / days_last_cpn_to_nxt_cpn);
106 	end if;
107 end CAL_BOND_PRICE;
108 ----------------------------------------------------------------------------------------------------------------
109 PROCEDURE CALC_OPTION_PRICE (l_expiry      IN DATE,
110 			     l_volatility  IN NUMBER,
111 			     l_counter_ccy IN CHAR,
112 			     l_market_rate IN NUMBER,
113 			     l_strike_rate IN NUMBER,
114 			     l_spot_rate   IN NUMBER,
115 			     l_subtype     IN CHAR,
116 			     l_int_rate    IN NUMBER,
117 			     l_ref_amount  IN NUMBER,
118 			     l_put_call    IN CHAR,
119 			     l_reval_amt   IN OUT NOCOPY NUMBER,
120 			     l_end_date    IN DATE) is
121 --
122 --**************** Note this Procedureis NOW REDUNDANT REPLACED BY STANDALONE
123 -- PROCEDURE CALC_OPTION_PRICES *********************
124  l_call_price   NUMBER;
125  l_put_price    NUMBER;
126  l_percent_put  NUMBER;
127  l_prem_put     NUMBER;
128  l_percent_call NUMBER;
129  l_prem_call    NUMBER;
130  exp1           NUMBER(13,8);
131  exp2           NUMBER(13,8);
132  exp3           NUMBER(13,8);
133  lan1           NUMBER(13,9);
134  lan2           NUMBER(13,9);
135  lan3           NUMBER(13,9);
136  r              NUMBER(13,9);
137  t              NUMBER(13,9);
138  fp             NUMBER(9,4);
139  ep             NUMBER(9,4);
140  vol            NUMBER(13,9);
141  prob           NUMBER(13,9);
142  lan            NUMBER(13,9);
143  d1             NUMBER(9,5);
144  d2             NUMBER(9,5);
145  nd1_calc_diff  NUMBER(9,5);
146  nd2_calc_diff  NUMBER(9,5);
147  nd20           NUMBER(9,5);
148  nd21           NUMBER(9,5);
149  nd22           NUMBER(9,5);
150  nd10           NUMBER(9,5);
151  nd11           NUMBER(9,5);
152  nd12           NUMBER(9,5);
153  nd1            NUMBER(9,5);
154  nd2            NUMBER(9,5);
155  year_basis     NUMBER(3,0);
156  expt           NUMBER(13,8);
157  calc_diff      NUMBER(13,9);
158  calc_diff1     NUMBER(13,9);
159 --
160  cursor YRBASIS is
161   select m.YEAR_BASIS
162    from  XTR_MASTER_CURRENCIES m
163    where CURRENCY = l_counter_ccy;
164 --
165  cursor LAN_VALUE is
166   select c.LAN, d.LAN, e.LAN
167    from  XTR_CUM_DIST_CALCS c,
168 	 XTR_CUM_DIST_CALCS d,
169 	 XTR_CUM_DIST_CALCS e
170    where c.MKT_EXP = round(fp/ep,2)
171    and   d.MKT_EXP = (round((FP/EP),2) + .005)
172    and   e.MKT_EXP = (round((FP/EP),2) - .005);
173 --
174  cursor EXPT_VALUE is
175   select c.EXPT,d.EXPT,e.EXPT
176    from  XTR_CUM_DIST_CALCS c,
177 	 XTR_CUM_DIST_CALCS d,
178 	 XTR_CUM_DIST_CALCS e
179    where c.INT_DAYS = round((-(1)*r*t),2)
180    and   d.INT_DAYS = (round((-(1)*r*t),2) + .005)
181    and   e.INT_DAYS = (round((-(1)*r*t),2) - .005);
182 --
183  cursor PROB_VALUE_1 is
184   select c.PROBABILITY, d.PROBABILITY, e.PROBABILITY
185    from  XTR_CUM_DIST_CALCS c,
186 	 XTR_CUM_DIST_CALCS d,
187 	 XTR_CUM_DIST_CALCS e
188    where c.DEVIATION = round(d1,2)
189    and   d.DEVIATION = (round(d1,2) + .005)
190    and   e.DEVIATION = (round(d1,2) - .005);
191 --
192  cursor PROB_VALUE_2 is
193   select c.PROBABILITY, d.PROBABILITY, e.PROBABILITY
194    from  XTR_CUM_DIST_CALCS c,
195 	 XTR_CUM_DIST_CALCS d,
196 	 XTR_CUM_DIST_CALCS e
197    where c.DEVIATION = round(d2,2)
198    and   d.DEVIATION = (round(d2,2) + .005)
199    and   e.DEVIATION = (round(d2,2) - .005);
200 --
201 begin
202  open YRBASIS;
203   fetch YRBASIS into year_basis;
204  if YRBASIS%NOTFOUND then
205    year_basis := 360;
206  end if;
207  close YRBASIS;
208  r  := l_int_rate / 100;
209  t  := (l_expiry - l_end_date) / year_basis;
210  fp := l_market_rate;
211  ep := l_strike_rate;
212  calc_diff := (-(1)*r*t) - round((-(1)*r*t),2);
213  calc_diff1 := (fp/ep) - round((fp/ep),2);
214  if l_subtype = 'SELL' then
215   -- Vol is brought in as a mid rate therefore assuming a 0.5 spread
216   -- the Offer vol is 0.25 higher
217   -- therefore if we previously sold the option Use Offer Vol for
218   -- closeout of the option
219   vol := (l_volatility + 0.25) / 100;
220  else
221   -- the Bid Vol is 0.25 lower
222   -- therefore if we previously purchased the option Use Bid Vol for
223   -- closeout of the option
224   vol := (l_volatility - 0.25) / 100;
225  end if;
226  open LAN_VALUE;
227   fetch LAN_VALUE into lan1,lan2,lan3;
228  if LAN_VALUE%NOTFOUND then
229   close LAN_VALUE;
230   goto NULL_VAL_FOUND;
231   --DISP_ERR(980);--Log value not found
232  end if;
233  close LAN_VALUE;
234  open EXPT_VALUE;
235   fetch EXPT_VALUE into exp1, exp2, exp3;
236  if EXPT_VALUE%NOTFOUND then
237   close EXPT_VALUE;
238   goto NULL_VAL_FOUND;
239   -- DISP_ERR(981);--Exponential value
240  end if;
241  close EXPT_VALUE;
242  if round((-(1) * r * t),2) > (-(1) * r * t) then
243   expt := exp1 - ((calc_diff / .005) * (exp3 - exp1));
244  else expt := exp1 + ((calc_diff / .005) * (exp2 - exp1));
245  end if;
246  if round((FP/EP),2) < (FP/EP) then
247   lan := lan1 + ((calc_diff1 /.005) * (lan2 - lan1));
248  else lan := lan1 - ((calc_diff1 /.005) * (lan3 - lan1));
249  end if;
250  d1 := (lan + (vol * vol / 2 * t)) / (vol * sqrt(t));
251  d2 := d1 - (vol * sqrt(t));
252  nd1_calc_diff := d1 - round(d1,2);
253  nd2_calc_diff := d2 - round(d2,2);
254  open PROB_VALUE_1;
255   fetch PROB_VALUE_1 into nd10,nd11,nd12;
256  if PROB_VALUE_1%NOTFOUND then
257   close PROB_VALUE_1;
258   goto NULL_VAL_FOUND;
259   --DISP_ERR(982);--Probabilty value not found for d1.
260  end if;
261  close PROB_VALUE_1;
262  if round(d1,2) < d1 then
263    ND1 := nd10 + ((nd1_calc_diff /.005) * (nd11 - nd10));
264  else ND1 := nd10 - ((nd1_calc_diff /.005) * (nd12 - nd10));
265  end if;
266  open PROB_VALUE_2;
267   fetch PROB_VALUE_2 into nd20,nd21,nd22;
268  if PROB_VALUE_2%NOTFOUND then
269   close PROB_VALUE_2;
270   goto NULL_VAL_FOUND;
271   --DISP_ERR(983);--Probabilty value not found for D2
272  end if;
273  close PROB_VALUE_2;
274  if round(d2,2) < d2 then
275    ND2 := nd20 + ((nd2_calc_diff /.005) * (nd21 - nd20));
276  else ND2 := nd20 - ((nd2_calc_diff /.005) * (nd22 - nd20));
277  end if;
278  l_call_price    := expt * ((fp * nd1) - (ep * nd2));
279  l_put_price     := l_call_price + (expt * (ep - fp));
280  l_percent_put   := l_put_price / nvl(l_spot_rate,l_strike_rate);
281  l_percent_put   := round(l_percent_put * 100,3);
282  l_prem_put      := l_percent_put / 100 * l_ref_amount;
283  l_percent_call  := l_call_price / nvl(l_spot_rate,l_strike_rate);
284  l_percent_call  := round(l_percent_call * 100,3);
285  l_prem_call     := l_percent_call / 100 * l_ref_amount;
286  if l_put_call = 'P' then
287   l_reval_amt := l_prem_put;
288  else
289   l_reval_amt := l_prem_call;
290  end if;
291  <<NULL_VAL_FOUND>>
292   l_reval_amt := nvl(l_reval_amt,0);
293 end CALC_OPTION_PRICE ;
294 ----------------------------------------------------------------------------------------------------------------
295 --   Procedure to calculate tax and brokerage amounts
296 PROCEDURE CALC_TAX_BROKERAGE(l_deal_type    IN VARCHAR2,
297                              l_deal_date    IN DATE,
298                              l_tax_ref      IN VARCHAR2,
299 			     l_bkge_ref     IN VARCHAR2,
300 			     l_ccy          IN VARCHAR2,
301 			     l_yr_basis     IN NUMBER,
302 			     l_num_days     IN NUMBER,
303 			     l_tax_amt_type IN VARCHAR2,
304 			     l_tax_amt      IN NUMBER,
305 			     l_tax_rate     IN OUT NOCOPY NUMBER,
306 			     l_bkr_amt_type IN VARCHAR2,
307 			     l_bkr_amt      IN NUMBER,
308 			     l_bkr_rate     IN OUT NOCOPY NUMBER,
309 			     l_tax_out      IN OUT NOCOPY NUMBER,
310 			     l_tax_out_hce  IN OUT NOCOPY NUMBER,
311 			     l_bkge_out     IN OUT NOCOPY NUMBER,
312 			     l_bkge_out_hce IN OUT NOCOPY NUMBER,
313 			     l_err_code        OUT NOCOPY NUMBER,
314 			     l_level           OUT NOCOPY VARCHAR2) is
315 /*
316 			     l_amt_type1    IN VARCHAR2,
317 			     l_amt1         IN NUMBER,
318 			     l_amt_type2    IN VARCHAR2,
319 			     l_amt2         IN NUMBER,
320 			     l_amt_type3    IN VARCHAR2,
321 			     l_amt3         IN NUMBER,
322 */
323 --
324  tax_base_amt       NUMBER;
325  bkge_base_amt      NUMBER;
326  l_rounding_factor  NUMBER;
327  l_tax_c_basis      VARCHAR(6);
328  l_bkge_c_basis     VARCHAR(6);
329  l_tax_amt_ty       VARCHAR(7);
330  l_bkge_amt_ty      VARCHAR(7);
331 -- yr_basis        NUMBER;
332  l_dummy_char       VARCHAR(7);
333 --
334  -------------------
335  -- AW Bug 1585466
336  -------------------
337  cursor  GET_ROUND_FACTOR is
338   select nvl(rounding_factor,2)
339    from  XTR_MASTER_CURRENCIES_V s
340    where s.CURRENCY   = l_ccy;
341 --
342  cursor BKGE_DETAILS is
343   select b.CALC_BASIS,
344          nvl(d.INTEREST_RATE,0)
345    from  XTR_TAX_BROKERAGE_SETUP a,
346 	 XTR_DEDUCTION_CALCS b,
347          XTR_TAX_BROKERAGE_RATES d
348    where a.REFERENCE_CODE      = l_bkge_ref
349    and   nvl(a.AUTHORISED,'N') = 'Y'
350    and   b.DEAL_TYPE           = l_deal_type
351    and   b.CALC_TYPE           = a.CALC_TYPE
352    and   b.AMOUNT_TYPE         = l_bkr_amt_type
353    and   d.RATE_GROUP          = a.RATE_GROUP
354    and   d.REF_TYPE            = 'B'
355    and   d.EFFECTIVE_FROM     <= l_deal_date
356    and   nvl(d.MIN_AMT,0)     <= l_bkr_amt
357    and   (d.MAX_AMT >= l_bkr_amt or d.MAX_AMT is NULL)
358    order by d.EFFECTIVE_FROM desc;
359 --
360  cursor TAX_DETAILS is
361   select b.CALC_BASIS,
362          nvl(d.INTEREST_RATE,0)
363    from  XTR_TAX_BROKERAGE_SETUP a,
364 	 XTR_DEDUCTION_CALCS b,
365          XTR_TAX_BROKERAGE_RATES d
366    where a.REFERENCE_CODE      = l_tax_ref
367    and   nvl(a.AUTHORISED,'N') = 'Y'
368    and   b.DEAL_TYPE           = l_deal_type
369    and   b.CALC_TYPE           = a.CALC_TYPE
370    and   b.AMOUNT_TYPE         = l_tax_amt_type
371    and   d.RATE_GROUP          = a.RATE_GROUP
372    and   d.REF_TYPE            = 'T'
373    and   d.EFFECTIVE_FROM     <= l_deal_date
374    and   nvl(d.MIN_AMT,0)     <= l_tax_amt
375    and   (d.MAX_AMT >= l_tax_amt or d.MAX_AMT is NULL)
376    order by d.EFFECTIVE_FROM desc;
377 
378  -------------------
379  -- AW Bug 1585466
380  -------------------
381  cursor CALC_HCE_AMTS is
382   select round((l_tax_out / s.hce_rate),nvl(rounding_factor,2)),
383 	 round((l_bkge_out / s.hce_rate),nvl(rounding_factor,2))
384    from  XTR_MASTER_CURRENCIES_V s
385    where s.CURRENCY   = l_ccy;
386 --
387 /*
388  cursor Y_BASE is
389   select YEAR_BASIS
390    from XTR_MASTER_CURRENCIES
391    where CURRENCY = l_ccy;
392 */
393  v_tax_rate  NUMBER;
394  v_bkr_rate  NUMBER;
395 --
396 begin
397 /*
398  open Y_BASE;
399   fetch Y_BASE INTO yr_basis;
400  if Y_BASE%NOTFOUND then
401   yr_basis := 365;
402  end if;
403  close Y_BASE;
404 */
405 
406  -------------------
407  -- AW Bug 1585466
408  -------------------
409  open GET_ROUND_FACTOR;
410  fetch GET_ROUND_FACTOR into l_rounding_factor;
411  close GET_ROUND_FACTOR;
412 
413  v_tax_rate := l_tax_rate;
414  v_bkr_rate := l_bkr_rate;
415 
416  ----------------
417  -- Tax Details
418  ----------------
419  if l_tax_ref is NOT NULL then
420     open TAX_DETAILS;
421     fetch TAX_DETAILS INTO l_tax_c_basis, v_tax_rate;
422     close TAX_DETAILS;
423 /*
424   if l_tax_amt_ty = l_amt_type1 then
425    tax_base_amt := l_amt1;
426   elsif l_tax_amt_ty = l_amt_type2 then
427    tax_base_amt := l_amt2;
428   elsif l_tax_amt_ty = l_amt_type3 then
432     tax_base_amt := l_tax_amt;
429    tax_base_amt := l_amt3;
430   end if;
431 */
433     if l_tax_rate is null then
434        l_tax_rate := v_tax_rate;
435     end if;
436     if l_tax_c_basis = 'FLAT' then
437        l_tax_out := tax_base_amt * (l_tax_rate/100);
438     elsif l_tax_c_basis = 'ANNUAL' then
439        l_tax_out := (tax_base_amt * (l_tax_rate/100)/ l_yr_basis) * l_num_days;
440     else
441        l_tax_out := 0;
442     end if;
443  else
444     l_tax_out := 0;
445  end if;
446 
447  ----------------------
448  -- Brokerage Details
449  ----------------------
450  if l_bkge_ref is NOT NULL then
451     open BKGE_DETAILS;
452     fetch BKGE_DETAILS INTO l_bkge_c_basis, v_bkr_rate;
453     close BKGE_DETAILS;
454 /*
455   if l_bkge_amt_ty = l_amt_type1 then
456    bkge_base_amt := l_amt1;
457   elsif l_bkge_amt_ty = l_amt_type2 then
458    bkge_base_amt := l_amt2;
459   elsif l_bkge_amt_ty = l_amt_type3 then
460    bkge_base_amt := l_amt3;
461   end if;
462 */
463     bkge_base_amt := l_bkr_amt;
464     if l_bkr_rate is null then
465        l_bkr_rate := v_bkr_rate;
466     end if;
467     if l_bkge_c_basis = 'FLAT' then
468        l_bkge_out := bkge_base_amt * (l_bkr_rate/100);
469     elsif l_bkge_c_basis = 'ANNUAL' then
470        l_bkge_out := (bkge_base_amt * (l_bkr_rate/100)/ l_yr_basis) * l_num_days;
471     end if;
472  end if;
473 
474  -------------------
475  -- AW Bug 1585466
476  -------------------
477  l_tax_out  := round(l_tax_out,l_rounding_factor);
478  l_bkge_out := round(l_bkge_out,l_rounding_factor);
479 
480  if nvl(l_tax_out,0) <> 0 or nvl(l_bkge_out,0) <> 0 then
481     open CALC_HCE_AMTS;
482     fetch CALC_HCE_AMTS INTO l_tax_out_hce,l_bkge_out_hce;
483     if CALC_HCE_AMTS%NOTFOUND then
484        l_err_code := 886; l_level := 'E'; -- Unable to find Spot Rate Data
485     end if;
486     close CALC_HCE_AMTS;
487  end if;
488 
489 end CALC_TAX_BROKERAGE;
490 ----------------------------------------------------------------------------------------------------------------
491 /*****************************************************************************/
492 -- This procedure should be called to calculate tax amounts, whereas
493 -- the above procedure, calc_tax_brokerage, should only be used for calculating
494 -- brokerage amounts.
495 -- Parameters:
496 --   l_deal_type = deal type
497 --   l_deal_date = tax "as of" date
498 --   l_prin_tax_ref = principal tax schedule code, null only want income tax
499 --   l_income_tax_ref = income tax schedule code, null if only want principal
500 --								tax
501 --   l_ccy_buy = for FX deals, buy currency; else currency of deal
502 --   l_ccy_sell = for FX deals, sell currency; else null
503 --   l_year_basis = number of days in a year, null if calc_type like '%_A'
504 --   l_num_days = number of days for tax calculation, null if calc type like
505 --							'%_A'
506 --   l_prin_tax_amount = base amount for principal tax calculation, required if
507 --		l_prin_tax_ref is not null
508 --   l_prin_tax_rate = tax rate of l_prin_tax_ref; if null, and l_prin_tax_ref
509 --		is not null, will return tax rate as of l_deal_date; not
510 --		required if l_prin_tax_ref is null
511 --   l_income_tax_amount = base amount for income tax calculation, required if
512 --		l_income_tax_amount is not null
513 --   l_income_tax_rate = base amount for income tax calculation; if null, and
514 --		l_income_tax_ref is not null, will return tax rate as of
515 --		l_deal_date; not required if l_income_tax_ref is null
516 --   l_prin_tax_out = calculated principal tax, rounded according to setup
517 --   l_income_tax_out = calculated income tax, rounded according to setup
518 
519 
520 PROCEDURE CALC_TAX_AMOUNT (l_deal_type IN VARCHAR2,
521 			   l_deal_date IN DATE,
522 			   l_prin_tax_ref   IN VARCHAR2,
523 			   l_income_tax_ref IN VARCHAR2,
524   			   l_ccy_buy   IN VARCHAR2, -- ccy for MM deals
525 			   l_ccy_sell  IN VARCHAR2,
526 			   l_year_basis  IN NUMBER,
527 			   l_num_days    IN NUMBER,
528 			   l_prin_tax_amount    IN      NUMBER,
529 			   l_prin_tax_rate      IN OUT NOCOPY  NUMBER,
530 			   l_income_tax_amount  IN      NUMBER,
531 			   l_income_tax_rate    IN OUT NOCOPY  NUMBER,
532 			   l_prin_tax_out	IN OUT NOCOPY  NUMBER,
533 			   l_income_tax_out     IN OUT NOCOPY NUMBER,
534 			   l_err_code		   OUT NOCOPY NUMBER,
535 			   l_level		   OUT NOCOPY  VARCHAR2) is
536 
537   v_calc_basis VARCHAR2(10);
538   v_calc_type VARCHAR2(9);
539   v_tax_rate NUMBER;
540   l_rounding_factor NUMBER;
541   l_ccy VARCHAR2(15);
542   l_rounding_rule VARCHAR2(1);
543   l_rounding_precision VARCHAR2(20);
544 
545  cursor TAX_DETAILS (l_tax_ref VARCHAR2) is
546   select b.CALC_BASIS, b.CALC_TYPE, nvl(d.INTEREST_RATE,0)
547    from  XTR_TAX_BROKERAGE_SETUP a,
548 	 XTR_TAX_DEDUCTION_CALCS b,
549          XTR_TAX_BROKERAGE_RATES d
550    where a.REFERENCE_CODE      = l_tax_ref
551    and   nvl(a.AUTHORISED,'N') = 'Y'
552    and   b.DEAL_TYPE           = l_deal_type
553    and   b.CALC_TYPE           = a.CALC_TYPE
554    and   d.RATE_GROUP          = a.RATE_GROUP
555    and   d.REF_TYPE            = 'T'
556    and   d.EFFECTIVE_FROM     <= l_deal_date
560  cursor GET_ROUNDING_RULES(l_ref VARCHAR2) is
557    order by d.EFFECTIVE_FROM desc;
558 
559 
561    select tax_rounding_rule, tax_rounding_precision
562    from XTR_TAX_BROKERAGE_SETUP
563    where reference_code = l_ref;
564 
565 begin
566   -- inititate out variables
567   l_prin_tax_out := 0;
568   l_income_tax_out := 0;
569 
570   -- calculate principal tax amount
571   open TAX_DETAILS(l_prin_tax_ref);
572   fetch TAX_DETAILS into v_calc_basis, v_calc_type, v_tax_rate;
573   close TAX_DETAILS;
574 
575   if (l_prin_tax_rate is null) then
576      l_prin_tax_rate := v_tax_rate;
577   end if;
578 
579   if (v_calc_type IN ('PRN_A', 'MAT_A', 'CON_A')) then
580      l_prin_tax_out := l_prin_tax_out +
581 	((l_prin_tax_amount*l_prin_tax_rate*l_num_days)/(100*l_year_basis));
582   else
583      l_prin_tax_out := l_prin_tax_amount*(l_prin_tax_rate/100);
584   end if;
585 
586   if (l_deal_type = 'FX') then
587     if (v_calc_type = 'SELL_F') then
588       l_ccy := l_ccy_sell;
589     else
590       l_ccy := l_ccy_buy;
591     end if;
592   else
593     l_ccy := l_ccy_buy;
594   end if;
595 
596 
597   -- calculate income tax amount
598   open TAX_DETAILS(l_income_tax_ref);
599   fetch TAX_DETAILS into v_calc_basis, v_calc_type, v_tax_rate;
600   close TAX_DETAILS;
601 
602   if (l_income_tax_rate is null) then
603      l_income_tax_rate := v_tax_rate;
604   end if;
605   l_income_tax_out := l_income_tax_amount*(l_income_tax_rate/100);
606 
607 
608   --bug 2727920 if CCY is null then do not do rounding
609   if l_ccy_buy is not null then
610      -- round principal tax
611      open GET_ROUNDING_RULES(l_prin_tax_ref);
612      fetch GET_ROUNDING_RULES into l_rounding_rule, l_rounding_precision;
613      close GET_ROUNDING_RULES;
614      l_rounding_factor := GET_TAX_ROUND_FACTOR(l_rounding_precision, l_ccy);
615      l_prin_tax_out := XTR_FPS2_P.interest_round(l_prin_tax_out,
616 					      l_rounding_factor,
617 					      l_rounding_rule);
618 
619      -- round income tax
620      open GET_ROUNDING_RULES(l_income_tax_ref);
621      fetch GET_ROUNDING_RULES into l_rounding_rule, l_rounding_precision;
622      close GET_ROUNDING_RULES;
623      l_rounding_factor := GET_TAX_ROUND_FACTOR(l_rounding_precision, l_ccy);
624      l_income_tax_out := XTR_FPS2_P.interest_round(l_income_tax_out,
625 					        l_rounding_factor,
626 					        l_rounding_rule);
627   else
628   --round enough (12 decimals) so that it does not cause FRM-40831 since
629   --the form only has 38 digits
630      if l_prin_tax_out is not null then
631         l_prin_tax_out := ROUND(l_prin_tax_out,12);
632      end if;
633      if l_income_tax_out is not null then
634         l_income_tax_out := ROUND(l_income_tax_out,12);
635      end if;
636   end if;
637 
638 end CALC_TAX_AMOUNT;
639 -------------------------------------
640 FUNCTION GET_TAX_SETTLE_METHOD (l_tax_ref VARCHAR2)
641 	RETURN VARCHAR2 IS
642 
643    l_settle_method  VARCHAR2(15);
644 
645    CURSOR get_settle_method IS
646 	SELECT tax_settle_method
647 	FROM XTR_TAX_BROKERAGE_SETUP
648 	WHERE reference_code = l_tax_ref;
649 BEGIN
650    OPEN get_settle_method;
651    FETCH get_settle_method INTO l_settle_method;
652    IF (get_settle_method%FOUND) THEN
653       CLOSE get_settle_method;
654       return l_settle_method;
655    ELSE
656       return null;
657    END IF;
658 END;
659 -------------------------------------
660 FUNCTION GET_TAX_ROUND_FACTOR(l_rounding_precision VARCHAR2,
661 			      l_ccy VARCHAR2)
662 	RETURN NUMBER IS
663 
664    l_rounding_factor NUMBER;
665    l_ccy_precision NUMBER;
666 
667    CURSOR get_ccy_precision IS
668       SELECT precision
669       FROM fnd_currencies
670       WHERE currency_code = l_ccy;
671 
672 BEGIN
673    IF (l_rounding_precision = 'THOUSANDS') THEN
674       l_rounding_factor := -3;
675    ELSIF (l_rounding_precision = 'HUNDREDS') THEN
676       l_rounding_factor := -2;
677    ELSIF (l_rounding_precision = 'TENS') THEN
678       l_rounding_factor := -1;
679    ELSIF (l_rounding_precision = 'ONES') THEN
680       l_rounding_factor := 0;
681    ELSE
682 	OPEN get_ccy_precision;
683 	FETCH get_ccy_precision INTO l_ccy_precision;
684 	CLOSE get_ccy_precision;
685 
686         IF (l_rounding_precision = 'UNITS') THEN
687 	    l_rounding_factor := l_ccy_precision;
688 	ELSIF (l_rounding_precision IN ('TENTHS', 'HUNDREDTHS')) THEN
689 	    IF (l_rounding_precision = 'TENTHS') THEN
690 		l_rounding_factor := 1;
691 	    ELSE
692 		l_rounding_factor := 2;
693 	    END IF;
694 	    IF (l_ccy_precision <= l_rounding_factor) THEN
695 		l_rounding_factor := l_ccy_precision;
696 	    END IF;
697 	END IF;
698    END IF;
699    RETURN l_rounding_factor;
700 END GET_TAX_ROUND_FACTOR;
701 
702 
703 ----------------------------------------------------------------------
704 --   Procedure to check currency code is valid.
705 PROCEDURE CHK_CCY_CODE (l_currency    IN VARCHAR2,
706 			l_ccy_name    IN OUT NOCOPY VARCHAR2,
707 			l_yr_basis    IN OUT NOCOPY NUMBER,
711 --
708 			l_round       IN OUT NOCOPY NUMBER,
709 			l_err_code         OUT NOCOPY NUMBER,
710 			l_level                OUT NOCOPY VARCHAR2) is
712  cursor CCY is
713   select NAME, YEAR_BASIS, ROUNDING_FACTOR
714    from  XTR_MASTER_CURRENCIES_V
715    where CURRENCY   = l_currency;
716 --   and   AUTHORISED = 'Y';
717 --
718 begin
719  if (l_currency is NOT NULL) then
720   open CCY;
721    fetch CCY INTO l_ccy_name, l_yr_basis, l_round;
722   if CCY%NOTFOUND then
723     l_err_code := 418; l_level := 'E';--This Currency does not exist or is not authorised
724   end if;
725   close CCY;
726  end if;
727 end CHK_CCY_CODE;
728 ----------------------------------------------------------------------------------------------------------------
729 --   Procedure to validate Client Code.
730 PROCEDURE CHK_CLIENT_CODE (l_client_code IN VARCHAR2,
731 			   l_client_name IN OUT NOCOPY VARCHAR2,
732 			   l_query       IN VARCHAR2,
733 			   l_err_code         OUT NOCOPY NUMBER,
734 			   l_level                OUT NOCOPY VARCHAR2) is
735 --
736  cursor PTY_NAME is
737   select SHORT_NAME
738    from  XTR_PARTIES_V
739    where PARTY_CODE = l_client_code
740    and   PARTY_TYPE = 'CP'
741    and   PARTY_CATEGORY = 'CL'
742    and   AUTHORISED = 'Y';
743 --
744  cursor QRY_NAME is
745   select SHORT_NAME
746    from  XTR_PARTY_INFO_V
747    where PARTY_CODE = l_client_code;
748 --
749 begin
750  if nvl(l_query,'N') = 'Y' then
751   open QRY_NAME;
752    fetch QRY_NAME INTO l_client_name;
753   close QRY_NAME;
754  else
755   open PTY_NAME;
756    fetch PTY_NAME INTO l_client_name;
757   if PTY_NAME%NOTFOUND then
758     l_err_code := 701; l_level := 'E';--The Client does not exist
759   end if;
760   close PTY_NAME;
761  end if;
762 end CHK_CLIENT_CODE;
763 ----------------------------------------------------------------------------------------------------------------
764 --   Procedure to validate company code.
765 PROCEDURE CHK_COMPANY_CODE (l_company_code IN VARCHAR2,
766 			    l_company_name IN OUT NOCOPY VARCHAR2,
767                             l_query        IN  VARCHAR2,
768 			    l_err_code     OUT NOCOPY NUMBER,
769 			    l_level        OUT NOCOPY VARCHAR2) is
770  l_user		VARCHAR2(10);
771  fnd_user	NUMBER;
772 --
773  cursor USER (fnd_user in number) is
774   select dealer_code
775   from xtr_dealer_codes_v
776   where user_id = fnd_user;
777 
778  cursor COMP_NAME(l_user VARCHAR2) is
779   select p.SHORT_NAME
780    from XTR_PARTIES_V p
781    where p.PARTY_CODE = l_company_code
782    and p.PARTY_TYPE = 'C'
783    and p.AUTHORISED = 'Y'
784    and p.party_code in(select c.party_code
785                         from XTR_COMPANY_AUTHORITIES c
786                         where c.dealer_code = l_user
787                         and c.company_authorised_for_input='Y');
788 --
789  cursor QRY_NAME is
790   select p.SHORT_NAME
791    from XTR_PARTY_INFO_V p
792    where p.PARTY_CODE = l_company_code;
793 --
794 begin
795 fnd_user := fnd_global.user_id;
796 open USER(fnd_user);
797  fetch USER into l_user;
798 close USER;
799 
800 if nvl(l_query,'N') = 'Y' then
801   open QRY_NAME;
802    fetch QRY_NAME INTO l_company_name;
803   close QRY_NAME;
804 else
805  open COMP_NAME(l_user);
806   fetch COMP_NAME INTO l_company_name;
807  if COMP_NAME%NOTFOUND then
808    l_err_code := 701; l_level := 'E';--This Company does not exist
809  end if;
810  close COMP_NAME;
811 end if;
812 end CHK_COMPANY_CODE;
813 ----------------------------------------------------------------------------------------------------------------
814 --   Procedure to check counterparty account number is valid
815 PROCEDURE CHK_CPARTY_ACCOUNT (l_cparty_code    IN VARCHAR2,
816 			      l_cparty_ref     IN VARCHAR2,
817 			      l_currency       IN VARCHAR2,
818 			      l_cparty_account IN OUT NOCOPY VARCHAR2,
819 			      l_err_code         OUT NOCOPY NUMBER,
820 			      l_level                OUT NOCOPY VARCHAR2) is
821 --
822 cursor ACCT_NOS is
823  select ACCOUNT_NUMBER
824   from  XTR_BANK_ACCOUNTS
825   where PARTY_CODE = l_cparty_code
826   and   BANK_SHORT_CODE = l_cparty_ref
827   and   CURRENCY = l_currency;
828 --
829 begin
830  if l_cparty_ref is NOT NULL then
831   open ACCT_NOS;
832    fetch ACCT_NOS INTO l_cparty_account;
833 /*
834   if ACCT_NOS%NOTFOUND then
835     l_err_code := 701; l_level := 'E';--This Cparty A/C Reference does not exist
836   end if;
837 */
838   close ACCT_NOS;
839  end if;
840 end CHK_CPARTY_ACCOUNT;
841 ----------------------------------------------------------------------------------------------------------------
842 --   Procedure to validate the Counterparty Code.
843 PROCEDURE CHK_CPARTY_CODE (l_cparty_code IN VARCHAR2,
844 			   l_cparty_name IN OUT NOCOPY VARCHAR2,
845 			   l_query       IN VARCHAR2,
846 			   l_err_code    OUT NOCOPY NUMBER,
847 			   l_level       OUT NOCOPY VARCHAR2) is
848 --
849  cursor PTY_NAME is
850   select SHORT_NAME
851    from  XTR_PARTIES_V
852    where PARTY_CODE = l_cparty_code
853    and   PARTY_TYPE in('CP','C')
854    and   AUTHORISED = 'Y';
855 --
856  cursor QRY_NAME is
857   select SHORT_NAME
858    from  XTR_PARTY_INFO_V
859    where PARTY_CODE = l_cparty_code;
860 --
861 begin
862  if nvl(l_query,'N') = 'Y' then
863   open QRY_NAME;
864    fetch QRY_NAME INTO l_cparty_name;
865   close QRY_NAME;
866  else
867   open PTY_NAME;
868    fetch PTY_NAME INTO l_cparty_name;
869   if PTY_NAME%NOTFOUND then
870     l_err_code := 701; l_level := 'E';--The Counterparty does not exist
871   end if;
872   close PTY_NAME;
873  end if;
874 end CHK_CPARTY_CODE;
875 ----------------------------------------------------------------------------------------------------------------
876 --   Procedure to validate counterparty limit type entered.
877 PROCEDURE CHK_CPARTY_LIMIT (l_cparty_code  IN VARCHAR2,
878 			    l_company_code IN VARCHAR2,
879 			    l_limit_code   IN VARCHAR2,
880 			    l_err_code         OUT NOCOPY NUMBER,
881 			    l_level                OUT NOCOPY VARCHAR2) is
882 --
883  cursor LIMIT_TYPE is
884   select 1
885    from  XTR_COUNTERPARTY_LIMITS cpl
886    where cpl.CPARTY_CODE  = l_cparty_code
887    and   cpl.COMPANY_CODE = l_company_code
888    and   cpl.LIMIT_CODE   = l_limit_code
889    and   (cpl.EXPIRY_DATE >= trunc(sysdate) or
890             cpl.EXPIRY_DATE is NULL);
891 --
892  v_dummy                number(1);
893 begin
894  if (l_company_code is NOT NULL and l_cparty_code is NOT NULL and
895      l_limit_code is NOT NULL) then
896    open LIMIT_TYPE;
897    fetch LIMIT_TYPE INTO v_dummy;
898    if LIMIT_TYPE%NOTFOUND then
899      close limit_type;
900      l_err_code := 701; l_level := 'E';--This Limit Type does not exist
901    else
902      close limit_type;
903    end if;
904  end if;
905 end CHK_CPARTY_LIMIT;
906 ----------------------------------------------------------------------------------------------------------------
907 --   Procedure to check the entered Dealer Code
908 PROCEDURE CHK_DEALER_CODE (l_dealer_code IN VARCHAR2,
909 							l_err_code         OUT NOCOPY NUMBER,
910 							l_level                OUT NOCOPY  VARCHAR2) is
911 --
912 cursor CHK_CODE is
913  select 1
914   from  XTR_DEALER_CODES
915   where DEALER_CODE = l_dealer_code;
916 --
917 v_dummy          number(1);
918 begin
919  if l_dealer_code is NOT NULL then
920   open CHK_CODE;
921    fetch CHK_CODE INTO v_dummy;
922    if CHK_CODE%NOTFOUND then
923     close CHK_CODE;
924     l_err_code := 701; l_level := 'E';--Invalid Code. Refer <LIST>.
925    else
926     close CHK_CODE;
927    end if;
928  end if;
929 end CHK_DEALER_CODE;
930 ----------------------------------------------------------------------------------------------------------------
931 --   Procedure to check deal status to make sure that only
932 --  CURRENT deals are updated.
933 PROCEDURE CHK_DEAL_STATUS (l_deal_number IN NUMBER,
934 						       l_err_code         OUT NOCOPY NUMBER,
935 						       l_level                OUT NOCOPY VARCHAR2) is
936 --
937  cursor D_STATUS is
938   select   1
939    from    XTR_DEALS_V
940    where   deal_no     = l_deal_number
941    and     status_code = 'CURRENT';
942 --
943  v_dummy        number(1);
944 begin
945  open D_STATUS;
946  fetch D_STATUS INTO v_dummy;
947  if D_STATUS%NOTFOUND then
948    close D_STATUS;
949    l_err_code := 58; l_level := 'E';--This deal is not CURRENT and cannot be updated
950  else
951    close D_STATUS;
952  end if;
953 end CHK_DEAL_STATUS;
954 end XTR_FPS1_P;