Program f11zafe
! F11ZAF Example Program Text
! Mark 26.1 Release. NAG Copyright 2016.
! .. Use Statements ..
Use nag_library, Only: f11mlf, f11zaf, nag_wp
! .. Implicit None Statement ..
Implicit None
! .. Parameters ..
Integer, Parameter :: nin = 5, nout = 6
! .. Local Scalars ..
Real (Kind=nag_wp) :: anorm
Integer :: i, ifail, n, nnz
Character (1) :: dup, norm, zer
! .. Local Arrays ..
Real (Kind=nag_wp), Allocatable :: a(:)
Integer, Allocatable :: icol(:), irow(:), istr(:), iwork(:)
! .. Executable Statements ..
Write (nout,*) 'F11ZAF Example Program Results'
Write (nout,*)
! Skip heading in data file
Read (nin,*)
! Read order of matrix and number of nonzero entries
Read (nin,*) n
Read (nin,*) nnz
Allocate (a(nnz),icol(nnz),irow(nnz),istr(n+1),iwork(n))
! Read and output the original nonzero elements
Do i = 1, nnz
Read (nin,*) a(i), irow(i), icol(i)
End Do
Write (nout,*) 'Original elements'
Write (nout,99999) nnz
Write (nout,99997)
Do i = 1, nnz
Write (nout,99998) i, a(i), irow(i), icol(i)
End Do
! Reorder, sum duplicates and remove zeros
dup = 'S'
zer = 'R'
! ifail: behaviour on error exit
! =0 for hard exit, =1 for quiet-soft, =-1 for noisy-soft
ifail = 0
Call f11zaf(n,nnz,a,irow,icol,dup,zer,istr,iwork,ifail)
! Output results
Write (nout,*) 'Reordered elements, along rows first'
Write (nout,99999) nnz
Do i = 1, nnz
Write (nout,99998) i, a(i), irow(i), icol(i)
End Do
! Reorder down columns, fail on duplicates or zeros.
! Creates CCS storage format as side-effect
dup = 'F'
zer = 'F'
ifail = 0
Call f11zaf(n,nnz,a,icol,irow,dup,zer,istr,iwork,ifail)
! Output results
Write (nout,*) 'Reordered elements, along columns first'
Write (nout,99999) nnz
Do i = 1, nnz
Write (nout,99998) i, a(i), irow(i), icol(i)
End Do
Write (nout,99996)
Do i = 1, n + 1
Write (nout,99995) i, istr(i)
End Do
! Calculate 1-norm in Compressed Column Storage format
norm = '1'
Call f11mlf(norm,anorm,n,istr,irow,a,ifail)
! Output norm
Write (nout,99994) anorm
99999 Format (1X,'NNZ = ',I4)
99998 Format (1X,I8,1P,E16.4,2I8)
99997 Format (24X,'A',4X,'IROW',4X,'ICOL')
99996 Format (13X,'ISTR')
99995 Format (1X,2I8)
99994 Format (1X,'One norm ',1P,E16.4)
End Program f11zafe