PROGRAM g02hafe ! G02HAF Example Program Text ! Mark 23 Release. NAG Copyright 2011. ! .. Use Statements .. USE nag_library, ONLY : g02haf, nag_wp, x04abf ! .. Implicit None Statement .. IMPLICIT NONE ! .. Parameters .. INTEGER, PARAMETER :: iset = 1, nin = 5, nout = 6 ! .. Local Scalars .. REAL (KIND=nag_wp) :: cpsi, cucv, dchi, h1, h2, h3, sigma, & tol INTEGER :: i, ifail, indc, indw, ipsi, isigma, & ldc, ldx, lwork, m, maxit, n, nadv, & nitmon ! .. Local Arrays .. REAL (KIND=nag_wp), ALLOCATABLE :: c(:,:), rs(:), theta(:), wgt(:), & work(:), x(:,:), y(:) ! .. Executable Statements .. WRITE (nout,*) 'G02HAF Example Program Results' WRITE (nout,*) ! Skip heading in data file READ (nin,*) ! Read in the problem size READ (nin,*) n, m ldx = n ldc = m lwork = 4*n + m*(n+m) ALLOCATE (x(ldx,m),y(n),theta(m),c(ldc,m),work(lwork),rs(n),wgt(n)) ! Read in data READ (nin,*) (x(i,1:m),y(i),i=1,n) ! Read in control parameters READ (nin,*) indw, ipsi, isigma, nitmon, maxit, tol ! Read in appropriate weight function parameters IF (indw/=0) THEN READ (nin,*) cucv, indc END IF IF (ipsi>0) THEN IF (ipsi==1) THEN READ (nin,*) cpsi ELSE IF (ipsi==2) THEN READ (nin,*) h1, h2, h3 END IF IF (isigma>0) THEN READ (nin,*) dchi END IF END IF ! Set the advisory channel to NOUT for monitoring information IF (nitmon/=0) THEN nadv = nout CALL x04abf(iset,nadv) END IF ! Read in initial values READ (nin,*) sigma READ (nin,*) theta(1:m) ! Perform M-estimate regression ifail = -1 CALL g02haf(indw,ipsi,isigma,indc,n,m,x,ldx,y,cpsi,h1,h2,h3,cucv,dchi, & theta,sigma,c,ldc,rs,wgt,tol,maxit,nitmon,work,ifail) IF (ifail/=0) THEN IF (ifail<7) THEN GO TO 20 ELSE WRITE (nout,*) & ' Some of the following reslts may be unreliable' END IF END IF ! Display results WRITE (nout,99999) 'Sigma = ', sigma WRITE (nout,*) WRITE (nout,*) ' THETA Standard' WRITE (nout,*) ' errors' WRITE (nout,99998) (theta(i),c(i,i),i=1,m) WRITE (nout,*) WRITE (nout,*) ' Weights Residuals' WRITE (nout,99998) (wgt(i),rs(i),i=1,n) 20 CONTINUE 99999 FORMAT (1X,A,F10.4) 99998 FORMAT (1X,F12.4,F13.4) END PROGRAM g02hafe