Program c06psfe
! C06PSF Example Program Text
! Mark 26.2 Release. NAG Copyright 2017.
! .. Use Statements ..
Use nag_library, Only: c06psf, nag_wp
! .. Implicit None Statement ..
Implicit None
! .. Parameters ..
Integer, Parameter :: nin = 5, nout = 6
! .. Local Scalars ..
Integer :: i, ieof, ifail, j, m, n
! .. Local Arrays ..
Complex (Kind=nag_wp), Allocatable :: work(:), x(:)
! .. Intrinsic Procedures ..
Intrinsic :: aimag, real
! .. Executable Statements ..
Write (nout,*) 'C06PSF Example Program Results'
! Skip heading in data file
Read (nin,*)
loop: Do
Read (nin,*,Iostat=ieof) m, n
If (ieof<0) Then
Exit loop
End If
Allocate (work(n*m+n+15),x(m*n))
Do j = 1, m*n, n
Read (nin,*)(x(j+i),i=0,n-1)
End Do
Write (nout,*)
Write (nout,*) 'Original data values'
Do j = 1, m*n, n
Write (nout,*)
Write (nout,99999) 'Real ', (real(x(j+i)),i=0,n-1)
Write (nout,99999) 'Imag ', (aimag(x(j+i)),i=0,n-1)
End Do
! ifail: behaviour on error exit
! =0 for hard exit, =1 for quiet-soft, =-1 for noisy-soft
ifail = 0
Call c06psf('F',n,m,x,work,ifail)
Write (nout,*)
Write (nout,*) 'Discrete Fourier transforms'
Do j = 1, m*n, n
Write (nout,*)
Write (nout,99999) 'Real ', (real(x(j+i)),i=0,n-1)
Write (nout,99999) 'Imag ', (aimag(x(j+i)),i=0,n-1)
End Do
Call c06psf('B',n,m,x,work,ifail)
Write (nout,*)
Write (nout,*) 'Original data as restored by inverse transform'
Do j = 1, m*n, n
Write (nout,*)
Write (nout,99999) 'Real ', (real(x(j+i)),i=0,n-1)
Write (nout,99999) 'Imag ', (aimag(x(j+i)),i=0,n-1)
End Do
Deallocate (x,work)
End Do loop
99999 Format (1X,A,6F10.4)
End Program c06psfe