Program g02dnfe ! G02DNF Example Program Text ! Mark 24 Release. NAG Copyright 2012. ! .. Use Statements .. Use nag_library, Only: g02daf, g02dnf, nag_wp ! .. Implicit None Statement .. Implicit None ! .. Parameters .. Integer, Parameter :: nin = 5, nout = 6 ! .. Local Scalars .. Real (Kind=nag_wp) :: rss, sestat, stat, t, tol Integer :: i, idf, ifail, ip, irank, ldq, ldx, & lwk, lwt, m, n Logical :: est, svd Character (1) :: mean, weight ! .. Local Arrays .. Real (Kind=nag_wp), Allocatable :: b(:), cov(:), f(:), h(:), p(:), & q(:,:), res(:), se(:), wk(:), wt(:), & x(:,:), y(:) Integer, Allocatable :: isx(:) ! .. Intrinsic Procedures .. Intrinsic :: count, max ! .. Executable Statements .. Write (nout,*) 'G02DNF 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),isx(m),y(n),wt(lwt)) 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 lwk = max(5*(ip-1)+ip*ip,ip) ldq = n Allocate (b(ip),se(ip),cov(ip*(ip+1)/2),res(n),h(n),q(ldq,ip+1),p(2*ip+ & ip*ip),wk(lwk),f(ip)) ! Use suggested value for tolerance tol = 0.000001E0_nag_wp ! Fit general linear regression model ifail = 0 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) ! Display initial parameter estimates Write (nout,*) 'Estimates from G02DAF' Write (nout,*) Write (nout,99999) 'Residual sum of squares = ', rss Write (nout,99998) 'Degrees of freedom = ', idf Write (nout,*) Write (nout,*) 'Variable Parameter estimate Standard error' Write (nout,*) Write (nout,99997)(i,b(i),se(i),i=1,ip) Write (nout,*) i = 0 estfn_lp: Do Read (nin,*,Iostat=ifail) f(1:ip) If (ifail/=0) Then Exit estfn_lp End If i = i + 1 ! Compute the estimable function ifail = -1 Call g02dnf(ip,irank,b,cov,p,f,est,stat,sestat,t,tol,wk,ifail) If (ifail/=0) Then If (ifail/=2) Then Go To 100 End If End If ! Display results Write (nout,99996) 'Function ', i Write (nout,*) Write (nout,99995) f(1:ip) Write (nout,*) If (est) Then Write (nout,99994) 'STAT = ', stat, ' SE = ', sestat, ' T = ', t Else Write (nout,*) 'Function not estimable' End If Write (nout,*) End Do estfn_lp 100 Continue 99999 Format (1X,A,E12.4) 99998 Format (1X,A,I4) 99997 Format (1X,I6,2E20.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 g02dnfe