Program f11zpfe
! F11ZPF Example Program Text
! Mark 29.2 Release. NAG Copyright 2023.
! .. Use Statements ..
Use nag_library, Only: f11zpf, nag_wp
! .. Implicit None Statement ..
Implicit None
! .. Parameters ..
Integer, Parameter :: nin = 5, nout = 6
! .. Local Scalars ..
Integer :: i, ifail, n, nnz
Character (1) :: dup, zer
! .. Local Arrays ..
Complex (Kind=nag_wp), Allocatable :: a(:)
Integer, Allocatable :: icol(:), irow(:), istr(:), iwork(:)
! .. Executable Statements ..
Write (nout,*) 'F11ZPF Example Program Results'
! 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,99997) 'NNZ = ', nnz
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 f11zpf(n,nnz,a,irow,icol,dup,zer,istr,iwork,ifail)
! Output results
Write (nout,*) 'Reordered elements'
Write (nout,99999) 'NNZ = ', nnz
Do i = 1, nnz
Write (nout,99998) i, a(i), irow(i), icol(i)
End Do
99999 Format (1X,A,I4)
99998 Format (I8,5X,'(',E16.4,',',E16.4,')',2I8)
99997 Format (1X,A,I16)
End Program f11zpfe