Stef1611
Stef1611

Reputation: 2387

OOP Fortran : how to put "abstract derived type", "abstract interface" and submodules ALL TOGETHER?

This question follow this one(fortran, how to have a number of variable dimensions in dimension (allocatable) , allocate and affectation?).

Frederico suggested me to use OOP and gave me a solution to my initial problem. Now, I would like to use submodule (cf 4. The advantages of submodules in https://fortran.bcs.org/2004/ukfortran04.htm).

This is my code :

module grids
   implicit none

   type, abstract, public :: grid
      contains
      procedure (grid_init), deferred :: init
   end type grid
   
   type, public, extends(grid) :: grid2D
      real, dimension(:,:), allocatable :: myArray
      contains
         procedure :: init=>grid_init
   end type grid2D
   
   type, public, extends(grid) :: grid3D
      real, dimension(:,:,:), allocatable :: myArray
      contains
         procedure :: init=>grid_init
   end type grid3D

   ! Define procedure APIs 
   abstract interface
      module subroutine grid_init(this,size)
         class(grid), intent(inout) :: this
         integer, intent(in) :: size
      end subroutine grid_init
   end interface
   
end module grids

submodule (grids) grid2D
   contains
   
   module procedure grid_init
      allocate(this%myArray(size,size))
   end subroutine grid_init
   
end submodule grid2D
   

submodule (grids) grid3D    
   contains
   
   module procedure grid_init
      allocate(this%myArray(size,size,size))
   end subroutine grid_init
   
end submodule grid3D

program main

    use grids
    
    type(grid2D) :: myGrid
    
    call myGrid%init(3)
    print *,myGrid%myArray
    
end program main

But, it does not compile because grid_init is an abstract interface. What must I change in this code ?

edit 1

Federico said in his answer : To put in a submodule only the routines, without the type definition, you may have to define additional interfaces for all their functions, which is nonsense. I understand clearly the problem. This part of code illustrates well the problem (For sake of brevity, module grids_base is omitted but it is unchanged and the same modifications applied to grids_3d)

module grids_2d 
   use grids_base
   implicit none
   
   type, public, extends(grid) :: grid2D
      real, dimension(:,:), allocatable :: myArray
      contains
         procedure :: init=>grid_init2d
   end type grid2D   
      
   interface
        module subroutine grid_init2d(this,size)
            class(grid2D), intent(out) :: this
            integer, intent(in) :: size
        end subroutine grid_init2d
   end interface
   
end module grids_2d

submodule (grids_2d) grid_2dsub
   contains
   
   module procedure grid_init2d
      allocate(this%myArray(size,size))
   end procedure grid_init2d
   
end submodule grid_2dsub

I wonder, if it is possible (with some "OOP tricks", that I am not aware of) to simplify this code because grid_init2d interface is very similar to the grid_init abstract interface. The only difference is the class of this : grid changes togrid2D but the type grid2D is derived from grid where the abstract interface grid_init is defined.

Upvotes: 2

Views: 421

Answers (1)

Federico Perini
Federico Perini

Reputation: 1416

Your compiler is complaining not because of the submodule, but cause you're pointing to an abstract routine. the interface keyword means you're only defining an API, not an actual implementation. To put in a submodule only the routines, without the type definition, you may have to define additional interfaces for all their functions, which is nonsense, but AFAICT the Fortran standard doesn't consider this yet.

I think the most elegant/standard way to do this is to have each class with its own module, and only use submodules in case the class-specific file gets too large. In your case, you'd have:

module grids_base
   implicit none

   type, abstract, public :: grid
      contains
      procedure (grid_init), deferred :: init
   end type grid

   ! Define procedure APIs 
   abstract interface
      module subroutine grid_init(this,size)
         class(grid), intent(out) :: this
         integer, intent(in) :: size
      end subroutine grid_init
   end interface
   
end module grids_base

module grids_2d 
   use grids_base
   implicit none
   
   type, public, extends(grid) :: grid2D
      real, dimension(:,:), allocatable :: myArray
      contains
         procedure :: init=>grid_init2d
   end type grid2D   
   
   contains
   
   subroutine grid_init2d(this,size)
      class(grid2D), intent(out) :: this
      integer, intent(in) :: size
      allocate(this%myArray(size,size))
   end subroutine grid_init2d
   
end module grids_2d
   

module grids_3d 
   use grids_base    
   implicit none   
   
   type, public, extends(grid) :: grid3D
      real, dimension(:,:,:), allocatable :: myArray
      contains
         procedure :: init=>grid_init3d
   end type grid3D   
   
   contains
   
   subroutine grid_init3d(this,size)
      class(grid3D), intent(out) :: this
      integer, intent(in) :: size
      allocate(this%myArray(size,size,size))
   end subroutine grid_init3d
   
end module grids_3d

! Global interface to grids
module grids
  use grids_base
  use grids_2d
  use grids_3d
  implicit none
end module grids  


program main

    use grids
    
    type(grid2D) :: myGrid
    
    call myGrid%init(3)
    print *,myGrid%myArray
    
end program main

Upvotes: 2

Related Questions