- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
I treied using both DIM and LEN to pass information about an array I input
to a subroutine. For example:
REAL A(-23:35)
CALL SUB1(A)
Do I explicititly have to tell it how big the array is in a separate
item in the call sequence? In this case, A has 59 elements,
(35-(-23)+1) so would I have to say:
REAL A(-23:35)
CALL SUB1(59,A)
SUBROUTINE SUB1(NA,A)
REAL A(1:NA)
INTEGER NA
---------------------------------------------------------------------------------------
I thought that the newest Fotran has a way to provide all that info
just by passing the array name.
Maybe there is an article about this somewhere?
I could not find it.
Does the subroutine have a way of knowing the upper and limits of
the array for boundary checking, to prevent storing information
outside its bounds? Otherwise you could get some nasty hard to find bugs.
Link Copied
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Passing info about an array
I treied using both DIM and LEN to pass information about an array I input
to a subroutine. For example:
REAL A(-23:35)
CALL SUB1(A)
Do I explicititly have to tell it how big the array is in a separate
item in the call sequence? In this case, A has 59 elements,
(35-(-23)+1) so would I have to say:
REAL A(-23:35)
CALL SUB1(59,A)
SUBROUTINE SUB1(NA,A)
REAL A(1:NA)
INTEGER NA
---------------------------------------------------------------------------------------
I thought that the newest Fotran has a way to provide all that info
just by passing the array name.
Maybe there is an article about this somewhere?
I could not find it.
Does the subroutine have a way of knowing the upper and limits of
the array for boundary checking, to prevent storing information
outside its bounds? Otherwise you could get some nasty hard to find bugs.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Use, for example, assumed shape arrays. See if this complete example illustrates their usage:
[fortran]
program passarr
real, allocatable :: A(:)
real :: s
integer :: i
allocate(A(-23:35))
do i=-23,35
A(i) = 0.5*i+13.1
end do
call sub(A,s)
write(*,*)'s = ',s
CONTAINS
subroutine sub(A,s)
real, dimension(:),intent(in) :: A
real,intent(out) :: s
s=sum(A*A)
return
end subroutine sub
end program passarr
[/fortran]
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
I will try that, but I am wondering:
Does it HAVE to be allocatable for this to work?
Also, you multiply A by itself - -
Is that a DOT product, or an element by element multiply?
Actually, this example doesn't work.
It says I cannot omit the upper bound with
an assumed size array, a compiler error message.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
It also says that " the required interface info is missing."
Error 7978. What do they mean?
I will try making it "allocatable," see what happens.
Well, that crashes it also. Error 6646.
Does that subroutine have to be CONTAINED inside the
calling program? With what I did, they are in separate files.
Does that imply that the interface info cannot be passed in the calling sequence?
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
There are some instances of calling subprograms, one of those being the passing of assumed-size arrays as arguments, where an explicit interface is required. If, as a result of making haphazard changes to a working program, or for other reasons, such a required interface is not provided, the altered program may fail to compile or may cause runtime errors.
Intel Fortran provides the /warn:interfaces option to help catch such errors. Finally, at some point a Fortran textbook or the reference manual provided with the compiler may have to be consulted.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
"some" instances? What instances?
Why does this have to be a guessing game?
Can't they spell it out?
Doesn't Intel have a reference?
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
In the help for version 13.1, have a look under Language Reference > Program Units and Procedures > Procedure Interfaces > Procedures that Require Explicit Interfaces. Here's an online link.
Assumed size arrays are dummy arguments declared with * as their last dimension specification. At runtime the compiler/program doesn't inately know the shape of an assumed size array - hence you are prohibited from using the array in a context where the shape is required.
Assumed or deferred shape arrays are dummy arguments declared with : for their dimension specifications - the additional argument passing machinery for these arrays means that the compiler/program does know at runtime what the shape of the array is.
(Passing an assumed size array, without any qualification, as an actual argument to a an assumed shape dummy is an example of an operation that effectively requires the compiler to know the size of the assumed size array - hence this isn't permitted - you need to provide an upper bound for the array reference in the actual argument.)
For completeness a dummy argument which has all dimensions explicitly specified out (perhaps using expressions involving other dummy arguments or common block variables) is known as an explicit shape array.
Note that you need an explicit interface for both assumed shape and deferred shape - the "new stuff" (over two decades new now!). You don't need one for "old style" assumed size or explicit shape. Module procedures and internal procedures (procedures that appear after a contains in a module, or after contains in the same procedure, respectively) automatically get an explicit interface (if a module procedure is referenced outside of the module that defines the procedure then you need a USE statement that references the defininig module). If you have a traditional external subprogram then you typically need to write an INTERFACE block for the procedure in the scope in which is is referenced order to give it an explicit interface. All up, putting procedures in a module is usually the easiest way to go.
[fortran]SUBROUTINE sub(assumed_size, assumed_shape, deferred_shape)
INTEGER :: assumed_size(*)
INTEGER :: assumed_shape(:)
INTEGER, ALLOCATABLE :: deferred_shape(:) ! or POINTER[/fortran]
The default lower bound for assumed size and assumed shape arrays is one. You can override this in the declaration of the dummy argument if you want. For assumed shape the upper bound is then whatever value corresponds to the shape of the actual argument, such that the number of elements in a dimension corresponds between actual and dummy arguments.
The lower and upper bounds for a deferred shape argument are those of the actual argument, assuming the actual argument is allocated or associated. Note this is the case that you originally requested - the distinction being whether you just want the shape (extent) of the array passed across, or you want the bounds passed across.
The multiplication of the two "whole array references" inside the SUM in mecej4's example is an element by element multiplication, that produces and array that is the same size as the operands to the multiplication. The SUM applied to that element by element multiplication then results in the dot product.
If you have the appropriate debugging options enabled (I just use /check:all) then the compiler will check that array subscripts are in range at runtime for assumed shape and deferred shape at least. It will also check the within-procedure suitability of explicit shape arrays, but I don't think it checks that the size of actual arguments exceeds the specified size of a dummy argument.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
That was very helpful - - Thanks ! !
But I think with an upgraded compiler, there should be no reason why the calling
subroutine can't send all the information about upper and lower bounds, array size, etc.
Can the CALLED subroutine still use SIZE and SHAPE to get needed info?
Some of that info cannot be known at compile time, of course.
Especially if the array is allocated.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
When you use the assumed shape feature, with the colon for dimension, an explicit interface is required by the language. While the Intel compiler has an option to help you find cases where you need an explicit interface and don't have one, the language does not allow the compiler to "peek" into routines to do this for you. For some background, see Doctor Fortran Gets Explicit - Again!
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
OK, I will look into that -
Thanks ! ! !
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Two comments here--and somebody please correct me if I am wrong!
Ian's comments are very useful but he may be unclear about being "prohibited from using an assumed SIZE array" (one declared with * as the last dimension). It's true that the compiler doesn't know the size of this dimension, but there are many many many traditional Fortran subroutines that work this way and I believe they still work (even though this practice may be discouraged by some, but it can still be damn convenient). The disadvantage is that the compiler will not be able to flag out-of-bounds run time errors--it is the programmer's responsibility that the size of * is not exceeded.
Regarding a simple way for the compiler to pass the size information automatically in this day and age, keep in mind that a cornerstone of Fortran is that two subroutines may not be in the same file, and the compiler compiles different files separately and independently. So the size details (as well as other details such as type agreement) cannot be passed. The "inventions" of modules, internal procedures, and explicit interfaces are what provides the information in these cases.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
The prohibition on assumed size arrays relates to their use in certain situations, it is not a general prohibition or some sort of style recommendation against them. They are still very much legal fortran (and still required in certain use cases, regardless of people's personal style). I only mentioned them because this aspect was behind one of the error messages that billsincl saw, where it looks there was an attempt to pass an assumed size array (on the calling side) to an assumed shape dummy.
For clarity, you can't do:
[fortran]SUBROUTINE sub(assumed_size)
REAL, INTENT(IN) :: assumed_size(*)
PRINT *, SUM(assumed_size)
[/fortran]
because in order to calculate the sum of an array, the compiler/program needs to know the size of the array (how many elements to sum). The same requirement would exist if SUM was a user procedure that had an assumed shape dummy argument. If the print statement was changed to:
[fortran]PRINT *, SUM(assumed_size(:some_upper_bound))[/fortran]
then it is fine - the size information has been provided by the programmer.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
I see your point, but what I am trying to say is that the compiler (or linker)
COULD provide the size by default. Now whether or not the CALLED routine wants to USE that would be optional.
Example:
REAL A(-25:25)
CALL SUB1(A(-7:13))
subroutine sub1(x)
real x(:)
Supposedly, the CALLED routine should know that you are passing 21 elements to it.
So there could be a check to see if a subscript was <1 or > 21,
and generate a breakpoint if needed by default.
however, if it was called this way:
CALL SUB1(A)
Then SUB1 would know that you are passing 51 elements.
Now what if we did this:
REAL A(50)
CALL SUB1(A)
SUBROUTINE SUB1(X)
real X(-5:5)
Then x(-5) would correspond to A(1), x(0) would correspond to a(6),
etc. This is what I meant by an "imbedded" array. I suppose in this case, the
subscript check on X would be from -5 to +5. So you are OVERRIDING
the information passed to it.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
In the first case, Bill, the compiler does exactly what you want - but an explicit interface is required. The second case is also legal in Fortran, but there is no bounds information passed so it can't be automatically checked.
Theoretically, yes, the compiler could come up with a way to pass the bounds information in some other way, and check for it, but that would create incompatibilities when calling routines not compiled that way. Do keep in mind that arrays can have run-time bounds - it's not as simple as you think.
Just use assumed-shape arrays (and module or contained procedures) and it will all work out automatically the way the language is designed.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Hi Steve;
I understand what you are saying-
But when you say "not compiled that way," are you saying that the two routines
(CALLED and CALLING) are compiled with different compilers? I was assuming
that if they are in the SAME PROJECT they would be compiled the same way.
Of course if one is C++ and the other Fortran, all bets are off. Maybe if they are in the same SOLUTION
space, they would by default be compiled the "same way." Perhaps for mixed languages, there could
be a universal standard?
"Never the twain shall meet ?"
I made that suggestion mostly because of the problem
with run-time bounds. With an allocatable array, there is
no way the compiler would know about those, since they can be
determined by user input.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
tropfen, when you use (*) in the array bounds, only the base address of the array is passed - no size information. It is, however, the programmer's responsibility to make sure that the called routine does not access past the end of the array that was passed.
Bill, I am not talking about different compilers, but objects compiled at different times. There are other compilers that do have options to pass "hidden" information about array bounds for debugging purposes, but we don't do that. The Static Analysis feature can sometimes uncover errors made in this regard, but using modern Fortran programming practices obviates a need for worrying about implicit array bounds.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Bill,
You might want to run this simple example from the code you provided:
[fortran]
! test of array bounds
!
REAL A(-25:25), B(-3:19)
!
interface
subroutine sub1 (x)
real x(:)
end subroutine sub1
end interface
!
CALL SUB1(A(-7:13))
CALL SUB1(A)
CALL SUB1(B)
end
subroutine sub1 (x)
real x(:)
!
write (*,*) 'Sub1 : size =',size(x), lbound(x), ubound(x)
end
[/fortran]
With INTERFACE, you only get the size information, not the bounds if they are not of the form A(1:n)
John
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Now with this example, you would not get the bounds of the CALLING routine array, right?
I will play with this - thanks....
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
You get the extent of the array - the number of elements. The lower bound will always be 1 (unless you specify something like (0:).) The original bounds are not available this way, but it allows the subroutine to accept something that doesn't really have bounds, such as an array section.
If you must preserve the bounds, then you need to pass a POINTER to a dummy argument that is also a POINTER.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Bill,
If you want the bounds info, then code it, as you have always been able to do, and it does not require an INTERFACE !
[fortran]! test of array bounds
!
REAL A(-25:25), B(-3:19)
!
CALL SUB77 (A(-7:13),-7,13)
CALL SUB77 (A, lbound(a), ubound(a))
CALL SUB77 (B, lbound(b), ubound(b))
end
!
subroutine sub77 (x,i,j)
integer i,j
real x(i:j)
!
write (*,*) 'Sub1 : size =',size(x), lbound(x), ubound(x)
end
[/fortran]
John

- Subscribe to RSS Feed
- Mark Topic as New
- Mark Topic as Read
- Float this Topic for Current User
- Bookmark
- Subscribe
- Printer Friendly Page