Program f11jbfe
! F11JBF Example Program Text
! Mark 29.3 Release. NAG Copyright 2023.
! .. Use Statements ..
Use nag_library, Only: f11jaf, f11jbf, nag_wp
! .. Implicit None Statement ..
Implicit None
! .. Parameters ..
Integer, Parameter :: nin = 5, nout = 6
! .. Local Scalars ..
Real (Kind=nag_wp) :: dscale, dtol
Integer :: i, ifail, la, lfill, liwork, n, nnz, &
nnzc, npivm
Character (1) :: check, mic, pstrat
! .. Local Arrays ..
Real (Kind=nag_wp), Allocatable :: a(:), x(:), y(:)
Integer, Allocatable :: icol(:), ipiv(:), irow(:), istr(:), &
iwork(:), perm_fwd(:), perm_inv(:)
! .. Executable Statements ..
Write (nout,*) 'F11JBF 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
la = 3*nnz
liwork = 2*la + 7*n + 1
Allocate (a(la),x(n),y(n),icol(la),ipiv(n),irow(la),istr(n+1), &
iwork(liwork),perm_fwd(n),perm_inv(n))
! Read the matrix A
Do i = 1, nnz
Read (nin,*) a(i), irow(i), icol(i)
End Do
! Read the vector y
Read (nin,*) y(1:n)
! Calculate Cholesky factorization
lfill = -1
dtol = 0.0E0_nag_wp
mic = 'N'
dscale = 0.0E0_nag_wp
pstrat = 'M'
! ifail: behaviour on error exit
! =0 for hard exit, =1 for quiet-soft, =-1 for noisy-soft
ifail = 0
Call f11jaf(n,nnz,a,la,irow,icol,lfill,dtol,mic,dscale,pstrat,ipiv,istr, &
nnzc,npivm,iwork,liwork,ifail)
! Check the output value of NPIVM
If (npivm/=0) Then
Write (nout,99998) 'Factorization is not complete', npivm
Else
! Solve P L D L^T P^T x = y
check = 'C'
ifail = 0
Call f11jbf(n,a,la,irow,icol,ipiv,istr,check,y,x,ifail)
! Output results
Write (nout,*) ' Solution of linear system'
Write (nout,99999) x(1:n)
End If
! Compute reverse Cuthill-McKee permutation for bandwidth reduction
Call do_rcm(irow,icol,a,y,istr,perm_fwd,perm_inv,iwork)
ifail = 0
Call f11jaf(n,nnz,a,la,irow,icol,lfill,dtol,mic,dscale,pstrat,ipiv,istr, &
nnzc,npivm,iwork,liwork,ifail)
! Check the output value of NPIVM
If (npivm/=0) Then
Write (nout,99998) 'Factorization is not complete', npivm
Else
! Solve P L D L^T P^T x = y
ifail = 0
Call f11jbf(n,a,la,irow,icol,ipiv,istr,check,y,x,ifail)
! Output results
Write (nout,*) ' Solution of linear system with Reverse Cuthill-McKee'
Write (nout,99999)(x(perm_inv(i)),i=1,n)
End If
99999 Format (1X,E16.4)
99998 Format (1X,A,I20)
Contains
Subroutine do_rcm(irow,icol,a,y,istr,perm_fwd,perm_inv,iwork)
! .. Use Statements ..
Use nag_library, Only: f11yef, f11zaf, f11zbf
! .. Parameters ..
Logical, Parameter :: lopts(5) = (/.False.,.False.,.True., &
.True.,.True./)
! .. Array Arguments ..
Real (Kind=nag_wp), Intent (Inout) :: a(la), y(n)
Integer, Intent (Inout) :: icol(la), irow(la), istr(n+1), &
iwork(*)
Integer, Intent (Out) :: perm_fwd(n), perm_inv(n)
! .. Local Scalars ..
Integer :: i, ifail, j, nnz_cs, nnz_scs
! .. Local Arrays ..
Real (Kind=nag_wp), Allocatable :: rwork(:)
Integer :: info(4), mask(1)
! .. Intrinsic Procedures ..
Intrinsic :: size
! .. Executable Statements ..
! SCS to CS, must add the upper triangle entries.
j = nnz + 1
Do i = 1, nnz
If (irow(i)>icol(i)) Then
! strictly lower triangle, add the transposed
a(j) = a(i)
irow(j) = icol(i)
icol(j) = irow(i)
j = j + 1
End If
End Do
nnz_cs = j - 1
! Reorder, CS to CCS, icolzp in istr
ifail = 0
Call f11zaf(n,nnz_cs,a,icol,irow,'F','F',istr,iwork,ifail)
! Calculate reverse Cuthill-McKee
ifail = 0
Call f11yef(n,nnz_cs,istr,irow,lopts,mask,perm_fwd,info,ifail)
! compute inverse perm, in perm_inv(1:n)
Do i = 1, n
perm_inv(perm_fwd(i)) = i
End Do
! Apply permutation on column/row indices
icol(1:nnz_cs) = perm_inv(icol(1:nnz_cs))
irow(1:nnz_cs) = perm_inv(irow(1:nnz_cs))
! restrict to lower triangle, SCS format
! copying entries upwards
j = 1
Do i = 1, nnz_cs
If (irow(i)>=icol(i)) Then
! non-upper triangle, bubble up
a(j) = a(i)
icol(j) = icol(i)
irow(j) = irow(i)
j = j + 1
End If
End Do
nnz_scs = j - 1
! sort
ifail = 0
Call f11zbf(n,nnz_scs,a,irow,icol,'S','K',istr,iwork,ifail)
! permute rhs vector
Allocate (rwork(size(perm_fwd)))
rwork(:) = y(perm_fwd(:))
y(:) = rwork(:)
Deallocate (rwork)
End Subroutine do_rcm
End Program f11jbfe