Program g02gpfe
! G02GPF Example Program Text
! Mark 25 Release. NAG Copyright 2014.
! .. Use Statements ..
Use nag_library, Only: g02gaf, g02gpf, nag_wp
! .. Implicit None Statement ..
Implicit None
! .. Parameters ..
Integer, Parameter :: nin = 5, nout = 6
! .. Local Scalars ..
Real (Kind=nag_wp) :: a, eps, rss, s, tol
Integer :: i, idf, ifail, ip, iprint, irank, &
ldv, ldx, loff, lt, lwk, lwt, m, &
maxit, n, tldx
Logical :: vfobs
Character (1) :: errfn, link, mean, offset, weight
! .. Local Arrays ..
Real (Kind=nag_wp), Allocatable :: b(:), cov(:), eta(:), off(:), &
pred(:), se(:), seeta(:), sepred(:), &
t(:), twt(:), tx(:,:), ty(:), &
v(:,:), wk(:), wt(:), x(:,:), y(:)
Integer, Allocatable :: isx(:)
! .. Intrinsic Procedures ..
Intrinsic :: count
! .. Executable Statements ..
Write (nout,*) 'G02GPF Example Program Results'
Write (nout,*)
! Skip headings in data file
Read (nin,*)
Read (nin,*)
! Read in training data for model that will be used for prediction
Read (nin,*) link, mean, offset, weight, n, m, s
If (weight=='W' .Or. weight=='w') Then
lwt = n
Else
lwt = 0
End If
tldx = n
Allocate (tx(tldx,m),ty(n),twt(lwt),isx(m))
! Read in data
If (lwt>0) Then
Read (nin,*)(tx(i,1:m),ty(i),twt(i),i=1,n)
Else
Read (nin,*)(tx(i,1:m),ty(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
! Call routine to fit generalized linear model, with Normal errors,
! to training data
ifail = -1
Call g02gaf(link,mean,offset,weight,n,tx,tldx,m,isx,ip,ty,twt,s,a,rss, &
idf,b,irank,se,cov,v,ldv,tol,maxit,iprint,eps,wk,ifail)
If (ifail/=0) Then
If (ifail<6) Then
Go To 100
End If
End If
! Display parameter estimates for training data
Write (nout,99999) 'Residual sum of squares = ', rss
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)
! Skip second lot of headings in data file
Read (nin,*)
! Read in size of prediction data
Read (nin,*) n, vfobs, offset, weight
! Used G02GAF to fit training model, so error structure is normal is
! do not require T array
errfn = 'N'
lt = 0
ldx = n
If (weight=='W' .Or. weight=='w') Then
lwt = n
Else
lwt = 0
End If
If (offset=='Y' .Or. offset=='y') Then
loff = n
Else
loff = 0
End If
Allocate (x(ldx,m),y(n),wt(lwt),off(loff),eta(n),seeta(n),pred(n), &
sepred(n),t(lt))
! Read in predication data
If (lwt>0) Then
Read (nin,*)(x(i,1:m),wt(i),i=1,n)
Else
Read (nin,*)(x(i,1:m),i=1,n)
End If
! Read in offset for the prediction data
If (offset=='Y' .Or. offset=='y') Then
Read (nin,*) off(1:n)
End If
! Call prediction routine
ifail = -1
Call g02gpf(errfn,link,mean,offset,weight,n,x,ldx,m,isx,ip,t,off,wt,s,a, &
b,cov,vfobs,eta,seeta,pred,sepred,ifail)
If (ifail/=0) Then
Write (nout,99995) ifail
If (ifail/=22) Then
Go To 100
End If
End If
! Display predicted values
Write (nout,*)
Write (nout,*) ' I ETA SE(ETA) Predicted ', &
' SE(Predicted)'
Write (nout,*)
Write (nout,99996)(i,eta(i),seeta(i),pred(i),sepred(i),i=1,n)
100 Continue
99999 Format (1X,A,E12.4)
99998 Format (1X,A,I0)
99997 Format (1X,2F14.4)
99996 Format (1X,I3,')',F10.5,3F14.5)
99995 Format (1X,A,I5)
End Program g02gpfe