Example description
    Program g02dffe

!     G02DFF Example Program Text

!     Mark 26.2 Release. NAG Copyright 2017.

!     .. Use Statements ..
      Use nag_library, Only: g02daf, g02ddf, g02dff, 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, indx, ip, irank, ldq, &
                                          ldx, lwk, lwt, m, n
      Logical                          :: svd
      Character (1)                    :: mean, weight
!     .. Local Arrays ..
      Real (Kind=nag_wp), Allocatable  :: b(:), cov(:), h(:), p(:), q(:,:),    &
                                          res(:), se(:), wk(:), wt(:), x(:,:), &
                                          y(:)
      Integer, Allocatable             :: isx(:)
!     .. Intrinsic Procedures ..
      Intrinsic                        :: max
!     .. Executable Statements ..
      Write (nout,*) 'G02DFF Example Program Results'
      Write (nout,*)

!     Skip heading in data file
      Read (nin,*)
      Read (nin,*) n, m, weight, mean

      If (weight=='W' .Or. weight=='w') Then
        lwt = n
      Else
        lwt = 0
      End If
      ldx = n
      Allocate (x(ldx,m),isx(m),y(n),wt(lwt))

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

!     Include all variables in the model
      isx(1:m) = 1
      ip = m
      If (mean=='M' .Or. mean=='m') Then
        ip = ip + 1
      End If

      lwk = max(5*(ip-1)+ip*ip,2*ip)
      ldq = n
      Allocate (b(ip),se(ip),cov(ip*(ip+1)/2),res(n),h(n),q(ldq,ip+1),p(2*ip+  &
        ip*ip),wk(lwk))

!     Use suggested value for tolerance
      tol = 0.000001E0_nag_wp

!     Fit general linear regression model
      ifail = 0
      Call g02daf(mean,weight,n,x,ldx,m,isx,ip,y,wt,rss,idf,b,se,cov,res,h,q,  &
        ldq,svd,irank,p,tol,wk,ifail)

!     Display results from G02DAF
      Write (nout,*) 'Results from full model'
      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,*)

!     Loop over list of variables to drop
u_lp: Do
        Read (nin,*,Iostat=ifail) indx
        If (ifail/=0) Then
          Exit u_lp
        End If

        If (ip<=0) Then
          Write (nout,*) 'No terms left in model'
          Exit u_lp
        End If

!       Drop variable INDX from the model
        ifail = 0
        Call g02dff(ip,q,ldq,indx,rss,wk,ifail)

        ip = ip - 1
        Write (nout,99998) 'Variable', indx, ' dropped'

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

!       Display the results for model with variable INDX dropped
        Write (nout,99999) 'Residual sum of squares = ', rss
        Write (nout,99998) 'Degrees of freedom = ', idf
        Write (nout,*)
        Write (nout,*) 'Parameter estimate   Standard error'
        Write (nout,*)
        Write (nout,99997)(b(i),se(i),i=1,ip)
      End Do u_lp

99999 Format (1X,A,E13.4)
99998 Format (1X,A,I4,A)
99997 Format (1X,E15.4,E20.4)
    End Program g02dffe