Example description
    Program f06wafe

!     F06WAF Example Program Text

!     Mark 26.2 Release. NAG Copyright 2017.

!     .. Use Statements ..
      Use nag_library, Only: dlansf, dtrttf, 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, info, lda, n
      Character (1)                    :: transr, uplo
!     .. Local Arrays ..
      Real (Kind=nag_wp), Allocatable  :: a(:,:), ar(:), work(:)
!     .. Executable Statements ..
      Write (nout,*) 'F06WAF Example Program Results'

!     Skip heading in data file
      Read (nin,*)

      Read (nin,*) n, uplo, transr

      lda = n
      Allocate (a(lda,n),ar((n*(n+1))/2),work(n))

!     Read upper or lower triangle of matrix A from data file

      If (uplo=='L' .Or. uplo=='l') Then
        Do i = 1, n
          Read (nin,*) a(i,1:i)
        End Do
      Else
        Do i = 1, n
          Read (nin,*) a(i,i:n)
        End Do
      End If

!     Convert A to rectangular full packed storage in ar

!     The NAG name equivalent of dtrttf is f01vef
      Call dtrttf(transr,uplo,n,a,lda,ar,info)

      Write (nout,*)
      Write (nout,99999)                                                       &
        'Norms of symmetric matrix stored in RFP format in ar:'
      Write (nout,*)

!     The NAG name equivalent of dlansf is f06waf
      r_one = dlansf('1-norm',transr,uplo,n,ar,work)
      Write (nout,99998) 'One norm           = ', r_one

      r_inf = dlansf('Infinity',transr,uplo,n,ar,work)
      Write (nout,99998) 'Infinity norm      = ', r_inf

      r_fro = dlansf('Frobenius',transr,uplo,n,ar,work)
      Write (nout,99998) 'Frobenius norm     = ', r_fro

      r_max = dlansf('Max norm',transr,uplo,n,ar,work)
      Write (nout,99998) 'Maximum norm       = ', r_max

99999 Format (1X,A)
99998 Format (1X,A,F9.4)
    End Program f06wafe