Program g08cjfe

!     G08CJF Example Program Text
!     Mark 26.1 Release. NAG Copyright 2016.

!     .. Use Statements ..
      Use nag_library, Only: g08cjf, nag_wp
!     .. Implicit None Statement ..
      Implicit None
!     .. Parameters ..
      Integer, Parameter               :: nin = 5, nout = 6
!     .. Local Scalars ..
      Real (Kind=nag_wp)               :: a2, mu, p
      Integer                          :: i, ifail, n
      Logical                          :: issort
!     .. Local Arrays ..
      Real (Kind=nag_wp), Allocatable  :: x(:), y(:)
!     .. Intrinsic Procedures ..
      Intrinsic                        :: exp
!     .. Executable Statements ..
      Write (nout,*) 'G08CJF Example Program Results'
      Write (nout,*)

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

!     Read number of observations and parameter value
      Read (nin,*) n, mu

!     Memory allocation
      Allocate (x(n),y(n))

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

!     PIT
      Do i = 1, n
        y(i) = 1.0E0_nag_wp - exp(-x(i)/mu)
      End Do

!     Let g08cjf sort the uniform variates
      issort = .False.

!     Calculate A-squared and probability
      ifail = 0
      Call g08cjf(n,issort,y,a2,p,ifail)

!     Results
      Write (nout,'(1X,A,E11.4)')                                              &
        'H0: data from exponential distribution with mean', mu
      Write (nout,'(1X,A,1X,F8.4)') 'Test statistic, A-squared: ', a2
      Write (nout,'(1X,A,1X,F8.4)') 'Upper tail probability:    ', p

    End Program g08cjfe