A gfortran issue with parameterized derived types

Hi, I ran into something problematic and I have no idea how to fix it. Here is the minimum code that generates the error:

program main
   use iso_fortran_env, only: real32
   implicit none

   type :: arr_o_rarr(k)
      integer, kind :: k
      real(k), allocatable :: arr(:)
   end type arr_o_rarr

   type(arr_o_rarr(real32)), allocatable :: arrs(:)
   integer :: i, j, dims

   dims = 10
   allocate (arrs(dims))
   do i = 1, dims
      arrs(i)%arr = [(j*1., j = 1, i)]
   end do
end program main

It seems ifort can compile and run this code happily but gfortran will end up with core dumped. How could I fix it if I want to use gfortran?

1 Like

You’re using parameterized derived type (PDT) facility introduced since the Fortran 2003 standard. The implementation of this facility in gfortran has gaps. See this.

If you can join the GCC/gfortran community and do compiler development (it’s open source initiative as you may know), that may be your fastest route to resolving this problem.

2 Likes

There is definitely a bug here or better as @FortranFan said its implementation in gfortran is not complete yet. However, there is a walkaround but not the exact solution you would expect.
In short: you cannot have both allocatable: the internal array and the PDT (parameterized derived type) and actually the latter case I couldn’t make it work.

The following module is common for both the following examples:

module m_matrix
    implicit none
    type :: t_matrix(rows, k)
        integer, len :: rows
        integer, kind :: k 
        real(kind = k):: values(rows) ! note that I am not declaring it here as allocatable!!!
    end type 
end module m_matrix

First (working) example with an allocatable internal array (link):

program test_matrix
    use iso_fortran_env, only:real32
    use m_matrix
    implicit none
    type(t_matrix(k=real32,rows=:)), allocatable :: m
    integer :: dims, i

    dims = 10
    allocate(t_matrix(k=real32, rows=dims) :: m)

    m%values = [(i*1., i = 1, dims)]
    print*, m%values
end program test_matrix

Second (non-working) example with allocatable PDT (link):

program test_matrix
    use iso_fortran_env, only:real32
    use m_matrix
    implicit none
    integer, parameter :: rr = 5
    type(t_matrix(k=real32, rows=rr)), allocatable ::  m(:)
    integer :: dims, i

    dims = 10
    allocate(m(dims)) ! Program compiles until here provided 
    ! the below lines are commented, and I have no idea why it does so.
    
    ! but if you try to access the allocated memory, as I do below, it throws a 
    ! segmentation fault (see link above)
    !do i = 1, dims
    !    m(i)%values = 0.
    !    print*,m(i)%values
    !end do
end program test_matrix

Even with the first working example, if I am being honest, I am not sure why it compiles or if it should.

ps1. Regarding the second case, I also tried to wrap the t_matrix in another derived type but not matter what I tried I was getting the same error.

ps2. Regardless of the current state of PDT, I personally never found a good reason to use them, nothing I cannot code with a simple DT, and since most times the parameters are known at run time this feature as it is, is just useless. Also, the parameter integer, kind :: k must always be known at compile-time, which is what really matters for me. Of course, if that wasn’t the case then we would be talking about the first template feature of Fortran.

3 Likes

Just to clarify for the benefit of readers who may not be fully familiar with the topic on hand: the above comment suggesting the “the internal array and the PDT (parameterized derived type)” “cannot have both allocatable” may only apply to the current state of gfortran implementation.

Fortran language as well as other compiler implementations do support both to have the ALLOCATABLE attribute. As mentioned by @han190, the code in the original post works as expected per the Fortran standard with Intel Fortran compiler.

5 Likes

I disagree entirely with the above assertion.

Given a robust compiler implementation, the parameterized derived type (PDT) facility is rather convenient and useful in design of good scientific software. Here’re some immediate use cases that come to my mind:

  1. The “problem size(s)” in several computations and simulations in scientific and technical computing are themselves parameterized in terms of numbers of certain things that are known right at the start of the calculation e.g., number of species and their elemental composition in chemical physics calculations, say CO2 and other molecular components in climate systems (whether it be atmosphere, ocean, etc.) modeling. PDTs lend themselves nicely to such needs: allocation of an object of a PDT type ensures all the subobjects are all immediately allocated to the right sizes. The code for the PDT type can be simplified considerably relative to code designs that rely on subobjects that have the ALLOCATABLE attribute.
  2. Computations requiring improved performance based on vectorization and SIMD intrinsics, etc. can benefit from code designs with SoA (structure of arrays) approach whereas the conceptualization, abstraction, and problem formulation and other calculation modes are often more amenable to AoS (arrays of structure) approach. For certain problems, PDTs with length-type parameters can offer a design solution that combines the two yielding the typical convenience with performance benefits.
  3. Higher-level abstraction of applications of the only intrinsic ‘container’ class in Fortran which is arrays. Such as matrices including toward sparse matrix designs. Or certain needs involving limited heterogeneity e.g., hashing in encryption, etc. PDTs can serve as a convenient encapsulation ‘class’ for these applications.
  4. Packaging of utility ‘classes’ which are known ‘a priori’ to only support certain variants e.g., a solver class that works with the supported floating-point precision options in a processor implementation that is usually only in the range of 3 to 4 kinds (e.g., Intel supports 3 as given by REAL_KINDS constant in ISO_FORTRAN_ENV). Or a pre or postprocessing utility toward spatial transformations that may only support 1D, 2D, and 3D modes. The use of PDTs with kind-type parameters toward such ‘classes’ prove really convenient.

Of course, all of the use cases can be improved greatly with better support for generics in Fortran. I can only hope any work toward in a future Fortran standard (202Y?) will build and expand upon the current PDT facility in the language.

4 Likes

I just want to clarify that this assertion was based on my personal opinion and (limited) experience.

  1. Where I come from, in our codes, there is not a single hardcoded/compile-time known parameter with the only exception that of a couple of physical constants (Boltzmann and Avogadro number) and pi.
  2. No objection about SoAs. I agree. But I do not see how the concept of SoAs is only or better served by PDTs and not just simple DTs.

Can you give an example, or explain how this can work? This is a genuine question, I really do not know how PDTs can be a middle solution.

  1. Same as 2.
  2. This is indeed a case and most probably one of many others that I am not familiar with and I will take your word for it.
2 Likes

The use case for PDT that I encountered is letting the user choose the real type kind at run time rather than compile time in the client code rather than using a pre-processor when compiling the library . Alternatively this could be accomplished with generic procedures, but for a derived type with many methods that work on the real array component of the type, the code quickly explodes in size.

2 Likes

My point in the earlier post is PDTs can be more convenient and efficient with both design and consumption compared to type components of ALLOCATABLE attribute and as such PDTs are rather valuable in Fortran.

In this link in the post dated “02-17-2019 08:07 AM”, I post a generic, simple example involving PDTs that hints at how SoA approach can be achieved in what may be primarily an AoS based ‘class’ design. I don’t have the rights to share an actual example from industry that employs a similar design approach but in more elaborate fashion.

Similarly, in this thread - scroll way down in the thread to comment dated Thu, 10/26/2017 - 21:46 - I show a simple case of a utility class that can work with different precision of the ‘data’ of interest, such as the molar volume of a fluid, in the same program.

4 Likes

I can see a good use of PDT for defining generic derived types similar to what Milan suggests below. But I have always tried to avoid it for performance reasons, which may be totally ungrounded (My fear stems from an anonymous feedback in a Fortran survey the standard committee distributed around 2015). I have never tested the performance of PDT. Any thoughts or advice on this matter? Thanks in advance.

Re: PDTs, as you know few compilers support robust and reasonably full-featured implementations. Intel Fortran i.e., IFORT is nearly there but users have to beware, it too falls over when it comes to real-life problems. So I agree it’s still impractical to start “coding in anger” using PDTs in one’s day job, the “internal compiler errors (ICEs)” with PDTs alone will get one fired!

Given this, it is unfortunately still too early to fully evaluate performance, but you’re right: when compilers are struggling with implementing the feature itself, the most important aspect of compiler optimizations are essentially pending when it comes to PDTs.

Nonetheless, I suggest you take a look at these 2 links - I repost them since one of the links in my previous post doesn’t work anymore:

  1. An alternate method to support different floating-point kinds,
  2. An option to combine SoA approach with AoS class design.

With both of these cases, PDTs provide several benefits overall with program design and with little to no adverse effect on performance.

But I agree the performance aspect may end up varying significantly with quality of compiler implementations, thus YMMV may apply here too.

So I have to admit unfortunately: given the state of compilers, proceed with great caution when it comes to PDTs.

1 Like

Thanks! The Intel forum example is super helpful. I spent all last night trying to implement a case similar to your example. Either I did it wrong or gfortran 10 has some bugs in type-bound procedures within PDTs.

Some updates: Here is a regeneration of FortranFan’s example on the Intel Fortran forum (for simplicity, I have included the include-file in the code below):

module kinds_m
   use, intrinsic :: iso_fortran_env, only : I8 => int64
   implicit none
   integer, parameter :: R4 = selected_real_kind( p=6 )
   integer, parameter :: R8 = selected_real_kind( p=12 )
end module

module cpu_m
   use kinds_m, only : I8, R8
   implicit none
contains
   subroutine cpu_t( time )
      !.. Argument list
      real(R8), intent(inout) :: time
      !.. Local variables
      integer(I8) :: tick
      integer(I8) :: rate
      call system_clock (tick, rate)
      time = real(tick, kind=kind(time) ) / real(rate, kind=kind(time) )
      return
   end subroutine cpu_t
end module

module aux_m

   use kinds_m, only : R4, R8
   use cpu_m, only : cpu_t

   implicit none

   interface calc_aux
      module procedure calc_aux_R4
      module procedure calc_aux_R8
   end interface

   real(R8), protected, public :: calc_time = 0.0_r8

contains

   subroutine calc_aux_R8( x, y, z, xx, yy, zz, xxx, yyy, zzz, aux )

      ! Argument list
      real(kind=R8), contiguous, intent(inout) :: x(:)
      real(kind=R8), contiguous, intent(inout) :: y(:)
      real(kind=R8), contiguous, intent(inout) :: z(:)
      real(kind=R8), contiguous, intent(inout) :: xx(:)
      real(kind=R8), contiguous, intent(inout) :: yy(:)
      real(kind=R8), contiguous, intent(inout) :: zz(:)
      real(kind=R8), contiguous, intent(inout) :: xxx(:)
      real(kind=R8), contiguous, intent(inout) :: yyy(:)
      real(kind=R8), contiguous, intent(inout) :: zzz(:)
      real(kind=R8), intent(out)               :: aux

      !include 'calc_aux.f90'

      ! Local variables
      integer :: i
      real(R8) :: t1, t2

      call cpu_t( time=t1 )
      do concurrent ( i = 1:size(x) )
         x(i) = 56*real(i)-1000
         y(i) = 56*real(i)-1000*log(real(i))
         z(i) = 56*real(i)-1000*log(real(i+1))
         xx(i) = 56*real(i)-1000*log(real(i+10))
         yy(i) = 56*real(i)-1000*log(real(i+3))
         zz(i) = 56*real(i)-1000*log(real(i+2))
         xxx(i) = 56*real(i)-1000*log(real(i+5))
         yyy(i) = 56*real(i)-1000*log(real(i+4))
         zzz(i) = 56*real(i)-1000*log(real(i+9))
      end do      
      aux = sum(x) - sum(y) + sum(z) - sum(xx) + sum(yy) - sum(zz) + sum(xxx) - sum(yyy) - sum(zzz)
      call cpu_t( time=t2 )

      calc_time = t2 - t1

      return

   end subroutine

   subroutine calc_aux_R4( x, y, z, xx, yy, zz, xxx, yyy, zzz, aux )

      ! Argument list
      real(kind=R4), contiguous, intent(inout) :: x(:)
      real(kind=R4), contiguous, intent(inout) :: y(:)
      real(kind=R4), contiguous, intent(inout) :: z(:)
      real(kind=R4), contiguous, intent(inout) :: xx(:)
      real(kind=R4), contiguous, intent(inout) :: yy(:)
      real(kind=R4), contiguous, intent(inout) :: zz(:)
      real(kind=R4), contiguous, intent(inout) :: xxx(:)
      real(kind=R4), contiguous, intent(inout) :: yyy(:)
      real(kind=R4), contiguous, intent(inout) :: zzz(:)
      real(kind=R4), intent(out)               :: aux

      !include 'calc_aux.f90'

      ! Local variables
      integer :: i
      real(R8) :: t1, t2

      call cpu_t( time=t1 )
      do concurrent ( i = 1:size(x) )
         x(i) = 56*real(i)-1000
         y(i) = 56*real(i)-1000*log(real(i))
         z(i) = 56*real(i)-1000*log(real(i+1))
         xx(i) = 56*real(i)-1000*log(real(i+10))
         yy(i) = 56*real(i)-1000*log(real(i+3))
         zz(i) = 56*real(i)-1000*log(real(i+2))
         xxx(i) = 56*real(i)-1000*log(real(i+5))
         yyy(i) = 56*real(i)-1000*log(real(i+4))
         zzz(i) = 56*real(i)-1000*log(real(i+9))
      end do      
      aux = sum(x) - sum(y) + sum(z) - sum(xx) + sum(yy) - sum(zz) + sum(xxx) - sum(yyy) - sum(zzz)
      call cpu_t( time=t2 )

      calc_time = t2 - t1

      return

   end subroutine

end module aux_m

module pdt_m

   use kinds_m, only : R4, R8
   use cpu_m, only : cpu_t
   use aux_m, only : caux => calc_aux

   implicit none

   type :: pdt_t(K,N)
      integer, kind :: K = R4
      integer, len :: N = 1
      real(kind=K) :: x(N)
      real(kind=K) :: y(N)
      real(kind=K) :: z(N)
      real(kind=K) :: xx(N)
      real(kind=K) :: yy(N)
      real(kind=K) :: zz(N)
      real(kind=K) :: xxx(N)
      real(kind=K) :: yyy(N)
      real(kind=K) :: zzz(N)
   contains
      private
      procedure, pass(this) :: calc_aux_R4
      procedure, pass(this) :: calc_aux_R8
      generic, public :: calc_aux => calc_aux_R4, calc_aux_R8
   end type pdt_t

   real(R8), protected, public :: calc_time = 0.0_r8

contains

   subroutine calc_aux_R4( this, aux )

      ! Argument list
      class(pdt_t(K=R4,N=*)), intent(inout) :: this
      real(kind=R4), intent(out)            :: aux

      ! Local variables
      real(R8) :: t1, t2

      call cpu_t( time=t1 )
      aux = 0.0_R4
      call caux( this%x, this%y, this%z, this%xx, this%yy, this%zz, this%xxx, this%yyy, this%zzz, aux )
      call cpu_t( time=t2 )

      return

   end subroutine

   subroutine calc_aux_R8( this, aux )

      ! Argument list
      class(pdt_t(K=R8,N=*)), intent(inout) :: this
      real(kind=R8), intent(out)            :: aux

      ! Local variables
      real(R8) :: t1, t2

      call cpu_t( time=t1 )
      aux = 0.0_R8
      call caux( this%x, this%y, this%z, this%xx, this%yy, this%zz, this%xxx, this%yyy, this%zzz, aux )
      call cpu_t( time=t2 )

      calc_time = t2 - t1

      return

   end subroutine

end module pdt_m

module dt_m

   use kinds_m, only : R8
   use cpu_m, only : cpu_t

   implicit none

   type :: dt_t
      real(kind=R8) :: x
      real(kind=R8) :: y
      real(kind=R8) :: z
      real(kind=R8) :: xx
      real(kind=R8) :: yy
      real(kind=R8) :: zz
      real(kind=R8) :: xxx
      real(kind=R8) :: yyy
      real(kind=R8) :: zzz
   end type dt_t

   real(R8), protected, public :: calc_time = 0.0_r8

contains

   subroutine calc_aux( this, aux )

      ! Argument list
      type(dt_t), intent(inout)  :: this(:)
      real(kind=R8), intent(out) :: aux

      ! Local variables
      integer :: i
      real(R8) :: t1, t2

      call cpu_t( time=t1 )
      aux = 0.0_R8
      do i = 1, size(this)

         this(i)%x = 56*real(i)-1000
         aux = aux  + this(i)%x

         this(i)%y = 56*real(i)-1000*log(real(i))
         aux = aux  - this(i)%y

         this(i)%z = 56*real(i)-1000*log(real(i+1))
         aux = aux  + this(i)%z

         this(i)%xx = 56*real(i)-1000*log(real(i+10))
         aux = aux  - this(i)%xx

         this(i)%yy = 56*real(i)-1000*log(real(i+3))
         aux = aux  + this(i)%yy

         this(i)%zz = 56*real(i)-1000*log(real(i+2))
         aux = aux  - this(i)%zz

         this(i)%xxx = 56*real(i)-1000*log(real(i+5))
         aux = aux  + this(i)%xxx

         this(i)%yyy = 56*real(i)-1000*log(real(i+4))
         aux = aux  - this(i)%yyy

         this(i)%zzz = 56*real(i)-1000*log(real(i+9))
         aux = aux  - this(i)%zzz

      end do
      call cpu_t( time=t2 )

      calc_time = t2 - t1

      return

   end subroutine

end module dt_m

program p

   !dir$ if defined (rbytes)
   !dir$ else
      !dir$ define rbytes = 64
   !dir$ end if
   !dir$ if (rbytes == 32)
   use kinds_m, only : WP => R4
   !dir$ else
   use kinds_m, only : WP => R8
   !dir$ end if

   implicit none

   integer, parameter :: N = 50000000

   blk1: block
      use pdt_m, only : pdt_t, calc_time
      type(pdt_t(K=WP,N=:)), allocatable :: pdt
      real(WP) :: aux
      allocate( pdt_t(K=WP,N=N) :: pdt )
      call pdt%calc_aux( aux )
      print *, "Block 1: PDT"
      print *, "aux = ", aux
      print "(g0,g10.3,g0)", "Calc time = ", calc_time, " seconds"
      print *
   end block blk1

   blk2: block
      use dt_m, only : dt_t, calc_aux, calc_time
      type(dt_t), allocatable :: dt(:)
      real(WP) :: aux
      allocate( dt(N) )
      call calc_aux( dt, aux )
      print *, "Block 2: Derived Type"
      print *, "aux = ", aux
      print "(g0,g10.3,g0)", "Calc time = ", calc_time, " seconds"
      print *
   end block blk2

   blk3: block
      use aux_m, only : calc_aux, calc_time
      real(WP), allocatable :: x(:), y(:), z(:), xx(:), yy(:), zz(:), xxx(:), yyy(:), zzz(:)
      real(WP) :: aux
      allocate( x(N), y(N), z(N), xx(N), yy(N), zz(N), xxx(N), yyy(N), zzz(N) )
      call calc_aux( x, y, z, xx, yy, zz, xxx, yyy, zzz, aux )
      print *, "Block 3: Arrays"
      print *, "aux = ", aux
      print "(g0,g10.3,g0)", "Calc time = ", calc_time, " seconds"
   end block blk3

   stop

end program

The above compiles and runs fine with the Intel Fortran compiler 2021, but it does not compile with Gfortran. Here is the error message:

main.f90:146:15:
146 |       procedure, pass(this) :: calc_aux_R4
    |               1
Error: Argument ‘this’ of ‘calc_aux_r4’ with PASS(this) at (1) must be of the derived-type ‘pdt_t’

main.f90:147:15:
147 |       procedure, pass(this) :: calc_aux_R8
|               1
Error: Argument ‘this’ of ‘calc_aux_r8’ with PASS(this) at (1) must be of the derived-type ‘pdt_t’

main.f90:287:10:
287 |       use pdt_m, only : pdt_t, calc_time
|          1
Fatal Error: Cannot open module file ‘pdt_m.mod’ for reading at (1): No such file or directory
compilation terminated.

Does anyone know if this is a gfortran bug or it can be somehow fixed to work? Thanks again in advance.

@shahmoradi , please see discussion over at comp.lang.fortran when the announcement re: gfortran and PDTs was first made.

What you have encountered is a gap in gfortran implementation. Unfortunately there are quite a few such outstanding issues as you will note at that comp.lang.fortran and they date back to year 2017 when Paul Rich Thomas, a FOSS warrior for GNU, first attempted PDT implementation in gfortran. Unfortunately the problems have since remained outstanding.

Re: “it can be somehow fixed?,” note the fixes truly need to be made in the compiler itself. What the GCC/gfortran ecosystem truly needs are many volunteers who are willing to do C programming in the gfortran front-end to enhance the compiler for this and many other features. It will be really cool if the greatly increased Community engagement and awareness (and dare I say, excitement) around Fortran can translate to many new volunteers for gfortran willing to work on all the pending features and issues from 2003 revision thru’ Fortran 202X.

1 Like

Here’s a trivial case one can try:

module m
   type :: t(k)
      integer, kind :: k
   contains
      procedure, pass(this) :: sub   
   end type
contains
   subroutine sub( this )
      class(t(k=1)), intent(inout) :: this
   end subroutine 
end module 

C:\Temp>gfortran -c m.f90
m.f90:5:15:

5 |       procedure, pass(this) :: sub
  |               1

Error: Argument ‘this’ of ‘sub’ with PASS(this) at (1) must be of the derived-type ‘t’

Note there is nothing wrong with this example, readers can check it out with a few other compilers that support PDTs: IFORT, NagFor, etc.

1 Like

Honestly, my feelings have mostly been the same. I still struggle to understand what this feature is attempting to accomplish. My tries of involving PDTs ended when I learned that you actually only can implement type-bound procedures for one kind at a time, with no way to make it generic (without using workarounds like: preprocessors, include, copying the code). Perhaps it’s an attempt at fooling around with generics, but even if the compiler support was complete, with “kind” being problematic and “len” being easily replaced by allocatable arrays, I really cannot see a scenario in which I would choose PDTs for the code design. It could be my lack of understanding of this feature, but in my opinion at this point it is still too limited to have any application. At least until the kinds become generic, without the need for code duplication.

I only recently realized a clear use case for PDT, defining generic derived types. Right now, I have to write generic derived types in a codebase, and simply replicating the type definitions for all kinds is highly undesirable. PDT seems to be the only path forward, at least for now. Unfortunately, GFortran does not have a fully-featured implementation of PDT yet, removing all the benefits of its support by other compilers.

2 Likes

Compilers are expected to check “TKR” at call boundaries: Type Kind and Rank. Not size of arrays.

With a length-parameter PDT, the size becomes a type parameter and is subject to checking.

2 Likes

@FortranFan out of curiosity I took your mwe and tested it with a couple of extra tweaks Compiler Explorer and saw that gfortran 14.1 now enables compiling and running this code. I do not know how far the bugs with PDTs have been improved, but this seems encouraging.

@han190 A slight modification of your code enables it to run with the latest gfortran:

program main
   use iso_fortran_env, only: real32
   implicit none

   type :: arr_o_rarr(k)
      integer, kind :: k
      real(k), allocatable :: arr(:)
   end type arr_o_rarr

   type(arr_o_rarr(real32)), allocatable :: arrs(:)
   integer :: i, j, dims

   dims = 10
   allocate (arrs(dims))
   do i = 1, dims
      allocate(arrs(i)%arr(i), source= [(j*1., j = 1, i)] ) !> this: "arrs(i)%arr = [(j*1., j = 1, i)]" produced a segfault
      print *, arrs(i)%arr
   end do
   
end program main
stdout with gfortran 14.1
Program stdout

   1.00000000    
   1.00000000       2.00000000    
   1.00000000       2.00000000       3.00000000    
   1.00000000       2.00000000       3.00000000       4.00000000    
   1.00000000       2.00000000       3.00000000       4.00000000       5.00000000    
   1.00000000       2.00000000       3.00000000       4.00000000       5.00000000       6.00000000    
   1.00000000       2.00000000       3.00000000       4.00000000       5.00000000       6.00000000       7.00000000    
   1.00000000       2.00000000       3.00000000       4.00000000       5.00000000       6.00000000       7.00000000       8.00000000    
   1.00000000       2.00000000       3.00000000       4.00000000       5.00000000       6.00000000       7.00000000       8.00000000       9.00000000    
   1.00000000       2.00000000       3.00000000       4.00000000       5.00000000       6.00000000       7.00000000       8.00000000       9.00000000       10.0000000    
2 Likes

Thanks @hkvzjal. It seems gfortran developers are subtly improving the PDT features since I can’t find these changes in their release note. But I still won’t trust the PDT implementation of gfortran. Here is an example,

module utility

  implicit none

  public :: vector_type
  private

  type :: vector_type(len)
    integer, len :: len
    integer :: values(len)
  end type vector_type

  interface vector_type
    module procedure :: new_vector
  end interface vector_type

contains

  pure function new_vector(array) result(vector)
    integer, intent(in) :: array(:)
    type(vector_type(len=:)), allocatable :: vector

    if (allocated(vector)) then
      if (vector%len /= size(array)) then
        deallocate (vector)
        allocate (vector_type(len=size(array)) :: vector)
      end if
    else
      allocate (vector_type(len=size(array)) :: vector)
    end if
    vector%values = array
  end function new_vector
  
end module utility

program main
  use, non_intrinsic :: utility
  implicit none

  type(vector_type(len=:)), allocatable :: vector

  vector = vector_type([1, 2])
  print *, vector%values
  vector = vector_type([1, 2, 3])
  print *, vector%values
end program main

gfortran 13.3.1 pops nothing while ifx gives me correct results

stdout with ifx (IFX) 2024.0.2 1 2
1 2 3
Maybe gfortran 14 solves the issue already?

Probably not, since GNU Fortran (GCC) 15.0.0 20240707 on Windows from equation.com still produces no output.

1 Like