PROGRAM c09cafe

!      C09CAF Example Program Text

!      Mark 23 Release. NAG Copyright 2011.

!      .. Use Statements ..
       USE nag_library, ONLY : c09aaf, c09caf, c09cbf, nag_wp
!      .. Implicit None Statement ..
       IMPLICIT NONE
!      .. Parameters ..
       INTEGER, PARAMETER              :: nin = 5, nout = 6
!      .. Local Scalars ..
       INTEGER                         :: ifail, n, nf, nwc, nwl, ny
       CHARACTER (12)                  :: mode, wavnam, wtrans
!      .. Local Arrays ..
       REAL (KIND=nag_wp), ALLOCATABLE :: ca(:), cd(:), x(:), y(:)
       INTEGER                         :: icomm(100)
!      .. Executable Statements ..
       WRITE (nout,*) 'C09CAF 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 = 'Single Level'

!         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 c09caf(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 c09cbf(nwc,ca,cd,ny,y,icomm,ifail)

       WRITE (nout,99995)
       WRITE (nout,99997) y(1:ny)

99999  FORMAT (1X,'DWT :: 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 c09cafe