NAG Library Manual, Mark 28.5
Interfaces:  FL   CL   CPP   AD 

NAG FL Interface Introduction
Example description
    Program g01hbfe

!     G01HBF Example Program Text

!     Mark 28.5 Release. NAG Copyright 2022.

!     .. Use Statements ..
      Use nag_library, Only: g01hbf, nag_wp
!     .. Implicit None Statement ..
      Implicit None
!     .. Parameters ..
      Integer, Parameter               :: nin = 5, nout = 6
!     .. Local Scalars ..
      Real (Kind=nag_wp)               :: prob, tol
      Integer                          :: i, ifail, ldsig, lwk, n
      Character (1)                    :: tail
!     .. Local Arrays ..
      Real (Kind=nag_wp), Allocatable  :: a(:), b(:), sig(:,:), wk(:), xmu(:)
!     .. Intrinsic Procedures ..
      Intrinsic                        :: max
!     .. Executable Statements ..
      Write (nout,*) 'G01HBF Example Program Results'
      Write (nout,*)

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

!     Read in the problem size
      Read (nin,*) n, tol, tail

!     Use more workspace, unless N is very large
!     as LWK also defines the number of sub-intervals
      lwk = max(2000,4*n)

      ldsig = n
      Allocate (a(n),b(n),xmu(n),sig(ldsig,n),wk(lwk))

!     Read in the means
      Read (nin,*) xmu(1:n)

!     Read in the variance covariance matrix
      Read (nin,*)(sig(i,1:n),i=1,n)

!     Read in bounds
      If (tail=='C' .Or. tail=='c' .Or. tail=='U' .Or. tail=='u') Then
        Read (nin,*) a(1:n)
      End If
      If (tail=='C' .Or. tail=='c' .Or. tail=='L' .Or. tail=='l') Then
        Read (nin,*) b(1:n)
      End If

!     Calculate probability
      ifail = -1
      prob = g01hbf(tail,n,a,b,xmu,sig,ldsig,tol,wk,lwk,ifail)
      If (ifail/=0) Then
        If (ifail<=3) Then
          Go To 100
        End If
      End If

!     Display results
      Write (nout,99999) 'Multivariate Normal probability =', prob

100   Continue

99999 Format (1X,A,F7.4)
    End Program g01hbfe