Parameterized derived types

I was attempting something like the following, where I am initializing a parameterized derived type

module test

implicit none

type x_t(n)
    integer, len :: n
    integer :: v(n)
    character(len = 8), dimension(n) :: str
end type x_t

type y_t
    type(x_t(1)) :: a
    type(x_t(2)) :: b
end type y_t

contains

    ! ...

end module test

program main
    use test
    implicit none
    type(x_t(1)), parameter :: a = x_t(1)([1], [character(len = 8) :: "a1"])
    type(x_t(2)), parameter :: b = x_t(2)([1, 2], [character(len = 8) :: "b1", "b2"])
    type(y_t), parameter :: y = y_t(a, b)

    print *, a
    print *, b
    print *, y

end program main

Should this work? In ifort I get an internal compiler error

Internal error store_pdtlen_data_space: Cannot find record
problem.f90: catastrophic error: **Internal compiler error: internal abort** Please report this error along with the circumstances in which it occurred in a Software Problem Report.  Note: File and line given may not be explicit cause of this error.

In gfortran I get errors beginning with


   25 |     type(x_t(1)), parameter :: a = x_t(1)([1], [character(len = 8) :: "a1"])
      |                                   1
Error: No initializer for component ‘v’ given in the structure constructor at (1)

Is there a problem with my syntax, or are these compiler issues?

The following runs with ifort

module test

implicit none
public

type x_t(n)
    integer, len :: n
    integer :: v(n)
    character(len=8) :: str(n)
end type x_t

type y_t
    type(x_t(n=1)) :: a
    type(x_t(n=2)) :: b
end type y_t

end module test

program main

    use test
    implicit none
    
    type(x_t(n=1)) :: a
    type(x_t(n=2)) :: b
    type(y_t) :: y

    a = x_t(n=1)([1],    [character(len=8) :: "a1"])
    b = x_t(n=2)([1, 2], [character(len=8) :: "b1", "b2"])

    y = y_t(a, b)

    print *, a
    print *, b
    print *, y

end program main

Here’s the output:

ivan@maxwell:~/fortran/20220418_discourse_3263_pdt$ ifort -warn all main.f90 
ivan@maxwell:~/fortran/20220418_discourse_3263_pdt$ ./a.out
           1 a1      
           1           2 b1                  a1      
           1 a1                 1           2 b1                  a1            

I have no clue if it should also work in the parameter case. I was surprised to see the structure constructor of the form x_t(n=1)( ... ) work to begin with. One workaround if you really need the parameter attribute could be to abandon the PDT, and simply use parameter arrays of integer and character string type.

Interestingly, the new Intel Fortran compiler ifx recognizes it as a not yet supported language feature:

$ ifx -warn all main.f90 
/opt/intel/oneapi/compiler/2022.0.2/linux/bin-llvm/xfortcom[0xde27a9]

main.f90(28): error #5533: Feature found on this line is not yet supported in ifx 
    a = x_t(n=1)([1],    [character(len=8) :: "a1"])
--------^
compilation aborted for main.f90 (code 3)

Hopefully, full support will be added soon.

Concerning gfortran, support of parameterized derived types is it’s Achilles’ heel currently. Hopefully it will be improved in the future.

See 84120 – Syntax for used for PDT constructors is incorrect

1 Like

Thanks. I was able to test my example using nagfor and that works properly, but I think it will be wise for me to avoid using parameterized derived types for now.

Internal compiler errors should always be reported to the compiler vendor. If your program was valid it should have been compiled. If not, the compiler should have told you about its bugs. (I have reported various internal compiler errors over the years to various vendors. They appreciate it if you can send them a very short program that produces the error. )