Program f11dxfe

!     F11DXF Example Program Text

!     Mark 26.1 Release. NAG Copyright 2016.

!     .. Use Statements ..
      Use nag_library, Only: f11brf, f11bsf, f11btf, f11dxf, f11xnf, nag_wp
!     .. Implicit None Statement ..
      Implicit None
!     .. Parameters ..
      Integer, Parameter               :: nin = 5, nout = 6
!     .. Local Scalars ..
      Real (Kind=nag_wp)               :: anorm, sigmax, stplhs, stprhs, tol
      Integer                          :: i, ifail, ifail1, irevcm, iterm,     &
                                          itn, lwork, lwreq, m, maxitn, monit, &
                                          n, niter, nnz
      Logical                          :: verbose
      Character (1)                    :: init, norm, precon, weight
      Character (8)                    :: method
!     .. Local Arrays ..
      Complex (Kind=nag_wp), Allocatable :: a(:), b(:), diag(:), work(:), x(:)
      Real (Kind=nag_wp), Allocatable  :: wgt(:)
      Integer, Allocatable             :: icol(:), irow(:)
!     .. Intrinsic Procedures ..
      Intrinsic                        :: log, nint
!     .. Executable Statements ..
      Write (nout,*) 'F11DXF Example Program Results'

!     Skip heading in data file

      Read (nin,*)
      Read (nin,*) n
      Read (nin,*) nnz
      lwork = 300
      Allocate (a(nnz),b(n),diag(n),work(lwork),x(n),wgt(n),icol(nnz),         &
        irow(nnz))

!     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,*) niter

!     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

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

!     Call F11BDF to initialize the solver

!     ifail: behaviour on error exit
!             =0 for hard exit, =1 for quiet-soft, =-1 for noisy-soft
      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
      init = 'I'

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

        If (irevcm/=4) Then
          ifail1 = -1
          If (irevcm==-1) Then
            Call f11xnf('Transpose',n,nnz,a,irow,icol,'No checking',x,b,       &
              ifail1)
          Else If (irevcm==1) Then
            Call f11xnf('No transpose',n,nnz,a,irow,icol,'No checking',x,b,    &
              ifail1)
          Else If (irevcm==2) Then
            Call f11dxf('Non Hermitian','N',init,niter,n,nnz,a,irow,icol,      &
              'Check',x,b,diag,work(lwreq+1),ifail1)
            init = 'N'
          Else If (irevcm==3) Then
            Call f11btf(itn,stplhs,stprhs,anorm,sigmax,work,lwreq,ifail1)
            If (ifail1==0) Then
              If (itn<=3) Then
                Write (nout,99999) itn
                Write (nout,99998) nint(log(stplhs)/log(10.0_nag_wp))
              End If
            End If
          End If
          If (ifail1/=0) Then
            irevcm = 6
          End If
        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,99997)
      verbose = .False.
      If (verbose) Then
        Write (nout,99996) 'Number of iterations for convergence:    ', itn
        Write (nout,99995) 'Residual norm:                           ', stplhs
        Write (nout,99995) 'Right-hand side of termination criterion:', stprhs
        Write (nout,99995) '1-norm of matrix A:                      ', anorm
      End If

!     Output x

      Write (nout,99994)
      Write (nout,99993) x(1:n)

99999 Format (/,1X,'Monitoring at iteration number',I4)
99998 Format (1X,'  order of residual norm:',I4)
99997 Format (/,1X,'Final Results')
99996 Format (1X,A,I5)
99995 Format (1X,A,1P,E11.1)
99994 Format (/,2X,'  Solution vector')
99993 Format (1X,'(',F8.3,',',F8.3,')')
    End Program f11dxfe