Program c09dafe
! C09DAF Example Program Text
! Mark 28.7 Release. NAG Copyright 2022.
! .. Use Statements ..
Use nag_library, Only: c09aaf, c09daf, c09dbf, nag_wp
! .. Implicit None Statement ..
Implicit None
! .. Parameters ..
Integer, Parameter :: nin = 5, nout = 6
! .. Local Scalars ..
Integer :: ifail, n, nf, nwc, nwl, ny
Character (14) :: mode, wavnam, wtrans
! .. Local Arrays ..
Real (Kind=nag_wp), Allocatable :: ca(:), cd(:), x(:), y(:)
Integer :: icomm(100)
! .. Executable Statements ..
Write (nout,*) 'C09DAF Example Program Results'
! Skip heading in data file
Read (nin,*)
! Read problem parameters.
Read (nin,*) n
Read (nin,*) wavnam, mode
Allocate (x(n),y(n))
Write (nout,99999) wavnam, mode
! Read array
Read (nin,*) x(1:n)
Write (nout,*) 'Input Data X :'
Write (nout,99997) x(1:n)
! Query wavelet filter dimensions
wtrans = 'Time invariant'
! ifail: behaviour on error exit
! =0 for hard exit, =1 for quiet-soft, =-1 for noisy-soft
ifail = 0
Call c09aaf(wavnam,wtrans,mode,n,nwl,nf,nwc,icomm,ifail)
Allocate (ca(nwc),cd(nwc))
ifail = 0
Call c09daf(n,x,nwc,ca,cd,icomm,ifail)
Write (nout,99998)
Write (nout,99997) ca(1:nwc)
Write (nout,99996)
Write (nout,99997) cd(1:nwc)
ny = n
ifail = 0
Call c09dbf(nwc,ca,cd,ny,y,icomm,ifail)
Write (nout,99995)
Write (nout,99997) y(1:ny)
99999 Format (1X,'MODWT :: Wavelet: ',A,', End mode: ',A)
99998 Format (1X,'Approximation coefficients CA : ')
99997 Format (1X,8(F8.4,1X),:)
99996 Format (1X,'Detail coefficients CD : ')
99995 Format (1X,'Reconstruction Y : ')
End Program c09dafe