! F12AAF Example Program Text
! Mark 26.2 Release. NAG Copyright 2017.
Module f12aafe_mod
! F12AAF Example Program Module:
! Parameters and User-defined Routines
! .. Use Statements ..
Use nag_library, Only: nag_wp
! .. Implicit None Statement ..
Implicit None
! .. Accessibility Statements ..
Private
Public :: av
! .. Parameters ..
Integer, Parameter, Public :: imon = 0, ipoint = 0, nin = 5, &
nout = 6
Contains
Subroutine tv(nx,x,y)
! Compute the matrix vector multiplication y<---T*x where T is a nx
! by nx tridiagonal matrix with constant diagonals (DD, DL and DU).
! .. Parameters ..
Real (Kind=nag_wp), Parameter :: half = 0.5_nag_wp
Real (Kind=nag_wp), Parameter :: rho = 100.0_nag_wp
! .. Scalar Arguments ..
Integer, Intent (In) :: nx
! .. Array Arguments ..
Real (Kind=nag_wp), Intent (In) :: x(nx)
Real (Kind=nag_wp), Intent (Out) :: y(nx)
! .. Local Scalars ..
Real (Kind=nag_wp) :: dd, dl, du, nx1, nx2
Integer :: j
! .. Intrinsic Procedures ..
Intrinsic :: real
! .. Executable Statements ..
nx1 = real(nx+1,kind=nag_wp)
nx2 = nx1*nx1
dd = 4.0_nag_wp*nx2
dl = -nx2 - half*rho*nx1
du = -nx2 + half*rho*nx1
y(1) = dd*x(1) + du*x(2)
Do j = 2, nx - 1
y(j) = dl*x(j-1) + dd*x(j) + du*x(j+1)
End Do
y(nx) = dl*x(nx-1) + dd*x(nx)
Return
End Subroutine tv
Subroutine av(nx,v,w)
! .. Use Statements ..
Use nag_library, Only: daxpy
! .. Scalar Arguments ..
Integer, Intent (In) :: nx
! .. Array Arguments ..
Real (Kind=nag_wp), Intent (In) :: v(nx*nx)
Real (Kind=nag_wp), Intent (Out) :: w(nx*nx)
! .. Local Scalars ..
Real (Kind=nag_wp) :: nx2
Integer :: j, lo
! .. Intrinsic Procedures ..
Intrinsic :: real
! .. Executable Statements ..
nx2 = -real((nx+1)*(nx+1),kind=nag_wp)
Call tv(nx,v(1),w(1))
! The NAG name equivalent of daxpy is f06ecf
Call daxpy(nx,nx2,v(nx+1),1,w(1),1)
Do j = 2, nx - 1
lo = (j-1)*nx
Call tv(nx,v(lo+1),w(lo+1))
Call daxpy(nx,nx2,v(lo-nx+1),1,w(lo+1),1)
Call daxpy(nx,nx2,v(lo+nx+1),1,w(lo+1),1)
End Do
lo = (nx-1)*nx
Call tv(nx,v(lo+1),w(lo+1))
Call daxpy(nx,nx2,v(lo-nx+1),1,w(lo+1),1)
Return
End Subroutine av
End Module f12aafe_mod
Program f12aafe
! F12AAF Example Main Program
! .. Use Statements ..
Use f12aafe_mod, Only: av, imon, ipoint, nin, nout
Use nag_library, Only: dnrm2, f12aaf, f12abf, f12acf, f12adf, f12aef, &
nag_wp
! .. Implicit None Statement ..
Implicit None
! .. Local Scalars ..
Real (Kind=nag_wp) :: sigmai, sigmar
Integer :: i, ifail, ifail1, irevcm, lcomm, &
ldv, licomm, n, nconv, ncv, nev, &
niter, nshift, nx
! .. Local Arrays ..
Real (Kind=nag_wp), Allocatable :: ax(:), comm(:), d(:,:), mx(:), &
resid(:), v(:,:), x(:)
Integer, Allocatable :: icomm(:)
! .. Executable Statements ..
Write (nout,*) 'F12AAF Example Program Results'
Write (nout,*)
! Skip heading in data file
Read (nin,*)
Read (nin,*) nx, nev, ncv
n = nx*nx
ldv = n
lcomm = 3*n + 3*ncv*ncv + 6*ncv + 60
licomm = 140
Allocate (ax(n),comm(lcomm),d(ncv,3),mx(n),resid(n),v(ldv,ncv),x(n), &
icomm(licomm))
! 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 region of the spectrum that is required.
ifail = 0
Call f12adf('SMALLEST MAG',icomm,comm,ifail)
If (ipoint/=0) Then
! Use pointers to workspace in calculating matrix vector products
! rather than interfacing through the array X.
ifail = 0
Call f12adf('POINTERS=YES',icomm,comm,ifail)
End If
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 matrix vector multiplication y <--- Op*x
If (ipoint==0) Then
Call av(nx,x,ax)
x(1:n) = ax(1:n)
Else
Call av(nx,comm(icomm(1)),comm(icomm(2)))
End If
Else If (irevcm==4 .And. imon/=0) Then
! Set IMON=1 to 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 and
! (by default) the corresponding eigenvectors.
ifail1 = 0
Call f12acf(nconv,d,d(1,2),v,ldv,sigmar,sigmai,resid,v,ldv,comm,icomm, &
ifail1)
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 smallest magnitude are:',/)
99997 Format (1X,I8,5X,'( ',F12.4,' , ',F12.4,' )')
End Program f12aafe