Type bound procedures in external module and explicit interface error

The following program works fine with gfortran on windows 10. It makes a call to type bound procedure defined in the external module.

program main_test
  use grid_module
  implicit none
  
  type(GridType) :: grid
  integer :: i
  
  ! Allocate a 4x4 grid with random numbers
  call grid%createGrid(4, 4)
  
  ! Display the grid  
  print *, "Grid data:"
  do i = 1, size(grid%data, 1)
    write(*, "(4F8.3)") grid%data(i, :)
  end do
  
end program main_test

The module file is

module grid_module
  implicit none
  public :: GridType

  type :: GridType
     real, allocatable :: data(:,:)
  contains
     procedure :: createGrid => allocateGrid
  end type GridType

contains

  ! Type-bound procedure to allocate and fill the grid with random numbers
  subroutine allocateGrid(this, rows, cols)
    class(GridType), intent(inout) :: this
    integer, intent(in) :: rows, cols

    ! Allocate the 2D array
    allocate(this%data(rows, cols))

    ! Fill the grid with random numbers between 0 and 1
    call random_number(this%data)
  end subroutine allocateGrid

end module grid_module

But if I put the type bound procedures in a separate module then I get the error of explicit interface.

9 |      procedure :: createGrid => allocateGrid
  |              1

Error: ‘allocategrid’ must be a module procedure or an external procedure with an explicit interface at (1)

Now the main program uses that module with

program main_test
  use grid_module
  use procedures_module
  implicit none
   ...

and the procedure module is

module procedure_module
use grid_module
contains

  ! Type-bound procedure to allocate and fill the grid with random numbers
  subroutine allocateGrid(this, rows, cols)
    class(GridType), intent(inout) :: this
    integer, intent(in) :: rows, cols

    ! Allocate the 2D array
    allocate(this%data(rows, cols))

    ! Fill the grid with random numbers between 0 and 1
    call random_number(this%data)
  end subroutine allocateGrid
  
end module 

My understanding of using module is that it provides the explicit interface of the procedure calls. So why does it show the error of explicit interface and how to rectify it ?

By splitting this into two modules, you are creating a circular dependency: grid_module needs to know procedures_module and procedures_module needs grid_module. Which should be compiled first?

To solve your issue, just either put both into the same module, or make procedure_module a submodule.

I still face the same error

submodule (procedure_module) procedure_module_exec
contains

! Type-bound procedure to allocate and fill the grid with random numbers
module subroutine allocateGrid(this, rows, cols)
  class(GridType), intent(inout) :: this
  integer, intent(in) :: rows, cols
  
  ! Allocate the 2D array
  allocate(this%data(rows, cols))
  
  ! Fill the grid with random numbers between 0 and 1
  call random_number(this%data)
end subroutine allocateGrid

end submodule procedure_module_exec

Sorry I should have explained it better. You should have:

program main_test
  use grid_module
  implicit none
  
  type(GridType) :: grid
  integer :: i
  
  ! Allocate a 4x4 grid with random numbers
  call grid%createGrid(4, 4)
  
  ! Display the grid  
  print *, "Grid data:"
  do i = 1, size(grid%data, 1)
    write(*, "(4F8.3)") grid%data(i, :)
  end do
  
end program main_test

then

module grid_module
  implicit none
  public :: GridType

  type :: GridType
     real, allocatable :: data(:,:)
  contains
     procedure :: createGrid => allocateGrid
  end type GridType
  
  interface
     ! Type-bound procedure to allocate and fill the grid with random numbers
     module subroutine allocateGrid(this, rows, cols)
       class(GridType), intent(inout) :: this
       integer, intent(in) :: rows, cols
     end subroutine allocateGrid  
  end interface

end module grid_module

And finally in the submodule

submodule(grid_module) procedure_module
contains

  ! Type-bound procedure to allocate and fill the grid with random numbers
  module subroutine allocateGrid(this, rows, cols)
    class(GridType), intent(inout) :: this
    integer, intent(in) :: rows, cols

    ! Allocate the 2D array
    allocate(this%data(rows, cols))

    ! Fill the grid with random numbers between 0 and 1
    call random_number(this%data)
  end subroutine allocateGrid
  
end submodule
1 Like

Thanks for the explanation.