Intel® Fortran Compiler Classic and Intel® Fortran Compiler Developer Guide and Reference
A newer version of this document is available. Customers should click here to go to the newest version.
SUBMODULE
Statement: Marks the beginning of a submodule program unit, which contains specifications and definitions that can be used by one or more program units.
SUBMODULE (ancestor-module-name [:parent-submodule-name]) name
[specification-part]
[module-subprogram
[module-subprogram]...]
END [SUBMODULE [name]]
| ancestor-module-name | Must be the name of a nonintrinsic module. It is the name of the module at the root of the module or submodule tree. | 
| parent-submodule-name | (Optional) Is the name of the parent submodule, if any. The parent submodule must be a descendant of ancestor-module-name. | 
| name | Is the name of the submodule. | 
| specification-part | Is one or more specification statements, except for the following: 
 An automatic object must not appear in a specification statement. | 
| module-subprogram | Is a function or subroutine subprogram that defines the module procedure. A function must end with END FUNCTION and a subroutine must end with END SUBROUTINE. A module subprogram can contain internal procedures. | 
Description
If a name follows the END statement, it must be the same as the name specified in the SUBMODULE statement.
Each submodule has exactly one ancestor module and exactly one parent module or submodule. If the parent is a module then it must be the ancestor module. The relationship is tree-like, with the parent module or submodule at the root of the tree, and its descendant submodules as the branches of the tree.
A module or submodule may have one or more descendent submodules.
A submodule can access the entities from its parent module or submodule by host association. Unlike a module, a submodule cannot be referenced in other program units by use association. Entities declared in a submodule are only accessible from the submodule and its descendent submodules. Furthermore, a module procedure can have its interface declared in a module or submodule and its implementation contained in a descendent submodule in a separate file.
Submodules help the modularization of a large module in several ways:
- Internal data can be shared among submodules without being exposed to users of the module. Without the submodule feature, when a large module is split into smaller modules, internal data may be forced to become public in order to be shared among the modules. 
- Even if a module procedure implementation in a submodule is changed, as long as the module procedure interface declared in the ancestor module remains the same, a recompilation would not be needed for the user of the module. This could reduce the rebuilding time for a complex system. 
- Separate concepts with circular dependencies can now be implemented in different submodules. It cannot be done with just modules. 
A submodule is uniquely identified by a submodule identifier which consists of its ancestor-module-name and the name of the submodule. The name of a submodule can therefore be the same as the name of another submodule so long as they do not have the same ancestor module.
The following rules also apply to submodules:
- The specification part of a submodule must not contain IMPORT, ENTRY, FORMAT, executable, or statement function statements. 
- A variable, common block, or procedure pointer declared in a submodule implicitly has the SAVE attribute, which may be confirmed by explicit specification. 
- If a specification or constant expression in the specification-part of a submodule includes a reference to a generic entity, there must be no specific procedures of the generic entity defined in the submodule subsequent to the specification or constant expression. 
Unlike a module, the specification part of a submodule must not contain PUBLIC and PRIVATE specifications.
Any executable statements in a module or submodule can only be specified in a module or submodule subprogram.
A submodule can contain one or more procedure interface blocks, which let you specify an explicit interface for an external subprogram or dummy subprogram.
Example
Consider the following example of a multilevel submodule system:
| Module M | ||||
| Submodule A | Submodule B | Submodule C | ||
| Submodule X | Submodule Y | Submodule Z | ||
In the above example, module M is extended by submodules up to two levels. Module M is the ancestor module of all the submodules. Entities declared in module M can be shared among all the submodules. A is the parent submodule of X, Y, and Z. Entities declared in submodule A can be shared among submodules X, Y, and Z, but not by B or C.
Only public entities declared in M can be available to other program units by use association.
The SUBMODULE declarations for A and X are:
   SUBMODULE (M) A
      …
   END SUBMODULE A
   SUBMODULE (M : A) X
      …
   END SUBMODULE XThe following example shows modules and submodules, separate module procedures, and how circular dependency can be avoided with submodules. There are five parts in the example:
- module color_points 
- level-1 submodule color_points_a 
- level-2 submodule color_points_b 
- module palette_stuff 
- program main 
! part 1
module color_points  ! This is the ancestor module
   type color_point
      private
      real :: x, y
      integer :: color
   end type color_point
   ! Below is the interface declaration of the separate module procedures. 
   ! No IMPORT statement is used in the interface bodies.
   ! The separate module procedures are implemented in the two submodules.
   interface
      module subroutine color_point_del ( p ) 
      type(color_point), allocatable :: p
      end subroutine color_point_del
      real module function color_point_dist ( a, b )
      type(color_point), intent(in) :: a, b
      end function color_point_dist
      module subroutine color_point_draw ( p )
      type(color_point), intent(in) :: p
      end subroutine color_point_draw
      module subroutine color_point_new ( p )
      type(color_point), allocatable :: p
      end subroutine color_point_new
   end interface
end module color_points
! part 2
submodule ( color_points ) color_points_a  ! submodule of color_points
   integer :: instance_count = 0
   ! Below is the interface declaration of the separate module procedure
   !   inquire_palette, which is implemented in the submodule color_points_b.
   interface 
      module subroutine inquire_palette ( pt, pal )
         use palette_stuff 
         ! Later you will see that module palette_stuff uses color_points.
         ! This use of palette_stuff however does not cause a circular
         !   dependence because this use is not in the module.
         type(color_point), intent(in) :: pt
         type(palette), intent(out) :: pal
      end subroutine inquire_palette
   end interface
contains  
   ! Here are the implementations of three of the four separate module
   !   procedures declared in module color_point. 
   module subroutine color_point_del ( p )
     type(color_point), allocatable :: p
     instance_count = instance_count - 1
     deallocate ( p )
   end subroutine color_point_del
   real module function color_point_dist ( a, b ) result ( dist )
     type(color_point), intent(in) :: a, b
     dist = sqrt( (b%x - a%x)**2 + (b%y - a%y)**2 )
   end function color_point_dist
   module subroutine color_point_new ( p )
     type(color_point), allocatable :: p
     instance_count = instance_count + 1
     allocate ( p )
   end subroutine color_point_new
end submodule color_points_a
! part 3
submodule ( color_points:color_points_a ) color_points_b
! submodule of color_point_a
contains
   ! Implementation of a module procedure declared in the ancestor module
   module subroutine color_point_draw ( p )
     use palette_stuff, only: palette
     type(color_point), intent(in) :: p
     type(palette) :: MyPalette
     ...; call inquire_palette ( p, MyPalette ); ...
   end subroutine color_point_draw
   ! Implementation of a module procedure declared in the parent submodule
   module procedure inquire_palette
     ... 
   end procedure inquire_palette
   ! A procedure only accessible from color_points_b and its submodules
   subroutine private_stuff 
     ...
   end subroutine private_stuff
end submodule color_points_b
! part 4
module palette_stuff
   type :: palette ; ... ; end type palette
contains
   subroutine test_palette ( p )
     use color_points
     ! This does not cause a circular dependency because the
     !  "use palette_stuff" that is logically within color_points
     !  is in the color_points_a submodule.
     type(palette), intent(in) :: p
     ...
   end subroutine test_palette
end module palette_stuff
! part 5
program main
   use color_points
   ! Only public entities in color_points can be accessed here, not the
   !   entities from its submodules.
   ! The separate module procedure color_point_draw can be a specific
   !   procedure for a generic here. Recall that color_point_draw is
   !   implemented in a submodule, but its interface is public in a module.
   interface draw
     module procedure color_point_draw
   end interface
   type(color_point), allocatable :: c_1, c_2
   real :: rc
   ...
   call color_point_new (c_1)  ! body in color_points_a, interface in
                               !   color_points
   ...
   call draw (c_1)             ! body in color_points_b, specific interface
                               !   in color_points, generic interface here
   ...
   rc = color_point_dist (c_1, c_2)  ! body in color_points_a, interface in
                                     !   color_points
   ...
   call color_point_del (c_1)  ! body in color_points_a, interface in 
                               !   color_points
   ...
end program main