Program c09ccfe

!     C09CCF Example Program Text

!     Mark 25 Release. NAG Copyright 2014.

!     .. Use Statements ..
      Use nag_library, Only: c09aaf, c09ccf, c09cdf, nag_wp
!     .. Implicit None Statement ..
      Implicit None
!     .. Parameters ..
      Integer, Parameter               :: nin = 5, nout = 6
!     .. Local Scalars ..
      Integer                          :: ifail, lenc, n, nf, nnz, nwc, nwl,   &
                                          nwlinv, nwlmax
      Character (10)                   :: mode, wavnam, wtrans
!     .. Local Arrays ..
      Real (Kind=nag_wp), Allocatable  :: c(:), x(:), y(:)
      Integer, Allocatable             :: dwtlev(:)
      Integer                          :: icomm(100)
!     .. Intrinsic Procedures ..
      Intrinsic                        :: sum
!     .. Executable Statements ..
      Write (nout,*) 'C09CCF 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, n

!     Read data array and write it out

      Read (nin,*) x(1:n)

      Write (nout,*) ' Input Data      X :'
      Write (nout,99998) x(1:n)

!     Query wavelet filter dimensions
!     For Multi-Resolution Analysis, decomposition, wtrans = 'M'
      wtrans = 'Multilevel'

!     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,nwlmax,nf,nwc,icomm,ifail)

      lenc = nwc
      Allocate (c(lenc),dwtlev(nwlmax+1))

      nwl = nwlmax

!     Perform Discrete Wavelet transform
      ifail = 0
      Call c09ccf(n,x,lenc,c,nwl,dwtlev,icomm,ifail)

      Write (nout,99997) nwl
      Write (nout,99996)
      Write (nout,99995) dwtlev(1:nwl+1)
      nnz = sum(dwtlev(1:nwl+1))
      Write (nout,99994)
      Write (nout,99998) c(1:nnz)

!     Reconstruct original data
      nwlinv = nwl

      ifail = 0
      Call c09cdf(nwlinv,lenc,c,n,y,icomm,ifail)

      Write (nout,99993)
      Write (nout,99998) y(1:n)

99999 Format (1X,' MLDWT :: Wavelet : ',A10,', End mode : ',A10,' N = ',I10)
99998 Format (8(F8.4,1X):)
99997 Format (1X,' Number of Levels : ',I10)
99996 Format (1X,' Number of coefficients in each level : ')
99995 Format (8(I8,1X):)
99994 Format (1X,' Wavelet coefficients C : ')
99993 Format (1X,' Reconstruction              Y : ')
    End Program c09ccfe