3

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.

O Smith
  • 375
  • 1
  • 3
  • 11
  • These arrays are actually passed further from GMRES to GMRESREVCOM as `WORK( LDW,* ), WORK2( LDW2,* )`. If you changed it to `WORK( LDW,* ), WORK2( LDW2,* )` in `GMRES` as well, it would still work, but you would be limited to 2D arrays only. Look for *sequence association* in your Fortran textbook. – Vladimir F Героям слава Jul 07 '15 at 16:54
  • @VladimirF Isn't it problematic to change the declaration of WORK and WORK2 in GMRES() to 2D assumed-size ones, because they are already used in MATVEC() as above? (for which compilers may complain.) – roygvib Jul 07 '15 at 17:10
  • Yes, that would break it, I missed tha line. Could be adapted of course, but there is no reason to do that. – Vladimir F Героям слава Jul 07 '15 at 17:14
  • I initially read your question about `WORK(NDX1)` and "just one index" again being about the ranks for the arrays. From the edit, I now think that you actually wondered about the single _element_, so passing a scalar. Could you confirm/clarify this? – francescalus Jul 07 '15 at 21:38
  • In `matvec` you have `real(dp), dimension(*,*) :: A`. However, `A` isn't a dummy argument so this declaration is not legal: `A` cannot be an assumed-size array; it isn't a named constant so it can't be implied-shape. Can you check you really have this? – francescalus Jul 07 '15 at 21:44

3 Answers3

3

WORK( * ) declares an assumed size array, which can be two-dimensional. See here.

The compiler will not complain if you feed a one-dimensional array to the subroutine, but weird things (up to and including a segmentation fault) might happen.

Better use arrays matching the specifications.

Community
  • 1
  • 1
Alexander Vogt
  • 17,879
  • 13
  • 52
  • 68
3

The same Fortran array can be managed as one dimensional, two dimensional, etc. It is stored in contiguous memory in any case.

Let's say you have

double precision x(3, 2)

call somefunc (x)

This can be accessed, inside somefunc, as y (6).

The array elements are stored in "column major order" which means

x(1, 1) is y(1)
x(2, 1) is y(2)
x(3, 1) is y(3)
x(1, 2) is y(4)
x(2, 2) is y(5)
x(3, 2) is y(6)

As long as the function knows the limits of each dimension, it can calculate linear access by simple arithmetic. Alas, this "relaxed type" is also a frequent source of bugs.

wallyk
  • 56,922
  • 16
  • 83
  • 148
2

Further to the answer by wallyk the dummy argument work(*) is a rank-1 assumed size array. With such an array

The rank and extents may differ for the effective and dummy arguments; only the size of the effective argument is assumed by the dummy argument.

This means that it is quite acceptable for such a structure as

double precision work(LDW,5)
call GMRES(..., work, ...)
! ...

end

subroutine GMRES(..., work, ...)
  double precision work(*)
  ! ...
end subroutine

Indeed, with the dummy argument as a rank-1 array it isn't allowed to reference it as a rank-2 array. A rank-2 assumed size array would look something like

double precision work(LDW,*)

where then, of course, work(ndx1) would be bad.

Coming to the comment by roygvib, later on in the Netlib source code there is the line

call GMRESREVCOM(..., work, ...)

where that subroutine has the dummy argument

double precision work(LDW,*)

There is probably, then, an expectation that the user of the code will provide initially a rank-2 actual argument.

What all of this means is that it doesn't matter what rank the actual argument passed to work in GMRES as long as it has at least LDW*5 elements. I'd be careful calling the dummy argument as being of "arbitrary length", though, as referencing work(LDW*5+1) (according to my first example) would be wrong. The size of the dummy array is exactly the size of the passed array.

The later call to matvec is not troublesome for yet another reason. This subroutine has four arguments, the first and third of which are scalar. The second and fourth are again assumed-size arrays of rank-1. We've established that assumed-size arrays don't care about the rank of the effective/actual argument, but you're likely wondering why you can pass the scalar argument work(ndx1) to this rank-1 array.

The answer to that is something called sequence association. This means that when your actual argument is an array element designator and the dummy argument is an array dummy argument then that dummy argument is argument associated with a sequence of elements from the actual argument, starting with the element element designated.

That is, you have a rank-1 array like [work(ndx1), work(ndx1+1), ...] as your array x in matvec.

This is all fine, as long as you don't attempt to reference beyond the extent of your actual argument.

francescalus
  • 30,576
  • 16
  • 61
  • 96
  • Thanks. I find myself with a new problem though. The GMRES routines requires a user supplied routine called MatVec. If you look in the GMRES code, its being called like `call MatVec(scalar, Work(ndx1), scalar2, Work2(ndx2))` It requires the Matvec function to be compute y = scalar*A*x + scalar2*y, where y is a vector. Anything else would give rank mismatch. And yet in the code, MatVec is being called on non-vectors. Unsurprisingly this gives segmentation error. At this point I'm tempted to give up and just ask my university to give me access to the NAG library! – O Smith Jul 07 '15 at 20:05
  • `scalar1` and `scalar2` are indeed scalar, but... Although you may think `Work(ndx1)` is a scalar you have what is known as _sequence association_. The dummy argument will actually be an array associated with the elements of `Work` starting at the element `Work(ndx1)`. That's possibly a new question, but I think you should already be able to find one about the wonders that introduces. – francescalus Jul 07 '15 at 20:14
  • 1
    @OSmith If you post the interface parts of your code (incl. Matvec), I believe people will find out how to pass variables flawlessly. This type of argument passing is very old-fashioned but very frequently used in old codes (and frankly I also used this much before :) Also pls note that the interface may need to be implicit to avoid shape checking by recent compilers... – roygvib Jul 07 '15 at 20:34
  • Thank you, I have edited my post above to include more code - specifically showing the matvec routine that I need to pass to GMRES. This seems to be where my problems are arising. – O Smith Jul 07 '15 at 21:13
  • 1
    @OSmith I'd suggest checking carefully that the results (in particular `n`) from `make_Jac` match the sizes of the assumed-size arrays for the call to `dgemv`. I'd not advise editing the question much more as such creeping scope isn't usually gracefully welcomed. If you can narrow down a question about `make_Jac` etc., then a new question (perhaps referencing this one) may be best. There you could show more details about this new subroutine. I hope, though, that the answers you now have sucessfully address your initial question about the changing ranks. – francescalus Jul 07 '15 at 21:34
  • @OSmith I agree with francescalus; for example, I suggest positing a new Question that shows (1) the EDIT part above (hopefully with some more info about make_Jac), (2) a link to the current Question, and (3) a short description of the problem that segfault occurs for your current Matvec. Then I believe it will gather more attention and so more answer. – roygvib Jul 07 '15 at 21:55
  • Yes, thank you - I'm going to try and change my MatVec a little bit and possibly post a new question about that specifically. Could I just double check with you that when `WORK(NDX1)` is passed to MatVec, it is passing a vector? i.e can you confirm that `WORK(NDX1)` is not single scalar element of `WORK`, but is instead some subset of `WORK` : therefore an array of indeterminate length. – O Smith Jul 07 '15 at 21:56
  • The dummy argument `x` corresponding to `work(ndx1)` will indeed be an assumed-size array. Not of indeterminate size but of all elements left in `work` after `work(ndx1)`. Before you do much more checking, I'd suggest you go for the `dimension(*,*)` declaration of `A`, as I'm surprised that even compiles. – francescalus Jul 07 '15 at 21:58
  • @OSmith If you are familar with C, it may be more straight-forward to think that the address of the element, i.e. &(work(ndx1)), is actually passed; the called routine can refer to it any way (e.g. as a scalar or N-dim array). The declaration in the called routine just tells the compiler how to access the memory from the address given. – roygvib Jul 07 '15 at 22:09