Today I gave a try to the newly released nvfortran 23.1. Is it known when there will be support for submodules in nvfortran?
I think complete support for F2008 and F2018 in nvfortran is deferred until new-flang (llvm flang) is ready for prime time. At the rate (or lack of) that new FLANG is progressing, I doubt it will be anytime soon. It’s disappointing (at least to me) that I can’t do a sudo apt install llvm-flang etc and get a working (as in generate an executable binary) compiler
Thanks for the answer, rwmsu. Indeed, I was testing the llvm-flang myself some time ago, and it is a lot of different things one has to compile before being able to try it out. And then, if there are updates it is not clear to me if it is sufficient to update the repo of flang from time to time, or one better needs to git-pull also llvm repo. In any case, what scares me away is that this is only a parser, and does not really compile/assemble code, such that one needs a running (back-end) compiler in addition.
Another issue I have is that none of the LLVM based compilers (nvfortran, AMD AOCC, or ifx) will compile one of my codes without generating an ICE. No problems with ifort or gfortran. The code is standard F2003 with some F2008 that is supposed to be supported by nvfortran etc. Yes, I know compilers are compicated pieces of software but to me an ICE is just a sign of inadequate or poorly implemented internal testing.
@rwmsu , re: IFX
, if your code encountering ICE is online someplace, or if you can post a reproducer here, chances are high someone from Intel Fortran team will follow-up and work to get IFX
resolved, particularly if the code works with IFORT
. You can also post about it at the Intel Fortran forum.
I think the work around for this, is some weird compiler flag (I forgot what it is )
Also what’s an ICE ?
@Aurelius_Nero , ICE = Internal Compiler Error. Unfortunately, my code that generates one is too large and too complicated to reduce to a simple reproducer. The fact that the none of the LLVM compilers work and two (nvfortran and AOCC) generate ICE in the same subroutine (with similar error messages) indicates its something inherent to LLVM (or maybe the old PGI frontend in “classic-flang”). Actually, the previous (not 2023) release of ifx did compile O.K at least for the one time I tried it. Current one doesn’t so its a regression of some kind.
Hmm.
Thanks.
Submodules appear to be available with the 24.1 release of the NVHPC SDK: Nvfortran error with submodules - nvc, nvc++ and nvfortran - NVIDIA Developer Forums
Not really. very simple constructions fail to compile, e.g. the code below fails with
NVFORTRAN-S-0155-Derived type has not been declared - t1_node_t (binary_tree.f90: 37)
0 inform, 0 warnings, 1 severes, 0 fatal for
module t1
implicit none
private
type :: t1_iterator_t
integer, dimension(:), allocatable :: key
contains
procedure :: init => t1_iterator_init
end type t1_iterator_t
type :: t1_node_t
end type t1_node_t
type :: t1_t
type(t1_node_t), pointer :: root => null ()
end type t1_t
interface
module subroutine t1_iterator_init (iterator, btree)
class(t1_iterator_t), intent(inout) :: iterator
type(t1_t), target :: btree
end subroutine t1_iterator_init
end interface
end module t1
submodule (t1) t1_s
implicit none
contains
module subroutine t1_iterator_init (iterator, btree)
class(t1_iterator_t), intent(inout) :: iterator
type(t1_t), target :: btree
type(t1_node_t), pointer :: node
contains
subroutine fill_key (node)
type(t1_node_t), pointer, intent(out) :: node
end subroutine fill_key
end subroutine t1_iterator_init
end submodule t1_s
Given that you declared your module private, here you should declare
type, public :: t1_node_t
Then, it compiles without problems with nvfortran 24.1
No, the submodule should access all entities of its parent module or parent submodule by host association, cf. J3/24-007, Sec. 5.2.5.
This is a compiler syntax parsing error.
You are most probably right! This doesn’t bother ifort or gfortran, nor even flang-new. Then, in a slightly different subject about implicit none
The standard says "An - Intel Community I just learned that a submodule is its own scope, so it seems like in practice one could make mistakes by assuming that everything is inherited. (I was personally seen submodules as a kind of “extended scope”)
nvfortran 24.3 also fails unless you declare t1_node_t public. It compiles correctly then.
The thread you linked is about implicit typing, not about using type declarations of the parent module. Intel ifort had a similar issue, which was confirmed as such by Steve Lionel:
I guess this a good mwe to open a thread at the nvfortran Forum https://forums.developer.nvidia.com/, they usually reply quite fast.
I reported this in April 2022,
still waiting for it to be fixed. In flang-new it is working