Program g02mcfe
! G02MCF Example Program Text
! Mark 26.1 Release. NAG Copyright 2016.
! .. Use Statements ..
Use nag_library, Only: g02maf, g02mcf, nag_wp
! .. Implicit None Statement ..
Implicit None
! .. Parameters ..
Integer, Parameter :: nin = 5, nout = 6
! .. Local Scalars ..
Integer :: i, ifail, ip, k, ktype, ldb, ldd, &
ldnb, lisx, lnk, lropt, m, mnstep, &
mtype, n, nstep, pred, prey
! .. Local Arrays ..
Real (Kind=nag_wp), Allocatable :: b(:,:), d(:,:), fitsum(:,:), &
nb(:,:), nk(:), ropt(:), y(:)
Integer, Allocatable :: isx(:)
! .. Intrinsic Procedures ..
Intrinsic :: max, repeat
! .. Executable Statements ..
Write (nout,*) 'G02MCF Example Program Results'
Write (nout,*)
! Skip heading in data file
Read (nin,*)
! Read in the problem size
Read (nin,*) n, m
! Read in the model specification
Read (nin,*) mtype, pred, prey, mnstep
! Use all of the variables
lisx = 0
Allocate (isx(lisx))
! Optional arguments (using defaults)
lropt = 0
Allocate (ropt(lropt))
! Read in the data
ldd = n
Allocate (y(n),d(ldd,m))
Read (nin,*)(d(i,1:m),y(i),i=1,n)
! Allocate output arrays
ldb = m
Allocate (b(ldb,mnstep+2),fitsum(6,mnstep+1))
! Call the model fitting routine
ifail = -1
Call g02maf(mtype,pred,prey,n,m,d,ldd,isx,lisx,y,mnstep,ip,nstep,b,ldb, &
fitsum,ropt,lropt,ifail)
If (ifail/=0) Then
If (ifail/=112 .And. ifail/=161 .And. ifail/=162 .And. ifail/=163) &
Then
! IFAIL = 112, 161, 162 and 163 are warnings, so no need to terminate
! if they occur
Go To 100
End If
End If
! Read in the number of additional parameter estimates required and the
! way they will be specified
Read (nin,*) ktype, lnk
ldnb = ip
Allocate (nk(lnk),nb(ip,lnk))
! Read in the target values
Read (nin,*) nk(1:lnk)
! Calculate the additional parameter estimates
ifail = 0
Call g02mcf(nstep,ip,b,ldb,fitsum,ktype,nk,lnk,nb,ldnb,ifail)
Write (nout,*) 'Parameter Estimates from G02MAF'
Write (nout,*) ' Step ', repeat(' ',max((ip-2),0)*5), &
' Parameter Estimate'
Write (nout,*) repeat('-',5+ip*10)
Do k = 1, nstep
Write (nout,99999) k, b(1:ip,k)
End Do
Write (nout,*)
Write (nout,*) 'Additional Parameter Estimates from G02MCF'
Write (nout,*) ' NK ', repeat(' ',max((ip-2),0)*5), &
' Parameter Estimate'
Write (nout,*) repeat('-',5+ip*10)
Do k = 1, lnk
Write (nout,99998) nk(k), nb(1:ip,k)
End Do
100 Continue
99999 Format (2X,I3,10(1X,F9.3))
99998 Format (1X,F4.1,10(1X,F9.3))
End Program g02mcfe