Example description
!   E04HYF Example Program Text
!   Mark 26.2 Release. NAG Copyright 2017.
    Module e04hyfe_mod

!     E04HYF Example Program Module:
!            Parameters and User-defined Routines

!     .. Use Statements ..
      Use nag_library, Only: nag_wp
!     .. Implicit None Statement ..
      Implicit None
!     .. Accessibility Statements ..
      Private
      Public                           :: lsfun2, lshes2
!     .. Parameters ..
      Integer, Parameter, Public       :: m = 15, n = 3, nin = 5, nout = 6,    &
                                          nt = 3
      Integer, Parameter, Public       :: lw = 8*n + 2*n*n + 2*m*n + 3*m
!     .. Local Arrays ..
      Real (Kind=nag_wp), Public, Save :: 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.0E0_nag_wp
          dummy = -1.0E0_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
      Subroutine lshes2(m,n,fvec,xc,b,lb,iuser,ruser)
!       Routine to compute the lower triangle of the matrix B
!       (stored by rows in the array B).

!       .. Scalar Arguments ..
        Integer, Intent (In)           :: lb, m, n
!       .. Array Arguments ..
        Real (Kind=nag_wp), Intent (Out) :: b(lb)
        Real (Kind=nag_wp), Intent (In) :: fvec(m), xc(n)
        Real (Kind=nag_wp), Intent (Inout) :: ruser(*)
        Integer, Intent (Inout)        :: iuser(*)
!       .. Local Scalars ..
        Real (Kind=nag_wp)             :: dummy, sum22, sum32, sum33
        Integer                        :: i
!       .. Executable Statements ..
        b(1) = 0.0E0_nag_wp
        b(2) = 0.0E0_nag_wp
        sum22 = 0.0E0_nag_wp
        sum32 = 0.0E0_nag_wp
        sum33 = 0.0E0_nag_wp

        Do i = 1, m
          dummy = 2.0E0_nag_wp*t(i,1)/(xc(2)*t(i,2)+xc(3)*t(i,3))**3
          sum22 = sum22 + fvec(i)*dummy*t(i,2)**2
          sum32 = sum32 + fvec(i)*dummy*t(i,2)*t(i,3)
          sum33 = sum33 + fvec(i)*dummy*t(i,3)**2
        End Do

        b(3) = sum22
        b(4) = 0.0E0_nag_wp
        b(5) = sum32
        b(6) = sum33

        Return

      End Subroutine lshes2
    End Module e04hyfe_mod
    Program e04hyfe

!     E04HYF Example Main Program

!     .. Use Statements ..
      Use e04hyfe_mod, Only: lsfun2, lshes2, lw, m, n, nin, nout, nt, t, y
      Use nag_library, Only: e04hyf, nag_wp
!     .. 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,*) 'E04HYF 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.5E0_nag_wp,1.0E0_nag_wp,1.5E0_nag_wp/)

      ifail = -1
      Call e04hyf(m,n,lsfun2,lshes2,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 e04hyfe