Example description
    Program g02cbfe

!     G02CBF Example Program Text

!     Mark 26.2 Release. NAG Copyright 2017.

!     .. Use Statements ..
      Use nag_library, Only: g02cbf, nag_wp
!     .. Implicit None Statement ..
      Implicit None
!     .. Parameters ..
      Integer, Parameter               :: nin = 5, nout = 6
!     .. Local Scalars ..
      Integer                          :: i, ifail, n
!     .. Local Arrays ..
      Real (Kind=nag_wp)               :: reslt(20)
      Real (Kind=nag_wp), Allocatable  :: x(:), y(:)
!     .. Executable Statements ..
      Write (nout,*) 'G02CBF Example Program Results'
      Write (nout,*)

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

!     Read in problem size
      Read (nin,*) n

      Allocate (x(n),y(n))

!     Read in data
      Read (nin,*)(x(i),y(i),i=1,n)

!     Display data
      Write (nout,*) ' Case     Independent     Dependent'
      Write (nout,*) 'number     variable       variable'
      Write (nout,*)
      Write (nout,99999)(i,x(i),y(i),i=1,n)
      Write (nout,*)

!     Fit linear regression model
      ifail = 0
      Call g02cbf(n,x,y,reslt,ifail)

!     Display results
      Write (nout,99998) 'Mean of independent variable               = ',      &
        reslt(1)
      Write (nout,99998) 'Mean of   dependent variable               = ',      &
        reslt(2)
      Write (nout,99998) 'Standard deviation of independent variable = ',      &
        reslt(3)
      Write (nout,99998) 'Standard deviation of   dependent variable = ',      &
        reslt(4)
      Write (nout,99998) 'Correlation coefficient                    = ',      &
        reslt(5)
      Write (nout,*)
      Write (nout,99998) 'Regression coefficient                     = ',      &
        reslt(6)
      Write (nout,99998) 'Standard error of coefficient              = ',      &
        reslt(8)
      Write (nout,99998) 't-value for coefficient                    = ',      &
        reslt(10)
      Write (nout,*)
      Write (nout,*) 'Analysis of regression table :-'
      Write (nout,*)
      Write (nout,*)                                                           &
        '      Source        Sum of squares  D.F.    Mean square     F-value'
      Write (nout,*)
      Write (nout,99997) 'Due to regression', reslt(12:15)
      Write (nout,99997) 'About  regression', reslt(16:18)
      Write (nout,99997) 'Total            ', reslt(19:20)

99999 Format (1X,I4,2F15.4)
99998 Format (1X,A,F8.4)
99997 Format (1X,A,F14.4,F8.0,2F14.4)
    End Program g02cbfe