I have been working for quite some time with a scientific (academic) software for mechanical analysis. Now, the code started from the eighties (Fortran 77) and arrived to me in a mixed/hybrid form of Fortran 90/95. However, due to the necessities of adding powerful tools like MKL, I decided to move from the old Intel Visual Fortran 11.072 (using VS2008) to the "recent" 14.0 (in ComposerXE 2013). The F77 core compiles without problem, but I am having troubles with some interfaces in subroutines that deals with deferred definition of variables. Instead of annoying with huge routines, I made a MWE able to repeat the issues.
The mini-program is copied in the following, so you can tinker with it:
program main
implicit none
print *, 'Start of the program'
call mainsub
print *, 'End of the program'
pause
end program
There is a module problem.f that define sizes:
module problem
implicit none
save
integer, parameter :: size1 = 6
integer, parameter :: size2 = 3
integer, parameter :: size3 = 18
end module problem
So, there is a main subroutine that call the "first level" subroutines:
SUBROUTINE mainsub
use problem ! here there are the dimensions defined
implicit none
! Scalars (almost)
REAL*8 :: sca01, sca02(size2), sca03
! Vectors
REAL*8 :: arr01(size1)
REAL*8 :: arr02(size1)
REAL*8 :: arr03(size3)
REAL*8 :: arr04(size1)
! Matrices
REAL*8 :: mat01(size1,size1)
REAL*8 :: mat02(size3)
! trying to trick IFORT with interface (hiding dimension)
print *, 'Calling sub11'
CALL sub11(arr01)
print *, 'Calling sub11 - end'
pause
print *, 'Calling sub12'
CALL sub12(arr02,arr03,arr04)
print *, 'Calling sub12 - end'
pause
print *, 'Calling sub13'
CALL sub13(mat01,mat02)
print *, 'Calling sub13 - end'
pause
print *, 'Calling sub14'
CALL sub14(sca01,sca02,sca03)
print *, 'Calling sub14 - end'
pause
contains
subroutine sub11(arr01)
use problem
implicit none
REAL*8, DIMENSION(:) :: arr01
print *, 'This is sub11, size arr01: ', SIZE(arr01), SHAPE(arr01)
CALL sub21(arr01)
end subroutine
end subroutine
These are the "first level" subroutines
SUBROUTINE sub12(arr02, arr03, arr04)
use problem
implicit none
REAL*8 :: arr02(*)
REAL*8 :: arr03(size3)
REAL*8 :: arr04(*)
REAL*8 :: dummy(600)
print *, 'sub 12'
call sub22(arr02, dummy, arr04)
END SUBROUTINE
SUBROUTINE sub13(mat01,mat02)
use problem
implicit none
REAL*8 :: mat01(size1,size1)
REAL*8 :: mat02(size3,*)
print *, 'sub 13'
call sub23(mat01, mat02)
END SUBROUTINE
SUBROUTINE sub14(sca01,sca02,sca03)
use problem
implicit none
REAL*8 :: sca01, sca02(*), sca03
REAL*8 :: dummy(600)
print *, 'sub 14'
call sub24(sca01, dummy, sca03)
END SUBROUTINE
And finally these are the "second level" subroutines:
SUBROUTINE sub21(arr01)
use problem
implicit none
REAL*8 :: arr01(size3,size1)
print *, 'This is sub21, size arr01: ', SIZE(arr01)
END SUBROUTINE
SUBROUTINE sub22(arr02, arr03, arr04)
use problem
implicit none
REAL*8 :: arr02(size3)
REAL*8 :: arr03(size3)
REAL*8 :: arr04(size2,size3)
print *, 'sub22'
print *, SIZE(arr02)
print *, SIZE(arr03)
print *, SIZE(arr04)
END SUBROUTINE
SUBROUTINE sub23(mat01,mat02)
use problem
implicit none
REAL*8 :: mat01(size1,size2)
REAL*8 :: mat02(size1,size2,size3)
print *, 'sub 23'
print *, SHAPE(mat01), SIZE(mat01)
print *, SHAPE(mat02), SIZE(mat02)
end subroutine
SUBROUTINE sub24(sca01,sca02,sca03)
use problem
implicit none
REAL*8 :: sca01, sca02(*), sca03
print *, 'sub 24'
print *, SHAPE(sca01), SHAPE(sca03)
end subroutine
This code compiles correctly on my machine with Intel Fortran 14. Now, let's consider the series of cases that can arise.
Common variable mismatchs If I define one actual variable as Real*8 and in the subroutine the respective dummy one is Real*4 or, mixing up Real*8 --> Integer*8, the compiler recognizes the mismatch and gives the error. Similarly, if I define a scalar variable Real sca01 and in the subroutine I define it Real sca01(*) or Real sca01(size1), the compiler recognize again that one is array and the other is not, so it throws an error. (error #6633: The type of the actual argument differs from the type of the dummy argument.)
Array size mismatch If you define one array as arr02(size1) and in the called subroutine arr02(size2), the mismatch is noticed by the compiler only if the runtime check error are active and if the integers size1,size2 are declared as parameters (like in the module problem.f).
However, I put an intermediate subroutine in the middle of two definitions, like in the MWE above:
sub11 -- sub21
/
mainsub --- sub12 -- sub22
\
sub13 -- sub23
The interface with the CONTAINS statement (mainsub to sub11) checks that the size and the dimensions of the actual and dummy variables coincide. However, it does not check that the next call to sub21 loses track of the size on the way out from the interfaced subroutine.
In sub12, by using the assumed shape array (*) definition, I can change shape and size as I want. Surely, I will have a segmentation fault at some point but even if I have all runtime checks on and constant sizes, no error or warning is thrown.
Finally, for sub12 the trick works also in multiple dimensions, and sometimes even if it is not shape-assumed array, like in the case of mat02 (which is strange...).
Consequently, I have few questions:
which is the difference between the interface definition with ( * ) and ( : )?
if ( * ) is like deferred definition of the size of the array, why does it not work with scalars? (assuming that scalars are array 1x1) and why does it not check the sizes through the subroutines?
in Intel Fortran 11 many size check of array were not done. Now, with Intel Fortran 14, I have a lot of #6633, #6634 and #8284 errors. What did it change?
given this hybrid Fortran77/90/95 panorama, which definitions should I consider to maintain and which not? (obviously among the used above and not entering in object oriented, since it is a procedural program)
which is then the philosophy (o main practical reason) of variable definition in Fortran? If I can "trick" the compiler with a procedural program (and sizes that are constant, no allocatables), I guess I am missing something.
I would like to apologize for the length of the question, but having studied Fortran alone and not having a CS background, I feel I am missing the jist of the question...
Thank you!
For dummy arguments, dummy(*)
declares an assumed size array, dummy(:)
declares an assumed shape array [and for completeness, dummy(some_expression)
declares an explicit shape array].
For an assumed size array:
The actual argument must be something that can yield an array element sequence, but the dimensions of the actual argument do not need to be the same as the dimensions of the dummy.
Inside the procedure with the dummy, the size of the actual argument is not automatically known, and you cannot invoke operations on the dummy argument that require that size (e.g. SIZE(dummy)
is not permitted. If the size of the array element sequence designated by the actual argument is required inside the procedure for some reason, then the user needs to pass it separately.
An explicit interface is not required in a scope that invokes the procedure. (Assumed size is a concept from Fortran 77, before the language had the concept of an explicit interface.)
For an assumed shape array:
The actual argument must match in rank with the dummy.
Inside the procedure, the size and shape of the actual argument is automatically available through the dummy.
An explicit interface to the procedure is required in any scope that invokes the procedure.
Explicit size arrays are similar to assumed size arrays, but inside the procedure the size of the array is known (because it was explicitly declared!). The size of the array element sequence designated by the actual argument must be the same or greater than the explicitly specified size.
An actual argument that is a scalar variable name (that isn't of type CHARACTER and of default or C_CHAR kind) does not designate an array element sequence. As a general principle, a scalar is not an array.
Improvements to the ability of the compiler to find errors in your program have been made. Also, some compiler options related to error checking may have changed defaults. (Note that different compilers have different diagnostic capability in this area.)
Which type of array declaration (and there are others besides those discussed here) is best depends on what you are trying to do, but as a guideline for new code, if the restrictions around assumed shape don't cause issues, then use assumed shape for arrays.
There is no guarantee that the compiler will catch all programming errors. Different declarations are for different purposes.