Program f11jdfe ! F11JDF Example Program Text ! Mark 24 Release. NAG Copyright 2012. ! .. Use Statements .. Use nag_library, Only: f11gdf, f11gef, f11gff, f11jdf, f11xef, nag_wp ! .. Implicit None Statement .. Implicit None ! .. Parameters .. Integer, Parameter :: nin = 5, nout = 6 ! .. Local Scalars .. Real (Kind=nag_wp) :: anorm, omega, sigerr, sigmax, & sigtol, stplhs, stprhs, tol Integer :: i, ifail, ifail1, irevcm, iterm, & itn, its, liwork, lwneed, lwork, & maxitn, maxits, monit, n, nnz Character (1) :: ckjdf, ckxef, norm, precon, sigcmp, & weight Character (6) :: method ! .. Local Arrays .. Real (Kind=nag_wp), Allocatable :: a(:), b(:), rdiag(:), wgt(:), & work(:), x(:) Integer, Allocatable :: icol(:), irow(:), iwork(:) ! .. Executable Statements .. Write (nout,*) 'F11JDF Example Program Results' ! Skip heading in data file Read (nin,*) ! Read algorithmic parameters Read (nin,*) n Read (nin,*) nnz liwork = n + 1 lwork = 6*n + 120 Allocate (a(nnz),b(n),rdiag(n),wgt(n),work(lwork),x(n),icol(nnz), & irow(nnz),iwork(liwork)) Read (nin,*) method Read (nin,*) precon, sigcmp, norm, iterm Read (nin,*) tol, maxitn Read (nin,*) anorm, sigmax Read (nin,*) sigtol, maxits Read (nin,*) omega ! Read 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) ! Call F11GDF 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 f11gdf(method,precon,sigcmp,norm,weight,iterm,n,tol,maxitn,anorm, & sigmax,sigtol,maxits,monit,lwneed,work,lwork,ifail) ! Calculate reciprocal diagonal matrix elements. 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) Then rdiag(irow(i)) = 1.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 ! Call F11GEF to solve the linear system irevcm = 0 ckxef = 'C' ckjdf = 'C' ifail = 1 loop: Do Call f11gef(irevcm,x,b,wgt,work,lwork,ifail) If (irevcm/=4) Then ifail1 = -1 Select Case (irevcm) Case (1) ! Compute matrix vector product Call f11xef(n,nnz,a,irow,icol,ckxef,x,b,ifail1) ckxef = 'N' Case (2) ! SSOR preconditioning Call f11jdf(n,nnz,a,irow,icol,rdiag,omega,ckjdf,x,b,iwork,ifail1) ckjdf = 'N' End Select If (ifail1/=0) irevcm = 6 Else If (ifail/=0) Then Write (nout,99996) ifail Go To 100 Else Exit loop End If End Do loop ! Termination Call f11gff(itn,stplhs,stprhs,anorm,sigmax,its,sigerr,work,lwork,ifail) Write (nout,99999) 'Converged in', itn, ' iterations' Write (nout,99998) 'Final residual norm =', stplhs ! Output x Write (nout,99997) x(1:n) 100 Continue 99999 Format (1X,A,I10,A) 99998 Format (1X,A,1P,E16.3) 99997 Format (1X,1P,E16.4) 99996 Format (1X/1X,' ** F11GEF returned with IFAIL = ',I5) End Program f11jdfe