I'm writing some subroutines in Fortran90 to perform some numerical computations. However, as part of this, I need to include some codes from the netlib templates library that are written in Fortran77. I'm having a hard time getting them to work - specifically understanding the usage of arrays.
For instance, I need to use a subroutine called GMRES. Here are the arguments:
SUBROUTINE GMRES( N, B, X, RESTRT, WORK, LDW, WORK2, LDW2,
$ ITER, RESID, MATVEC, PSOLVE, INFO )
* .. Scalar Arguments ..
INTEGER N, RESTRT, LDW, LDW2, ITER, INFO
DOUBLE PRECISION RESID
* ..
* .. Array Arguments ..
DOUBLE PRECISION B( * ), X( * ), WORK( * ), WORK2( * )
* ..
* .. Function Arguments ..
*
EXTERNAL MATVEC, PSOLVE
*
*
* Arguments
* =========
*
* N (input) INTEGER.
* On entry, the dimension of the matrix.
* Unchanged on exit.
*
* B (input) DOUBLE PRECISION array, dimension N.
* On entry, right hand side vector B.
* Unchanged on exit.
*
* X (input/output) DOUBLE PRECISION array, dimension N.
* On input, the initial guess; on exit, the iterated solution.
*
* RESTRT (input) INTEGER
* Restart parameter, <= N. This parameter controls the amount
* of memory required for matrix WORK2.
*
* WORK (workspace) DOUBLE PRECISION array, dimension (LDW,5).
* Note that if the initial guess is the zero vector, then
* storing the initial residual is not necessary.
*
* LDW (input) INTEGER
* The leading dimension of the array WORK. LDW >= max(1,N).
*
* WORK2 (workspace) DOUBLE PRECISION array, dimension (LDW2,2*RESTRT+2).
* This workspace is used for constructing and storing the
* upper Hessenberg matrix. The two extra columns are used to
* store the Givens rotation matrices.
*
* LDW2 (input) INTEGER
* The leading dimension of the array WORK2.
* LDW2 >= max(1,RESTRT).
*
* ITER (input/output) INTEGER
* On input, the maximum iterations to be performed.
* On output, actual number of iterations performed.
*
* RESID (input/output) DOUBLE PRECISION
* On input, the allowable error tolerance.
* On ouput, the norm of the residual vector if solution
* approximated to tolerance, otherwise reset to input
* tolerance.
*
* INFO (output) INTEGER
* = 0: successful exit
* = 1: maximum number of iterations performed;
* convergence not achieved.
*
* MATVEC (external subroutine)
* The user must provide a subroutine to perform the
* matrix-vector product A*x = y.
* Vector x must remain unchanged. The solution is
* over-written on vector y.
*
* The call is:
*
* CALL MATVEC( X, Y )
Notice how the arrays are defined WORK( * ), WORK2( * ). So to my mind these are 1D arrays of arbitrary length. But then in the argument description, it seems to be suggesting that they are 2D arrays, matrices, with dimension WORK(LDW, 5). So are they 1D or 2D?
Also, in the GMRES algorithm, these WORK arrays are used like this:
CALL MATVEC(SCLR1, WORK(NDX1), SCLR2, WORK(NDX2))
So if the WORK arrays are 2D, wouldn't the above give a rank mismatch? What does it mean to access a 2D array with just one index like that? Should I define the WORK arrays as 2D or 1D?
Edit
The GMRES routine requires a matvec routine to be supplied. In the GMRES code it is being called like
CALL MATVEC(SCLR1, X, SCLR2, WORK(NDX2))
and also like
CALL MATVEC(SCLR1, WORK(NDX1), SCLR2, WORK(NDX2))
My subroutine MATVEC that I'm trying to supply looks like:
subroutine matvec(alpha, x, beta, y)
real(dp), intent(in) :: alpha, beta
real(dp), dimension(*), intent(in) :: x
real(dp), dimension(*), intent(inout) :: y
real(dp), dimension(*,*) :: A
integer :: n
call make_Jac(n,A)
call dgemv('notranspose', n, n, alpha, A, n, x, 1, beta, y, 1)
end subroutine matvec
Where make_Jac
returns my matrix for the problem I'm working on, along with its dimension n. The blas routine dgemv
then handles the matrix-vector product.