• Back to MAIN


  • 1. Simple compounding vs continuous compounding

    The inverse discount rate we can express as :
    di-1 = 1 + rsi tsi/Ysi = e rcctcc/365
    so, we get rcc=(365/tcc)Ln(1 + rsi tsi / Ysi) .. where

    rcc is the continuously compounded rate, Ysi is the no of days in one year based on the money market convention
    rsi is the simple compounded rate, tcc is the actual number of days in a period
    tsi is the number of days in a period based on the money market convention.

    the simple k4/kdb+ function for this can be :

    tC:{[rsi;tsi;Ysi;tcc](365f%tcc)*log 1f+rsi*tsi%Ysi} /and we can now define a projection of tC ..
    tCact360:{tC . (x;y;360f;y)}


    2. The Future curves If a futures market is available for a specific currency, we will get a sequence of implied forward rates
    (from the quoted futures prices) f1,f2, .. ,fn-1,fn and the corresponding forward discount factors p1,p2, .. ,pn-1,pn

    where on the index set In holds: pj=1 + fj tmj/Ysi and p0 is a stub-rate*.. In is equivalent to the set of the first n natural numbers.
    tmj is the number of days per future period j based on the convention of the money market.
    The continuously compounded zero coupon rates we can obtain by : zj+1cc=(-365/Fj+1)Ln p0p1...pj-1pj where j is in the index set
    In including element {0}. In reality represents this product a recursion of pairs: (fn,tn), where tn is the difference
    between the 1st futures IMM dates Tn and Tn+1.

    Just a sample....

    We assume a given stub-rate of 1.64% on the 17.Sep.2003 (simple compounded), the maturities of the futures we takes as:
    (i should mention that we assume here also a significant trading volume of those sample contracts)
    The reference spot date of the stub-rate is 04.Aug.2003, and the table-dates below are 1st IMM dates


    Future Strips of a currency X (act/360)
    dates 17.9.2003 17.12.2003 17.3.2004 16.6.2004 22.9.2004 22.12.2004 23.3.2005 15.6.2005 21.9.2005
    quotes 98.25 98.05 97.81 97.49 97.11 96.76 96.39 96.05 last 1st IMM


    the simple k4 solution for this can be :

    T:2003.08.04,2003.09.17,2003.12.17,2004.03.17,2004.06.16,2004.09.22,2004.12.22,2005.03.23,2005.06.15,2005.09.12
    R:1.64,100.0-98.25,98.05,97.81,97.49,97.11,96.76,96.39,96.05

    k)daysa:+\daysd:1_-':T
    r:tCact360 . (0.01*R;daysd)

    (r@0) {[x;y]((x*y0-y2)+(y@1)*y2:y@2)%y0:y@0}\ +(1_daysa;1_r;1_daysd)

    .. returns the zero points determined by our future prices

    * The stub-rate corresponds to the period from now to the maturity of the first futures contract can be obtained by
    linearly interpolating the last two continuously compounded money market rates ricc and ri+1cc, so that
    F1 in the closed interval [ti , ti+1] where F1 is the maturity date of the futures contract which falls between the two money market dates
    If ricc is not available from money market data, we assume that : ricc = ri+1cc = p0cc,
    where p0cc is the continuously compounded stub rate. In the normal case we get it from : p0cc=[ricc Dti+(F1 - ti)(ri+1cc - ricc)]/Dti
    where Dti = ti+1 - ti.

    3. Playing with FRA's

    An FRA is simply one pair of cashflows.
    Let be t1 the time from the transaction date to the settlement date and t2 the time between the transaction date and the maturity date,
    and rccc is the continuously compounded FRA contract rate, r1cc is the zero-coupon rate at the settlement, r2cc is the zero-coupon
    rate of the maturity.
    The net unrealized profit at a time t = t0 we simply obtain as the sum of the both cashflows As(settlement) and -Am(maturity).
    So, the FRApl = Ase-r1cc(t1-t0)+(-Am)e-r2cc(t2-t0) = As(e-r1cc(t1-t0)-erccc(t2-t1)-r2cc(t2-t0))

    We can now use the definition of the delta D s where the index s refers to the simple compounding, and we let be r(i) the
    mapping from the continuous into the simple compounding form.
    The D s = dVt/di=dVt/drt*drt/di where Vt is the present value at the current timepoint t and F0 the originally invested nominal
    in t = 0, so Vt=F0er2cct2 - rtcc(t2-t) and where t2 is the maturity timepoint and the rcc are as usual the correspondingly observed
    cont.compounded zero rates.
    As drt/di = tM[YM(t2-t)]-1e- rtcc(t2-t) .. thus dVt/di= - VttMYM-1e-rtcc(t2-t) .... however in practice we rather use the
    socalled basis point value bpv = -0.0001 VttMYM-1e-rtcc(t2-t)
    In FRA terms we obtain the bpvFRA as the sum of bpvS and bpvM where S refers again to the settlement and M to the maturity.
    So, bpvFRA = 0.0001 AsYM-1[(t2-t)Me-2r2cc(t2-t)+rccc(t2-t1) - (t1-t)Me-2r1cc(t1-t)] where the subscript M relates to the money market day count convetion.

    Here a simple kdb script simulating a random portfolio of 300'000 FRA's having 40 currencies. The FRA valuation itself is
    actually a one or two-liner, all other lines are just used for comment and for building my sample portfolio, which would
    clearly exceed the classical size of an FRA-book of a large bank by many times (10 to 100). The currency variety i took
    is higher than in any other "real" portfolio.

  • FRA simulation Kdb+ script


  • 4. European Options ..just a short introduction...

    The payoff(expectation value) of an European call we can express as :

    C = e-r(T-t)J[ max(0;ST-X)h(XT)dST;0;infinity ]
    where J[ f ; a; b ] describes the definite integral of f over [a;b]
    where X is the strike, S is the spot(asset) price, T is the maturity date, t is our timepoint, r is the (riskless) rate


    Changes in the spot price are the sum of a random component and a time-dependent deterministic component..
    Eg: dS = (r - d )Sdt + s Sdz, where d represents the annual dividend yield. dz represents a sum of independent random
    events over the time horizon dt. So, dz must follow a normal distribution, according to the central limit theorem, eg we can
    describe dz by its variance (which is dt) and mean (which is 0).

    This means the process for x = ln(S) leads us to the equation:

    dx = (r - d - 0.5 s 2)dt + s dz
    dx is a linear combination of a constant and the normally distributed dz, so must be normally distributed, too.
    The mean of dx is (r - d - 0.5 s 2)dt, and its variance is s 2dt.
    The natural logarithm of S at maturity is normally distributed with the following parameters:

    N [(Ln S) + (r - d - 0.5 s 2)(T - t) ; s (T - t)0.5
    This allows to revisit the integral mentioned above - and to solve it. This way we obtain
    the Black-Scholes solution for an

    European call option.
    C = Se-d (T - t)N(d1) - Xe-r (T - t)N(d2)

    ..and symetrically for the European put-option
    P = Xe-r (T - t)N(-d2) - Se-d (T - t)N(-d1)

    ..and where d1 = s -1(T - t)- 0.5[ Ln (S/X) + (r - d + 0.5 s 2)(T - t)] and d2 = d1 - s (T - t)0.5

    A solution in Kdb+ can look like...(in case of an european currency option)

    optBS:{{[S;X;rf;rd;t;s] /rd=domestic yield(cc), rf=foreign yield(cc), s=implied volatility
    d1:((log S%X)+t0*((s*s*0.5)+rd-rf))%a:s*sqrt t0:t%365f;(S*(exp neg rf*t0)*g d1)-X*(exp neg rd*t0)*g d1-a}

    ..where g is the gauss function ..
    pi:acos -1
    g:{abs (neg x>0f)+(1f%sqrt 2f*pi)*(exp -0.5*x*x)*t*0.31938153+t*-0.356563782+t*1.781477937+ ..
    .. t*-1.821255978+1.330274429*t:1f%1f+0.2316419*abs x}

    if we change the Spot S..and let the other dimensions constant..we will obtain (in case of a call) the profile:
    x-units are in 0.001 .. (if C=1 we have a call, C=0 we have a put)

    call profile

    5. American Options

    This formula of Black and Scholes is of course widely used and it is quite handy and traceable from the
    analytical point of view. Its simplicity has the price that it can be only used for classical European
    styled options. American styled options are more "worth" than European styled options, as they can be
    exercised at any day until the option maturity. One possible way to price an American option is the
    binomial method, which is the common method. The binomial method has been introduced 1978 by Sharpe.
    Although the binomial method is not that handy closed a formula, it is a fairly simple and intuitive method.
    As the name suggests..there are only two possible states(up and down) in that tree in each time-interval
    T/n.(T is the maturity and n the number of chosen intervals). Further we assume recombining nodes on the
    tree, so we don't run into a messy mega-tree.
    As we stated above already, Ln Sdt is normally distributed, and the mean is Ln S0 + (rd - rf - 0.5 s 2)dt,
    the variance is s 2dt
    Exactly this finding helps us to find the UP's and DOWN's in the binomial tree. Theoretically we "assume"
    that the chosen time-metrics is small enough, that we can find based on the above stated characteristics
    of Ln Sdt and the classical relation for independent random variables, VAR(X) = E(X2) - [E(X)]2,
    that VAR(S1,T) = S02e2T(rd - rf)(e s 2T - 1). We see here also that the standard deviation of S1,T is
    monotonously increasing with s . With this, the future exchange rate movements are defined.
    Thus:

    UP p S0u
    S0
    DOWN 1-p S0d

    Where: u = e s (Dt)0.5, d = u-1 and p = (u - d)-1(e(rd - rf)Dt - d). For each last time-point jDt
    we calculate the option-tree out of the price-tree: QjDt,i = max [0,L*S0z2(i-1) - X] ..where i in {1,2,..., j+1}, z in {u,d} and where
    L = 1 for a call option, and -1 for a put.
    The rest of the option-tree (where m in {j-1,j-2,...,1,0}) we have for each QmDt,n the equation that:
    QmDt,n = max{L*E*(S0zm - 2(n-1) - X) , e-rdDt(pQ(n+1)Dt,n + (1 - p)Q(n+1)Dt,n+1) } and where E is the early exercise flag.
    eg. E is 1 in case we exercise, and otherwise 0.

    The answer using Kdb+ can be..

    Xn:neg X;dt:T%n;n1:-1f;l:exp n1*rd*dt
    q:1-p:((neg@ d)+exp dt*rd-rf)%(u:1f%d)-d:exp neg@ s*sqrt dt:T%n
    On:0f|h*Xn+S*last atree:xexp[u;{x-2*til x+1} each 1+til n];
    On {max each flip (n1*Xn+S*y;fx x)}/1 _ reverse 1f,atree

    function fx should remain secret, but is only a short expression.

    The graph below shows how the binomial model converges against the correct value in case of variable time-intervals
    which represent the x-axis(starting from 1 and going up to 300)
    The upper path in the graph below is an European put, and the other is an American put.

    binomial convergence

  • Back to MAIN


  • © ++ MILAN ONDRUS