PROGRAM f11mefe

!      F11MEF Example Program Text

!      Mark 23 Release. NAG Copyright 2011.

!      .. Use Statements ..
       USE nag_library, ONLY : f11mdf, f11mef, nag_wp, x04cbf
!      .. Implicit None Statement ..
       IMPLICIT NONE
!      .. Parameters ..
       REAL (KIND=nag_wp), PARAMETER   :: one = 1.E0_nag_wp
       INTEGER, PARAMETER              :: nin = 5, nout = 6
!      .. Local Scalars ..
       REAL (KIND=nag_wp)              :: flop, thresh
       INTEGER                         :: i, ifail, n, nnz, nnzl, nnzu, nzlmx, &
                                          nzlumx, nzumx
       CHARACTER (1)                   :: spec
!      .. Local Arrays ..
       REAL (KIND=nag_wp), ALLOCATABLE :: a(:), lval(:), uval(:)
       INTEGER, ALLOCATABLE            :: icolzp(:), il(:), iprm(:),           &
                                          irowix(:), iu(:)
       CHARACTER (1)                   :: clabs(1), rlabs(1)
!      .. Executable Statements ..
       WRITE (nout,*) 'F11MEF Example Program Results'
       FLUSH (nout)
!      Skip heading in data file
       READ (nin,*)

!      Read order of matrix

       READ (nin,*) n

       ALLOCATE (icolzp(n+1),iprm(7*n))

!      Read the matrix A

       READ (nin,*) icolzp(1:n+1)
       nnz = icolzp(n+1) - 1

       ALLOCATE (a(nnz),lval(8*nnz),uval(8*nnz),il(7*n+8*nnz+4),irowix(nnz), &
          iu(2*n+8*nnz+1))

       DO i = 1, nnz
          READ (nin,*) a(i), irowix(i)
       END DO

!      Calculate COLAMD permutation

       spec = 'M'

!      ifail: behaviour on error exit
!             =0 for hard exit, =1 for quiet-soft, =-1 for noisy-soft
       ifail = 0
       CALL f11mdf(spec,n,icolzp,irowix,iprm,ifail)

!      Factorise

       thresh = one
       ifail = 0
       nzlmx = 8*nnz
       nzlumx = 8*nnz
       nzumx = 8*nnz
       CALL f11mef(n,irowix,a,iprm,thresh,nzlmx,nzlumx,nzumx,il,lval,iu,uval, &
          nnzl,nnzu,flop,ifail)

!      Output results

       WRITE (nout,99999)
       WRITE (nout,99998) nnzl + nnzu - n
       FLUSH (nout)

       CALL x04cbf('G','X',1,10,lval,1,'F7.2','Factor elements in LVAL','N', &
          rlabs,'N',clabs,80,0,ifail)
       CALL x04cbf('G','X',1,4,uval,1,'F7.2','Factor elements in UVAL','N', &
          rlabs,'N',clabs,80,0,ifail)

99999  FORMAT (1X/1X,'Number of nonzeros in factors (excluding unit', &
          ' diagonal)')
99998  FORMAT (1X,I8)
    END PROGRAM f11mefe