Program s30jafe
! S30JAF Example Program Text
! Mark 25 Release. NAG Copyright 2014.
! .. Use Statements ..
Use nag_library, Only: nag_wp, s30jaf
! .. 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 :: p(:,:), t(:), x(:)
! .. Executable Statements ..
Write (nout,*) 'S30JAF 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 (p(ldp,n),t(n),x(m))
Read (nin,*)(x(i),i=1,m)
Read (nin,*)(t(i),i=1,n)
ifail = 0
Call s30jaf(calput,m,n,x,s,t,sigma,r,lambda,jvol,p,ldp,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,99998) ' Spot = ', s
Write (nout,99998) ' Volatility = ', sigma
Write (nout,99998) ' Rate = ', r
Write (nout,99998) ' Jumps = ', lambda
Write (nout,99998) ' Jump vol = ', jvol
Write (nout,*)
Write (nout,*) ' Strike Expiry Option Price'
Do i = 1, m
Do j = 1, n
Write (nout,99999) x(i), t(j), p(i,j)
End Do
End Do
99999 Format (1X,2(F9.4,1X),6X,F9.4)
99998 Format (A,1X,F8.4)
End Program s30jafe