Program f11mdfe
! F11MDF Example Program Text
! Mark 29.2 Release. NAG Copyright 2023.
! .. Use Statements ..
Use nag_library, Only: f11mdf
! .. Implicit None Statement ..
Implicit None
! .. Parameters ..
Integer, Parameter :: nin = 5, nout = 6
! .. Local Scalars ..
Integer :: ifail, n, nnz
Character (1) :: spec
! .. Local Arrays ..
Integer, Allocatable :: icolzp(:), iprm(:), irowix(:)
! .. Executable Statements ..
Write (nout,*) 'F11MDF Example Program Results'
! Skip heading in data file
Read (nin,*)
! Read order of matrix
Read (nin,*) n
Allocate (icolzp(n+1),iprm(7*n))
! Read the matrix
Read (nin,*) icolzp(1:n+1)
nnz = icolzp(n+1) - 1
Allocate (irowix(nnz))
Read (nin,*) irowix(1:nnz)
! 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)
! Output results
Write (nout,*)
Write (nout,*) 'COLAMD Permutation'
Write (nout,'(10I6)') iprm(n+1:2*n)
! Calculate user permutation
spec = 'U'
iprm(1) = 4
iprm(2) = 3
iprm(3) = 2
iprm(4) = 1
iprm(5) = 0
ifail = 0
Call f11mdf(spec,n,icolzp,irowix,iprm,ifail)
! Output results
Write (nout,*)
Write (nout,*) 'User Permutation'
Write (nout,'(10I6)') iprm(n+1:2*n)
! Calculate natural permutation
spec = 'N'
ifail = 0
Call f11mdf(spec,n,icolzp,irowix,iprm,ifail)
! Output results
Write (nout,*)
Write (nout,*) 'Natural Permutation'
Write (nout,'(10I6)') iprm(n+1:2*n)
End Program f11mdfe