! E04GYF Example Program Text ! Mark 24 Release. NAG Copyright 2012. Module e04gyfe_mod ! E04GYF Example Program Module: ! Parameters and User-defined Routines ! .. Use Statements .. Use nag_library, Only: nag_wp ! .. Implicit None Statement .. Implicit None ! .. Parameters .. Integer, Parameter :: m = 15, n = 3, nin = 5, & nout = 6, nt = 3 Integer, Parameter :: lw = 8*n + 2*n*n + 2*m*n + 3*m ! .. Local Arrays .. Real (Kind=nag_wp) :: t(m,nt), y(m) Contains Subroutine lsfun2(m,n,xc,fvec,fjac,ldfjac,iuser,ruser) ! Routine to evaluate the residuals and their 1st derivatives. ! .. Scalar Arguments .. Integer, Intent (In) :: ldfjac, m, n ! .. Array Arguments .. Real (Kind=nag_wp), Intent (Inout) :: fjac(ldfjac,n), ruser(*) Real (Kind=nag_wp), Intent (Out) :: fvec(m) Real (Kind=nag_wp), Intent (In) :: xc(n) Integer, Intent (Inout) :: iuser(*) ! .. Local Scalars .. Real (Kind=nag_wp) :: denom, dummy Integer :: i ! .. Executable Statements .. Do i = 1, m denom = xc(2)*t(i,2) + xc(3)*t(i,3) fvec(i) = xc(1) + t(i,1)/denom - y(i) fjac(i,1) = 1.0_nag_wp dummy = -1.0_nag_wp/(denom*denom) fjac(i,2) = t(i,1)*t(i,2)*dummy fjac(i,3) = t(i,1)*t(i,3)*dummy End Do Return End Subroutine lsfun2 End Module e04gyfe_mod Program e04gyfe ! E04GYF Example Main Program ! .. Use Statements .. Use nag_library, Only: e04gyf, nag_wp Use e04gyfe_mod, Only: lsfun2, lw, m, n, nin, nout, nt, t, y ! .. Implicit None Statement .. Implicit None ! .. Local Scalars .. Real (Kind=nag_wp) :: fsumsq Integer :: i, ifail ! .. Local Arrays .. Real (Kind=nag_wp) :: ruser(1), w(lw), x(n) Integer :: iuser(1) ! .. Executable Statements .. Write (nout,*) 'E04GYF Example Program Results' ! Skip heading in data file Read (nin,*) ! Observations of TJ (J = 1, 2, ..., nt) are held in T(I, J) ! (I = 1, 2, ..., m) Do i = 1, m Read (nin,*) y(i), t(i,1:nt) End Do x(1:nt) = (/0.5_nag_wp,1.0_nag_wp,1.5_nag_wp/) ifail = -1 Call e04gyf(m,n,lsfun2,x,fsumsq,w,lw,iuser,ruser,ifail) Select Case (ifail) Case (0,2:8,10:) Write (nout,*) Write (nout,99999) 'On exit, the sum of squares is', fsumsq Write (nout,99999) 'at the point', x(1:n) End Select 99999 Format (1X,A,3F12.4) End Program e04gyfe