That’s a major win for gfortran I really hope Intel would start doing this as well!
Could something like the code below work for you in this case? It’s a bit of ceremony, but this approach completely hides the implementation details from the module with the interface specification. The downside is that you have to rely on polymorphism, but if you’re already using that it might no be such a big deal.
mytype.f90:
module mytype_mod
implicit none
private
public mytype_t
public mytype_factory
type, abstract :: mytype_t
private
contains
procedure(public_sub), deferred :: public_sub
end type
interface
subroutine public_sub(this)
import mytype_t
class(mytype_t), intent(inout) :: this
end subroutine
module function mytype_factory(i) result(this)
integer, intent(in) :: i
class(mytype_t), allocatable :: this
end function
end interface
end module
mytype_impl.f90:
submodule(mytype_mod) mytype_impl
implicit none
type, extends(mytype_t) :: mytype_impl_t
integer :: i
contains
procedure :: public_sub => public_sub_impl
procedure :: private_sub
end type
contains
module function mytype_factory(i) result(this)
integer, intent(in) :: i
class(mytype_t), allocatable :: this
allocate(this, source=mytype_impl_t(i))
end function
subroutine public_sub_impl(this)
class(mytype_impl_t), intent(inout) :: this
write(*,*) 'This is public sub for mytype_impl_t with i = ', this%i
call this%private_sub()
end subroutine
subroutine private_sub(this)
class(mytype_impl_t), intent(inout) :: this
write(*,*) 'This is private sub for mytype_impl_t with i = ', this%i
end subroutine
end submodule
main.f90
program main
use mytype_mod, only: mytype_t, mytype_factory
implicit none
class(mytype_t), allocatable :: mytype
mytype = mytype_factory(42)
call mytype%public_sub()
end program
When run, it gives me the following output:
This is public sub for mytype_impl_t with i = 42
This is private sub for mytype_impl_t with i = 42