NAG Library Manual, Mark 29.3
Interfaces:  FL   CL   CPP   AD 

NAG FL Interface Introduction
Example description
    Program c09fafe

!     C09FAF Example Program Text
!     Mark 29.3 Release. NAG Copyright 2023.

!     .. Use Statements ..
      Use nag_library, Only: c09acf, c09faf, c09fbf, c09fyf, nag_wp
!     .. Implicit None Statement ..
      Implicit None
!     .. Parameters ..
      Integer, Parameter               :: nin = 5, nout = 6
!     .. Local Scalars ..
      Integer                          :: cindex, fr, i, ifail, j, lda, ldb,   &
                                          ldd, lenc, m, n, nf, nwcfr, nwcm,    &
                                          nwcn, nwct, nwl, sda, sdb, sdd
      Character (12)                   :: mode, wavnam, wtrans
      Character (33)                   :: title
!     .. Local Arrays ..
      Real (Kind=nag_wp), Allocatable  :: a(:,:,:), b(:,:,:), c(:), d(:,:,:)
      Integer                          :: icomm(260)
      Character (3)                    :: cpass(0:7)
!     .. Executable Statements ..
      Write (nout,*) 'C09FAF Example Program Results'

!     Skip heading in data file
      Read (nin,*)
!     Read problem parameters.
      Read (nin,*) m, n, fr
      Read (nin,*) wavnam, mode
      Write (nout,99999) wavnam, mode

      lda = m
      sda = n
      Allocate (a(lda,sda,fr))
      ldb = m
      sdb = n
      Allocate (b(ldb,sdb,fr))

!     Read data array
      Do j = 1, fr
        Read (nin,*)
        Read (nin,*)(a(i,1:n,j),i=1,m)
      End Do

      Write (nout,99998) 'Input Data                    A'
      Do j = 1, fr
        Write (nout,99996) j
        Do i = 1, m
          Write (nout,99997) a(i,1:n,j)
        End Do
      End Do

!     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 c09acf(wavnam,wtrans,mode,m,n,fr,nwl,nf,nwct,nwcn,nwcfr,icomm,      &
        ifail)
      nwcm = nwct/(8*nwcn*nwcfr)
      lenc = nwct
      Allocate (c(lenc))

!     3D DWT decomposition
      ifail = 0
      Call c09faf(m,n,fr,a,lda,sda,lenc,c,icomm,ifail)

      ldd = nwcm
      sdd = nwcn
      Allocate (d(ldd,sdd,nwcfr))

!     Loop over low/high passes from LLL to HHH
      cpass(0:7) = (/'LLL','LLH','LHL','LHH','HLL','HLH','HHL','HHH'/)
      Do cindex = 0, 7
        If (cindex==0) Then
          title = 'Approximation coefficients (LLL)'
        Else
          title = 'Detail coefficients (' // cpass(cindex) // ')'
        End If

!       Extract coefficients
        Call c09fyf(0,cindex,lenc,c,d,ldd,sdd,icomm,ifail)

        Write (nout,99992) title
        Write (nout,99995)('Frame ',j,j=1,nwcfr)
        Write (nout,99994) cindex, (d(1,1:nwcn,j),j=1,nwcfr)
        Do i = 2, nwcm
          Write (nout,99993)(d(i,1:nwcn,j),j=1,nwcfr)
        End Do
      End Do

!     3D DWT reconstruction
      ifail = 0
      Call c09fbf(m,n,fr,lenc,c,b,ldb,sdb,icomm,ifail)

      Write (nout,99998) 'Output Data                    B'
      Do j = 1, fr
        Write (nout,99996) j
        Do i = 1, m
          Write (nout,99997) b(i,1:n,j)
        End Do
      End Do

99999 Format (/,1X,'DWT ::',/,1X,'       Wavelet : ',A,/,1X,                   &
        '       End mode: ',A)
99998 Format (/,1X,A,' : ')
99997 Format (1X,8(F8.4,1X),:)
99996 Format (1X,'Frame ',I2,' : ')
99995 Format (11X,6(10X,A,I2))
99994 Format (4X,I4,6X,8(1X,F8.4))
99993 Format (14X,8(1X,F8.4))
99992 Format (/,1X,A)
    End Program c09fafe