Program c06fqfe
! C06FQF Example Program Text
! Mark 29.3 Release. NAG Copyright 2023.
! .. Use Statements ..
Use nag_library, Only: c06fpf, c06fqf, 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 ..
Real (Kind=nag_wp), Allocatable :: trig(:), u(:), v(:), work(:), x(:)
! .. Executable Statements ..
Write (nout,*) 'C06FQF 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 (trig(2*n),u(n),v(n),work(2*m*n),x(m*n))
Do j = 1, m
Read (nin,*)(x(i*m+j),i=0,n-1)
End Do
Write (nout,*)
Write (nout,*) 'Original data values'
Write (nout,*)
Write (nout,99999)(' ',(x(i*m+j),i=0,n-1),j=1,m)
Write (nout,*)
Write (nout,*) 'Original data written in full complex form'
Do j = 1, m
u(1:n) = x(j:m*n:m)
v(1:n) = 0.0_nag_wp
v(2:(n+1)/2) = u(n:n-(n-1)/2+1:-1)
u(n:n-(n-1)/2+1:-1) = u(2:(n+1)/2)
v(n-(n-1)/2+1:n) = -v((n+1)/2:2:-1)
Write (nout,*)
Write (nout,99999) 'Real ', u(1:n)
Write (nout,99999) 'Imag ', v(1:n)
End Do
ifail = 0
Call c06fqf(m,n,x,'Initial',trig,work,ifail)
Write (nout,*)
Write (nout,*) 'Discrete Fourier transforms (real values)'
Write (nout,*)
Write (nout,99999)(' ',(x(i*m+j),i=0,n-1),j=1,m)
Call c06fpf(m,n,x,'Subsequent',trig,work,ifail)
x((n/2+1)*m+1:m*n) = -x((n/2+1)*m+1:m*n)
Write (nout,*)
Write (nout,*) 'Original data as restored by inverse transform'
Write (nout,*)
Write (nout,99999)(' ',(x(i*m+j),i=0,n-1),j=1,m)
Deallocate (trig,u,v,work,x)
End Do loop
99999 Format (1X,A,6F10.4)
End Program c06fqfe