Example description
    Program f11brfe

!     F11BRF Example Program Text

!     Mark 26.2 Release. NAG Copyright 2017.

!     .. Use Statements ..
      Use nag_library, Only: f11brf, f11bsf, f11btf, f11dnf, f11dpf, f11xnf,   &
                             nag_wp
!     .. Implicit None Statement ..
      Implicit None
!     .. Parameters ..
      Integer, Parameter               :: nin = 5, nout = 6
!     .. Local Scalars ..
      Real (Kind=nag_wp)               :: anorm, dtol, sigmax, stplhs, stprhs, &
                                          tol
      Integer                          :: i, ifail, ifail1, irevcm, iterm,     &
                                          itn, la, lfill, liwork, lwork,       &
                                          lwreq, m, maxitn, monit, n, nnz,     &
                                          nnzc, npivm
      Character (8)                    :: method
      Character (1)                    :: milu, norm, precon, pstrat, weight
!     .. Local Arrays ..
      Complex (Kind=nag_wp), Allocatable :: a(:), b(:), work(:), x(:)
      Real (Kind=nag_wp), Allocatable  :: wgt(:)
      Integer, Allocatable             :: icol(:), idiag(:), ipivp(:),         &
                                          ipivq(:), irow(:), istr(:), iwork(:)
!     .. Executable Statements ..
      Write (nout,*) 'F11BRF Example Program Results'

!     Skip heading in data file

      Read (nin,*)
      Read (nin,*) n
      Read (nin,*) nnz
      la = 2*nnz
      liwork = 7*n + 2
      lwork = 200
      Allocate (a(la),b(n),work(lwork),x(n),wgt(n),icol(la),idiag(n),ipivp(n), &
        ipivq(n),irow(la),istr(n+1),iwork(liwork))

!     Read or initialize the parameters for the iterative solver

      Read (nin,*) method
      Read (nin,*) precon, norm, weight, iterm
      Read (nin,*) m, tol, maxitn
      Read (nin,*) monit
      anorm = 0.0E0_nag_wp
      sigmax = 0.0E0_nag_wp

!     Read the parameters for the preconditioner

      Read (nin,*) lfill, dtol
      Read (nin,*) milu, pstrat

!     Read the nonzero elements of the matrix A

      Do i = 1, nnz
        Read (nin,*) a(i), irow(i), icol(i)
      End Do

!     Read right-hand side vector b and initial approximate
!     solution x

      Read (nin,*) b(1:n)
      Read (nin,*) x(1:n)

!     Calculate incomplete LU factorization

!     ifail: behaviour on error exit
!             =0 for hard exit, =1 for quiet-soft, =-1 for noisy-soft
      ifail = 0
      Call f11dnf(n,nnz,a,la,irow,icol,lfill,dtol,pstrat,milu,ipivp,ipivq,     &
        istr,idiag,nnzc,npivm,iwork,liwork,ifail)

!     Call F11BRF to initialize the solver

      ifail = 0
      Call f11brf(method,precon,norm,weight,iterm,n,m,tol,maxitn,anorm,sigmax, &
        monit,lwreq,work,lwork,ifail)

!     Call repeatedly F11BSF to solve the equations
!     Note that the arrays B and X are overwritten

!     On final exit, X will contain the solution and B the residual
!     vector

      irevcm = 0
      lwreq = lwork

      ifail = 1
loop: Do
        Call f11bsf(irevcm,x,b,wgt,work,lwreq,ifail)

        If (irevcm/=4) Then
          ifail1 = -1
          Select Case (irevcm)
          Case (-1)

            Call f11xnf('Transpose',n,nnz,a,irow,icol,'No checking',x,b,       &
              ifail1)

          Case (1)

            Call f11xnf('No transpose',n,nnz,a,irow,icol,'No checking',x,b,    &
              ifail1)

          Case (2)

            Call f11dpf('No transpose',n,a,la,irow,icol,ipivp,ipivq,istr,      &
              idiag,'No checking',x,b,ifail1)

          Case (3)

            ifail1 = 0
            Call f11btf(itn,stplhs,stprhs,anorm,sigmax,work,lwreq,ifail1)

            Write (nout,99999) itn, stplhs
            Write (nout,99998)
            Write (nout,99996) x(1:n)
            Write (nout,99997)
            Write (nout,99996) b(1:n)

          End Select
          If (ifail1/=0) Then
            irevcm = 6
          End If
        Else If (ifail/=0) Then
          Write (nout,99992) ifail
          Go To 100
        Else
          Exit loop
        End If
      End Do loop

!     Obtain information about the computation

      ifail1 = 0
      Call f11btf(itn,stplhs,stprhs,anorm,sigmax,work,lwreq,ifail1)

!     Print the output data

      Write (nout,99995)
      Write (nout,99994) 'Number of iterations for convergence:    ', itn
      Write (nout,99993) 'Residual norm:                           ', stplhs
      Write (nout,99993) 'Right-hand side of termination criterion:', stprhs
      Write (nout,99993) '1-norm of matrix A:                      ', anorm

!     Output x

      Write (nout,99998)
      Write (nout,99996) x(1:n)
      Write (nout,99997)
      Write (nout,99996) b(1:n)
100   Continue

99999 Format (/,1X,'Monitoring at iteration no.',I4,/,1X,1P,'residual no',     &
        'rm: ',E14.4)
99998 Format (/,2X,'  Solution vector')
99997 Format (/,2X,'  Residual vector')
99996 Format (1X,'(',1P,E16.4,',',1P,E16.4,')')
99995 Format (/,1X,'Final Results')
99994 Format (1X,A,I4)
99993 Format (1X,A,1P,E14.4)
99992 Format (1X,/,1X,' ** F11BSF returned with IFAIL = ',I5)
    End Program f11brfe