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

Confusion with FORTRAN 2008 OO

holysword
Novice
394 Views

The more I use F08 object orientation, the more confused I get... I was pretty sure I had tested this previously with Intel compiler and it worked (about 4 years ago) but now it refuses to!

Imagine a simple linked list implementation:

TYPE :: List_T
  CLASS(List_T), POINTER :: next => null()
  CLASS(List_T), POINTER :: prev => null()
  
  CONTAINS
    PROCEDURE, PUBLIC :: insert  => ListInsert
    PROCEDURE, PUBLIC :: first   => ListFirst
    PROCEDURE, PUBLIC :: last    => ListLast
    PROCEDURE, PUBLIC :: found   => ListFound
    PROCEDURE, PUBLIC :: append  => ListAppend
    PROCEDURE, PUBLIC :: print   => ListPrint
    FINAL :: ListFree
END TYPE List_T

SUBROUTINE ListAppend(this,new)
  CLASS(List_T), INTENT(INOUT), TARGET  :: this
  CLASS(List_T), INTENT(IN),    POINTER :: new
  ! do stuff here
END SUBROUTINE ListAppend

Then I create a type ExtList_T which extends List_T. I don't want to redefine the "append" function because it is exactly the same, I just want to inherit it. But then if I try something like

TYPE(ExtList_T), POINTER  :: instance1
TYPE(ExtList_T), POINTER  :: instance2

ALLOCATE(instance1)
ALLOCATE(instance2)
! put stuff inside each
CALL instance1%append(instance2)

Intel Compiler complains "error #6633: The type of the actual argument differs from the type of the dummy argument.   [INSTANCE2]"

gfortran compiles that fine. Am I doing something conceptually wrong? Isn't downcasting like that allowed in Fortran?

0 Kudos
9 Replies
Steven_L_Intel1
Employee
394 Views

Your code snippet doesn't match your description. What is type spParams_T? You don't show any use of an ExtList_T.

Please construct and show us a small but complete source that demonstrates the problem. I'd rather not respond to your question until I understand exactly what you're doing (though "downcasting", if I understand your term correctly, is not generally allowed. If you have CLASS(extended-type) you can't pass a base-type.)

0 Kudos
holysword
Novice
394 Views

Steve Lionel (Intel) wrote:

Your code snippet doesn't match your description. What is type spParams_T? You don't show any use of an ExtList_T.

Please construct and show us a small but complete source that demonstrates the problem. I'd rather not respond to your question until I understand exactly what you're doing (though "downcasting", if I understand your term correctly, is not generally allowed. If you have CLASS(extended-type) you can't pass a base-type.)

Woops, by spParams_T I meant ExtList_T. Sorry, I should have paid more attention. I edited the original post to avoid further confusion.

Follows attached an example of module in which this problem happens.

By "downcasting" I mean treating a class as if it were its parent. From my understanding, any class extending List_T has all that it is needed to call ListAppend from the base class. All attributes are there. Is this not allowed in Fortran? I was pretty convinced I have done that in the past with Intel Fortran.

0 Kudos
Steven_L_Intel1
Employee
394 Views

Thanks. The rules change when the dummy argument is a pointer. For non-pointer dummy arguments, the dummy argument must be "type compatible" with the actual argument, which it would be in this case (CLASS(base-type) is type compatible with TYPE(extended-type)). But that's not what you have here. I will quote the standard (and bold the relevant text):

12.5.2.5 Allocatable and pointer dummy variables
1 The requirements in this subclause apply to actual arguments that correspond to either allocatable or pointer dummy data objects.

2 The actual argument shall be polymorphic if and only if the associated dummy argument is polymorphic, and either both the actual and dummy arguments shall be unlimited polymorphic, or the declared type of the actual argument shall be the same as the declared type of the dummy argument.

 

NOTE 12.27
The dynamic type of a polymorphic allocatable or pointer dummy argument may change as a result of
execution of an ALLOCATE statement or pointer assignment in the subprogram. Because of this the
corresponding actual argument needs to be polymorphic and have a declared type that is the same as the
declared type of the dummy argument or an extension of that type
. However, type compatibility requires
that the declared type of the dummy argument be the same as, or an extension of, the type of the actual
argument. Therefore, the dummy and actual arguments need to have the same declared type.
Dynamic type information is not maintained for a nonpolymorphic allocatable or pointer dummy argument.
However, allocating or pointer assigning such a dummy argument would require maintenance of this information
if the corresponding actual argument is polymorphic. Therefore, the corresponding actual argument
needs to be nonpolymorphic.

The compiler is correct to complain here, since the actual argument is not polymorphic and of the same declared type as the dummy argument. Unfortunately, resolving this complicates your code somewhat.... See also C.9.5 in the F2008 standard.

0 Kudos
FortranFan
Honored Contributor II
394 Views

holysword wrote:

.. By "downcasting" I mean treating a class as if it were its parent. From my understanding, any class extending List_T has all that it is needed to call ListAppend from the base class. ..

You stated earlier, "The more I use F08 object orientation, the more confused I get."  Perhaps trying to simply things might help (you know the cliche - KISS).  If you need a linked list type, then currently in Intel Fortran the use of pointers is practically unavoidable.  But that doesn't "consumers", the code that uses such a type, needs pointers too.  A general rule is: use allocatables in place of pointers as much as possible.  With this in mind, can you use something like the following and employ the facility with the target attribute:

module List_m

   implicit none

   type :: List_T
      integer :: idx
      class(List_T), pointer :: next => null()
   contains
      procedure, public :: append  => ListAppend
   end type List_T

   type, extends(List_T) :: ExtList_T
      real :: value
   end type ExtList_T

contains

   recursive subroutine ListAppend(this,new)

      class(List_T), intent(inout), target :: this
      class(List_T), intent(in),    target :: new

      !if (.not. associated(new)) return
      if (associated(this%next)) then
         call ListAppend(this%next,new)
      else
         this%next => new
      end if

      return

   end subroutine ListAppend

end module List_m
program p

   use List_m, only : ExtList_T

   implicit none

   type(ExtList_T), allocatable :: instance1  !.. Note allocatable type
   type(ExtList_T), allocatable :: instance2

   allocate(instance1)
   allocate(instance2)
   instance1%idx = 1
   instance1%value = -1.0
   instance2%idx = 2
   instance2%value = 5.0

   call instance1%append(instance2)

   print *, "Instance 1: ", instance1%idx, instance1%value
   print *, "Instance 2: ", instance2%idx, instance2%value
   print *, "Instance 1 => next: ", instance1%next%idx

end program p

Both Intel Fortran and gfortran give:

 Instance 1:  1 -1.000000
 Instance 2:  2 5.000000
 Instance 1 => next:  2
Press any key to continue . . .

Look into finalization with your linked list type and what consider what might happen if instance2 is deallocated before instance1 and it gets used.

Look into Fortran 2008 feature of "allocatable components of recursive type" as a design alternative for your needs. when it becomes available in Intel Fortran (not there yet. 

0 Kudos
Steven_L_Intel1
Employee
394 Views

Why would you want to use ALLOCATABLE in a linked list?

0 Kudos
FortranFan
Honored Contributor II
394 Views

Steve Lionel (Intel) wrote:

Why would you want to use ALLOCATABLE in a linked list?

OP hasn't presented the use case for List_T type, but if it is only a simple container such as a stack or something, then all the advantages of allocatables come into play in terms of memory leaks, being able to more easily avoid aliasing and deep copy, etc.  Not knowing the actual use cases is why I only suggested to OP to look into it as a possible alternative; I didn't not say to him it was an exact replacement that will work in all situations.

0 Kudos
jimdempseyatthecove
Honored Contributor III
394 Views

>>Why would you want to use ALLOCATABLE in a linked list?

Why would you want to use non-ALLOCATABLE nodes in a linked list? (rhetorical question)

If the list of nodes were static or non-ALLOCATABLE stack, then you would want to refer to them as array.

If a node were non-ALLOCATABLE stack, and linked to a global list, then what do you expect to happen on return from the subroutine without unlinking the node from the global list.

Jim Dempsey

0 Kudos
Steven_L_Intel1
Employee
394 Views

Typically a linked list has items removed and added. With allocatable, you're not creating a linked list but rather a nested one that you can't traverse arbitrarily. Some applications can use allocatable here, but it would be unusual.

0 Kudos
holysword
Novice
394 Views

Lionel is right, in a typical linked list implementation you'd want to be able to insert and remove elements from arbitrary points of the list, not only at the end. In my application I do have an "insert" and "prepend" procedures too, and I am not sure how to make it work with ALLOCATABLE only.

Particularly for the append procedure it can be done with TARGET. I had some other more complicated and problem dependent routines that were relying on the input being pointer, but in the end I workarounded it.

Thank you all!

0 Kudos
Reply