PROGRAM g02effe

!      G02EFF Example Program Text

!      Mark 23 Release. NAG Copyright 2011.

!      .. Use Statements ..
       USE nag_library, ONLY : g02buf, g02eff, g02efh, nag_wp
!      .. Implicit None Statement ..
       IMPLICIT NONE
!      .. Parameters ..
       INTEGER, PARAMETER              :: nin = 5, nout = 6
!      .. Local Scalars ..
       REAL (KIND=nag_wp)              :: fin, fout, rms, rsq, sw, tau
       INTEGER                         :: df, i, ifail, ldz, liuser, lruser,   &
                                          m, m1, monlev, n
       CHARACTER (1)                   :: mean, weight
!      .. Local Arrays ..
       REAL (KIND=nag_wp), ALLOCATABLE :: b(:), c(:), ruser(:), se(:),         &
                                          wmean(:), z(:,:)
       REAL (KIND=nag_wp)              :: wt(1)
       INTEGER, ALLOCATABLE            :: isx(:), iuser(:)
!      .. Executable Statements ..
       WRITE (nout,*) 'G02EFF Example Program Results'
       WRITE (nout,*)
       FLUSH (nout)

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

!      Read in the problem size and various control parameters
       READ (nin,*) n, m, fin, fout, tau, monlev

!      Not using the user supplied arrays RUSER and IUSER
       liuser = 0
       lruser = 0

       m1 = m + 1
       ldz = n
       ALLOCATE (wmean(m1),c(m1*(m+2)/2),isx(m),b(m1),se(m1),iuser(liuser), &
          ruser(lruser),z(ldz,m1))

!      Read in augmented design matrix Z = (X | Y)
       READ (nin,*) (z(i,1:m1),i=1,n)

!      Read in variable inclusion flags
       READ (nin,*) isx(1:m)

!      G02EFF always adds the intercept term, so need to calculate correlation
!      matrix with mean included.
       mean = 'M'

!      No weights.
       weight = 'U'

!      Compute upper-triangular correlation matrix of the augmented design
!      matrix.
       ifail = 0
       CALL g02buf(mean,weight,n,m1,z,ldz,wt,sw,wmean,c,ifail)

!      Perform stepwise selection of variables.
       ifail = 0
       CALL g02eff(m,n,wmean,c,sw,isx,fin,fout,tau,b,se,rsq,rms,df,monlev, &
          g02efh,iuser,ruser,ifail)

!      Display results
       WRITE (nout,*)
       WRITE (nout,99999) 'Fitted Model Summary'
       WRITE (nout,99999) 'Term              Estimate   Standard Error'
       WRITE (nout,99998) 'Intercept:', b(1), se(1)
       DO i = 1, m
          IF (isx(i)==1 .OR. isx(i)==2) THEN
             WRITE (nout,99997) 'Variable:', i, b(i+1), se(i+1)
          END IF
       END DO
       WRITE (nout,*)
       WRITE (nout,99996) 'RMS:', rms

99999  FORMAT (1X,A)
99998  FORMAT (1X,A,4X,1P,E12.3,5X,E12.3)
99997  FORMAT (1X,A,1X,I3,1X,1P,E12.3,5X,E12.3)
99996  FORMAT (1X,A,1X,1P,E12.3)
    END PROGRAM g02effe