Program g02qffe
! G02QFF Example Program Text
! Mark 25 Release. NAG Copyright 2014.
! .. Use Statements ..
Use nag_library, Only: g02qff, nag_wp
! .. Implicit None Statement ..
Implicit None
! .. Parameters ..
Integer, Parameter :: nin = 5, nout = 6
! .. Local Scalars ..
Real (Kind=nag_wp) :: df
Integer :: i, ifail, j, l, m, n, ntau
! .. Local Arrays ..
Real (Kind=nag_wp), Allocatable :: b(:,:), bl(:,:), bu(:,:), tau(:), &
x(:,:), y(:)
Integer, Allocatable :: info(:)
! .. Executable Statements ..
Write (nout,*) 'G02QFF Example Program Results'
Write (nout,*)
! Skip heading in data file
Read (nin,*)
! Read in the problem size
Read (nin,*) n, m, ntau
! Read in the data
Allocate (y(n),tau(ntau),x(n,m))
Read (nin,*)(x(i,1:m),y(i),i=1,n)
! Read in the quantiles required
Read (nin,*) tau(1:ntau)
! Allocate memory for output arrays
Allocate (b(m,ntau),info(ntau),bl(m,ntau),bu(m,ntau))
! Call the model fitting routine
ifail = -1
Call g02qff(n,m,x,y,ntau,tau,df,b,bl,bu,info,ifail)
If (ifail/=0) Then
If (ifail==111) Then
Write (nout,*) 'Additional error information (INFO): ', info(1:ntau)
Else
Go To 100
End If
End If
! Display the parameter estimates
Do l = 1, ntau
Write (nout,99999) 'Quantile: ', tau(l)
Write (nout,*)
Write (nout,*) ' Lower Parameter Upper'
Write (nout,*) ' Limit Estimate Limit'
Do j = 1, m
Write (nout,99998) j, bl(j,l), b(j,l), bu(j,l)
End Do
Write (nout,*)
Write (nout,*)
End Do
100 Continue
99999 Format (1X,A,F6.3)
99998 Format (1X,I3,3(3X,F7.3))
End Program g02qffe