Program f06wpfe

!     F06WPF Example Program Text

!     Mark 26.1 Release. NAG Copyright 2016.

!     .. Use Statements ..
      Use nag_library, Only: nag_wp, x04daf, ztfsm, ztrttf
!     .. Implicit None Statement ..
      Implicit None
!     .. Parameters ..
      Integer, Parameter               :: nin = 5, nout = 6
!     .. Local Scalars ..
      Complex (Kind=nag_wp)            :: alpha
      Integer                          :: i, ifail, info, lda, ldb, m, n
      Character (1)                    :: side, trans, transr, uplo
!     .. Local Arrays ..
      Complex (Kind=nag_wp), Allocatable :: a(:,:), ar(:), b(:,:), work(:)
!     .. Executable Statements ..
      Write (nout,*) 'F06WPF Example Program Results'

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

      Read (nin,*) m, n, uplo, transr, side, alpha, trans

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

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

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

!     Read matrix B from data file

      Read (nin,*)(b(i,1:n),i=1,m)

!     Convert A to rectangular full packed storage in ar

!     The NAG name equivalent of ztrttf is f01vff
      Call ztrttf(transr,uplo,m,a,lda,ar,info)

      Write (nout,*)
      Flush (nout)

!     Perform the matrix-matrix operation

!     The NAG name equivalent of ztfsm is f06wpf
      Call ztfsm(transr,side,uplo,trans,'N',m,n,alpha,ar,b,ldb)

!     Print the result

      ifail = 0
      Call x04daf('General',' ',m,n,b,ldb,'The Solution',ifail)

    End Program f06wpfe