Program g02ddfe

!     G02DDF Example Program Text

!     Mark 26.1 Release. NAG Copyright 2016.

!     .. Use Statements ..
      Use nag_library, Only: g02ddf, g02def, nag_wp
!     .. Implicit None Statement ..
      Implicit None
!     .. Parameters ..
      Integer, Parameter               :: nin = 5, nout = 6
!     .. Local Scalars ..
      Real (Kind=nag_wp)               :: rss, tol
      Integer                          :: i, idf, ifail, ip, irank, ldq, lwt,  &
                                          m, n
      Logical                          :: svd
      Character (1)                    :: weight
!     .. Local Arrays ..
      Real (Kind=nag_wp), Allocatable  :: b(:), cov(:), p(:), q(:,:), se(:),   &
                                          wk(:), wt(:), x(:,:)
!     .. Executable Statements ..
      Write (nout,*) 'G02DDF Example Program Results'
      Write (nout,*)

!     Skip heading in data file
      Read (nin,*)

!     Read in the problem size
      Read (nin,*) n, m, weight

      If (weight=='W' .Or. weight=='w') Then
        lwt = n
      Else
        lwt = 0
      End If
      ldq = n
      Allocate (b(m),cov(m*(m+1)/2),p(m*(m+2)),q(ldq,m+1),se(m),wk(m*m+5*m),wt &
        (n),x(n,m))

!     Read in data
      If (lwt>0) Then
        Read (nin,*)(x(i,1:m),q(i,1),wt(i),i=1,n)
      Else
        Read (nin,*)(x(i,1:m),q(i,1),i=1,n)
      End If

!     Use suggested value for tolerance
      tol = 0.000001E0_nag_wp

!     Fit general linear regression model, adding each variable in turn
      ip = 0
      Do i = 1, m
        ifail = -1
        Call g02def(weight,n,ip,q,ldq,p,wt,x(1,i),rss,tol,ifail)
        If (ifail==0) Then
          ip = ip + 1
        Else If (ifail==3) Then
          Write (nout,99996) ' * Variable ', ip,                               &
            ' is linear combination of previous columns'
          Write (nout,99996) '   so it has not been added'
        Else
          Go To 100
        End If
      End Do

!     Get G02DDF to calculate RSS
      rss = 0.0E0_nag_wp

!     Calculate parameter estimates, RSS etc
      ifail = 0
      Call g02ddf(n,ip,q,ldq,rss,idf,b,se,cov,svd,irank,p,tol,wk,ifail)

!     Display results
      If (svd) Then
        Write (nout,*) 'Model not of full rank'
        Write (nout,*)
      End If
      Write (nout,99999) 'Residual sum of squares = ', rss
      Write (nout,99998) 'Degrees of freedom = ', idf
      Write (nout,*)
      Write (nout,*) 'Variable   Parameter estimate   Standard error'
      Write (nout,*)
      Write (nout,99997)(i,b(i),se(i),i=1,ip)

100   Continue

99999 Format (1X,A,E12.4)
99998 Format (1X,A,I4)
99997 Format (1X,I6,2E20.4)
99996 Format (1X,A,I0,A)
    End Program g02ddfe