Program f01vkfe
! F01VKF Example Program Text
! Mark 25 Release. NAG Copyright 2014.
! .. Use Statements ..
Use nag_library, Only: nag_wp, x04dbf, ztpttf
! .. 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 :: ifail, info, k, lar1, lar2, lenap, &
lenar, n, q
Character (47) :: title
Character (1) :: transr, uplo
! .. Local Arrays ..
Complex (Kind=nag_wp), Allocatable :: ap(:), ar(:)
Character (1) :: clabs(1), rlabs(1)
! .. Executable Statements ..
Write (nout,*) 'F01VKF Example Program Results'
! Skip heading in data file
Read (nin,*)
Write (nout,*)
Flush (nout)
Read (nin,*) n, uplo, transr
lenap = (n*(n+1))/2
lenar = lenap
Allocate (ap(lenap),ar(lenar))
! Read an order n matrix packed into a 1-D array
Read (nin,*) ap
! Print the packed vector
title = 'Packed Array 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 Rectangular Full Packed form
info = 0
! The NAG name equivalent of ztpttf is f01vkf
Call ztpttf(transr,uplo,n,ap,ar,info)
! Print the Rectangular Full Packed array
title = 'RFP Packed Array AR:'
ifail = 0
Call x04dbf(matrix,diag,lenar,inc1,ar,lenar,brac,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 x04dbf(matrix,diag,lar1,lar2,ar,lar1,brac,form,title,intlabel, &
rlabs,intlabel,clabs,ncols,indent,ifail)
End Program f01vkfe