Linked list with PDT

I am trying to create a linked list with parameterized derived type, and here is a minimal example that triggers the error:

module module_utility
implicit none

type :: array_type(kind, len)
  integer, kind :: kind
  integer, len :: len
  real(kind=kind) :: values(len)
end type array_type

type :: node_type(kind, len)
  integer, kind :: kind
  integer, len :: len
  type(array_type(kind, len)) :: array
  type(node_type(kind, len)), pointer :: next => null()
end type node_type

end module module_utility

program main

  use iso_fortran_env, only: real32
  use module_utility
  implicit none

  ! type(node_type(kind=real32, len=10)) :: list 
  ! It works

  type(node_type(kind=real32, len=:)), allocatable :: list
  ! error #6147: The structure definition stack has been exceeded.

end program main

Both ifx and ifort throw me

error #6147: The structure definition stack has been exceeded.

Since it is not an ICE, I must be doing something wrong. What is the proper method for constructing a linked list type using PDT?

1 Like

@han190, your pointer component of node_type needs to have deferred-length. Then with default initialization of type parameters you should get a not implemented error. You can follow-up on the Intel’s plans to implement support for this, you may be out of luck at the moment like with many other aspects of PDTs.

module module_utility
   use, intrinsic :: iso_fortran_env, only : real32
   type :: array_type(kind, len)
     integer, kind :: kind = real32
     integer, len :: len = 1
     real(kind=kind) :: values(len)
   end type array_type

   type :: node_type(kind, len)
     integer, kind :: kind = real32
     integer, len :: len = 1
     type(array_type(kind, len)) :: array
     type(node_type(kind, len=:)), pointer :: next => null()
   end type node_type

end module

  use, intrinsic :: iso_fortran_env, only : real32
  use module_utility

  type(node_type(kind=real32, len=:)), allocatable :: list
end
C:\temp>ifort /c /free /standard-semantics p.f
Intel(R) Fortran Intel(R) 64 Compiler Classic for applications running on Intel(R) 64, Version 2021.9.0 Build 20230302_000000
Copyright (C) 1985-2023 Intel Corporation.  All rights reserved.

p.f(15): error #7555: Not yet implemented: Type containing ALLOCATABLE/POINTER component of same type with different type parameters.   [KIND]
  type(node_type(kind, len=:)), pointer :: next => null()
-----------------^
p.f(23): error #7013: This module file was not generated by any release of this compiler.   [MODULE_UTILITY]
  use module_utility
------^
p.f(29): error #6457: This derived type name has not been declared.   [NODE_TYPE]
  type(node_type(kind=real32, len=:)), allocatable :: list
-------^
p.f(22): error #6580: Name in only-list does not exist or is not accessible.   [REAL32]
  use, intrinsic :: iso_fortran_env, only : real32
--------------------------------------------^
compilation aborted for p.f (code 1)

A strange error #6580 to boot.

1 Like

I understand that no compiler can compile this yet, but if they could, then what exactly does it do. Can each member in the linked list have an array with a different kind and a different len, or must all the arrays have the same kind and len, or is it the same kind but different len?

Over the last 15 years or so, I have tried several times to use PDTs, and there has always been at least one compiler that I need to target that can’t compile the code. On paper, they look like a really nice feature, but in practice, I guess they were just too difficult to implement.

1 Like

Thanks @FortranFan and @RonShepard . But by making the length of the pointer deferred kind of disobeys my original idea that I wanted a node_type with fixed len and kind when I allocate the type. I can always make values an allocatable array and achieve this by

type :: array_type(kind)
  integer, kind :: kind
  real(kind=kind), allocatable :: values(:)
end type array_type

type :: node_type(kind)
  integer, kind :: kind
  type(array_type(kind)) :: array
  type(node_type(kind)), pointer :: next => null()
end type node_type

Then I must create a suitable constructor and destructor, given that the particular type I am working with consists of several such components. At the moment, I don’t seem to have any alternative options.

Just out of curiosity I tried to compile the code by @FortranFan in godbolt with gfortran 12.2 and it compiled without any issue as can be seen here.

A question for the compiler developers and those who have more experience with PDTs than I do. Are most of the problems compilers have with PDTs due to the len parameter (either fixed, assumed or deferred). I recently went through an exercise trying to use PDTs to develop an automatic differentiation package based on operator overloading. I was using the len parameter to set the size of the differential/derivative array. In a test problem that tried to return the derived type containing the function evaluation and its derivatives as a function result, I kept getting all sorts of weird memory allocation type errors even though I wasn’t using any kind of allocatable array. So far only the most recent version of ifx works as I expect it to. Ifort, gfortran, and nvfortran all gag with errors that appear to be related to trying to set the size of the derivative arrray with a len parameter.

Edit: the gfortran version was 11.2, ifort and nvfortran are the latest versions as of today

+1

That’s superb news, outstanding progress by gfortran team, they leapfrog over everyone else.

Not sure I understand your concern here. The standard semantics with deferred-length component gives you the flexibility to work with rectangular lists or jagged ones. You can review the simple word list case to see how it can work for you.

module wordlist_m
   use, intrinsic :: iso_c_binding, only : CK => c_char
   type :: wordlist_t(k,n)
      integer, kind :: k = CK
      integer, len  :: n = 1
      character(kind=k,len=n) :: s
      type(wordlist_t(k=k,n=:)), pointer :: next => null()
   end type
contains
   subroutine add_to_list( list, s )
      ! Argument list
      type(wordlist_t(k=CK,n=:)), pointer, intent(inout) :: list
      character(len=*), intent(in) :: s
      ! Local variables
      type(wordlist_t(k=CK,n=:)), pointer :: item
      ! Elided are checks, etc.
      allocate( wordlist_t(k=CK,n=len(s)) :: item )
      item%s = s
      item%next => list
      list => item
      item => null()
   end subroutine 
   subroutine print_list( list )
      ! Argument list
      type(wordlist_t(k=CK,n=:)), pointer, intent(in) :: list
      ! Local variables
      type(wordlist_t(k=CK,n=:)), pointer :: item
      integer :: i
      character(len=*), parameter :: fmtg = "(g0,t10,g0,t20,g0)"
      i = 0
      item => list
      loop_items: do
         if ( .not. associated(item) ) exit loop_items
         i = i + 1 
         if ( i == 1 ) print fmtg, "i", "Length", "item"
         print fmtg, i, len(item%s), trim( item%s )
         item => item%next 
      end do loop_items
      item => null()
   end subroutine 
end module
   use wordlist_m
   type(wordlist_t(k=CK,n=:)), pointer :: words
   words => null()
   call add_to_list( words, ck_"Hello" ) 
   call add_to_list( words, ck_"Fortran" ) 
   call add_to_list( words, ck_"Lang" )
   call add_to_list( words, ck_"Discourse" )
   call print_list( words )
   ! Elided is clean up
end
C:\temp>gfortran -ffree-form p.f -o p.exe

C:\temp>p.exe
i        Length    item
1        9         Discourse
2        4         Lang
3        7         Fortran
4        5         Hello
2 Likes

@RonShepard , see this trivial example re: your question, “but if they could, then what exactly does it do.” The example works with gfortran but not IFORT or IFX, the latter two issue, “error #7555: Not yet implemented.”

Given the brilliant enhancements in gfortran of late, perhaps you will give PDTs another look. I agree entirely, “they look like a really nice feature”

Apologize for the late reply. Yes, this is exactly what I want and the example you present looks neat! But as you mentioned the intel compiler throws “Not yet implemented” errors. I am actually surprised that gfortran compiles and runs the sample code with no problems.

Not yet implemented? I thought ifort claimed full F2003 conformance a long time.ago.