Difference between subroutine inside module "contains" and outside module - fortran

I have a large source code where subroutines in modules are defined outside the module ... end module statement (ie. not inside a contains statement). I've included a simplified module below:
module core
implicit none
type :: disc_status
sequence
real*8 :: alpha1, alpha2, alpha3
end type disc_status
end module core
subroutine tester(input)
use core
type(disc_status), intent(in) :: input
print *, input%alpha1, input%alpha2, input%alpha3
end subroutine tester
Here's an example program using the module and subroutine:
program flyingDiscSimulator
use core
implicit none
type(disc_status) :: disc
disc%alpha1 = 1.1D0
disc%alpha2 = 1.2D0
disc%alpha3 = 1.3D0
call tester(disc)
print *, 'it works'
end program flyingDiscSimulator
Normally, I end up seeing subroutines use the contains statement within a module:
module core
implicit none
type :: disc_status
sequence
real*8 :: alpha1, alpha2, alpha3
end type disc_status
contains
subroutine tester(input)
type(disc_status), intent(in) :: input
print *, input%alpha1, input%alpha2, input%alpha3
end subroutine tester
end module core
However, the program file referenced above doesn't require any changes to use either way of including a subroutine in a module (using gfortran anyways). Thus, there appears to be no difference in the usage of the module or it's subroutine between the two solutions. Are there any "under the hood" differences between the two styles?

The versions
module m
contains
subroutine s()
end subroutine s
end module m
and
module m
end module m
subroutine s()
end subroutine s
say completely different things, but in the case of the question the end results are much the same.
The first version here creates a module procedure s with host m; the second version has an external procedure s with no host.
Although the example of the question has the external procedure using the module, there is more generally a difference: the module procedure has access to all entities in the module (except when made inaccessible through an import statement or by being obscured by local names; the external procedure using the module has access only to those public entities.
However, come the main program the effects are different. The external subroutine and its name are global entities. Going to my second version, then
program main
call s
end program
is a valid program which calls the external subroutine s. This subroutine reference is valid because the implicit interface for s in the main program suffices. If the external subroutine s were such than an explicit interface were required then main program here would not be allowed. It is acceptable, but not required, to have an external s statement in the main program to reinforce to the reader that the subroutine is an external one (with implicit interface). (implicit none external would make external s necessary.)
The example of the question is such that an explicit interface is not required.
A module procedure always has an explicit interface available when accessible. However, a module procedure is not a global entity and its name is not a global identifier.
Under the hood, there are implementation differences (stemming from the above): most notably compilers will often "name mangle" module procedures.
In summary, there are differences between the two approaches of the question, but they won't be noticed by the programmer in this case.

The procedure inside the module will have an explicit interface (aka the compiler knows about the arguments' characteristics).
Whereas the procedure outside of the module will have an implicit interface (aka the compiler must make assumptions about the arguments).
Explicit interfaces help the compiler to find programming errors and are therefore favourable.
For a more indepth discussion of advantages see for example this answer.
I am not even sure if it is valid Fortran to call tester inside the program when it is defined outside of core?
The line use core should just make the module's public objects known and the tester procedure needs its own external tester line.

Related

subroutine using module but is outside module and also used in module through an interface

When I have a subroutine outside a module but is used by means of a "pointer assignment" and the subroutine is defined by means of an interface but the real subroutine is in a separate file and used module I get compiler errors.
So when I have the following Fortran code:
module test_mod_a
save
type test_type_a
integer :: scl_a = 0
contains
procedure :: my_subr => test_subr_a
end type test_type_a
interface
subroutine test_subr_a(this)
import test_type_a
implicit none
class(test_type_a) :: this
end subroutine test_subr_a
end interface
end module test_mod_a
and
subroutine test_subr_a(this)
use test_mod_a
implicit none
class(test_type_a) :: this
end subroutine test_subr_a
When I give the commands (gfortran version 9.3.0):
gfortran -c test_a.f90
gfortran -c test_a_subr.f90
I get the compiler error:
test_a_subr.f90:3:6:
3 | use test_mod_a
| 1
Error: ‘test_subr_a’ of module ‘test_mod_a’, imported at (1), is also the name of the current program unit
There are a few ways to overcome this problem:
replace !use test_mod_a by !use test_mod_a, only : test_type_a
include the subroutine in the module (and discarding in the subroutine the use statement and in the module the interface
all a bit cumbersome for a large project.
Is there another way?
As well as the use of only (not including the name of the procedure), there are the two other techniques for avoiding identifier re-use:
private test_subr_a in the module
Use renaming in the subroutine with use test_mod_a, self_iface => test_subr_a
However, from the look of the structure it seems the intention really is for test_subr_a to be like a module subroutine but isn't for one of two reasons:
there's been incremental development of an old program and the external subroutine now wants to be used in a "modern" way
the implementation of the subroutine is split out for reasons of file size, avoiding compilation cascades, secrecy of implementation
With the luxury of changing the code in a significant way one can handle these.
For the first reason, one could go ahead and move the subroutine into the module and take the pain of having to update other references where it was an external subroutine. As mentioned in the question.
For the second reason, submodules could be considered:
module test_mod_a
implicit none
type test_type_a
integer :: scl_a = 0
contains
procedure :: my_subr => test_subr_a
end type test_type_a
interface
module subroutine test_subr_a(this)
class(test_type_a) :: this
end subroutine test_subr_a
end interface
end module test_mod_a
submodule(test_mod_a) implementation_a
implicit none
contains
module subroutine test_subr_a(this)
class(test_type_a) :: this
end subroutine test_subr_a
end submodule implementation_a
Again, test_subr_a is no longer an external subroutine, so other references may need fixing.

iso_fortran_env kind values not compile-time constant [duplicate]

In a Fortran 2003 module I'm defining a type called t_savepoint and, later, I want to define an interface for a subroutine called fs_initializesavepoint, which takes an object of type t_savepoint as only argument.
Here is the code for the whole module:
module m_serialization
implicit none
type :: t_savepoint
integer :: savepoint_index
real :: savepoint_value
end type t_savepoint
interface
subroutine fs_initializesavepoint(savepoint)
type(t_savepoint) :: savepoint
end subroutine fs_initializesavepoint
end interface
end module m_serialization
The reason why I want such an interface is that later on I will make this fortran module interoperate with C.
If I try to compile it (gfortran-4.7.0), I get the following error message:
type(t_savepoint) :: savepoint
1
Error: The type of 'savepoint' at (1) has not been declared within the interface
The error disappears if I move the definition of the type inside the subroutine; but if then I want to use the same type within many subroutines, should I repeat the definition in all of them?
Thank you in advance.
EDIT: a solution would be to move the definition of the type onto another module and then to use it in every subroutine. However I don't like this solution too much, because the type t_savepoint and the subroutines are part of the same conceptual topic.
Rightly or wrongly in an interface block you don't have access to the environment by host association. To fix this you need to import the datatype exlicitly:
[luser#cromer stackoverflow]$ cat type.f90
module m_serialization
implicit none
type :: t_savepoint
integer :: savepoint_index
real :: savepoint_value
end type t_savepoint
interface
subroutine fs_initializesavepoint(savepoint)
Import :: t_savepoint
type(t_savepoint) :: savepoint
end subroutine fs_initializesavepoint
end interface
end module m_serialization
[luser#cromer stackoverflow]$ gfortran -c type.f90
This is f2003.
However I suspect the way you have put this suggests you are not going about coding this up the best way. Better is simply to put the routine itself in the module. Then you don't need bother with the interface at all:
module m_serialization
implicit none
type :: t_savepoint
integer :: savepoint_index
real :: savepoint_value
end type t_savepoint
Contains
Subroutine fs_initializesavepoint(savepoint)
type(t_savepoint) :: savepoint
Write( *, * ) savepoint%savepoint_index, savepoint%savepoint_value
End Subroutine fs_initializesavepoint
end module m_serialization
[luser#cromer stackoverflow]$ gfortran -c type.f90
Given that modules are really designed to deal with connected entities this is really the way to do it in Fortran. It also has the advantage of only requiring a f95 compiler, so is universally available (though admittedly import is commonly implemented)

Nested contains statement

I have a program like this
program
call one()
contains one()
some vars
contains two()
use the vars of one
define its own vars
contains three()
use the vars of both one and two
This doesn't compile because Fortran allows only the first contains statement.
I used this design to avoid passing and retyping all the variables of one() into two() and three().
How can I rewrite the program so that the variable sharing is achieved?
I cannot define all the variable before the statement call one().
The code will be to hard to manage, I need the feature :
parent subroutine cannot access internal subroutine variables.
Maybe a solution is to use pointer
call one(pointer_to_two)
then define the routine two() in its own module.
But I find this design complicate with my limited Fortran skills.
And I'm worried it will impact performance.
Should I use a common block?
I use the latest dialect of Fortran with the Intel compiler.
Below is 'compilable' example.
program nested_routines
call one()
contains
subroutine one()
integer :: var_from_one = 10
print *, 1
call b()
contains
subroutine two()
integer :: var_from_two = 20
print *, 2, var_from_one
call c()
contains
subroutine three()
print *, 3, var_from_one, var_from_two
end subroutine
end subroutine
end subroutine
end module
I recommend placing your procedures (subroutines and functions) into a module after a single "contains" and using that module from your main program. The local variables of each procedure will be hidden their callers. The way that this differs from your goals is that you have to redeclare variables. I dislike the inheritance of all variables in a subroutine contained in another because it is possible to mistakenly reuse a variable. If you have a few variables that are shared across many procedures, perhaps the appropriate design choice is to make them global. With Fortran >=90, a module variable is better method for a global variable than common blocks. If you have variables that are communicated between a limited number of procedures, it is generally better to use arguments because that makes the information flow clearer.
this might be possible if there is a separate module for each of the functions specific variables and a separate module for each function implementation
watch out for the order of the module compilation, according to the usage hierarchy necessity
also, i have no idea on the performance effect of doing this
module m1_var
implicit none
contains
end module m1_var
!========================================================================================================================
module m2_var
implicit none
contains
end module m2_var
!========================================================================================================================
module m3_var
implicit none
contains
end module m3_var
!========================================================================================================================
module m3_sub
implicit none
contains
subroutine s3()
use m2_var !to see varibles
!arguments
!local
!allocation
!implementation
end subroutine s3
end module m3_sub
!========================================================================================================================
module m2_sub
implicit none
contains
subroutine s2()
use m3_sub
use m1_var
!arguments
!local
!allocation
!implementation
call s3
end subroutine s2
end module m2_sub
!========================================================================================================================
module m1_sub
use m1_var
implicit none
contains
subroutine s1()
use m2_sub
!arguments
!local
!allocation
!implementation
! call s2
end subroutine s1
end module m1_sub
!========================================================================================================================
program nestmoduse
use m1_sub
implicit none
call s1
end program nestmoduse

How to print data from a module used in my fortran subroutine

Thanks for the help in advance..
Kindly I want to print data in an output file of the main FORTRAN program and these data defined in a module and I already declare using that module in the main program. but I couldn't get the write statements neither in the main program nor in the module.
MODULE model
IMPLICIT NONE
SUBROUTINE model_initialize
IMPLICIT NONE
INTEGER a,dim REAL(float) :: E,nu
REAL(float) :: lambda,mu
E=5000 lambda = E*nu/(1.d0+nu)/(1.d0-2.d0*nu)
mu = E/2.d0/(1.d0+nu)
RETURN
END SUBROUTINE model_initialize
Write (6,)'Lambda',lambda
Write (6,)'mu',mu
END MODULE model
SUBROUTINE XXXX
USE model
IMPLICIT NONE
CALL model_initialize
Write (6,)'Lambda',lambda
Write (6,)'mu',mu
END SUBROUTINE XXX
When I put the write statements in the module or in the main subroutine , I cant see them in the output.
Many thanks for the help
Msekh
Mgilson has already provided you with an example that should work, but the code you posted will not compile. This is why:
Your subroutine model_initialize is in the "specification part" of your module. It should either be external (like xxxx) or internal to the module (in which case you have to provide a contains statement).
The variables in model_initialize are local to the subroutine and will not be accessible outside it.
You cannot have executable code (like write) in the specification part of a module, only in internal procedures.
float is not a native Fortran kind, you have to use the numerical parameters (usually 4, 8, 16), define your own, or use the definitions in the iso_fortran_env module.
That said, if you only need to define some data you want to make accessible, you can simply put that directly in the module like this:
module model
use iso_fortran_env
implicit none
integer :: A, dim
real(real32) :: E, nu, lambda, mu
E = 5000
lambda = E*nu/(1.d0+nu)/(1.d0-2.d0*nu) ! <-- nu is undefined
mu = E/2.d0/(1.d0+nu)
contains
subroutine xxxx
write (6,*) 'lambda', lambda
write (6,*) 'mu', mu
end subroutine xxxx
end module model
do you mean something like:
module material
real :: stress = 6.0
save
end module material
subroutine xxx()
use material, only: stress
write(6,*) stress
end subroutine
program main
call xxx()
end program main
This will write the value of stress to the file-like object connected with unit 6 (usually this is stdout, but it might create a new file called fort.6 depending on compiler and environment settings).

Pass kind parameter to subprogram

Is it possible in modern versions of Fortran to pass a kind parameter to a subprogram and to use this to 'cast' variables to this kind? As an example, in the following code I am trying to convert an default integer to an 16-bit integer before printing it.
program mwe
! Could use iso_fortran_env definition of int16, but I am stuck with
! old versions of ifort and gfortran.
! use, intrinsic :: iso_fortran_env, only : int16
implicit none
! 16-bit (short) integer kind.
integer, parameter :: int16 = selected_int_kind(15)
call convert_print(123, int16)
contains
subroutine convert_print(i, ikind)
implicit none
integer, intent(in) :: i
integer, intent(in) :: ikind
print*, int(i, ikind)
end subroutine convert_print
end program mwe
With this example code the Intel Fortran compiler complains that
mwe.f(24): error #6238: An integer constant expression is required in this context. [IKIND]
...
mwe.f(24): error #6683: A kind type parameter must be a compile-time constant [IKIND]
and gfortran complains
'kind' argument of 'int' intrinsic at (1) must be a constant
Using print*, int(i, int16) in place of print*, int(i, ikind) would of course work fine in this case. However, if convert_print were defined in a a module which does not define int16 then this would be useless.
Is there a way of passing a kind parameter as a constant to subprograms?
I have the same problem. I find extremely inconvenient that it is not allowed to pass the kind datatype as an argument to a procedures. In my case, I am writing write a subroutine to just read a matrix from a file and get the object in the data type that I want to. I had to write four different subroutines: ReadMatrix_int8(…), ReadMatrix_int16(…), ReadMatrix_int32(…) and ReadMatrix_int64(…) which are nothing but the same code with one single line different:
integer(kind=xxxx), allocatable, intent(out) :: matrix(:,:)
It would make sense to write only one subroutine and pass xxxx as an argument. If I find any solution I will let you know. But I am afraid that there is no better solution than writing the four subroutines and then writing an interface to create a generic procedure like:
interface ReadMatrix
module procedure ReadMatrix_int8
module procedure ReadMatrix_int16
module procedure ReadMatrix_int32
module procedure ReadMatrix_int64
end interface
As far as I can work out, what I am trying to do is expressly forbidden by the Fortran 2003 standard (PDF, 4.5 MB):
5.1.2.10 PARAMETER attribute
A named constant shall not be referenced unless it has been defined previously in the same statement, defined in a prior statement, or made accessible by use or host association.
Therefore is seems that I need to define a function for each conversion I wish to do, for example:
subroutine print_byte(i)
implicit none
integer, intent(in) :: i
print*, int(i, int8)
end subroutine print_byte
subroutine print_short(i)
implicit none
integer, intent(in) :: i
print*, int(i, int16)
end subroutine print_short
subroutine print_long(i)
implicit none
integer, intent(in) :: i
print*, int(i, int32)
end subroutine print_long
Obviously all of the above will have to be overloaded to accept different kinds of the input argument. This seems like a lot of work to get around not being able to pass a constant, so if someone has a better solution I am keen to see it.
This Intel expert gives an explanation and an elegant solution. I couldn't explain it better. A full cite follows:
"One day while I was wandering the aisles of my local grocery store, a woman beckoned me over to a table and asked if I would like to "try some imported chocolate?" Neatly arrayed on the table were packages of Lindt, Toblerone, and... Ghiradelli? I asked the woman if California had seceded from the Union, as Ghiradelli, despite its Italian name, hails from San Francisco. I suppose that from the vantage point of New Hampshire, California might as well be another country, much as depicted in that famous Saul Steinberg 1976 cover for The New Yorker, "View of the World from 9th Avenue".
(I've been warned that my blogs don't have enough arbitrary links - this should hold 'em for a while.)
Similarly, in Fortran (I'll bet you were wondering when I'd get to that), something can be so near yet seem so far away. A short time ago, I was writing a new module for Intel Visual Fortran to provide declarations for the Win32 Process Status API. This would contain declarations of types and constants as well as interface blocks for the API routines, some of which take arguments of the new type. The natural inclination is to write something like this:
MODULE psapi
TYPE sometype
some component
END TYPE sometype
INTERFACE
FUNCTION newroutine (arg)
INTEGER :: newroutine
TYPE (sometype) :: arg
END FUNCTION newroutine
END INTERFACE
END MODULE psapi
If you did and compiled it, you'd get an error that type sometype is undefined in the declaration of arg. "What? It's not undeclared, I can see it right above in the same module!" Well, yes and no. Yes, it's declared in the module and could be used anywhere in the module, except.. Except in interface blocks!
The problem is that interface blocks are a "window into the external routine" - they essentially duplicate the declarations you would see in the actual external routine, assuming that routine were written in Fortran. As such, they do not "host associate" any symbols from the enclosing scoping unit (the module in this case.)
In Fortran 90 and Fortran 95, the typical solution for this was to create a separate module, say, "psapi_types", containing all of the types and constants to be used, You'd then add a USE statement inside each function, just as you would have to in the hypothetical external routine written in Fortran. (If it were written in Fortran, the Doctor would slap your wrist with a wet punchcard and tell you to make the routine a module procedure, and then you wouldn't need to worry about this nonsense.) So you would end up with something like this:
MODULE psapi
USE psapi_types ! This is for the benefit of users of module psapi
INTERFACE
FUNCTION newroutine (arg)
USE psapi_types
INTEGER :: newroutine
TYPE (sometype) :: arg
...
Those of you who use Intel Visual Fortran know that in fact there's a giant module IFWINTY for this purpose, containing all of the types and constants for the other Win32 APIs. It's messy and inelegant, but that's what you have to do. Until now...
Fortran 2003 attempts to restore some elegance to this sorry situation, but to preserve compatibility with older sources, it couldn't just declare that interface blocks participate in host association. Instead, a new statement was created, IMPORT. IMPORT is allowed to appear in interface blocks only and it tells the compiler to import names visible in the host scope.
IMPORT is placed following any USE statements but before any IMPLICIT statements in an interface body (the FUNCTION or SUBROUTINE declaration). IMPORT can have an optional import-name-list, much like USE. Without one, all entities accessible in the host become visible inside the interface body. With a list, only the named entities are visible.
With IMPORT, my PSAPI module can look like the first example with the following change:
...
FUNCTION newroutine (arg)
IMPORT
INTEGER :: newroutine
TYPE(sometype) :: arg
...
I could, if I wanted to, use:
IMPORT :: sometype
to say that I wanted only that one name imported. Nice and neat and all in one module!
"But why are you telling me this?", you might ask, "That's a Fortran 2003 feature and Intel Fortran doesn't yet do all of Fortran 2003." True enough, but we keep adding more and more F2003 features to the compiler and IMPORT made it in back in August! So if you are keeping reasonbly current, you can now IMPORT to your heart's content and do away with the mess of a separate module for your types and constants.
If you want to know what other F2003 goodies are available to you, just check the Release Notes for each update. A full list of supported F2003 features is in each issue. Collect 'em all!"