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

NAG FL Interface Introduction
Example description
    Program f01dffe

!     F01DFF Example Program Text

!     Mark 28.6 Release. NAG Copyright 2022.

!     .. Use Statements ..
      Use nag_library, Only: f01dff, 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, lda, ldb, ldc, n
      Logical                          :: lta, ltb, lu
      Character (1)                    :: transa, transb, uplo
!     .. Local Arrays ..
      Real (Kind=nag_wp), Allocatable  :: a(:,:), b(:,:), c(:,:)
!     .. Executable Statements ..
      Write (nout,*) 'F01DFF Example Program Results'

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

!     Values for uplo, transa, transb
      Read (nin,*) uplo, transa, transb

      lu = (uplo=='U')
      lta = (transa=='N')
      ltb = (transb=='N')

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

!     Scaling constant alpha
      Read (nin,*) alpha, beta

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

!     Read input matrix A from data file
      If (lu .Eqv. lta) 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 (lu .Eqv. ltb) Then
        Read (nin,*)(b(i,i:n),i=1,n)
      Else
        Read (nin,*)(b(i,1:i),i=1,n)
      End If

!     Read input matrix C from data file
      Read (nin,*)(c(i,1:n),i=1,n)

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

!     Compute the triangular matrix product and update C
      Call f01dff(uplo,transa,transb,n,alpha,a,lda,b,ldb,beta,c,ldc,ifail)

!     Print the solution
      If (ifail==0) Then
        ifail = 0
        Call x04caf('G','N',n,n,c,n,'Solution matrix C',ifail)
      End If

    End Program f01dffe