Program f01vdfe
! F01VDF Example Program Text
! Mark 25 Release. NAG Copyright 2014.
! .. Use Statements ..
Use nag_library, Only: nag_wp, x04dbf, ztpttr
! .. Implicit None Statement ..
Implicit None
! .. Parameters ..
Integer, Parameter :: inc1 = 1, indent = 0, ncols = 80, &
nin = 5, nout = 6
Character (1), Parameter :: brac = 'B', diag = 'N', intlabel = &
'I', matrix = 'G', nolabel = 'N'
Character (4), Parameter :: form = 'F5.2'
! .. Local Scalars ..
Integer :: i, ifail, info, lda, lenap, n
Character (18) :: title
Character (1) :: uplo
! .. Local Arrays ..
Complex (Kind=nag_wp), Allocatable :: a(:,:), ap(:)
Character (1) :: clabs(1), rlabs(1)
! .. Executable Statements ..
Write (nout,*) 'F01VDF Example Program Results'
! Skip heading in data file
Read (nin,*)
Write (nout,*)
Flush (nout)
Read (nin,*) n, uplo
lda = n
lenap = (n*(n+1))/2
Allocate (a(lda,n),ap(lenap))
! Read a packed vector of order n
Do i = 1, lenap
Read (nin,*) ap(i)
End Do
! Print the packed vector
title = 'Packed Matrix AP: '
ifail = 0
Call x04dbf(matrix,diag,lenap,inc1,ap,lenap,brac,form,title,intlabel, &
rlabs,nolabel,clabs,ncols,indent,ifail)
Write (nout,*)
Flush (nout)
! Convert to triangular form
info = 0
! The NAG name equivalent of ztpttr is f01vdf
Call ztpttr(uplo,n,ap,a,lda,info)
! Print the unpacked matrix
title = 'Unpacked Matrix A:'
ifail = 0
Call x04dbf(uplo,diag,n,n,a,lda,brac,form,title,intlabel,rlabs,intlabel, &
clabs,ncols,indent,ifail)
End Program f01vdfe