Daisy-chaining USE statements with Fortran modules - fortran

The context to my question isn't really easy to describe, so suffice it to say that I have good reasons for attempting to structure a DLL F90 project such that -
I have some low-level modules (characterised by having little or no
dependency on other modules),
some intermediate-level modules (that
primarily perform intermediate calculations using data from low-level
modules) and
some high-level modules (and the main DLL) that
assembles the results of these calculations into output.
A simplified version of my target structure would end up with something like:
module1 (no dependencies)
module2 (no dependencies)
module3 (USEs module1)
module4 (USEs module2)
module5 (USEs module1 parameters and module3 methods)
module6 (USEs module2 parameters and module4 methods)
main DLL code (USEs all of the above modules)
Question:
Do I need to USE all of the modules explicitly in the main DLL code, or will variables and methods from the 'lowest' levels be inherited by simply using module5 and module6?
Or, does module5 need two USE statements (module1 AND module3) OR just module3?
And, I also want to access some of the global constants in, for example, module1 in my main DLL code (e.g. pi), so I need the module1 public variables to be in the global namespace.

Do I need to USE all of the modules explicitly in the main DLL code,
or will variables and methods from the 'lowest' levels be inherited by
simply using module5 and module6?
You don't need to USE` the modules all-the-way-down to dependencies just to access an entity if that entity was made public in the used module.
Or, does module5 need two USE statements (module1 AND module3) OR just module3?
Just by using module5 you can have access to:
Any module entity declared within module5 itself, marked as public or protected
Any entity accessed by USE association in module5, marked as public by module5 (actually, public is the default accessibility if none was specified). If an entity is accessed by USE association from module1 or module3, but marked as private by module5, it won't be accessible.
I tried to cover as many situations as I could figure out in the following example. I used only variable declarations, but same would apply for variables, procedures, user defined types, operators, interfaces...
module module0
! Utiliy module with global constants, could be used at any level.
character(2) :: w = 'w0'
end
module module1
! Low level module. Exposes all the symbols that are not marked as private,
! both defined locally or accessed by use from 'module0'.
use :: module0
private :: z
character(2) :: x1 = 'x1', y1 = 'y1', z = 'z1'
! defined entities: w, x1, y1, z
! public entities : w, x1, y1
end
module module2
! Also low level module, but default access modifier was changed to private,
! so it exposes only symbols marked as public ('z' isn't).
use :: module0
public :: w, x2, y2
private
character(2) :: x2 = 'x2', y2 = 'y2', z = 'z2'
! defined entities: w, x2, y2, z
! public entities : w, x2, y2
end
module module3
! Uses all public names from 'module1' (including 'w' that is from 'module0'),
! but only exposes some of them. Also, defines and exposes local symbols.
use :: module1
private :: x3, y1
character(2) :: x3 = 'x3', y3 = 'y3'
! defined entities: w, x1, y1, x3, y3
! public entities : w, x1, y3
end
module module4
! Here, only selected symbols are accessed from 'module2', and 'w' has been
! renamed into 'w2' to avoid name-conflict with locally defined name 'w'
! (a compile error would had been thrown).
use :: module2, only: w2 => w, x2
public :: w, x2, y4
private
character(2) :: w = 'w4', x4 = 'x4', y4 = 'y4'
! defined entities: w, w2, x2, x4, y4
! public entities : w, x2, y4
end
module module5
! This module can use symbols from lowest level modules that are made public
! by 'module3', without explicitly using those modules.
use :: module3
character(2) :: z = 'z5'
! defined entities: w, x1, y3, z
! public entities : w, x1, y3, z
end
module module6
! As 'y2' is not exposed by 'module4', we could have access to it by using
! 'module2' directly. There is no name-conflict between 'w' from 'module0'
! and from 'module2' because both relate to the same entity. There would be
! conflict with 'w' from 'module4' though, hence the rename.
use :: module0
use :: module2
use :: module4, w4 => w
public :: w, x2, y4, z
private
character(2) :: z = 'z6'
! defined entities: w, w4, x2, y2, y4, z
! public entities : w, x2, y4, z
end
I strongly advise you to try to use explicit imports whenever posible, as it makes your code more clear and avoid name clashes. As a general rule, try to use distictive names for public entities in modules, or use rename clauses in USE statements.
This is a example of usage of the previous modules:
program main
! There aren't namespaces in Fortran (yet), so attention shall be paid when
! naming symbols meant to be accessed by use association, to avoid conflicts.
! That's why explicit imports are encouraged, as well as implicit none.
use :: module5
use :: module6, z6 => z
implicit none
character(2) :: v = 'v#'
call test_a
call test_b
call test_c
contains
subroutine test_a
! You can access used and defined names in procedures by host association.
print '(5a3)', v, w, x1, y3, z ! output: v# w0 x1 y3 z5
print '(5a3)', v, w, x2, y4, z6 ! output: v# w0 x2 y4 z6
end
subroutine test_b
! Also, you can use modules locally inside procedures. In this case, local
! names "shadow" host associated names, as with 'z' from 'module6' here.
use :: module6
print '(5a3)', v, w, x2, y4, z ! output: v# w0 x2 y4 z6
end
subroutine test_c
! There is no name-conflict error between host and local symbols; the local
! definition (or use association) always "shadows" the host associated name.
use :: module4, only: w
character(2) :: v = 'v_', z = 'z_'
print '(5a3)', v, w, x1, y3, z ! output: v_ w4 x1 y3 z_
end
end
For the sake of completeness, I would mention that the Fortran 2018 standard includes a new feature named Default accessibility for entities accessed from a module, that allows you to put a module name in a public or private statement, applying said accessibility modifier to all used entities from that module.
If a module a uses module b, the default accessibility for entities it
accesses from b is public. Specifying another accessibility for each
entity is awkward and error prone. It is now possible for the name of
a module to be included in the list of names of entities made public
or private on a public or private statement. This sets the default for
all entities accessed from that module.
The only compiler I know today (2018) that includes this feature is Intel Visual Fortran 19.0.

Related

Implicit interface procedure pointer member for derived type

In a derived type, I am trying to use a generic procedure function pointer member-type in order to point to different same derived type-bound procedures, which happen to have different interfaces.
module SharedMod
use SettingsMod
implicit none
type, public :: shared_t
type(settings_t) :: settings
...
contains
...
procedure, pass :: run
procedure, nopass :: readSettings, getSettingsFromProg
end type shared_t
contains
subroutine run(this, sett_file)
class(shared_t) :: this
character(len = 132), intent(in), optional :: sett_file
if (present(sett_file)) then
this%settings%GetSettings => this%readSettings
else
this%settings%GetSettings => this%getSettingsFromFinelg
endif
#if defined __PROG__
call this%settings%GetSettings(this%settings)
#else
call this%settings%GetSettings(this%settings, sett_file)
#endif
...
end subroutine run
...
subroutine readSettings(setts, file)
class(settings_t) :: setts
character(len = *), intent(in) :: file
integer :: itmp
real(RDP) :: rtmp
print *, '#Shared::readSetting() : reading settings from file..'
end subroutine readSettings
subroutine getSettingsFromProg(setts)
implicit none
class(settings_t) :: setts
print *, '#Shared::getSettingsFromProg() : reading settings from PROG..'
end subroutine getSettingsFromProg
end module
module SettingsMod
implicit none
type, public :: settings_t
...
procedure(), public, pointer, nopass :: GetSettings => null()
end module
When compiling using ifort I get:
error #8191: The procedure target must be a procedure or a procedure pointer. [READSETTINGS]
this%settings%GetSettings => this%readSettings
error #8191: The procedure target must be a procedure or a procedure pointer. [GETSETTINGSFROMFINELG]
this%settings%GetSettings => this%getSettingsFromFinelg
I also tried the version where GetSettings() is a type-boud procedure, i.e.
module SettingsMod
...
type, public :: settings_t
...
contains
procedure(), public, pass :: GetSettings => getSettingsFromProg, readSettings
...
end type settings_t
abstract interface
subroutine getSettingsFromProg(this)
import settings_t
class(settings_t) :: this
end subroutine getSettingsFromFinelg
end interface
abstract interface
subroutine readSettings(this, file)
import settings_t
class(settings_t) :: this
character(len = *), intent(in) :: file
end subroutine readSettings
end interface
...
end module
having :
error #6784: The number of actual arguments cannot be greater than the number of dummy arguments. [GETSETTINGS]
call this%settings%GetSettings(sett_file)
At this point, I have two questions:
Why do I get these errors??
How would you suggest to implement such a concept, if I was clear enough to explain it?
Thanks a lot.
EDIT after first #Vladimir 's comment.
After having post the answer in which I show how I finally found a working solution, still, I have more questions now:
Why did it work adding () just to the type-bound procedures pointed to?
Why did it work without pointer assignment?
Why did the equivalent type-bound procedure version not worked, even providing abstract interfaces to the two external procedures?
Still look forward to discussion.
It worked for the function-pointer procedure member-type version, after having added () after the procedure keyword in the shared_t type-bound procedures:
module SharedMod
use SettingsMod
implicit none
type, public :: shared_t
type(settings_t) :: settings
...
contains
...
procedure, pass :: run
procedure(), nopass :: readSettings, getSettingsFromProg
end type shared_t
contains
subroutine run(this, sett_file)
class(shared_t) :: this
character(len = 132), intent(in), optional :: sett_file
#if defined __PROG__
call this%settings%GetSettings(this%settings)
#else
call this%settings%GetSettings(this%settings, sett_file)
#endif
...
end subroutine run
...
subroutine readSettings(setts, file)
class(settings_t) :: setts
character(len = *), intent(in) :: file
integer :: itmp
real(RDP) :: rtmp
print *, '#Shared::readSetting() : reading settings from file..'
end subroutine readSettings
subroutine getSettingsFromProg(setts)
implicit none
class(settings_t) :: setts
print *, '#Shared::getSettingsFromProg() : reading settings from PROG..'
end subroutine getSettingsFromProg
end module
module SettingsMod
implicit none
type, public :: settings_t
...
procedure(), public, pointer, nopass :: GetSettings => null()
end module
Still, I have more questions now:
Why did it work adding () just to the type-bound procedures pointed to?
Why did it work without pointer assignment?
Why did the equivalent type-bound procedure version not worked, even providing abstract interfaces to the two external procedures?
Looking forward to discussion.

OCaml: How do I provide fully-qualified module names to avoid name collisions?

I'm working in a package Foo with a module called Base, but I'd also like to use the OCaml library Base. How can I distinguish between the two in open statements?
E.g., is there a module-root specifier like in other languages, so I could type open __root__.Base or open __root__.Foo.Base? E.g. in C++ I could type ::Base or ::Foo::Base, where the leading :: indicates the name is fully qualified starting at root.
First of all, you don't need to open a module to use it. So just refer to them as Foo.Base and Base respectively.
If you still want to open a module that shadows some definition, then the common practice is to rename the shadowed module before the the open statement, e.g.,
module B = Base
open Foo
It may also be worth noting that even after opening a module, you can still refer to it using the "full" name.
# module A = struct module C = struct let d = 42 end end ;;
module A : sig module C : sig val d : int end end
# module B = struct module C = struct let d = 27.3 end end ;;
module B : sig module C : sig val d : float end end
# open A
open B ;;
# open C ;;
# d;;
- : float = 27.3
# A.C.d ;;
- : int = 42
# B.C.d ;;
- : float = 27.3

Can I mimic multiple passed-object dummy arguments in Fortran?

I would like to write a procedure which takes two passed-object dummy arguments, such as
module m
type, abstract :: Parent
contains
procedure(f_Parent), deferred :: f
end type
abstract interface
subroutine f_Parent(foo,bar)
import Parent
implicit none
class(Parent), intent(in) :: foo
class(Parent), intent(in) :: bar
end subroutine
end interface
type, extends(Parent) :: Child
contains
procedure, public :: f => f_Child
end type
contains
subroutine f_Child(foo,bar)
implicit none
class(Child), intent(in) :: foo
class(Child), intent(in) :: bar
end subroutine
end module
but this is not allowed by the Fortran standard, as bar is not a passed-object dummy argument, and so must be class(Parent) and not class(Child).
My current solution is
subroutine f_Child(foo,bar)
implicit none
class(Child), intent(in) :: foo
class(Parent), intent(in) :: bar
select type(bar); type is(Child)
end select
end subroutine
which works, but the select type construct is too slow, and dominates the runtime of my code (this subroutine is called many times).
I have tried having a single passed-object argument which holds both foo and bar, e.g. as an array or pointer, but this is also forbidden by the standard.
Is there any way of mimicking the behaviour of having multiple passed-object dummy arguments which does not incur the cost of a select type construct? Or maybe a faster way of getting an argument of class(Child) from class(Parent)?
You can do it by using single dispatch twice:
Module m
Implicit None
Type, Public, Abstract :: Parent
Contains
Procedure( i_Parent_Parent ), Public , Deferred :: f
Procedure( i_Child_Parent ), Pass( bar ), Private, Deferred :: f_c_p
Procedure( i_set ), Public , Deferred :: set
End Type Parent
Type, Public, Extends( Parent ) :: Child
Integer , Private :: data
Contains
Procedure , Public :: f => f_Child_Parent
Procedure, Pass( bar ), Private :: f_c_p => f_Child_Child
Procedure , Public :: set => f_Child_set
End Type Child
Private
Abstract Interface
Subroutine i_Parent_Parent( foo, bar )
Import :: Parent
Implicit None
Class( Parent ), Intent( In ) :: foo
Class( Parent ), Intent( In ) :: bar
End Subroutine i_Parent_Parent
Subroutine i_Child_Parent( foo, bar )
Import :: Parent, Child
Implicit None
Class( Child ), Intent( In ) :: foo
Class( Parent ), Intent( In ) :: bar
End Subroutine i_Child_Parent
Subroutine i_set( foo, data )
Import :: Parent
Class( Parent ), Intent( InOut ) :: foo
Integer , Intent( In ) :: data
End Subroutine i_set
End Interface
Contains
Subroutine f_Child_Parent( foo, bar )
Implicit None
Class( Child ), Intent( In ) :: foo
Class( Parent ), Intent( In ) :: bar
Call bar%f_c_p( foo )
End Subroutine f_Child_Parent
Subroutine f_Child_Child( foo, bar )
Implicit None
Class( Child ), Intent( In ) :: foo
Class( Child ), Intent( In ) :: bar
Write( *, * ) 'In child child foo%data = ', foo%data, ' bar%data = ', bar%data
End Subroutine f_Child_Child
Subroutine f_Child_set( foo, data )
Implicit None
Class( Child ), Intent( InOut ) :: foo
Integer , Intent( In ) :: data
foo%data = data
End Subroutine f_Child_set
End Module m
Program driver
Use m, Only : Parent, Child
Class( Parent ), Allocatable :: foo, bar
Allocate( Child :: foo )
Allocate( Child :: bar )
Call foo%set( 3 )
Call bar%set( 4 )
Call foo%f( bar )
End Program driver
ian#eris:~/work/stack$ gfortran-8 -std=f2008 -fcheck=all -Wall -Wextra dd.f90
ian#eris:~/work/stack$ ./a.out
In child child foo%data = 3 bar%data = 4
ian#eris:~/work/stack$
Whether this is quicker than select type will be implementation dependent, but I think it is cleaner.

OCaml - confusion from type alias (warning 40)

I don't understand why OCaml is not able to figure out that there is no room for confusion here: anint below can't be other one but A's.
module A = struct
type test = Graphics.status
end
module type ASIG = sig
type test = A.test
val atest : test
end
module Func (H : ASIG) = struct
let _ = let open H in atest.key
end
However, it raises
Warning 40: key was selected from type Graphics.status.
It is not visible in the current scope, and will not
be selected if the type becomes unknown.
How can I tell it "it's fine" without disabling the warning?
I'm aware I can solve it by opening A. However, if H defines its own functions and types similar---but not equal---to A, then it will have unnecessary clashes. I also know I can duplicate the definition, but that defeats the purpose of type aliasing, and involves lots of unnecessary code duplication. Perhaps there is no solution, but I wonder why OCaml is so blind dumb on this one: type alias should mean also constructor and record fields alias, shouldn't it?
You can simply open the the module defining the original type locally when referring to the field key as in the following:
module A = struct
type test = Graphics.status
end
module type ASIG = sig
type test = A.test
val atest : test
end
module Func (H : ASIG) = struct
let _ = let open H in atest.Graphics.key
end
Or if you need to refer to several fields :
let _ = let open H in Graphics.(atest.key, atest.button)
Well, this happens because the module signature ASIG needs to look the definition of type test for the implementation of A. This often causes problems with visibility of the types, and sometimes require duplication of type definitions, where the contract satisfies the implementation instead of referring to it.
How can we fix this warning? In ASIG, instead of defining type test = A.test, we need to explicitly do type test = { anint: int }as we did in the implementation, so:
module ASIG = sig
type test = { anint: int }
val atest : test
end
module A = struct
type test = { anint: int }
end
module Func (H : ASIG) = struct
let _ = let open H in atest.anint
end
The H module would not be able to view anintin its scope, otherwise, because the signature has a type (contract) that links to the implementation. It is also a core concept of OCaml philosophy isolating signatures and implementations and avoiding signatures depending upon implementations.

gfortran operator overloading derived type and real()

I want to overload an operator (*) to perform vector-scalar multiplication in the following class:
module vectorField_mod
use constants_mod
implicit none
private
public :: vectorField
public :: allocateVectorField
public :: delete
type vectorField
real(dpn),dimension(:,:,:),allocatable :: x,y,z
end type
interface operator (*)
module procedure scalarMultiply
end interface
contains
function scalarMultiply(f,g) result(q)
implicit none
type(vectorField),intent(in) :: f
real(dpn),intent(in) :: g
type(vectorField) :: q
q%x = f%x * g
q%y = f%y * g
q%z = f%z * g
q%sx = f%sx; q%sy = f%sy; q%sz = f%sz
end function
...
end module
But I'm getting the following error:
Error: Operands of binary numeric operator '*' at (1) are REAL(8)/TYPE(vectorfield)
I'm trying to implement this like:
type(vectorField) :: a
real(8) :: dt = 0.001
call allocateVectorField(a,..)
a = a*dt
Is this not a binary operation? Is there still a way to do this? Any help is greatly appreciated!
Summary:
1) The answer by #francescalus was necessary, but not sufficient to yield a successful compilation.
2) In addition, it turns out that the order of multiplication is important. That is a = adt works, but a = dta does not work (this was the problem I was having)
Here's an illustrative sample:
module constants_mod
integer,parameter :: dpn = selected_real_kind(14)
end module
module vectorField_mod
use constants_mod
implicit none
private
public :: vectorField
public :: allocateX,allocateY,allocateZ
public :: delete
public :: operator(*)
type vectorField
integer,dimension(3) :: sx,sy,sz
real(dpn),dimension(:,:,:),allocatable :: x,y,z
end type
interface delete
module procedure deallocateVectorField
end interface
interface operator (*)
module procedure scalarMultiply
end interface
contains
function scalarMultiply(f,g) result(q)
implicit none
type(vectorField),intent(in) :: f
real(dpn),intent(in) :: g
type(vectorField) :: q
q%x = f%x * g; q%y = f%y * g; q%z = f%z * g
q%sx = f%sx; q%sy = f%sy; q%sz = f%sz
end function
subroutine allocateX(field,Nx,Ny,Nz)
implicit none
type(vectorField),intent(inout) :: field
integer,intent(in) :: Nx,Ny,Nz
if (allocated(field%x)) deallocate(field%x)
allocate(field%x(Nx,Ny,Nz))
field%sx = shape(field%x)
end subroutine
subroutine allocateY(field,Nx,Ny,Nz)
implicit none
type(vectorField),intent(inout) :: field
integer,intent(in) :: Nx,Ny,Nz
if (allocated(field%y)) deallocate(field%y)
allocate(field%y(Nx,Ny,Nz))
field%sy = shape(field%y)
end subroutine
subroutine allocateZ(field,Nx,Ny,Nz)
implicit none
type(vectorField),intent(inout) :: field
integer,intent(in) :: Nx,Ny,Nz
if (allocated(field%z)) deallocate(field%z)
allocate(field%z(Nx,Ny,Nz))
field%sz = shape(field%z)
end subroutine
subroutine deallocateVectorField(field)
implicit none
type(vectorField),intent(inout) :: field
deallocate(field%x,field%y,field%z)
field%sx = 0; field%sy = 0; field%sz = 0
end subroutine
end module
program test
use constants_mod
use vectorField_mod
implicit none
type(vectorField) :: a,b
integer :: N = 1
real(dpn) :: dt = 0.1
call allocateX(a,N,N,N)
call allocateY(a,N,N,N)
call allocateZ(a,N,N,N)
call allocateX(b,N,N,N)
call allocateY(b,N,N,N)
call allocateZ(b,N,N,N)
a%x = dble(1.0); a%y = dble(1.0); a%z = dble(1.0)
b%x = dble(1.0); b%y = dble(1.0); b%z = dble(1.0)
a = b
a = a*dt ! compiles fine
a = dt*a ! does not compile
call delete(a)
call delete(b)
end program
The default accessibility of the module is private. This default applies also to the defined operator.
To make the operator identifier public (so that it can be used outside the module) use a public statement like:
public :: operator(*)