Intel® Fortran Compiler
Build applications that can scale for the future with optimized code designed for Intel® Xeon® and compatible processors.
29390 Discussions

Implement generic data structure in Fortran?

Li_Dong
Beginner
1,343 Views
Dear all,
I would like to know is there a way to implement someelegantgeneric data structures in Fortran, like linked list? I have written one, using "extends", "type-bounded procedure", "class", etc. But there is still some functionality that Ican'trealize, such as don't really deallocate the memory for the later use.
Any comment andsuggestion is welcome! : )
My preliminary code is hosted athttps://github.com/dongli/FortranEnhancement.
Cheers,
dongli
0 Kudos
7 Replies
Tim_Gallagher
New Contributor II
1,343 Views
http://jblevins.org/research/generic-list

It uses the TRANSFER intrinsic to allow you to store arbitrary datasets inside the list.

Before I found this paper, I had written a generic tree using the same method. It's pretty simple, very elegant, but does incur some cost. TRANSFER adds to the expense, but it's worth it if you want a single code base that can store all sorts of different data.

Tim
0 Kudos
Li_Dong
Beginner
1,343 Views
Dear Tim,
Thanks for your information! It is really smart by storing the data in "integer" type.
I have adopted several new features in Fortran 2003, such as derived type, but I would like to create a more clean interface (user doesn't need to care about memory manipulation) and thus more efficient implementation~ What about m4, which seems can bring someflavorof template to Fortran?
Cheers,
dongli
0 Kudos
Tim_Gallagher
New Contributor II
1,343 Views
I actually prefer to us CHARACTER arrays to store the data rather than INTEGER arrays, but it's not a big deal on that one.

Rather than m4, which could work, I would recommend looking at PyF95++.

http://fortranwiki.org/fortran/show/BlockIt

I think the author contributes to these forums...

Tim
0 Kudos
zuch
Beginner
1,343 Views

Maybe Reinhold Bader's slides will be useful he has nice solution for linked list problem in f03

http://www.lrz.de/services/software/programmierung/fortran90/f03_material/Fortran_Object_Oriented.pdf

0 Kudos
Li_Dong
Beginner
1,343 Views
Hi, zuch,
Thanks! I have read the slides, it is a really nice introduction to OO programming in Fortran, but I think the solution there is still problematic. In page 58, the alternative 2 hasn't isolated the memory manipulation from user, because the argument stuff must be allocated by user, so user must take care when to deallocate it.
Cheers,
dongli
0 Kudos
Tim_Gallagher
New Contributor II
1,343 Views
I think, without knowing exactly what you are trying to do, reference counting your derived data types may be what you're after. That way when the number of references drops to 0, it automatically deallocates itself.

The link I gave before for PyF95++ has some offshoots to reference counting -- everything in that package is reference counted. They give a pretty good explanation and details of implementation at:

http://sourceforge.net/apps/mediawiki/blockit/index.php?title=PyF95%2B%2B/STL/Reference_Counting

There was also a recent paper about reference counting in Fortran here:

http://nro-dd.sagepub.com/lp/association-for-computing-machinery/a-reference-counting-implementation-in-fortran-95-2003-fIXSDMF18Z

Sorry the formatting sucks, I can't find another page that has the same article in complete text for free.

It may not be entirely possible to remove the user from the memory handling process depending on what you're trying to do. But I think with all of the above, you can get most of it done. For instance, you can use the generic linked list mentioned previously with a reference counter for the nodes so that the user just has to call a function to create the list. Then as they pop off nodes, it will automatically deallocate the memory associated with them because the reference count is 0 when popped. The user won't have to do any ALLOCATE or DEALLOCATE associated with the list itself.

Tim
0 Kudos
Dharma
Beginner
1,343 Views
Hello all,
I was also trying(experiment) to implement a genric linked list in fortran using unlimited polymorphic object as data holder in the node. I know ifort does not support allocate(...,source='polymorphic_extension'). As a workund i have created a procedure pointer in the list. User must link an allocate procedure to the list. (this will be a small code implimenting allocate( userType :: class(*) obj). Rest of the code is genreic. I have implement , set,get and clear methods for the list. When i run the executable with valgrind, results suggest that there is definatly memory leak which increase with size of the list. Can anyone help me spot the issue.

Here is the code.

[fortran]! Generic linked list implimentation using an unlimited
! polymorphic object
module genDList
 implicit none

 type glist_node
  class(*), pointer         :: data
 ! type(glist_node), pointer :: prev => null()
  type(glist_node), pointer :: next => null()
 end type glist_node

  type gDlist
   type(glist_node), pointer :: begin =>   null()
   type(glist_node), pointer :: end =>   null()
   procedure(allocate_polysource),pointer,nopass :: allocate
   contains
    procedure :: size 		=> size_gDlist
    procedure :: push_front	=> push_front_gDList
    procedure :: clear		=> clear_gDList
    procedure :: get		=> get_gDList
  end type gDlist
! user must implement a subrouitne with this interface
! and link it to allocate of the linked list
  interface
   subroutine allocate_polysource(upoly,poly_source)
    class(*),intent(inout),pointer :: upoly
    class(*),intent(in) :: poly_source
   end subroutine allocate_polysource
  end interface

 type(glist_node), pointer :: current_node =>null()

 contains


 function size_gDList(this) result(N)
  class(gDlist),intent(in) :: this
  integer :: N
  N=0
  current_node => this%begin
   if(associated(current_node)) then
    N=N+1
    do while (associated(current_node%next))
     current_node => current_node%next
     N=N+1
    end do
   end if
 end function size_gDList

 subroutine push_front_gDList(this,obj)
  class(gDlist),intent(inout) :: this
  class(*),intent(in),target :: obj
  integer :: i
  i=0
  if (.not. associated(this%begin)) then
    allocate(this%begin)
    this%end =>   this%begin
    call this%allocate(this%end%data,obj)
    this%end%data =>  obj
    i=i+1
       print*,i
  else
     allocate(this%end%next)
     call this%allocate(this%end%next%data,obj)
     this%end%next%data => obj
     this%end =>   this%end%next
     i=i+1
       print*,i
  end if
   print*,'exit'
 end subroutine push_front_gDList

     ! Clear the list
 subroutine clear_gDList(this)
       class(gDlist), intent(inout) :: this
       type(glist_node), pointer  :: next, current
       integer :: i=0
       nullify(this%end)
       current =>   this%begin

       do while (associated(current))
       i=i+1
       print*,i
          next =>   current%next
         ! deallocate(current%data)
         ! nullify(current%data)
          print*,'dat',associated(current%data)
          nullify(current%data)
           print*,'dat',associated(current%data)
         ! nullify(current%next)
          deallocate(current)
         ! nullify(current)
          current =>   next
       end do
      ! deallocate(this%begin)
 end subroutine clear_gDList


      subroutine get_gDList(this,idx,obj)
       implicit none
       class(gDlist), intent(in)   :: this
       integer, intent(in)       :: idx
       type(glist_node), pointer :: node
       class(*), pointer, intent(out) :: obj
       integer :: t
       integer :: i
       t=1
       node =>   this%begin
       i = 1
       if (i == idx) then
          call this%allocate(obj,node%data)
          obj => node%data
          print*,i,associated(obj,node%data)
          return
       end if
       if (associated(node)) then
          do while (associated(node%next))
             i = i + 1
             node =>   node%next
             if (i == idx) then
               call this%allocate(obj,node%data)
               obj => node%data
               print*,i,associated(obj,node%data)
               return
             end if
          end do
       end if
       write(*,'(a,i0)') 'element does not exist: ', idx

      end subroutine get_gDList

end module genDList

module genDlist_test
 use genDlist
 implicit none
 type A
  real :: R
 end type A
 type(gDlist) :: list_A
 type(A),allocatable, target :: data_A(:)
 contains
 ! user provided subroutine
 ! to implement allocate the list data to user type
  subroutine allocate_polysource_A(upoly,poly_source)
    class(*),intent(inout),pointer :: upoly
    class(*),intent(in) :: poly_source
  select type(poly_source)
   type is(A)
   allocate(A :: upoly)
  end select
  end subroutine allocate_polysource_A
end module genDlist_test

program Test_gDList
 use genDlist_test
 use genDlist
 implicit none
 class(*),pointer :: temp_data_ptr
 type(A),pointer :: temp_data_A
 integer :: N=5
 integer :: i,j
 allocate(data_A(N))
 list_A%allocate => allocate_polysource_A
 do i=1,N
  call random_number(data_A(i)%R)
  call list_A%push_front(data_A(i))
 end do
 print*,'length of the list:,',list_A%size()

  call list_A%clear()
   ! We see that after call to clear list is still associated
   print*,associated(list_A%begin)
   print*,associated(list_A%begin%next)

   do i=1,N
   print*,i,data_A(i)%R
   end do
   deallocate(data_A)
end program Test_gDList[/fortran]

Thanks
Reddy
0 Kudos
Reply