Program g08bafe
! G08BAF Example Program Text
! Mark 26.2 Release. NAG Copyright 2017.
! .. Use Statements ..
Use nag_library, Only: g08baf, nag_wp
! .. Implicit None Statement ..
Implicit None
! .. Parameters ..
Integer, Parameter :: nin = 5, nout = 6
! .. Local Scalars ..
Real (Kind=nag_wp) :: pv, pw, v, w
Integer :: ifail, itest, n, n1
! .. Local Arrays ..
Real (Kind=nag_wp), Allocatable :: r(:), x(:)
! .. Executable Statements ..
Write (nout,*) 'G08BAF Example Program Results'
Write (nout,*)
! Skip heading in data file
Read (nin,*)
! Read in problem size and type of test
Read (nin,*) n, n1, itest
Allocate (x(n),r(n))
! Read in data
Read (nin,*) x(1:n)
! Display title
Write (nout,*) 'Mood''s test and David''s test'
Write (nout,*)
! Display input data
Write (nout,*) 'Data values'
Write (nout,*)
Write (nout,*) 'Group 1 '
Write (nout,99999) x(1:n1)
Write (nout,*)
Write (nout,*) 'Group 2 '
Write (nout,99999) x((n1+1):n)
! Perform test
ifail = 0
Call g08baf(x,n,n1,r,itest,w,v,pw,pv,ifail)
! Display results
Write (nout,*)
Write (nout,99998) ' Mood''s measure = ', w, ' Significance = ', &
pw
Write (nout,99998) ' David''s measure = ', v, ' Significance = ', &
pv
99999 Format (1X,8F4.0)
99998 Format (1X,A,F8.3,A,F8.4)
End Program g08bafe