Why do we need TYPEOF?

Not pretty, but indeed I can’t see how name collisions can occur.

Sorry for the delay - at a funeral.

Directory structure:

├── build
│ └── build.sh
├── main
│ └── write_colours.f90
├── module_1
│ ├── colours.f90
│ └── m_car_1.f90
└── module_2
├── colours.f90
└── m_car_2.f90

main/write_colours.f90
PROGRAM write_colours

    USE m_car_1
    USE m_car_2

    CALL car_colour_1
    CALL car_colour_2

END PROGRAM write_colours ! **************************************************************

module_1/colours.f90
MODULE m_colour

    CHARACTER(LEN=*),PARAMETER :: car_colour = "red"

END MODULE m_colour ! ********************************************************************

module_1/m_car_1.f90
MODULE m_car_1

    USE m_colour

    CONTAINS

    SUBROUTINE car_colour_1
    WRITE(*,'("Car colour is: ",A)')car_colour
    END SUBROUTINE car_colour_1

END MODULE m_car_1 ! *********************************************************************

module_2/colours.f90
MODULE m_colour

    CHARACTER(LEN=*),PARAMETER :: car_colour = "blue"

END MODULE m_colour ! ********************************************************************

module_2/m_car_2.f90
MODULE m_car_2

    USE m_colour

    CONTAINS

    SUBROUTINE car_colour_2
    WRITE(*,'("Car colour is: ",A)')car_colour
    END SUBROUTINE car_colour_2

END MODULE m_car_2 ! *********************************************************************

build/build.sh
#!/bin/bash

build.sh

gfortran -c ../module_1/colours.f90
gfortran -c ../module_1/m_car_1.f90
gfortran -c ../module_2/colours.f90
gfortran -c ../module_2/m_car_2.f90
gfortran -c ../main/write_colours.f90
gfortran -o write_colours.exe *.o

End of build.sh

Output:
Car colour is: red
Car colour is: blue

So we have two different modules named m_colour in the same program. Didn’t even need to use libraries, though that is how it usually happens. Not standard conforming, but the compiler and linker can’t know. Who designed this language?

BTW also works with colors :face_with_raised_eyebrow:

2 Likes

Ah I see — using the same module name twice.

But that seems unrelated (orthogonal) to the “namespace for modules” feature?

I don’t think so. If the module name is passed down to the users a collision will occur?

For the following code, gfortran gives an error

module a
  implicit none
  integer, parameter :: one = 1
end module a

module b
  implicit none
  integer, parameter :: one = 2
end module b
program f
 use :: a
 use :: b
 implicit none

 print*, one
end program f

which is a what I expect.
The same should happen for repeated module names. It needs to be fixed, either by renaming one of the module names (possible only for own code) or by importing with an alias. Something like

use, namespace :: a_m => x_m

From my shallow understanding, Python modules behave exactly as what is shown in Why do we need TYPEOF? - #57 by jwmwalrus and I’m not aware of any severe issues.

I could imagine that submodules increase the complexity. Does Lfortran support them already @certik? That would be worth some prototyping to figure out whether (nested) submodules should reside in the namespace of the host module or introduce their own namespace.

Edit: I just had a look at the proposal (J3/25-119r1) and I find it pretty weak. It leaves the impression that namespaces are mainly to prevent name clashes. That is one aspect, but for me namespaces are a way to understand dependencies between different entities, i.e. modules. Also, the solution to prefix functions/subroutines with the module name (e.g. module math has functions like math%cos) is not really satisfactory because that “blocks” the underscore for other use cases. Is math_true_divide a function divide from math_true or true_divide from math?

2 Likes

There are many examples of non conforming codes that a compiler cannot detect, and not only in Fortran. In this case, even the linker is fooled because an object file is overwritten by another one.

What I’d rather like to see is an example of conforming code that would break if namespaces were introduced.

1 Like

We don’t yet. If there are an issues, we just need to resolve them. (The submodules go exactly the other way than Python nested modules, I personally prefer the Python approach, but that’s a separate issue.)

So far I am not aware of any issues that can’t be quite easily resolved. But let’s bring actual code and we’ll tackle it with actual code and compiler implementation, that settles everything.

1 Like

In regards to the namespaces feature, they shouldn’t; the namespace should allow access to public entities only. A submodule entity is only visible to the ancestor-module if it has an interface declared for it in said module (and interface means procedures only).

For example, if you declare a derived type in a submodule, an ancestor-module is unaware of such declaration (and therefore, it can never be made public). Something similar happens with submodules of submodules.

Only the linker needs to make sense of what’s there and what’s missing.

(The gfortran implementation of submodules is messed up in regards to entity access and what the linker sees, but that’s a different thing)

3 Likes

I agree, that is how submodules behave outside of the ancestor module. But what to do within a module that has nested submodules? Maybe some namespacing would be helpful there as well to know where exactly something is defined.
As far as I know, submodules are a unique feature of Fortran so there are no lessons learned from other languages. I therefore agree with @certik that one needs a prototype and I also agree with the fact that submodules are not considered for the upcoming standard because of the lack of experience. Otherwise, we get use, namespace :: a_m in 2028 and use, namespaced :: a_m in 2031. That happened with enum and enumeration.

By the way, if I understand it correctly the traditional way of agreeing on a Fortran standard was the formalization of vendor-specific extensions that turned out to be useful. That is more or less the same as having prototypes, just that there is an upfront discussion on how the extension should look like.

1 Like

But what do you buy as a gift for Ada, the language that has everything? :slightly_smiling_face: —i.e., Fortran submodules were likely modeled after Ada’s “package bodies”, so that’s the precedence.

3 Likes

The point of making the little example was to show that putting the module name into the namespace can cause a problem - this was @certik 's question. It is actually very unlikely that this could happen in real code. Duplicate module names usually occur because modules with the same name are accessed in different libraries. In this case the linker never sees the namespace and nothing will go wrong. It is a problem for us, and I assume for Polyhedon (Plusfort/spag), Understand for Fortran, Codee etc. We can’t (yet) process the source code of programs which contain duplicate modules. Working on it!

1 Like

I thought that they came from Modula 2. In Modula 2 modules have a definition component and an implementation component. This allows the decoupling of interface from implementation. Here is an extract from the next draft standard.

8 3 A submodule may provide implementations for separate module procedures (15.6.2.5), each of which is
9 declared (15.4.3.2)within that submodule or one of its ancestors, and declarations and de􀏐initions of other
10 entities that are accessible by host association in its descendants.

1 Like

Modula and Ada were (late '70s/early '80s) contemporaries. I know someone who worked behind the scenes on Ada, and could ask him. I suspect that at least in the case of Ada, it was influenced by the COMPOOLs in JOVIAL - since JOVIAL was one of the DOD languages Ada was supposed to replace.

1 Like