PROGRAM g13cafe

!      G13CAF Example Program Text

!      Mark 23 Release. NAG Copyright 2011.

!      .. Use Statements ..
       USE nag_library, ONLY : g13caf, nag_wp
!      .. Implicit None Statement ..
       IMPLICIT NONE
!      .. Parameters ..
       INTEGER, PARAMETER              :: nin = 5, nout = 6
!      .. Local Scalars ..
       REAL (KIND=nag_wp)              :: px
       INTEGER                         :: i, ic, ifail, iw, kc, l, lg, lxg,    &
                                          mtx, mw, nc, ng, nx, nxg
!      .. Local Arrays ..
       REAL (KIND=nag_wp), ALLOCATABLE :: c(:), xg(:)
       REAL (KIND=nag_wp)              :: stats(4)
!      .. Intrinsic Functions ..
       INTRINSIC                          max
!      .. Executable Statements ..
       WRITE (nout,*) 'G13CAF Example Program Results'
       WRITE (nout,*)

!      Skip heading in data file
       READ (nin,*)

!      Read in the problem size
       READ (nin,*) nx, nc

!      Read in smoothing parameters
       READ (nin,*) mtx, ic, px, iw, mw, l, lg
       IF (ic==0) THEN
          READ (nin,*) kc
       END IF

       IF (ic==0) THEN
          nxg = max(kc,l)
       ELSE
          nxg = l
       END IF
       lxg = max(nxg,nx)
       ALLOCATE (xg(lxg),c(nc))

!      Read in the data
       READ (nin,*) xg(1:nx)

!      Calculate smoothed spectrum
       ifail = -1
       CALL g13caf(nx,mtx,px,iw,mw,ic,nc,c,kc,l,lg,nxg,xg,ng,stats,ifail)
       IF (ifail/=0) THEN
          IF (ifail<4) THEN
             GO TO 20
          END IF
       END IF

!      Display results
       WRITE (nout,*) 'Covariances'
       WRITE (nout,99999) c(1:nc)
       WRITE (nout,*)
       WRITE (nout,99998) 'Degrees of freedom =', stats(1), &
          '      Bandwidth =', stats(4)
       WRITE (nout,*)
       WRITE (nout,99997) '95 percent confidence limits -     Lower =', &
          stats(2), '  Upper =', stats(3)
       WRITE (nout,*)
       WRITE (nout,*) &
          '      Spectrum       Spectrum      Spectrum       Spectrum'
       WRITE (nout,*) &
          '      estimate       estimate      estimate       estimate'
       WRITE (nout,99996) (i,xg(i),i=1,ng)

20     CONTINUE

99999  FORMAT (1X,6F11.4)
99998  FORMAT (1X,A,F4.1,A,F7.4)
99997  FORMAT (1X,A,F7.4,A,F7.4)
99996  FORMAT (1X,I4,F10.4,I5,F10.4,I5,F10.4,I5,F10.4)
    END PROGRAM g13cafe