Program f12abfe ! F12ABF Example Program Text ! Mark 24 Release. NAG Copyright 2012. ! .. Use Statements .. Use nag_library, Only: dgttrf, dgttrs, dnrm2, f12aaf, f12abf, f12acf, & f12adf, f12aef, nag_wp ! .. Implicit None Statement .. Implicit None ! .. Parameters .. Real (Kind=nag_wp), Parameter :: one = 1.0_nag_wp Real (Kind=nag_wp), Parameter :: two = 2.0_nag_wp Integer, Parameter :: imon = 0, nin = 5, nout = 6 ! .. Local Scalars .. Real (Kind=nag_wp) :: h, rho, s, s1, s2, s3, sigmai, sigmar Integer :: i, ifail, ifail1, info, irevcm, & lcomm, ldv, licomm, n, nconv, ncv, & nev, niter, nshift, nx ! .. Local Arrays .. Real (Kind=nag_wp), Allocatable :: comm(:), d(:,:), dd(:), dl(:), & du(:), du2(:), mx(:), resid(:), & v(:,:), x(:) Integer, Allocatable :: icomm(:), ipiv(:) ! .. Intrinsic Procedures .. Intrinsic :: real ! .. Executable Statements .. Write (nout,*) 'F12ABF Example Program Results' Write (nout,*) ! Skip heading in data file Read (nin,*) Read (nin,*) nx, nev, ncv, rho, sigmar, sigmai n = nx*nx ldv = n licomm = 140 lcomm = 3*n + 3*ncv*ncv + 6*ncv + 60 Allocate (comm(lcomm),d(ncv,3),dd(n),dl(n),du(n),du2(n),mx(n),resid(n), & v(ldv,ncv),x(n),icomm(licomm),ipiv(n)) ! ifail: behaviour on error exit ! =0 for hard exit, =1 for quiet-soft, =-1 for noisy-soft ifail = 0 Call f12aaf(n,nev,ncv,icomm,licomm,comm,lcomm,ifail) ! Set the mode. ifail = 0 Call f12adf('SHIFTED INVERSE REAL',icomm,comm,ifail) ! Construct C = A - SIGMA*I, and factorize using DGTTRF/F07CDF. h = one/real(n+1,kind=nag_wp) s = rho*h/two s1 = -one - s s2 = two - sigmar s3 = -one + s dl(1:n-1) = s1 dd(1:n-1) = s2 du(1:n-1) = s3 dd(n) = s2 ! The NAG name equivalent of dgttrf is f07cdf Call dgttrf(n,dl,dd,du,du2,ipiv,info) irevcm = 0 ifail = -1 loop: Do Call f12abf(irevcm,resid,v,ldv,x,mx,nshift,comm,icomm,ifail) If (irevcm/=5) Then If (irevcm==-1 .Or. irevcm==1) Then ! Perform x <--- OP*x = inv[A-SIGMA*I]*x. ! The NAG name equivalent of dgttrs is f07cef Call dgttrs('N',n,1,dl,dd,du,du2,ipiv,x,n,info) Else If (irevcm==4 .And. imon/=0) Then ! Output monitoring information Call f12aef(niter,nconv,d,d(1,2),d(1,3),icomm,comm) ! The NAG name equivalent of dnrm2 is f06ejf Write (6,99999) niter, nconv, dnrm2(nev,d(1,3),1) End If Else Exit loop End If End Do loop If (ifail==0) Then ! Post-Process using F12ACF to compute eigenvalues/vectors. ifail1 = 0 Call f12acf(nconv,d,d(1,2),v,ldv,sigmar,sigmai,resid,v,ldv,comm,icomm, & ifail1) ! Print computed eigenvalues. Write (nout,99998) nconv Do i = 1, nconv Write (nout,99997) i, d(i,1), d(i,2) End Do End If 99999 Format (1X,'Iteration',1X,I3,', No. converged =',1X,I3,', norm o', & 'f estimates =',E16.8) 99998 Format (1X/' The ',I4,' Ritz values of closest to unity are:'/) 99997 Format (1X,I8,5X,'( ',F12.4,' , ',F12.4,' )') End Program f12abfe