Program x04cffe
! X04CFF Example Program Text
! Mark 29.2 Release. NAG Copyright 2023.
! .. Use Statements ..
Use nag_library, Only: f01zcf, nag_wp, x04cff
! .. Implicit None Statement ..
Implicit None
! .. Parameters ..
Integer, Parameter :: n = 5, nout = 6
Character (7), Parameter :: clabs(n) = (/'Un ','Deux ', &
'Trois ','Quatre ','Cinq '/)
Character (7), Parameter :: rlabs(n) = (/'Uno ','Due ', &
'Tre ','Quattro','Cinque '/)
! .. Local Scalars ..
Integer :: i, ifail, indent, j, kl, ku, ku_a, &
lda, ldab, m, ncols
Character (1) :: job
! .. Local Arrays ..
Real (Kind=nag_wp), Allocatable :: a(:,:), ab(:,:)
! .. Intrinsic Procedures ..
Intrinsic :: max, min, real
! .. Executable Statements ..
Write (nout,*) 'X04CFF Example Program Results'
Write (nout,*)
Flush (nout)
! Generate a square array of data.
m = n
kl = 1
ku_a = 2
lda = m
Allocate (a(lda,n))
Do j = 1, n
Do i = max(1,j-ku_a), min(m,j+kl)
a(i,j) = real(10*i+j,kind=nag_wp)
End Do
End Do
! Convert a to packed storage, ignoring the second superdiagonal.
ldab = kl + ku_a + 1
Allocate (ab(ldab,n))
ku = 1
job = 'P'
ifail = 0
Call f01zcf(job,m,n,kl,ku,a,lda,ab,ldab,ifail)
ncols = 80
indent = 0
! Print m by n band matrix with kl subdiagonals, 1 superdiagonal,
! default format and integer row and column labels
ifail = 0
Call x04cff(m,n,kl,ku,ab,ldab,' ','Example 1:','Integer',rlabs, &
'Integer',clabs,ncols,indent,ifail)
Write (nout,*)
Flush (nout)
! Convert the whole matrix a to packed storage.
ku = ku_a
job = 'P'
ifail = 0
Call f01zcf(job,m,n,kl,ku,a,lda,ab,ldab,ifail)
! Print m by n band matrix with kl subdiagonals, ku superdiagonals,
! user-supplied format and row and column labels
ifail = 0
Call x04cff(m,n,kl,ku,ab,ldab,'F8.2','Example 2:','Character',rlabs, &
'Character',clabs,ncols,indent,ifail)
Write (nout,*)
Flush (nout)
! Print m by n band matrix with kl subdiagonals, ku superdiagonals,
! in MATLAB format
! Row and column labelling is ignored
ifail = 0
Call x04cff(m,n,kl,ku,ab,ldab,'MATLABF8.2','A',' ',rlabs,' ',clabs, &
ncols,indent,ifail)
End Program x04cffe