Program g13cdfe
! G13CDF Example Program Text
! Mark 25 Release. NAG Copyright 2014.
! .. Use Statements ..
Use nag_library, Only: g13cdf, nag_wp
! .. Implicit None Statement ..
Implicit None
! .. Parameters ..
Integer, Parameter :: nin = 5, nout = 6
! .. Local Scalars ..
Real (Kind=nag_wp) :: pw, pxy
Integer :: ifail, ish, j, kc, l, m, mtxy, mw, &
ng, nxy
! .. Local Arrays ..
Real (Kind=nag_wp), Allocatable :: xg(:), yg(:)
! .. Intrinsic Procedures ..
Intrinsic :: ceiling, log, real
! .. Executable Statements ..
Write (nout,*) 'G13CDF Example Program Results'
Write (nout,*)
! Skip heading in data file
Read (nin,*)
! Read in the problem size
Read (nin,*) nxy, l
! Read in control parameters
Read (nin,*) mtxy, pxy, pw, mw, ish
! Get a value for KC
m = ceiling(log(2.0E0_nag_wp*real(nxy,kind=nag_wp)/real(l, &
kind=nag_wp))/log(2.0E0_nag_wp))
kc = (2**m)*l
Allocate (xg(kc),yg(kc))
! Read in data
Read (nin,*) xg(1:nxy)
Read (nin,*) yg(1:nxy)
ifail = 0
Call g13cdf(nxy,mtxy,pxy,mw,ish,pw,l,kc,xg,yg,ng,ifail)
! Display results
Write (nout,*) ' Returned sample spectrum'
Write (nout,*)
Write (nout,*) &
' Real Imaginary Real Imaginary Real Imaginary'
Write (nout,*) &
' part part part part part part'
Write (nout,99999)(j,xg(j),yg(j),j=1,ng)
99999 Format (1X,I3,F8.4,F9.4,I5,F8.4,F9.4,I5,F8.4,F9.4)
End Program g13cdfe