PROGRAM g02gdfe

!      G02GDF Example Program Text

!      Mark 23 Release. NAG Copyright 2011.

!      .. Use Statements ..
       USE nag_library, ONLY : g02gdf, nag_wp
!      .. Implicit None Statement ..
       IMPLICIT NONE
!      .. Parameters ..
       INTEGER, PARAMETER              :: nin = 5, nout = 6
!      .. Local Scalars ..
       REAL (KIND=nag_wp)              :: a, dev, eps, s, tol
       INTEGER                         :: i, idf, ifail, ip, iprint, irank,    &
                                          ldv, ldx, lwk, lwt, m, maxit, n
       CHARACTER (1)                   :: link, mean, offset, weight
!      .. Local Arrays ..
       REAL (KIND=nag_wp), ALLOCATABLE :: b(:), cov(:), se(:), v(:,:), wk(:),  &
                                          wt(:), x(:,:), y(:)
       INTEGER, ALLOCATABLE            :: isx(:)
!      .. Intrinsic Functions ..
       INTRINSIC                          count
!      .. Executable Statements ..
       WRITE (nout,*) 'G02GDF Example Program Results'
       WRITE (nout,*)

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

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

       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

!      Read in power for exponential link
       IF (link=='E' .OR. link=='e') THEN
          READ (nin,*) a
       END IF

       ldv = n
       lwk = (ip*ip+3*ip+22)/2
       ALLOCATE (b(ip),se(ip),cov(ip*(ip+1)/2),v(ldv,ip+7),wk(lwk))

!      Read in the offset
       IF (offset=='Y' .OR. offset=='y') THEN
          READ (nin,*) v(1:n,7)
       END IF

!      Read in control parameters
       READ (nin,*) iprint, eps, tol, maxit

!      Fit generalized linear model with Gamma errors
       ifail = -1
       CALL g02gdf(link,mean,offset,weight,n,x,ldx,m,isx,ip,y,wt,s,a,dev,idf, &
          b,irank,se,cov,v,ldv,tol,maxit,iprint,eps,wk,ifail)
       IF (ifail/=0) THEN
          IF (ifail<7) THEN
             GO TO 20
          END IF
       END IF

!      Display results
       WRITE (nout,99999) 'Deviance = ', dev
       WRITE (nout,99998) 'Degrees of freedom = ', idf
       WRITE (nout,*)
       WRITE (nout,*) '     Estimate     Standard error'
       WRITE (nout,*)
       WRITE (nout,99997) (b(i),se(i),i=1,ip)
       WRITE (nout,*)
       WRITE (nout,*) '     Y        FV     Residual        H'
       WRITE (nout,*)
       WRITE (nout,99996) (y(i),v(i,2),v(i,5),v(i,6),i=1,n)

20     CONTINUE

99999  FORMAT (1X,A,E12.4)
99998  FORMAT (1X,A,I0)
99997  FORMAT (1X,2F14.4)
99996  FORMAT (1X,F7.1,F10.2,F12.4,F10.3)
    END PROGRAM g02gdfe