Program s30jbfe
! S30JBF Example Program Text
! Mark 25 Release. NAG Copyright 2014.
! .. Use Statements ..
Use nag_library, Only: nag_wp, s30jbf
! .. Implicit None Statement ..
Implicit None
! .. Parameters ..
Integer, Parameter :: nin = 5, nout = 6
! .. Local Scalars ..
Real (Kind=nag_wp) :: jvol, lambda, r, s, sigma
Integer :: i, ifail, j, ldp, m, n
Character (1) :: calput
! .. Local Arrays ..
Real (Kind=nag_wp), Allocatable :: charm(:,:), colour(:,:), crho(:,:), &
delta(:,:), gamma(:,:), p(:,:), &
rho(:,:), speed(:,:), t(:), &
theta(:,:), vanna(:,:), vega(:,:), &
vomma(:,:), x(:), zomma(:,:)
! .. Executable Statements ..
Write (nout,*) 'S30JBF Example Program Results'
! Skip heading in data file
Read (nin,*)
Read (nin,*) calput
Read (nin,*) lambda
Read (nin,*) s, sigma, r, jvol
Read (nin,*) m, n
ldp = m
Allocate (charm(ldp,n),colour(ldp,n),crho(ldp,n),delta(ldp,n), &
gamma(ldp,n),p(ldp,n),rho(ldp,n),speed(ldp,n),t(n),theta(ldp,n), &
vanna(ldp,n),vega(ldp,n),vomma(ldp,n),x(m),zomma(ldp,n))
Read (nin,*)(x(i),i=1,m)
Read (nin,*)(t(i),i=1,n)
ifail = 0
Call s30jbf(calput,m,n,x,s,t,sigma,r,lambda,jvol,p,ldp,delta,gamma,vega, &
theta,rho,vanna,charm,speed,colour,zomma,vomma,ifail)
Write (nout,*)
Write (nout,*) 'Merton Jump-Diffusion Model'
Select Case (calput)
Case ('C','c')
Write (nout,*) 'European Call :'
Case ('P','p')
Write (nout,*) 'European Put :'
End Select
Write (nout,99996) ' Spot = ', s
Write (nout,99996) ' Volatility = ', sigma
Write (nout,99996) ' Rate = ', r
Write (nout,99996) ' Jumps = ', lambda
Write (nout,99996) ' Jump vol = ', jvol
Write (nout,*)
Do j = 1, n
Write (nout,*)
Write (nout,99999) t(j)
Write (nout,*) ' Strike Price Delta Gamma Vega Theta' &
// ' Rho'
Do i = 1, m
Write (nout,99998) x(i), p(i,j), delta(i,j), gamma(i,j), vega(i,j), &
theta(i,j), rho(i,j)
End Do
Write (nout,*) &
' Strike Price Vanna Charm Speed Colour Zomma' // &
' Vomma'
Do i = 1, m
Write (nout,99997) x(i), p(i,j), vanna(i,j), charm(i,j), speed(i,j), &
colour(i,j), zomma(i,j), vomma(i,j)
End Do
End Do
99999 Format (1X,'Time to Expiry : ',1X,F8.4)
99998 Format (1X,7(F8.4,1X))
99997 Format (1X,8(F8.4,1X))
99996 Format (A,1X,F8.4)
End Program s30jbfe