PROGRAM g02dafe

!      G02DAF Example Program Text

!      Mark 23 Release. NAG Copyright 2011.

!      .. Use Statements ..
       USE nag_library, ONLY : g02buf, g02daf, nag_wp
!      .. Implicit None Statement ..
       IMPLICIT NONE
!      .. Parameters ..
       INTEGER, PARAMETER              :: nin = 5, nout = 6
!      .. Local Scalars ..
       REAL (KIND=nag_wp)              :: aic, arsq, en, mult, rsq, rss, sw, tol
       INTEGER                         :: i, idf, ifail, ip, irank, ldq, ldx,  &
                                          lwt, m, n
       LOGICAL                         :: svd
       CHARACTER (1)                   :: mean, weight
!      .. Local Arrays ..
       REAL (KIND=nag_wp), ALLOCATABLE :: b(:), cov(:), h(:), p(:), q(:,:),    &
                                          res(:), se(:), wk(:), wt(:), x(:,:), &
                                          y(:)
       REAL (KIND=nag_wp)              :: c(1), wmean(1)
       INTEGER, ALLOCATABLE            :: isx(:)
!      .. Intrinsic Functions ..
       INTRINSIC                          count, log, real
!      .. Executable Statements ..
       WRITE (nout,*) 'G02DAF Example Program Results'
       WRITE (nout,*)

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

!      Read in the problem size
       READ (nin,*) n, m, weight, mean

       IF (weight=='W' .OR. weight=='w') THEN
          lwt = n
       ELSE
          lwt = 0
       END IF
       ldx = n
       ALLOCATE (x(ldx,m),y(n),wt(lwt),isx(m))

!      Read in data
       IF (lwt>0) THEN
          READ (nin,*) (x(i,1:m),y(i),wt(i),i=1,n)
       ELSE
          READ (nin,*) (x(i,1:m),y(i),i=1,n)
       END IF

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

!      Calculate IP
       ip = count(isx(1:m)>0)
       IF (mean=='M' .OR. mean=='m') THEN
          ip = ip + 1
       END IF

       ldq = n
       ALLOCATE (b(ip),cov((ip*ip+ip)/2),h(n),p(ip*(ip+ &
          2)),q(ldq,ip+1),res(n),se(ip),wk(ip*ip+5*(ip-1)))

!      Use suggested value for tolerance
       tol = 0.000001E0_nag_wp

!      Fit general linear regression model
       ifail = -1
       CALL g02daf(mean,weight,n,x,ldx,m,isx,ip,y,wt,rss,idf,b,se,cov,res,h,q, &
          ldq,svd,irank,p,tol,wk,ifail)
       IF (ifail/=0) THEN
          IF (ifail/=5) THEN
             GO TO 20
          END IF
       END IF

!      Calculate (weighted) total sums of squares, adjusted for mean if required
!      If in G02DAF, an intercept is added to the regression by including a
!      column of 1's in X, rather than by using the MEAN argument then 
!      MEAN = 'M' should be used in this call to G02BUF.
       ifail = 0
       CALL g02buf(mean,weight,n,1,y,n,wt,sw,wmean,c,ifail)

!      Get effective number of observations (=N if there are no zero weights)
       en = real(idf+irank,kind=nag_wp)

!      Calculate R-squared, corrected R-squared and AIC
       rsq = 1.0_nag_wp - rss/c(1)
       IF (mean=='M' .OR. mean=='m') THEN
          mult = (en-1.0E0_nag_wp)/(en-real(irank,kind=nag_wp))
       ELSE
          mult = en/(en-real(irank,kind=nag_wp))
       END IF
       arsq = 1.0_nag_wp - mult*(1.0_nag_wp-rsq)
       aic = en*log(rss/en) + 2.0_nag_wp*real(irank,kind=nag_wp)

!      Display results
       IF (svd) THEN
          WRITE (nout,99999) 'Model not of full rank, rank = ', irank
          WRITE (nout,*)
       END IF
       WRITE (nout,99998) 'Residual sum of squares = ', rss
       WRITE (nout,99999) 'Degrees of freedom      = ', idf
       WRITE (nout,99998) 'R-squared               = ', rsq
       WRITE (nout,99998) 'Adjusted R-squared      = ', arsq
       WRITE (nout,99998) 'AIC                     = ', aic
       WRITE (nout,*)
       WRITE (nout,*) 'Variable   Parameter estimate   ', 'Standard error'
       WRITE (nout,*)
       IF (ifail==0) THEN
          WRITE (nout,99997) (i,b(i),se(i),i=1,ip)
       ELSE
          WRITE (nout,99996) (i,b(i),i=1,ip)
       END IF
       WRITE (nout,*)
       WRITE (nout,*) '   Obs          Residuals              H'
       WRITE (nout,*)
       WRITE (nout,99997) (i,res(i),h(i),i=1,n)

20     CONTINUE

99999  FORMAT (1X,A,I4)
99998  FORMAT (1X,A,E12.4)
99997  FORMAT (1X,I6,2E20.4)
99996  FORMAT (1X,I6,E20.4)
    END PROGRAM g02dafe