Question on structure constructors with private components in submodules

I have a question regarding the code below: I use a type declaration t1 with private components in a module, which has to be there because it is used as a component of another UDT made public in that module. Then I’m using a function in a submodule of that module with a structure constructor. gfortran and nagfor do compile this code and use it correctly, ifort complains about
error #6053: Structure constructor may not have components with the PRIVATE attribute
This is correct if the structure constructor is used outside of the scoping unit of the module, but I thought the submodule is part of the scoping unit of its (parent) module. Was my assumption incorrect or is that a wrong interpretation within the Intel compiler? (meaning that neither gfortran nor Nagfor would catch this). Or is it something the user should not do, and the compiler can but does not have to catch? And if the latter is true, what’s the best thing to work around this problem, besides removing the private statement in the type declaration?

module foo

  implicit none
  private

  type t1
     private
     integer :: i
  end type t1

  interface
     module function xxx ()
       integer :: xxx
     end function
  end interface
  
end module foo

submodule (foo) foo_s
  implicit none

contains
  module function xxx ()
    integer :: xxx
    xxx = 17
  end function
  
  pure function func () result (t)
    type(t1) :: t
    t = t1(42)
  end function func
end submodule foo_s

Thanks, Steve, for your fast reply. I’ll wait for a couple of days of other opinions and then contact Intel support.

Your example appears standards conforming to me (although I’ll note nothing in your module is public, nor is the function in submodule used, although that doesn’t mean it isn’t legal Fortran). I must say that submodules are one of the places I have found the most compiler bugs so it wouldn’t surprise me if this was one of them.

Yeah, this is just a reduced case. I wanted to explain why I can’t move the type declaration to the submodule. I would hypothesize that there are more bugs in parameterized derived types than submodules, but we just recently started to use submodules because nagfor only supports them since their version 7.

@jr_reuter , as other replies have indicated, it is the Intel compiler that is nonconformant here. This bug in IFORT is present in their latest update (oneAPI v2022.1 aka IFORT v2021.5) also. I suggest you submit a support request at Intel OSC if you are able to, or post at the Intel Fortran forum from where Intel staff does tend to pickup issues with IFORT, IFX compilers.

In the meantime you can consider implementing a generic interface with the same name as your derived type to suitable functions that can serve as your own “structure constructors.” Please note I only suggest this as a workaround until Intel fixes the bug which can be a while, as you will know. And if such a workaround fits into your program workflow.

A simple example with other readers in mind follows:

module m
   type t
      private
      integer :: i
   end type
   interface t
      pure module function construct_t(x) result(r)
         integer, intent(in), optional :: x
         type(t) :: r
      end function
   end interface
end module

submodule(m) sm
contains
   pure module function construct_t(x) result(r)
      integer, intent(in), optional :: x
      type(t) :: r
      if ( present(x) ) r%i = x
   end function
   pure function func() result(r)
      type(t) :: r
      r = t(42)
   end function func
end submodule

C:\temp>ifort /c /standard-semantics m.f90
Intel(R) Fortran Intel(R) 64 Compiler Classic for applications running on Intel(R) 64, Version 2021.5.0 > Build 20211109_000000
Copyright (C) 1985-2021 Intel Corporation. All rights reserved.

C:\temp>