Program f11drfe ! F11DRF Example Program Text ! Mark 24 Release. NAG Copyright 2012. ! .. Use Statements .. Use nag_library, Only: f11brf, f11bsf, f11btf, f11drf, f11xnf, nag_wp ! .. Implicit None Statement .. Implicit None ! .. Parameters .. Integer, Parameter :: nin = 5, nout = 6 ! .. Local Scalars .. Real (Kind=nag_wp) :: anorm, omega, sigmax, stplhs, & stprhs, tol Integer :: i, ifail, ifail1, irevcm, iterm, & itn, liwork, lwneed, lwork, m, & maxitn, monit, n, nnz Character (1) :: ckdrf, ckxnf, norm, precon, trans, & weight Character (8) :: method ! .. Local Arrays .. Complex (Kind=nag_wp), Allocatable :: a(:), b(:), rdiag(:), work(:), x(:) Real (Kind=nag_wp), Allocatable :: wgt(:) Integer, Allocatable :: icol(:), irow(:), iwork(:) ! .. Intrinsic Procedures .. Intrinsic :: max ! .. Executable Statements .. Write (nout,*) 'F11DRF Example Program Results' Write (nout,*) ! Skip heading in data file Read (nin,*) ! Read algorithmic parameters Read (nin,*) n, m Read (nin,*) nnz lwork = max(121+n*(3+m)+m*(m+5),120+7*n,120+(2*n+m)*(m+2)+2*n,120+10*n) liwork = 2*n + 1 Allocate (a(nnz),b(n),rdiag(n),work(lwork),x(n),wgt(n),icol(nnz), & irow(nnz),iwork(liwork)) Read (nin,*) method Read (nin,*) precon, norm, iterm Read (nin,*) tol, maxitn Read (nin,*) anorm, sigmax Read (nin,*) omega ! Read the matrix A Do i = 1, nnz Read (nin,*) a(i), irow(i), icol(i) End Do ! Read rhs vector b and initial approximate solution x Read (nin,*) b(1:n) Read (nin,*) x(1:n) ! Call F11BRF to initialize solver weight = 'N' monit = 0 ! 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,lwneed,work,lwork,ifail) ! Calculate reciprocal diagonal matrix elements if necessary If (precon=='P' .Or. precon=='p') Then iwork(1:n) = 0 Do i = 1, nnz If (irow(i)==icol(i)) Then iwork(irow(i)) = iwork(irow(i)) + 1 If (a(i)/=(0.0E0_nag_wp,0.0E0_nag_wp)) Then rdiag(irow(i)) = (1.0E0_nag_wp,0.0E0_nag_wp)/a(i) Else Write (nout,*) 'Matrix has a zero diagonal element' Go To 100 End If End If End Do Do i = 1, n If (iwork(i)==0) Then Write (nout,*) 'Matrix has a missing diagonal element' Go To 100 End If If (iwork(i)>=2) Then Write (nout,*) 'Matrix has a multiple diagonal element' Go To 100 End If End Do End If ! Call F11BSF to solve the linear system irevcm = 0 ckxnf = 'C' ckdrf = 'C' ifail = 1 loop: Do Call f11bsf(irevcm,x,b,wgt,work,lwork,ifail) If (irevcm/=4) Then ifail1 = 1 Select Case (irevcm) Case (1) ! Compute matrix-vector product trans = 'N' Call f11xnf(trans,n,nnz,a,irow,icol,ckxnf,x,b,ifail1) ckxnf = 'N' Case (-1) ! Compute conjugate transposed matrix-vector product trans = 'T' Call f11xnf(trans,n,nnz,a,irow,icol,ckxnf,x,b,ifail1) ckxnf = 'N' Case (2) ! SSOR preconditioning trans = 'N' Call f11drf(trans,n,nnz,a,irow,icol,rdiag,omega,ckdrf,x,b,iwork, & ifail1) ckdrf = 'N' End Select If (ifail1/=0) irevcm = 6 Else If (ifail==0) Then ! Termination ifail = 0 Call f11btf(itn,stplhs,stprhs,anorm,sigmax,work,lwork,ifail) Write (nout,99996) itn Write (nout,99997) 'Matrix norm =', anorm Write (nout,99997) 'Final residual norm =', stplhs Write (nout,*) ! Output x Write (nout,*) ' X' Write (nout,99998) x(1:n) Exit loop Else Write (nout,99999) ifail Exit loop End If End Do loop 100 Continue 99999 Format (1X/1X,' ** F11BSF returned with IFAIL = ',I5) 99998 Format (1X,'(',1P,E16.4,',',1P,E16.4,')') 99997 Format (1X,A,1P,E16.3) 99996 Format (1X,'Converged in',I10,' iterations') End Program f11drfe