Program f01vefe
! F01VEF Example Program Text
! Mark 25 Release. NAG Copyright 2014.
! .. Use Statements ..
Use nag_library, Only: dtrttf, nag_wp, x04cbf
! .. Implicit None Statement ..
Implicit None
! .. Parameters ..
Integer, Parameter :: inc1 = 1, indent = 0, ncols = 80, &
nin = 5, nout = 6
Character (1), Parameter :: diag = 'N', intlabel = 'I', matrix = &
'G', nolabel = 'N'
Character (4), Parameter :: form = 'F5.2'
! .. Local Scalars ..
Integer :: i, ifail, info, k, lar1, lar2, lda, &
lenar, n, q
Character (47) :: title
Character (1) :: transr, uplo
! .. Local Arrays ..
Real (Kind=nag_wp), Allocatable :: a(:,:), ar(:)
Character (1) :: clabs(1), rlabs(1)
! .. Executable Statements ..
Write (nout,*) 'F01VEF Example Program Results'
! Skip heading in data file
Read (nin,*)
Write (nout,*)
Flush (nout)
Read (nin,*) n, uplo, transr
lda = n
lenar = n*(n+1)/2
Allocate (a(lda,n),ar(lenar))
! Read a triangular matrix of order n into array A
Do i = 1, n
Read (nin,*) a(i,i:n)
End Do
! Print the unpacked array A
title = 'Unpacked Matrix A:'
ifail = 0
Call x04cbf(uplo,diag,n,n,a,lda,form,title,intlabel,rlabs,intlabel, &
clabs,ncols,indent,ifail)
Write (nout,*)
Flush (nout)
! Convert to Rectangular Full Packed form
info = 0
! The NAG name equivalent of dtrttf is f01vef
Call dtrttf(transr,uplo,n,a,lda,ar,info)
! Print the Rectangular Full Packed array
title = 'RFP Packed Array AR:'
ifail = 0
Call x04cbf(matrix,diag,lenar,inc1,ar,lenar,form,title,intlabel,rlabs, &
nolabel,clabs,ncols,indent,ifail)
Write (nout,*)
Flush (nout)
! Print the Rectangular Full Packed array showing how the elements are
! arranged.
title = 'RFP Packed Array AR (graphical representation):'
k = n/2
q = n - k
If (transr=='N' .Or. transr=='n') Then
lar1 = 2*k + 1
lar2 = q
Else
lar1 = q
lar2 = 2*k + 1
End If
ifail = 0
Call x04cbf(matrix,diag,lar1,lar2,ar,lar1,form,title,intlabel,rlabs, &
intlabel,clabs,ncols,indent,ifail)
End Program f01vefe