PROGRAM f04ajfe

!      F04AJF Example Program Text

!      Mark 23 Release. NAG Copyright 2011.

!      .. Use Statements ..
       USE nag_library, ONLY : f03aff, f04ajf, nag_wp
!      .. Implicit None Statement ..
       IMPLICIT NONE
!      .. Parameters ..
       INTEGER, PARAMETER              :: nin = 5, nout = 6
!      .. Local Scalars ..
       REAL (KIND=nag_wp)              :: d1, eps
       INTEGER                         :: i, id, ifail, ir, lda, ldb, n
!      .. Local Arrays ..
       REAL (KIND=nag_wp), ALLOCATABLE :: a(:,:), b(:,:), p(:)
!      .. Executable Statements ..
       WRITE (nout,*) 'F04AJF Example Program Results'
       WRITE (nout,*)
!      Skip heading in data file
       READ (nin,*)
       READ (nin,*) n
       ir = 1
       lda = n
       ldb = n
       ALLOCATE (a(lda,n),b(ldb,ir),p(n))
       READ (nin,*) (a(i,1:n),i=1,n)

!      ifail: behaviour on error exit
!             =0 for hard exit, =1 for quiet-soft, =-1 for noisy-soft
       ifail = 0
!      Crout decomposition
       CALL f03aff(n,eps,a,lda,d1,id,p,ifail)

       READ (nin,*) (b(i,1:ir),i=1,n)

!      Approximate solution of linear equations
       CALL f04ajf(n,ir,a,lda,p,b,ldb)

       WRITE (nout,*) ' Solution'
       DO i = 1, n
          WRITE (nout,99999) b(i,1:ir)
       END DO

99999  FORMAT (1X,8F9.4)
    END PROGRAM f04ajfe