Program f16ubfe
! F16UBF Example Program Text
! Mark 29.2 Release. NAG Copyright 2023.
! .. Use Statements ..
Use nag_library, Only: f01zdf, f16ubf, nag_frobenius_norm, nag_inf_norm, &
nag_max_norm, nag_one_norm, nag_wp
! .. Implicit None Statement ..
Implicit None
! .. Parameters ..
Integer, Parameter :: nin = 5, nout = 6
! .. Local Scalars ..
Real (Kind=nag_wp) :: r_fro, r_inf, r_max, r_one
Integer :: i, ifail, j, kl, ku, lda, ldab, m, n
Character (1) :: job
! .. Local Arrays ..
Complex (Kind=nag_wp), Allocatable :: a(:,:), ab(:,:)
! .. Intrinsic Procedures ..
Intrinsic :: max, min
! .. Executable Statements ..
Write (nout,*) 'F16UBF Example Program Results'
! Skip heading in data file
Read (nin,*)
Read (nin,*) m, n, kl, ku
lda = m
ldab = kl + ku + 1
Allocate (a(lda,n),ab(ldab,n))
! Read A from data file into rectangular storage
Do i = 1, m
Read (nin,*)(a(i,j),j=max(1,i-kl),min(n,i+ku))
End Do
! Convert A to packed storage
job = 'P'
ifail = 0
Call f01zdf(job,m,n,kl,ku,a,lda,ab,ldab,ifail)
Write (nout,*)
Write (nout,99999) 'Norms of banded matrix AB:'
Write (nout,*)
r_one = f16ubf(nag_one_norm,m,n,kl,ku,ab,ldab)
Write (nout,99998) 'One norm = ', r_one
r_inf = f16ubf(nag_inf_norm,m,n,kl,ku,ab,ldab)
Write (nout,99998) 'Infinity norm = ', r_inf
r_fro = f16ubf(nag_frobenius_norm,m,n,kl,ku,ab,ldab)
Write (nout,99998) 'Frobenius norm = ', r_fro
r_max = f16ubf(nag_max_norm,m,n,kl,ku,ab,ldab)
Write (nout,99998) 'Maximum norm = ', r_max
99999 Format (1X,A)
99998 Format (1X,A,F9.4)
End Program f16ubfe