Private type allowed in a submodule?

This program was inspired by a recent discussion in the Intel Fortran forum. It attempts to declare a private type in a submodule.

module points
   interface
      module function point_dist(p1, p2) result(distance)
        real,dimension(2),intent(in) :: p1, p2
        real :: distance
      end function point_dist
   end interface
 end module points
 
 submodule (points) points_a
   type, private :: point
      real :: x, y
   end type point
 contains
   module function point_dist(p1,p2) result(distance)
     real,dimension(2),intent(in) :: p1,p2
     real :: distance
     type(point) :: a, b
     a = point(p1(1),p1(2))
     b = point(p2(1),p2(2))
     distance = sqrt((a%x - b%x)**2 + (a%y - b%y)**2)
   end function point_dist
 end submodule points_a
 
 Program Test_program
   
   Use points
   Implicit none
   real, dimension(2):: p1 = [10,20], p2 = [20,10]
   real dist
   dist = point_dist(p1, p2)
   
   write(*,*)dist
   
 End program Test_program

Gfortran won’t compile it. Its first error message is

   11 |    type, private :: point
      |                 1
Error: Derived type at (1) can only be PRIVATE in the specification part of a module

If the 3 lines declaring the type point are moved from the beginning of the submodule to the beginning of its parent module then gfortran happily compiles and runs the program. My question: is a private type declaration forbidden in a submodule?

My comment does not answer your question. Best person would likely be @sblionel. Adding to the discussion, the attribute private would mean the entity is inaccessible outside the submodule. But isn’t it already inaccessible when placed in the submodule? Isn’t it, therefore, redundant to have the private attribute? I wish there was a way to access submodule declarations.

Extending @shahmoradi 's post a little bit:

In Fortran, the public|private|protected attributes belong to the module, so they cannot be used in a submodule, subprogram or main-program.

Additionally, a submodule has access to everything in the ancestor-module but anything declared in a submodule is private and can only be seen by its descendants, unless it’s a separate-module-subprogram —i.e., if it has its interface declared in the ancestor-module or in a parent-submodule, with module as a prefix.

1 Like