Is it possible to initialize a linked list?

Consider the following example of a linked list.

program pllassign
   implicit none
   type ll
      integer :: i=-1
      type(ll), pointer :: next=>null()
   end type ll
   type(ll), target, save :: first, second, third
   type(ll), pointer :: current => first
   third  = ll(3,null())
   second = ll(2,third)
   first  = ll(1,second)
   do while (associated(current))
      write(*,*) 'current%i=', current%i
      current => current%next
   enddo
end program pllassign

This works as intended, with output like:

$ gfortran pllassign.f90 && a.out
 current%i=           1
 current%i=           2
 current%i=           3

It occurred to me that it might be nice if the linked list could be constructed with initialization rather than assignment. So I tried this:

program pllinit
   implicit none
   type ll
      integer :: i=-1
      type(ll), pointer :: next=>null()
   end type ll
   type(ll), target, save :: third  = ll(3,null())
   type(ll), target, save :: second = ll(2,third)
   type(ll), target, save :: first  = ll(1,second)
   type(ll), pointer :: current => first
   do while (associated(current))
      write(*,*) 'current%i=', current%i
      current => current%next
   enddo
end program pllinit

This does not compile, with either gfortran or NAG, so I figure I must be doing something wrong. Is it possible to construct a linked list using pointers with initialization?

NOTE: Of course, in fortran, one would not use pointer elements of the ll derived type, one would naturally use allocatable instead. However, I already know that it is not allowed to initialize an allocatable variable, so I’m using pointer instead in these examples just because of that language limitation.

EDIT: I changed the original DO loop to a simpler DO WHILE loop.

1 Like

Ignore this - see below.

Fortran 2008 allows an initial-data-target as the initialization for a pointer variable. However, the target must be a variable, not a structure constructor. The constraint is:

C765 A designator that is an initial-data-target shall designate a nonallocatable, noncoindexed variable that has the TARGET and SAVE attributes and does not have a vector subscript. Every subscript, section subscript, substring starting point, and substring ending point in designator shall be a constant expression.

2 Likes

Thanks for the reply. In the code above, the pointer assignment (next) is to a variable (e.g. second). The pointer assignment occurs within the structure constructor ll(), but the structure constructor itself is not the target. The variable (e.g. second) does have the TARGET and SAVE attributes, as required. So I thought I had dodged that bullet.

Also, in the first code, which does compile and work, the pointer initialization

type(ll), pointer :: current => first

occurs. This is also a pointer assignment to a variable (first in that case) of that same derived type ll.

Sorry, I missed an important thing. These are not initial-data-targets, but just initialization, which means a constant expression is required.

1 Like

I experimented with this a little to try to understand this. The first initialization

   type(ll), target, save :: third  = ll(3,null())

seems to work. The following two

   type(ll), target, save :: second = ll(2,third)
   type(ll), target, save :: first  = ll(1,second)

are what causes the problem. Is that because third has a constant expression, while second and first do not?

Yes, exactly.

3 Likes

Ok, I think the following code is as close as I can get to what I wanted to do:

program pllinit
   implicit none
   type ll
      integer :: i=-1
      type(ll), pointer :: next=>null()
   end type ll
   type(ll), target, save :: third  = ll(3,null())
   type(ll), target, save :: second = ll(2,null())
   type(ll), target, save :: first  = ll(1,null())
   type(ll), pointer :: current => first
   first%next => second
   second%next => third
   do while (associated(current))
      write(*,*) 'current%i=', current%i
      current => current%next
   enddo
end program pllinit

Here the linked list data value is initialized at declaration, but the pointer component must be assigned at run time. Oddly, the pointer initialization of current is allowed at declaration.

That’s because first is a valid initialization-data-target.

2 Likes

Yes, but do you see the basis for the confusion? Consider the following:

   type(ll), target, save :: third  = ll(3,null())
   type(ll), target, save :: second = ll(2,third)                                                                         
   type(ll), pointer :: current => third

This does not compile, but remove the second line and it does. The pointer component second%next cannot point to the target third, while current can.

No, I don’t see a problem with this. third is not a pointer, and is initialized to a constant structure constructor - fine. current is a pointer and has a target, save variable as its initialization-data-target - fine. second is not a pointer and is initialized to a non-constant expression - not fine.

2 Likes

To spell this out in detail, a programmer would consider the declaration

type(ll), target, save :: second = ll(2,third)

to be equivalent to something like

second%i = 2
second%next => third

That pointer initialization seems like it should have the same kinds of restrictions as the following pointer initialization

current => third

That latter one is legal, while the former one is not. They both have the same information available at compile time, so I do not understand why the language restricts one but allows the other. Yes, I see that one pointer is on the right hand side of the declaration, while the other is on the left, but that seems to be just an artificial distinction in this case. If a compiler has the information to do one, it has that exact same information available to do the other.

As a practical matter, it would be quite useful if programmers could initialize data structures such as linked lists, trees, graphs, networks, heaps, and so on. By initialize, I mean at compile time on the declaration statement, not at run time with an initialization routine that uses assignments. Is there any chance that this capability could be added to the language?

@RonShepard ,

You may want to first summarize your idea(s) or change request(s) in a post the GitHub J3 Fortran site.

Also, why don’t you join the J3 Fortran committee? If not, please review the link below for the last available minutes of the meeting from July of last year - see if there are any institutions and/or representatives through whom you can try to table specific requests for the next or subsequent revisions to the standard. That way, the proposals of interest to you and the teams you work with can get more attention that what happens with discussion threads at comp.lang.fortran, this discourse, etc.

As far as I can guesstimate from the standard, there is no technical reason for the current restriction. The relaxation brought about by Fortran 2008 was not extended to component initialization of objects of types with derived type components of POINTER attribute via structure constructors. I think it is an oversight. Thus the restriction remains as it does with other components of derived types, meaning with the code below block4 is treated as block3 instead of block2 and block1.

   block1: block
      integer, target :: a = 42
      integer, pointer :: x => a !<-- Allowed
   end block block1
   block2: block
      type :: t
         integer :: n = 0
      end type
      type(t), target :: a
      type(t), pointer :: x => a !<-- Allowed
   end block block2
   block3: block
      type :: t
         integer :: n = 0
      end type
      integer :: a = 42
      type(t) :: x = t( n=a ) !<-- Not Allowed
   end block block3
   block4: block
      type :: t
         integer, pointer :: n => null()
      end type
      integer, target :: a = 42
      type(t) :: x = t( n=a )  !<-- Not Allowed
   end block block4
end 
C:\temp>gfortran -c q.f90
q.f90:17:26:

   17 |       type(t) :: x = t( n=a ) !<-- Not Allowed
      |                          1
Error: Parameter 'a' at (1) has not been declared or is a variable, which does not reduce to a constant expression
q.f90:24:26:

   24 |       type(t) :: x = t( n=a )  !<-- Not Allowed
      |                          1
Error: Parameter 'a' at (1) has not been declared or is a variable, which does not reduce to a constant expression

So what this will take is papers at the J3 Fortran site that can help with discussion and also tabling the proposal at the J3 meeting(s) toward consideration now for Fortran 202Y and/or the next revision.

Offhand, I agree with @FortranFan that the standard could be relaxed to allow a structure constructor where all non-pointer components are constant expressions and pointer components are either null() or a variable that meets the current requirements for initial-data-target.

1 Like

There is an easy workaround for the block3 case.

block3: block
      type :: t
         integer :: n = 0
      end type
      integer, parameter :: aval = 42
      integer :: a = aval
      type(t) :: x = t( n=aval )
   end block block3

So that just leaves block4 as the oddball case, and, unlike the block3 case, there is no workaround for this kind of pointer component initialization.

As a side comment, I would have preferred for pointer assignments to always use the => notation rather than the = notation. That is, in an assignment statement I would have preferred the syntax

   x = t(n=>a)

rather than

   x = t(n=a)

when the pointer component name is used. Anyone have any idea why they did it the way they did?

You’re referring to the use of = in the structure constructor, as otherwise pointer assignment is always =>. Here the = is not assignment but rather component identification. It’s a fine point, I’ll admit.

2 Likes

! Created Dec 2021
! Version 0.1a
! Updates: changes to some calls for ifort compatibility.
! Updates: changes to try showing off constructor like functions.
Program testing
implicit none

! Declare types
type :: t_beanpole
integer :: i_value
type(t_beanpole), pointer :: p_next, p_last
end type t_beanpole

! Declare variables
integer :: i_list(3)
type(t_beanpole), pointer :: p_root

! Start program
print *, “Testing program!”
print *, “Now testing linked list creation!”
i_list = (/11,11,11/)
print *, “Current array:”
print *, i_list
print *, “New linked list:”
call contructlist(i_list, p_root)
call printlist(p_root)

contains

! Subroutine to construct a linked list from an array.
subroutine contructlist(i_list, p_root)
implicit none

! Declare incoming variables and scope
! We are assuming only one dimension with the array...
integer, intent(in) :: i_list(:)
type(t_beanpole), pointer, intent(inout) :: p_root

! Declare local variables
integer :: i_loop, i_size
type(t_beanpole), pointer :: p_lefthand, p_righthand

! Start subroutine
i_size = size(i_list)
if (i_size .gt. 0) then  ! if at least one.
  allocate(p_lefthand)
  p_lefthand%p_next => null()
  p_lefthand%p_last => null()
  p_lefthand%i_value = i_list(1)
  p_root => p_lefthand   ! if more to link
  do i_loop = 2, size(i_list)
     allocate(p_righthand)
     p_righthand%p_next => null()
     p_righthand%p_last => p_lefthand
     p_lefthand%p_next => p_righthand
     p_lefthand => p_righthand
     p_lefthand%i_value = i_list(i_loop)
  end do
end if

end subroutine contructlist

! Subroutine to print a link list.
subroutine printlist(p_root)
implicit none

! Declare incoming varibale and scope
type(t_beanpole), pointer, intent(in) :: p_root

! Declare local variables
type(t_beanpole), pointer :: p_lefthand

! Start subroutine
p_lefthand => p_root
do while(associated(p_lefthand))  ! Start at front
   print *, p_lefthand%i_value    ! print
   p_lefthand => p_lefthand%p_next    ! and keep going
end do

end subroutine printlist

end program testing

***Might be a better bet?