Program x04cdfe
! X04CDF Example Program Text
! Mark 26.1 Release. NAG Copyright 2016.
! .. Use Statements ..
Use nag_library, Only: dtrttp, nag_wp, x04cdf
! .. 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, info, j, lda, &
ncols
Character (1) :: uplo
! .. Local Arrays ..
Real (Kind=nag_wp), Allocatable :: a(:,:), ap(:)
! .. Intrinsic Procedures ..
Intrinsic :: real
! .. Executable Statements ..
Write (nout,*) 'X04CDF Example Program Results'
Write (nout,*)
Flush (nout)
! Generate a full-format symmetric array of data
lda = n
Allocate (a(lda,n))
Do j = 1, n
Do i = 1, j
a(i,j) = real(10*i+j,kind=nag_wp)
a(j,i) = a(i,j)
End Do
End Do
ncols = 80
indent = 0
! Print order (n-1) lower triangular matrix with default format and
! integer row and column labels
! Convert a to packed storage.
Allocate (ap(n*(n+1)/2))
! The lower triangle.
uplo = 'L'
! The NAG name equivalent of dtrttp is f01vaf
Call dtrttp(uplo,n-1,a,lda,ap,info)
If (info/=0) Then
Write (nout,99999) 'Failure in DTRTTP. INFO =', info
Go To 100
End If
ifail = 0
Call x04cdf('Lower','Non-unit',n-1,ap,' ','Example 1:','Integer',rlabs, &
'Integer',clabs,ncols,indent,ifail)
Write (nout,*)
Flush (nout)
! Print order n upper triangular matrix with user-supplied format
! and row and column labels
! Convert the upper triangle of a to packed storage.
uplo = 'U'
! The NAG name equivalent of dtrttp is f01vaf
Call dtrttp(uplo,n,a,lda,ap,info)
If (info/=0) Then
Write (nout,99999) 'Failure in DTRTTP. INFO =', info
Go To 100
End If
ifail = 0
Call x04cdf('Upper','Unit',n,ap,'F8.2','Example 2:','Character',rlabs, &
'Character',clabs,ncols,indent,ifail)
Write (nout,*)
Flush (nout)
! Print order n upper triangular matrix in MATLAB format
! Row and column labelling is ignored
ifail = 0
Call x04cdf('Upper','Non-unit',n,ap,'MATLABF8.2','A',' ',rlabs,' ', &
clabs,ncols,indent,ifail)
100 Continue
99999 Format (1X,A,I4)
End Program x04cdfe