Linked list with PDT

+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