Program g01hcfe
! G01HCF Example Program Text
! Mark 29.3 Release. NAG Copyright 2023.
! .. Use Statements ..
Use nag_library, Only: g01hcf, nag_wp
! .. Implicit None Statement ..
Implicit None
! .. Parameters ..
Integer, Parameter :: nin = 5, nout = 6
! .. Local Scalars ..
Real (Kind=nag_wp) :: prob, rho
Integer :: df, ierr, ifail
Character (1) :: tail
! .. Local Arrays ..
Real (Kind=nag_wp) :: a(2), b(2)
! .. Executable Statements ..
Write (nout,*) 'G01HCF Example Program Results'
Write (nout,*)
! Skip heading in data file
Read (nin,*)
! Display titles
Write (nout,*) &
' A(1) B(1) A(2) B(2) DF RHO TAIL P'
Write (nout,*)
d_lp: Do
ierr = 0
a(1:2) = 0.0_nag_wp
b(1:2) = 0.0_nag_wp
Read (nin,Fmt='(a1)',Advance='no',Iostat=ierr) tail
! Read parameter values
Select Case (tail)
Case ('l','L')
Read (nin,*,Iostat=ierr) df, rho, b(1), b(2)
Case ('c','C')
Read (nin,*,Iostat=ierr) df, rho, a(1), b(1), a(2), b(2)
Case ('u','U')
Read (nin,*,Iostat=ierr) df, rho, a(1), a(2)
Case Default
Write (nout,*) 'Invalid problem specification in data file'
Exit d_lp
End Select
If (ierr/=0) Then
Exit d_lp
End If
! Calculate probability
ifail = 0
prob = g01hcf(tail,a,b,df,rho,ifail)
! Display results
Select Case (tail)
Case ('l','L')
Write (nout,99999,Advance='no') '-Inf', b(1), '-Inf', b(2)
Case ('u','U')
Write (nout,99998,Advance='no') a(1), 'Inf', a(2), 'Inf'
Case ('c','C')
Write (nout,99997,Advance='no') a(1), b(1), a(2), b(2)
End Select
Write (nout,99996) df, rho, tail, prob
End Do d_lp
99999 Format (1X,2(A4,8X,E11.4,1X))
99998 Format (1X,2(E11.4,2X,A3,8X))
99997 Format (1X,4(E11.4,1X))
99996 Format (I3,1X,F7.4,2X,A1,2X,F8.4)
End Program g01hcfe