NAG Library Manual, Mark 28.3
Interfaces:  FL   CL   CPP   AD 

NAG FL Interface Introduction
Example description
    Program f01dufe

!     F01DGF Example Program Text

!     Mark 28.3 Release. NAG Copyright 2022.

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

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

!     Values for side, uplo, and transa
      Read (nin,*) side, uplo, transa

!     Order of square matrices
      Read (nin,*) n
      lda = n
      ldb = n

!     Scaling constant alpha
      Read (nin,*) alpha

!     Allocate memory for local arrays
      Allocate (a(n,n),b(n,n))

!     Read input matrix A from data file
      If (uplo=='U') Then
        Read (nin,*)(a(i,i:n),i=1,n)
      Else
        Read (nin,*)(a(i,1:i),i=1,n)
      End If

!     Read input matrix B from data file
      If (uplo=='U') Then
        Read (nin,*)(b(i,i:n),i=1,n)
      Else
        Read (nin,*)(b(i,1:i),i=1,n)
      End If

!     ifail: behaviour on error exit
!           = 0 for hard exit, =1 for quiet-soft, =-1 for noisy-soft
      ifail = 0

!     Find B=alpha*A*B
      Call f01duf(side,uplo,transa,n,alpha,a,lda,b,ldb,ifail)

!     Print the solution
      If (ifail==0) Then
        If (transa=='N') Then
          Call x04daf(uplo,'N',n,n,b,n,'Solution matrix B',ifail)
        Else
          Call x04daf('G','N',n,n,b,n,'Solution matrix B',ifail)
        End If
      End If

    End Program f01dufe