Example description
    Program g08ckfe

!     G08CKF Example Program Text
!     Mark 26.2 Release. NAG Copyright 2017.

!     .. Use Statements ..
      Use nag_library, Only: g08ckf, nag_wp
!     .. Implicit None Statement ..
      Implicit None
!     .. Parameters ..
      Integer, Parameter               :: nin = 5, nout = 6
!     .. Local Scalars ..
      Real (Kind=nag_wp)               :: a2, aa2, p, ybar, yvar
      Integer                          :: i, ifail, n
      Logical                          :: issort
!     .. Local Arrays ..
      Real (Kind=nag_wp), Allocatable  :: y(:)
!     .. Executable Statements ..
      Write (nout,*) 'G08CKF Example Program Results'
      Write (nout,*)

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

!     Read number of observations
      Read (nin,*) n

!     Memory allocation
      Allocate (y(n))

!     Read observations
      Read (nin,*)(y(i),i=1,n)

!     Let g08ckf sort the data
      issort = .False.

!     Calculate A-squared and probability
      ifail = 0
      Call g08ckf(n,issort,y,ybar,yvar,a2,aa2,p,ifail)

!     Results
      Write (nout,'(1X,A,E11.4,1X,A,E11.4)')                                   &
        'H0: data from Normal distribution with mean', ybar, 'and variance',   &
        yvar
      Write (nout,'(1X,A,1X,F8.4)') 'Test statistic, A-squared: ', a2
      Write (nout,'(1X,A,1X,F8.4)') 'Adjusted A-squared:        ', aa2
      Write (nout,'(1X,A,1X,F8.4)') 'Upper tail probability:    ', p

    End Program g08ckfe