After an update commit on gfortran within the last week, the code below throws an error upon compilation, but it worked with earlier versions, with nagfor, intel, flang-new. Is it standard-conformant or a regression?
t1.f90:28:13:
28 | submodule (t1) t1_s
|             1
Error: Variable ‘n_external’ cannot appear in the expression at (1)
module t1
  use, intrinsic :: iso_c_binding !NODEP!
  implicit none
  private
  public :: t1_t
  integer :: N_EXTERNAL = 0
  type :: t1_t
  contains
    procedure :: set_n_external => t1_set_n_external
  end type t1_t
  abstract interface
     subroutine ol_eval (id, pp, emitter) bind(C)
       import
       real(kind = c_double), intent(in) :: pp(5 * N_EXTERNAL)
     end subroutine ol_eval
  end interface
  interface
    module subroutine t1_set_n_external (object, n)
      class(t1_t), intent(inout) :: object
      integer, intent(in) :: n
    end subroutine t1_set_n_external
  end interface
end module t1
submodule (t1) t1_s
  implicit none
contains
  module subroutine t1_set_n_external (object, n)
    class(t1_t), intent(inout) :: object
    integer, intent(in) :: n
    N_EXTERNAL = n
  end subroutine t1_set_n_external
end submodule t1_s