Program g02gkfe ! G02GKF Example Program Text ! Mark 24 Release. NAG Copyright 2012. ! .. Use Statements .. Use nag_library, Only: g02gcf, g02gkf, nag_wp ! .. Implicit None Statement .. Implicit None ! .. Parameters .. Integer, Parameter :: nin = 5, nout = 6 ! .. Local Scalars .. Real (Kind=nag_wp) :: a, dev, eps, tol Integer :: i, iconst, idf, ifail, ip, iprint, & irank, ldc, ldv, ldx, lwk, lwt, m, & maxit, n Character (1) :: link, mean, offset, weight ! .. Local Arrays .. Real (Kind=nag_wp), Allocatable :: b(:), c(:,:), cov(:), se(:), v(:,:), & wk(:), wt(:), x(:,:), y(:) Integer, Allocatable :: isx(:) ! .. Intrinsic Procedures .. Intrinsic :: count ! .. Executable Statements .. Write (nout,*) 'G02GKF 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 = (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 Poisson errors ifail = -1 Call g02gcf(link,mean,offset,weight,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 100 End If End If ! Display initial results Write (nout,99999) 'Deviance = ', dev Write (nout,99998) 'Degrees of freedom = ', idf Write (nout,*) ! Calculate the number of constraints required iconst = ip - irank ! Going to reallocate workspace, so deallocate it Deallocate (wk) lwk = 2*ip*ip + ip*iconst + 2*iconst*iconst + 4*iconst ldc = ip Allocate (c(ldc,iconst),wk(lwk)) ! Read in constraints Read (nin,*,Iostat=ifail)(c(i,1:iconst),i=1,ip) If (ifail/=0) Then Write (nout,99996) & ' ** Insufficient constraints supplied, was expecting ', iconst Go To 100 End If ! Re-estimate the model given the constraints ifail = 0 Call g02gkf(ip,iconst,v,ldv,c,ldc,b,1.0E0_nag_wp,se,cov,wk,ifail) ! Display the constrained parameter estimates Write (nout,*) ' Estimate Standard error' Write (nout,*) Write (nout,99997)(b(i),se(i),i=1,ip) 100 Continue 99999 Format (1X,A,E12.4) 99998 Format (1X,A,I2) 99997 Format (1X,2F14.4) 99996 Format (1X,A,I5) End Program g02gkfe