Program f01zcfe
! F01ZCF Example Program Text
! Mark 25 Release. NAG Copyright 2014.
! .. Use Statements ..
Use nag_library, Only: f01zcf, nag_wp, x04caf
! .. Implicit None Statement ..
Implicit None
! .. Parameters ..
Integer, Parameter :: nin = 5, nout = 6
! .. Local Scalars ..
Integer :: i, ifail, kl, ku, lda, ldb, m, n
! .. Local Arrays ..
Real (Kind=nag_wp), Allocatable :: a(:,:), b(:,:)
! .. Executable Statements ..
Write (nout,*) 'F01ZCF Example Program Results'
! Skip heading in data file
Read (nin,*)
Write (nout,*)
Flush (nout)
Read (nin,*) m, n, kl, ku
lda = n
ldb = lda
Allocate (a(lda,n),b(ldb,n))
! Read a banded matrix of size m by n. kl is the number of
! sub-diagonals, ku the number of super-diagonals.
Do i = 1, n
Read (nin,*) a(i,1:n)
End Do
! Clear the packed matrix array B, so that no elements are
! unassigned when we print B later.
b(1:(kl+ku+1),1:n) = 0.0E+0_nag_wp
! ifail: behaviour on error exit
! =0 for hard exit, =1 for quiet-soft, =-1 for noisy-soft
ifail = 0
! Print the unpacked matrix
Call x04caf('G','X',n,n,a,lda,'Unpacked Matrix A:',ifail)
Write (nout,*)
Flush (nout)
! Convert to packed matrix form
ifail = 0
Call f01zcf('Pack',m,n,kl,ku,a,lda,b,ldb,ifail)
! Print the packed matrix
ifail = 0
Call x04caf('G','X',kl+ku+1,n,b,ldb,'Packed Matrix B:',ifail)
End Program f01zcfe