Also posting this here, this has been reported already to the Intel forum: there is a regression regarding submodules in Intel oneAPI 2022.3 providing ifort 21.7. The code is posted below,
the Intel forum link is here:
The workaround is relatively easy, though, just adding the line
use ifiles, only: ifile_t
also to the submodule.
module ifiles
implicit none
private
public :: ifile_t
public :: line_p
type :: ifile_t
end type ifile_t
type :: line_p
end type line_p
end module ifiles
module lexers
use ifiles, only: ifile_t
use ifiles, only: line_p
implicit none
private
public :: stream_t
type :: stream_t
type(ifile_t), pointer :: ifile => null ()
type(line_p), pointer :: line => null ()
end type stream_t
type :: keyword_entry_t
private
type(keyword_entry_t), pointer :: next => null ()
end type keyword_entry_t
end module lexers
module syntax_rules
use ifiles, only: ifile_t
use lexers
implicit none
private
public :: syntax_t
public :: syntax_init
public :: syntax_rule_t
type :: rule_p
private
type(syntax_rule_t), pointer :: p => null ()
end type rule_p
type :: syntax_rule_t
private
type(rule_p), dimension(:), allocatable :: child
end type syntax_rule_t
type :: syntax_t
private
type(syntax_rule_t), dimension(:), allocatable :: rule
end type syntax_t
interface syntax_init
module procedure syntax_init_from_ifile
end interface
interface
module subroutine syntax_init_from_ifile (syntax, ifile)
type(syntax_t), intent(out), target :: syntax
type(ifile_t), intent(in) :: ifile
end subroutine syntax_init_from_ifile
end interface
end module syntax_rules
submodule (syntax_rules) syntax_rules_s
use ifiles, only: line_p
implicit none
contains
!!! Intel 21.7 Regression
module subroutine syntax_init_from_ifile (syntax, ifile)
type(syntax_t), intent(out), target :: syntax
type(ifile_t), intent(in) :: ifile
end subroutine syntax_init_from_ifile
end submodule syntax_rules_s