! E04YCF Example Program Text ! Mark 24 Release. NAG Copyright 2012. Module e04ycfe_mod ! E04YCF Example Program Module: ! Parameters and User-defined Routines ! .. Use Statements .. Use nag_library, Only: nag_wp ! .. Implicit None Statement .. Implicit None ! .. Parameters .. Integer, Parameter :: mdec = 15, ndec = 3, nin = 5, & nout = 6 Integer, Parameter :: & lwork = 7*ndec + ndec*ndec + 2*mdec*ndec + 3*mdec+ ndec*(ndec-1)/2 ! .. Local Arrays .. Real (Kind=nag_wp) :: t(mdec,ndec), y(mdec) Contains Subroutine lsfun1(m,n,xc,fvec,iuser,ruser) ! Routine to evaluate the residuals ! .. Scalar Arguments .. Integer, Intent (In) :: m, n ! .. Array Arguments .. Real (Kind=nag_wp), Intent (Out) :: fvec(m) Real (Kind=nag_wp), Intent (Inout) :: ruser(*) Real (Kind=nag_wp), Intent (In) :: xc(n) Integer, Intent (Inout) :: iuser(*) ! .. Executable Statements .. fvec(1:m) = xc(1) + t(1:m,1)/(xc(2)*t(1:m,2)+xc(3)*t(1:m,3)) - y(1:m) Return End Subroutine lsfun1 End Module e04ycfe_mod Program e04ycfe ! E04YCF Example Main Program ! .. Use Statements .. Use nag_library, Only: e04fyf, e04ycf, nag_wp Use e04ycfe_mod, Only: lsfun1, lwork, mdec, ndec, nin, nout, t, y ! .. Implicit None Statement .. Implicit None ! .. Local Scalars .. Real (Kind=nag_wp) :: fsumsq Integer :: i, ifail, job, ldv, m, n, ns, nv ! .. Local Arrays .. Real (Kind=nag_wp) :: cj(ndec), ruser(1), work(lwork), & x(ndec) Integer :: iuser(1) ! .. Intrinsic Procedures .. Intrinsic :: max ! .. Executable Statements .. Write (nout,*) 'E04YCF Example Program Results' ! Skip heading in data file Read (nin,*) m = mdec n = ndec ! Observations of TJ (J = 1, 2, ..., n) are held in T(I, J) ! (I = 1, 2, ..., m) Do i = 1, m Read (nin,*) y(i), t(i,1:n) End Do x(1:n) = (/0.5E0_nag_wp,1.0E0_nag_wp,1.5E0_nag_wp/) ifail = -1 Call e04fyf(m,n,lsfun1,x,fsumsq,work,lwork,iuser,ruser,ifail) Select Case (ifail) Case (0,2:) Write (nout,*) Write (nout,99999) 'On exit, the sum of squares is', fsumsq Write (nout,*) 'at the point' Write (nout,99998) x(1:n) ! Compute estimates of the variances of the sample regression ! coefficients at the final point. ! Since NS is greater than N we can use the first N elements ! of the array WORK for the dummy argument WORK. ns = 6*n + 2*m + m*n + 1 + max(1,(n*(n-1))/2) nv = ns + n job = 0 ldv = n ifail = -1 Call e04ycf(job,m,n,fsumsq,work(ns),work(nv),ldv,cj,work,ifail) Select Case (ifail) Case (0,3:) Write (nout,*) Write (nout,*) 'and estimates of the variances of the sample' Write (nout,*) 'regression coefficients are' Write (nout,99998) cj(1:n) End Select End Select 99999 Format (1X,A,F12.4) 99998 Format (1X,3F12.4) End Program e04ycfe