Example description
    Program f06wcfe

!     F06WCF Example Program Text

!     Mark 27.0 Release. NAG Copyright 2019.

!     .. Use Statements ..
      Use nag_library, Only: dsfrk, dtfttr, dtrttf, nag_wp, x04caf
!     .. Implicit None Statement ..
      Implicit None
!     .. Parameters ..
      Integer, Parameter               :: nin = 5, nout = 6
!     .. Local Scalars ..
      Real (Kind=nag_wp)               :: alpha, beta
      Integer                          :: i, ifail, info, k, lda, n
      Character (1)                    :: trans, transr, uplo
!     .. Local Arrays ..
      Real (Kind=nag_wp), Allocatable  :: a(:,:), c(:,:), cr(:)
!     .. Executable Statements ..
      Write (nout,*) 'F06WCF Example Program Results'

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

      Read (nin,*) n, k, uplo, transr, alpha, beta, trans

      lda = n
      Allocate (c(lda,n),cr((n*(n+1))/2),a(lda,k))

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

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

!     Read matrix A from data file

      Read (nin,*)(a(i,1:k),i=1,n)

!     Convert C to rectangular full packed storage in cr

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

      Write (nout,*)
      Flush (nout)

!     Perform the rank-k update

!     The NAG name equivalent of dsfrk is f06wcf
      Call dsfrk(transr,uplo,trans,n,k,alpha,a,lda,beta,cr)

!     Convert cr back from rectangular full packed to standard format in C

!     The NAG name equivalent of dtfttr is f01vgf
      Call dtfttr(transr,uplo,n,cr,c,lda,info)

!     Print out the result, stored in the lower triangle of matrix C

      ifail = 0
      Call x04caf('Lower','N',n,n,c,lda,'The Solution',ifail)

    End Program f06wcfe