Putting Fortran code in modules

I think in modern Fortran code other than that in the main program should be in modules, but there is much code that does not follow this convention. John Burkardt does not use modules in his vast Fortran 90 collection. His source files do contain multiple related procedures, so the obvious fix is to put

module m
contains

at the top and

end module m

at the bottom of such files. However, typically some declarations need to be removed. Here is an illustration. The code

function square(i) result(i2)
implicit none
integer, intent(in) :: i
integer             :: i2
i2 = i**2
end function square

function cube(i) result(i3)
implicit none
integer, intent(in) :: i
integer             :: i3
integer             :: square
i3 = i * square(i)
end function cube

program main
implicit none
integer :: cube
print*,cube(5)
end program main

compiles and runs. The equivalent code with a module that compiles and runs is

module m
contains
function square(i) result(i2)
implicit none
integer, intent(in) :: i
integer             :: i2
i2 = i**2
end function square

function cube(i) result(i3)
implicit none
integer, intent(in) :: i
integer             :: i3
! integer             :: square
i3 = i * square(i)
end function cube
end module m

program main
use m
implicit none
! integer :: cube
print*,cube(5)
end program main

In function cube the declaration integer :: square must be removed. If it is not, you get an error message such as

xmodule.f90:(.text+0x1a): undefined reference to square_’`

where xmodule.f90 is the file containing all the code. So to transform a Fortran code that is comprised of multiple source files to one in which procedures are in modules, one needs to

(1) put the code in each source file in a module. My convention is that a file foo.f90 contains module foo_mod.
(2) remove declarations of called functions in the caller, as shown above
(3) add the appropriate use foo_mod statement in the caller, for procedures invoked from other modules or the main program

I wonder if there are tools for this. It would be great if Burkardt’s codes could be organized into hundreds of modules and the demonstration programs USEd those modules.

4 Likes

I know of no particular tools, but with a bit of scripting, repeated compilation and stubborn editing we should be able to solve the issue.
Note that you missed one change: if the source file contains several subroutines and functions, then they should end with “end subroutine” and “end function”. Most of the changes can be done by a simple-minded script. That would reduce the amount of manual labour by 99% (rough estimate).

If I recall the standard correctly, the error doesn’t seem to make sense. The processor needn’t complain here. square will get used with an implicit interface even though explicit interface is available, but that is a separate (albeit serious) matter.

Re: the vast codes by Burkardt, should the same file organization be maintained, the use of SUBMODULEs can be a consideration though that can be far more work unfortunately.

From Fortran 2008 on, just end suffices, although I think end subroutine foo and
end function foo is more readable. For the code

module m
contains
function square(i) result(i2)
implicit none
integer, intent(in) :: i
integer             :: i2
i2 = i**2
end

function cube(i) result(i3)
implicit none
integer, intent(in) :: i
integer             :: i3
i3 = i * square(i)
end
end

program main
use m
implicit none
print*,cube(5)
end

ifort -nologo -stand:f03 xmodule_end.f90 says

xmodule_end.f90(8): warning #6377: The f2003 standard requires FUNCTION to be present on the end-function-stmt of an internal or module function.
end
^
xmodule_end.f90(15): warning #6377: The f2003 standard requires FUNCTION to be present on the end-function-stmt of an internal or module function.
end
^

but is silent with the default option or with stand:f08 or stand:f18. Gfortran is similar. G95 does not accept the code but is a Fortran 95 compiler with a few extensions.

Oh, I was not aware of that feature, but I fully agree that “end function”/“end subroutine” is more readable

The message is from the link step, so apparently the compiler has recognised it as an external procedure. Which is a bit odd, I’d say, since there is clearly a prcoedure by the same name in the module it is part of.

So to complete the thought, the “ideal” code structure in my mind per current Fortran standard while maintaining the organization by John Burkardt of separate files for major algorithmic implementations will be as follows:

! module with interfaces to be USE'd by practitioners
module intops_m
   implicit none ( type, external )
   interface
      module function square(i) result(i2)
         implicit none
         integer, intent(in) :: i
         integer             :: i2
      end function square
      module function cube(i) result(i3)
         implicit none
         integer, intent(in) :: i
         integer             :: i3
      end function cube
   end interface
end module
! Implementation in a separate file
submodule (intops_m) square_sm
contains
   module function square(i) result(i2)
      integer, intent(in) :: i
      integer             :: i2
      i2 = i**2
   end function square
end submodule
! Implementation in a separate file
submodule (intops_m) cube_sm
contains
   module function cube(i) result(i3)
      integer, intent(in) :: i
      integer             :: i3
      i3 = i * square(i)
   end function cube
end submodule

A script or a smart and kind processor should be able to take what might currently be a set of separate external procedures with implicit interfaces as with Burkardt’s code currently at the FSU site and refactor them into explicit interfaces facilitated by a module-submodule organization as suggested above. Something LFortran might consider?

(4) One also needs to remove EXTERNAL declarations from the code, since for example the code below will not compile if the commented out lines are reinstated:

module m
contains
function square(i) result(i2)
implicit none
integer, intent(in) :: i
integer             :: i2
i2 = i**2
end function square

function cube(i) result(i3)
implicit none
integer, intent(in) :: i
integer             :: i3
! external square
i3 = i * square(i)
end function cube
end module m

program main
use m
implicit none
! external cube
print*,cube(5)
end program main

An alternative to submodules might be a simple INCLUDE; not ideal but perhaps the lesser of two evils. With a large package of large files you are converting to a module it can work very nicely, and can be done
gradually. Have done it with a lot of older code where changes were also being made to use free-format and implicit none and other style changes. Tried submodules and folding editors and a variety of other methods.

Although not typically a fan of using INCLUDE files with modern-style code (they were good for ensuring old COMMON blocks were consistent in the past) it works very nicely for this purpose.

Nice example @kargl. Btw, you don’t need to use epsilon(ax), but 1e-8 is sufficient for double precision, because sin(x)/x = 1 in the range [0, 1e-8]. Btw, the series expansion is:

In [1]: from sympy import *

In [2]: var("x")
Out[2]: x

In [3]: (sin(x)/x).series(x)
Out[3]: 1 - x**2/6 + x**4/120 + O(x**6)

So one can see that that when x**2/6 < epsilon(x) ~ 2.22e-16, the result will be 1, equivalently x < sqrt(6*epsilon(x)) = sqrt(1.3e-15) = 3.6e-8. So I think you can write the code as:

if (ax < sqrt(6*epsilon(ax))) then
  res = 1
else
  res = sin(ax) / ax
end if

P.S. @FortranFan this another use case for generics.

I figured you knew what you were doing. :slight_smile:

Is the code I suggested incorrect? I’ve been computing it that way in my codes (I hardwire 1e-8, but I think the expression sqrt(6*epsilon(ax)) should also work).

F202X is getting the condition operator, so the above code (I think) will become valid.

In Arjen’s honour we have made a command in fpt to ensure all routines end with end subroutine or end function, naming the sub-program. Easy to put the routines into modules. But the compilation times can become a serious problem.

1 Like