! F12AQF Example Program Text ! Mark 24 Release. NAG Copyright 2012. Module f12aqfe_mod ! F12AQF Example Program Module: ! Parameters and User-defined Routines ! .. Use Statements .. Use nag_library, Only: nag_wp ! .. Implicit None Statement .. Implicit None ! .. Parameters .. Complex (Kind=nag_wp), Parameter :: four = (4.0_nag_wp,0.0_nag_wp) Complex (Kind=nag_wp), Parameter :: & one = (1.0E+0_nag_wp,0.0E+0_nag_wp) Complex (Kind=nag_wp), Parameter :: two = (2.0_nag_wp,0.0_nag_wp) Integer, Parameter :: imon = 0, licomm = 140, & nerr = 6, nin = 5, nout = 6 Contains Subroutine av(nx,v,w) ! .. Parameters .. Complex (Kind=nag_wp), Parameter :: rho = (10.0_nag_wp,0.0_nag_wp) ! .. Scalar Arguments .. Integer, Intent (In) :: nx ! .. Array Arguments .. Complex (Kind=nag_wp), Intent (In) :: v(nx*nx) Complex (Kind=nag_wp), Intent (Out) :: w(nx*nx) ! .. Local Scalars .. Complex (Kind=nag_wp) :: dd, dl, du, h, s Integer :: j, n ! .. Intrinsic Procedures .. Intrinsic :: cmplx ! .. Executable Statements .. n = nx*nx h = one/cmplx(n+1,kind=nag_wp) s = rho/two dd = two/h dl = -one/h - s du = -one/h + s w(1) = dd*v(1) + du*v(2) Do j = 2, n - 1 w(j) = dl*v(j-1) + dd*v(j) + du*v(j+1) End Do w(n) = dl*v(n-1) + dd*v(n) Return End Subroutine av Subroutine mv(nx,v,w) ! .. Use Statements .. Use nag_library, Only: zscal ! .. Scalar Arguments .. Integer, Intent (In) :: nx ! .. Array Arguments .. Complex (Kind=nag_wp), Intent (In) :: v(nx*nx) Complex (Kind=nag_wp), Intent (Out) :: w(nx*nx) ! .. Local Scalars .. Complex (Kind=nag_wp) :: h Integer :: j, n ! .. Intrinsic Procedures .. Intrinsic :: cmplx ! .. Executable Statements .. n = nx*nx w(1) = four*v(1) + one*v(2) Do j = 2, n - 1 w(j) = one*v(j-1) + four*v(j) + one*v(j+1) End Do w(n) = one*v(n-1) + four*v(n) h = one/cmplx(n+1,kind=nag_wp) ! The NAG name equivalent of zscal is f06gdf Call zscal(n,h,w,1) Return End Subroutine mv End Module f12aqfe_mod Program f12aqfe ! F12AQF Example Main Program ! .. Use Statements .. Use nag_library, Only: dznrm2, f12anf, f12apf, f12aqf, f12arf, f12asf, & nag_wp, zgttrf, zgttrs Use f12aqfe_mod, Only: av, four, imon, licomm, mv, nerr, nin, nout, one ! .. Implicit None Statement .. Implicit None ! .. Local Scalars .. Complex (Kind=nag_wp) :: h, sigma Integer :: ifail, ifail1, info, irevcm, j, & lcomm, ldv, n, nconv, ncv, nev, & niter, nshift, nx ! .. Local Arrays .. Complex (Kind=nag_wp), Allocatable :: comm(:), d(:,:), dd(:), dl(:), & du(:), du2(:), mx(:), resid(:), & v(:,:), x(:) Integer :: icomm(licomm) Integer, Allocatable :: ipiv(:) ! .. Intrinsic Procedures .. Intrinsic :: cmplx ! .. Executable Statements .. Write (nout,*) 'F12AQF Example Program Results' Write (nout,*) ! Skip heading in data file Read (nin,*) Read (nin,*) nx, nev, ncv n = nx*nx lcomm = 3*n + 3*ncv*ncv + 5*ncv + 60 ldv = n Allocate (comm(lcomm),d(ncv,2),dd(n),dl(n),du(n),du2(n),mx(n),resid(n), & v(ldv,ncv),x(n),ipiv(n)) ifail = 0 Call f12anf(n,nev,ncv,icomm,licomm,comm,lcomm,ifail) ! Set the mode. ifail = 0 Call f12arf('REGULAR INVERSE',icomm,comm,ifail) ! Set problem type. Call f12arf('GENERALIZED',icomm,comm,ifail) ! Use pointers to Workspace rather than interfacing through the array X. Call f12arf('POINTERS=YES',icomm,comm,ifail) h = one/cmplx(n+1,kind=nag_wp) dl(1:n-1) = h dd(1:n-1) = four*h du(1:n-1) = h dd(n) = four*h ! The NAG name equivalent of zgttrf is f07crf Call zgttrf(n,dl,dd,du,du2,ipiv,info) If (info/=0) Then Write (nerr,99999) info Go To 100 End If irevcm = 0 ifail = -1 revcm: Do Call f12apf(irevcm,resid,v,ldv,x,mx,nshift,comm,icomm,ifail) If (irevcm==5) Then Exit revcm Else If (irevcm==-1 .Or. irevcm==1) Then ! Perform y <--- OP*x = inv[M]*A*x | Call av(nx,comm(icomm(1)),comm(icomm(2))) ! The NAG name equivalent of zgttrs is f07csf Call zgttrs('N',n,1,dl,dd,du,du2,ipiv,comm(icomm(2)),n,info) If (info/=0) Then Write (nerr,99998) info Exit revcm End If Else If (irevcm==2) Then ! Perform y <--- M*x Call mv(nx,comm(icomm(1)),comm(icomm(2))) Else If (irevcm==4 .And. imon/=0) Then ! Output monitoring information Call f12asf(niter,nconv,d,d(1,2),icomm,comm) ! The NAG name equivalent of dznrm2 is f06jjf Write (6,99997) niter, nconv, dznrm2(nev,d(1,2),1) End If End Do revcm If (ifail==0 .And. info==0) Then ! Post-Process using F12AQF to compute eigenvalues/vectors. ifail1 = 0 Call f12aqf(nconv,d,v,ldv,sigma,resid,v,ldv,comm,icomm,ifail1) Write (nout,99996) nconv Write (nout,99995)(j,d(j,1),j=1,nconv) End If 100 Continue 99999 Format (1X,'** Error status returned by ZGTTRF, INFO =',I12) 99998 Format (1X,'** Error status returned by ZGTTRS, INFO =',I12) 99997 Format (1X,'Iteration',1X,I3,', No. converged =',1X,I3,', norm o', & 'f estimates =',E16.8) 99996 Format (1X/' The ',I4,' Ritz values of largest magnitude are:'/) 99995 Format (1X,I8,5X,'( ',F12.4,' , ',F12.4,' )') End Program f12aqfe