Program g01dcfe

!     G01DCF Example Program Text

!     Mark 26.1 Release. NAG Copyright 2016.

!     .. Use Statements ..
      Use nag_library, Only: g01daf, g01dcf, nag_wp
!     .. Implicit None Statement ..
      Implicit None
!     .. Parameters ..
      Integer, Parameter               :: nout = 6
!     .. Local Scalars ..
      Real (Kind=nag_wp)               :: errest, etol, exp1, exp2, sumssq
      Integer                          :: i, ifail, iw, j, k, lvec, n
!     .. Local Arrays ..
      Real (Kind=nag_wp), Allocatable  :: pp(:), vec(:), work(:)
!     .. Executable Statements ..
      Write (nout,*) 'G01DCF Example Program Results'
      Write (nout,*)

!     Set the problem size
      n = 6
      etol = 0.0001E0_nag_wp

      lvec = n*(n+1)/2
      iw = 3*n/2
      Allocate (pp(n),work(iw),vec(lvec))

!     Compute normal scores
      ifail = 0
      Call g01daf(n,pp,etol,errest,work,iw,ifail)

      exp1 = pp(n)
      exp2 = pp(n-1)
      sumssq = 0.0E0_nag_wp
      Do i = 1, n
        sumssq = sumssq + pp(i)*pp(i)
      End Do

!     Compute approximate variance-covariance matrix
      ifail = 0
      Call g01dcf(n,exp1,exp2,sumssq,vec,ifail)

!     Display results
      Write (nout,99999) 'Sample size = ', n
      Write (nout,*) 'Variance-covariance matrix'
      k = 1
      Do j = 1, n
        Write (nout,99998) vec(k:(k+j-1))
        k = k + j
      End Do

99999 Format (1X,A,I2)
99998 Format (1X,6F8.4)
    End Program g01dcfe