PROGRAM g02gnfe ! G02GNF Example Program Text ! Mark 23 Release. NAG Copyright 2011. ! .. Use Statements .. USE nag_library, ONLY : g02gcf, g02gnf, nag_wp ! .. Implicit None Statement .. IMPLICIT NONE ! .. Parameters .. INTEGER, PARAMETER :: nin = 5, nout = 6 ! .. Local Scalars .. REAL (KIND=nag_wp) :: a, dev, eps, sestat, stat, tol, z INTEGER :: i, idf, ifail, ip, iprint, irank, & ldv, ldx, lwk, lwt, m, maxit, n LOGICAL :: est CHARACTER (1) :: link, mean, offset, weight ! .. Local Arrays .. REAL (KIND=nag_wp), ALLOCATABLE :: b(:), cov(:), f(:), se(:), v(:,:), & wk(:), wt(:), x(:,:), y(:) INTEGER, ALLOCATABLE :: isx(:) ! .. Intrinsic Functions .. INTRINSIC count, max ! .. Executable Statements .. WRITE (nout,*) 'G02GNF 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 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 = max((ip*ip+3*ip+22)/2,ip) ALLOCATE (b(ip),se(ip),cov(ip*(ip+1)/2),v(ldv,ip+7),wk(lwk),f(ip)) ! 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 Poisson errors ifail = -1 CALL g02gcf('L','M','N','U',n,x,ldx,m,isx,ip,y,wt,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 initial 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) ! Estimate the estimable functions i = 0 FUN_LP: DO ! Read in the function READ (nin,*,IOSTAT=ifail) f(1:ip) IF (ifail/=0) THEN EXIT FUN_LP END IF i = i + 1 ! Estimate it ifail = -1 CALL g02gnf(ip,irank,b,cov,v,ldv,f,est,stat,sestat,z,tol,wk,ifail) IF (ifail/=0) THEN IF (ifail/=2) THEN GO TO 20 END IF END IF ! Display results WRITE (nout,*) WRITE (nout,99996) 'Function ', i WRITE (nout,99995) f(1:ip) WRITE (nout,*) IF (est) THEN WRITE (nout,99994) 'STAT = ', stat, ' SE = ', sestat, ' Z = ', z ELSE WRITE (nout,*) 'Function not estimable' END IF END DO FUN_LP 20 CONTINUE 99999 FORMAT (1X,A,E12.4) 99998 FORMAT (1X,A,I2) 99997 FORMAT (1X,2F14.4) 99996 FORMAT (1X,A,I4) 99995 FORMAT (1X,5F8.2) 99994 FORMAT (1X,A,F10.4,A,F10.4,A,F10.4) END PROGRAM g02gnfe