Program f11gdfe ! F11GDF Example Program Text ! Mark 24 Release. NAG Copyright 2012. ! .. Use Statements .. Use nag_library, Only: f11gdf, f11gef, f11gff, f11jaf, f11jbf, f11xef, & nag_wp ! .. Implicit None Statement .. Implicit None ! .. Parameters .. Integer, Parameter :: nin = 5, nout = 6 ! .. Local Scalars .. Real (Kind=nag_wp) :: anorm, dscale, dtol, sigerr, sigmax, & sigtol, stplhs, stprhs, tol Integer :: i, ifail, ifail1, irevcm, iterm, & itn, its, la, lfill, liwork, lwork, & lwreq, maxitn, maxits, monit, n, & nnz, nnzc, npivm Character (6) :: method Character (1) :: mic, norm, precon, pstrat, sigcmp, & weight ! .. Local Arrays .. Real (Kind=nag_wp), Allocatable :: a(:), b(:), wgt(:), work(:), x(:) Integer, Allocatable :: icol(:), ipiv(:), irow(:), istr(:), & iwork(:) ! .. Executable Statements .. Write (nout,*) 'F11GDF Example Program Results' ! Skip heading in data file Read (nin,*) Read (nin,*) n Read (nin,*) nnz la = 2*nnz liwork = 2*la + 7*n + 1 lwork = 200 Allocate (a(la),b(n),wgt(n),work(lwork),x(n),icol(la),ipiv(n),irow(la), & istr(n+1),iwork(liwork)) ! Read or initialize the parameters for the iterative solver Read (nin,*) method Read (nin,*) precon, sigcmp, norm, weight, iterm Read (nin,*) tol, maxitn Read (nin,*) monit anorm = 0.0E0_nag_wp sigmax = 0.0E0_nag_wp sigtol = 1.0E-2_nag_wp maxits = n ! Read the parameters for the preconditioner Read (nin,*) lfill, dtol Read (nin,*) mic, dscale Read (nin,*) pstrat ! Read the non-zero 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) If (method=='CG') Then Write (nout,99999) Else If (method=='SYMMLQ') Then Write (nout,99998) Else If (method=='MINRES') Then Write (nout,99997) End If ! Calculate incomplete Cholesky factorization ! ifail: behaviour on error exit ! =0 for hard exit, =1 for quiet-soft, =-1 for noisy-soft ifail = 0 Call f11jaf(n,nnz,a,la,irow,icol,lfill,dtol,mic,dscale,pstrat,ipiv,istr, & nnzc,npivm,iwork,liwork,ifail) ! Call F11GDF to initialize the solver ifail = 0 Call f11gdf(method,precon,sigcmp,norm,weight,iterm,n,tol,maxitn,anorm, & sigmax,sigtol,maxits,monit,lwreq,work,lwork,ifail) ! Call repeatedly F11GEF 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 f11gef(irevcm,x,b,wgt,work,lwreq,ifail) If (irevcm/=4) Then ifail1 = -1 Select Case (irevcm) Case (1) Call f11xef(n,nnz,a,irow,icol,'No checking',x,b,ifail1) Case (2) Call f11jbf(n,a,la,irow,icol,ipiv,istr,'No checking',x,b,ifail1) Case (3) ifail1 = 0 Call f11gff(itn,stplhs,stprhs,anorm,sigmax,its,sigerr,work,lwreq, & ifail1) Write (nout,99996) itn, stplhs Write (nout,99995) Write (nout,99994)(x(i),b(i),i=1,n) End Select If (ifail1/=0) irevcm = 6 Else If (ifail/=0) Then Write (nout,99990) ifail Go To 100 Else Exit loop End If End Do loop ! Obtain information about the computation ifail1 = 0 Call f11gff(itn,stplhs,stprhs,anorm,sigmax,its,sigerr,work,lwreq,ifail1) ! Print the output data Write (nout,99993) Write (nout,99992) 'Number of iterations for convergence: ', itn Write (nout,99991) 'Residual norm: ', stplhs Write (nout,99991) 'Right-hand side of termination criterion:', stprhs Write (nout,99991) '1-norm of matrix A: ', anorm Write (nout,99991) 'Largest singular value of A_bar: ', sigmax ! Output x Write (nout,99995) Write (nout,99994)(x(i),b(i),i=1,n) 100 Continue 99999 Format (/1X,'Solve a system of linear equations using the conjug', & 'ate gradient method') 99998 Format (/1X,'Solve a system of linear equations using the Lanczo', & 's method (SYMMLQ)') 99997 Format (/1X,'Solve a system of linear equations using the minimu', & 'm residual method (MINRES)') 99996 Format (/1X,'Monitoring at iteration no.',I4/1X,1P,'residual no','rm: ', & E14.4) 99995 Format (2X,'Solution vector',2X,'Residual vector') 99994 Format (1X,1P,E16.4,1X,E16.4) 99993 Format (/1X,'Final Results') 99992 Format (1X,A,I4) 99991 Format (1X,A,1P,E14.4) 99990 Format (1X/1X,' ** F11GEF returned with IFAIL = ',I5) End Program f11gdfe