Defined assignment for polymorphic variables

In the example below the following types are defined:

type, abstract :: base_t

type, extends(base_t) :: my_t

where my_t has a defined assignment subroutine. When I use a variable of type my_t, both ifort and gfortran invokes the defined assignment as I expect:

type(my_t), allocatable :: x
x = my_t()

However, neither do so when using a polymorphic variable of class base_t:

class(base_t), allocatable :: x
x = my_t()

Section 7.2.1.4 Defined assignment statement paragraph 2 of the Fortran standard has the following to say about defined assignments:

A subroutine defines the defined assignment x1 = x2 if
(1) the subroutine is specified with a SUBROUTINE (12.6.2.3) or ENTRY (12.6.2.6) statement that specifies two dummy arguments, d1 and d2,
(ā€¦)
the types of d1 and d2 are compatible with the dynamic types of x1 and x2, respectively,

The way I interpret this, the defined assignment should be invoked in both cases. Am I overseeing something or is this a compiler bug in both compilers?

Complete example:

module my_mod
    implicit none

    type, abstract :: base_t
    end type


    type, extends(base_t) :: my_t
    contains
        procedure, private :: assign
        generic :: assignment(=) => assign
        final :: finalize
    end type

    interface my_t
        module procedure :: init
    end interface

contains

    type(my_t) function init() result(this)
        write(*,*) 'init     ', loc(this)
    end function


    subroutine assign(lhs, rhs)
        class(my_t), intent(out) :: lhs
        type(my_t), intent(in) :: rhs

        write(*,*) 'assign', loc(lhs), ' -> ', loc(rhs)
    end subroutine


    subroutine finalize(this)
        type(my_t), intent(inout) :: this

        write(*,*) 'finalize ', loc(this)
    end subroutine
end module


program main
    use my_mod, only: base_t, my_t
    implicit none

    write(*,*) 'Concrete type example'
    block
        type(my_t), allocatable :: x

        x = my_t()
    end block
    write(*,*) 'Concrete type example done'
    write(*,*)

    write(*,*) 'Abstract base class example'
    block
        class(base_t), allocatable :: x

        x = my_t()
    end block
    write(*,*) 'Abstract base class example done'
end program

gfortran output:

 Concrete type example
 init           140722846631504
 finalize                     0
 assign                    0  ->       140722846632048
 Concrete type example done

 Abstract base class example
 init           140722846631504
 finalize        94805880428816
 Abstract base class example done

ifort output:

 Concrete type example
 init            140734944992808
 assign                     0  ->        140734944992808
 finalize        140734944992808
 Concrete type example done

 Abstract base class example
 init            140734944992800
 finalize        140734944992800
 finalize               13571168
 Abstract base class example done

Check out the section(s) on generic resolution, as defined assignment (I believe) falls into that category. Essentially, the procedure used to do the assignment is determined at compile time, and based on the declared type of the variable on the left hand side.

1 Like

@plevold , you may know of this thread and this one, you may want to review them.

Separately, do note given how things are with the Fortran standard, there is no safe and portable way to do what you show with your x = my_t() statement in the 2nd BLOCK construct i.e., to achieve allocation-upon-assignment with a defined assignment that is type-bound generic binding to a type-bound procedure. You may want to eshew defined assignments generally but if needed in certain attenuating circumstances, consider a Fortran 90-style generic interface for them instead.

Besides please note there are several nonconforming aspects in your code starting with your dummy argument lhs in your assgn procedure having an INTENT(OUT) attribute while the argument doesnā€™t get defined in the subprogram. Itā€™s surprising the compiler(s) didnā€™t detect and report this, some bug reports appear to be due.

This is more directed toward other readers that instrinsic assignments in Fortran do serve many a need in technical and scientific computing including with derived types and that defined assignment is a complexity that is best avoided:

module m
   type, abstract :: b_t
      character(len=50) :: name = ""
   end type
   type, extends(b_t) :: e_t
   end type
end module
   use m
   block
      type(e_t), allocatable :: x
      x = e_t("Concrete type example")
      print *, "x%name = ", x%name
   end block
   print *
   block
      class(b_t), allocatable :: x
      x = e_t("Abstract base class example")
      print *, "x%name = ", x%name
   end block
end

C:\temp>ifort /standard-semantics p.f90
Intel(R) Fortran Intel(R) 64 Compiler Classic for applications running on Intel(R) 64, Version 2021.5.0 Build 20211109_000000
Copyright (C) 1985-2021 Intel Corporation. All rights reserved.

Microsoft (R) Incremental Linker Version 14.30.30706.0
Copyright (C) Microsoft Corporation. All rights reserved.

-out:p.exe
-subsystem:console
p.obj

C:\temp>p.exe
x%name = Concrete type example

x%name = Abstract base class example

To reiterate, my suggestion will be to avoid defined assignments but if one wants to knock themselves out, hereā€™s a long rope to do what OP mentions in the original post with assignment of polymorphic variables:

module m
   type, abstract :: b_t
      character(len=:), allocatable :: name
   end type
   type, extends(b_t) :: e_t
   end type
   generic :: e_t => construct_e_t
   generic :: assignment(=) => assign_t
contains
   function construct_e_t( name ) result(r)
      character(len=*), intent(in) :: name
      type(e_t) :: r
      r%name = name 
   end function 
   subroutine assign_t( lhs, rhs )
      class(b_t), allocatable, intent(out) :: lhs
      type(e_t), intent(in) :: rhs
      print *, "In assign_t"
      allocate( e_t :: lhs ) !<- error handling elided
      lhs%name = rhs%name
   end subroutine 
end module
   use m
   block
      type(e_t), allocatable :: x
      x = e_t("Concrete type example")
      print *, "x%name = ", x%name
   end block
   print *
   block
      class(b_t), allocatable :: x
      x = e_t("Abstract base class example")
      print *, "x%name = ", x%name
   end block
end

C:\temp>ifort /standard-semantics p.f90
Intel(R) Fortran Intel(R) 64 Compiler Classic for applications running on Intel(R) 64, Version 2021.5.0 Build 20211109_000000
Copyright (C) 1985-2021 Intel Corporation. All rights reserved.

Microsoft (R) Incremental Linker Version 14.30.30706.0
Copyright (C) Microsoft Corporation. All rights reserved.

-out:p.exe
-subsystem:console
p.obj

C:\temp>p.exe
x%name = Concrete type example

In assign_t
x%name = Abstract base class example

Yes, but I somehow missed the part highlighting the difference between a type() variable and a class() variable.

Intel warns about this, but since the type in my example does not have any data an initialized and an uninitialized variable is exactly the same.

Itā€™s not a desire to use defined assignment itself, but rather a absolute need for it. When using pointer-s or type(c_ptr) in a derived type it is crucial to implement both assignment and finalization to avoid memory leaks, double frees or invalid memory access. In fact, the standard even notes this:

NOTE 4.49
If finalization is used for storage management, it often needs to be combined with defined assignment.

In current versions of ifort and gfortran however, declaring the variable as class(base_t), allocatable instead of type(my_t) will introduce memory issues if data has been allocated behind a pointer or a type(c_ptr). If one does

class(base_t), allocatable :: x, y

x = my_t()
y = x

the variables x and y will now share the data behind the pointers!

Complete example
module my_mod
    implicit none

    type, abstract :: base_t
    end type


    type, extends(base_t) :: my_t
        integer, pointer :: val => null()
    contains
        procedure, private :: assign
        generic :: assignment(=) => assign
        final :: finalize
    end type

    interface my_t
        module procedure :: init
    end interface

contains

    type(my_t) function init() result(this)
        write(*,*) 'init'
        allocate(this%val)
        this%val = 42
    end function


    subroutine assign(lhs, rhs)
        class(my_t), intent(out) :: lhs
        type(my_t), intent(in) :: rhs

        write(*,*) 'assign'
        allocate(lhs%val)
        lhs%val = rhs%val
    end subroutine


    subroutine finalize(this)
        type(my_t), intent(inout) :: this

        write(*,*) 'finalize'
        if (associated(this%val)) then
            deallocate(this%val)
        end if
    end subroutine
end module


program main
    use my_mod, only: base_t, my_t
    implicit none

    write(*,*) 'Concrete type example'
    block
        type(my_t) :: x, y

        x = my_t()
        y = x
        write(*,*) 'loc x%val: ', loc(x%val)
        write(*,*) 'loc y%val: ', loc(y%val)
    end block
    write(*,*) 'Concrete type example done'
    write(*,*)

    write(*,*) 'Abstract base class example'
    block
        class(base_t), allocatable :: x, y

        x = my_t()
        y = x
        select type (x)
            type is (my_t)
                write(*,*) 'loc x%val: ', loc(x%val)
        end select
        select type (y)
            type is (my_t)
                write(*,*) 'loc y%val: ', loc(y%val)
        end select
    end block
    write(*,*) 'Abstract base class example done'
    write(*,*)
end program

Output:

 Concrete type example
 init
 finalize
 assign
 finalize
 finalize
 assign
 loc x%val:               32937120
 loc y%val:               32937184
 finalize
 finalize
 Concrete type example done

 Abstract base class example
 init
 finalize
 loc x%val:               32937248
 loc y%val:               32937248
 finalize
 finalize
 Abstract base class example done
free(): double free detected in tcache 2
Aborted

Iā€™m still not sure exactly why this is standard conformant so I need to do some more readingā€¦

This now works with a variable declared as class(b_t), allocatable, but now the memory issues will occur for a variable declared as type(e_t). Also, one have to remember NOT to do use m, only: b_t, but rather use m, only: b_t, assignment(=) or else one will introduce memory issues again. Not very robust in my opinion. Intel letā€™s me combine our two suggestions into one, but gfortran complains about this:

Two defined assignments
module my_mod
    implicit none

    type, abstract :: base_t
    end type


    type, extends(base_t) :: my_t
    contains
        procedure, private :: assign
        generic :: assignment(=) => assign
        final :: finalize
    end type

    interface my_t
        module procedure :: init
    end interface

    interface assignment(=)
        module procedure assign_base
    end interface

contains

    type(my_t) function init() result(this)
        write(*,*) 'init     '!, loc(this%inner)
    end function


    subroutine assign_base(lhs, rhs)
        class(base_t), allocatable, intent(out) :: lhs
        type(my_t), intent(in) :: rhs

        write(*,*) 'assign base', loc(lhs), ' -> ', loc(rhs)
        allocate(lhs, mold=rhs)
    end subroutine


    subroutine assign(lhs, rhs)
        class(my_t), intent(out) :: lhs
        type(my_t), intent(in) :: rhs

        write(*,*) 'assign', loc(lhs), ' -> ', loc(rhs)
    end subroutine


    subroutine finalize(this)
        type(my_t), intent(inout) :: this

        write(*,*) 'finalize ', loc(this)
    end subroutine
end module

gfortran error:

  112 |     subroutine assign_base(lhs, rhs)
      |                          1
......
  121 |     subroutine assign(lhs, rhs)
      |                     2
Error: Ambiguous interfaces in intrinsic assignment operator for ā€˜assign_baseā€™ at (1) and ā€˜assignā€™ at (2)

Using an inner type as @aradi suggested in the previous post works well on Intel. If the bug is fixed in gfortran et. al. this might be the preferred approach.

1 Like

Yikesā€¦ Would be nice if Fortran added a way to explicitly delete the default assignment for a derived type to prevent bugs like these.

2 Likes

If you donā€™t want the data shared, why use pointer? Use allocatable and then intrinsic assignment works, and you donā€™t need a final subroutine. If you do want the data shared, you need to think much harder about which object ā€œownsā€ the data, and when it should be deallocated.

The defined assignment canā€™t tell the difference between x = my_t() and y = x. In the first case both defined assignment and the final subroutine will be called. In the second case only the defined assignment will be called. So should defined assignment always make a copy and then the temporary on the rhs should deallocate its copy? If so, then youā€™re just manually doing what allocatable already does for you automatically. Or should the data always be shared, in which case how do you determine which object should deallocate it? It canā€™t be the first one to have a final subroutine called, because that will be the temporary created in the first statement, and then x and y will both be pointing at already deallocated memory.

This is a whole can of worms, and the only language Iā€™ve seen actually try to tackle the problem directly is Rust, which I believe has actually done a pretty good job at it.

1 Like

Only because it was the easiest way to make a minimal example that demonstrates the issue :wink: C bindings with one or more type(c_ptr)-s would be a typical use case where one does not have the luxury of relying on allocatable.

This is not the problematic part. If you replace type(my_t), allocatable :: x with type(my_t) :: x in my first example youā€™ll see that both gfortran and ifort does exactly that:

 Concrete type example
 init            140735818920864
 finalize        140735818920856
 assign       140735818920856  ->        140735818920864
 finalize        140735818920864
 finalize        140735818920856
 Concrete type example done

What happens here is:

  1. my_t() is initialized as a temporaryā€™
  2. x is finalized
  3. x is assigned to the temporary (copied)
  4. The temporary is finalized
  5. When the blockends, x is finalized

Side note: I just noticed that gfortran and ifort does things differently for type(my_t), allocatable ::x in my first example so thatā€™s one more compiler bugā€¦

The problem is that type(my_t) and class(base_t) or class(my_t) behaves completely differently. Say I make a library out of my_t then I - which know how the memory should be managed - donā€™t have any control over how users decide to use my type.

My example doesnā€™t do anything like this, but thatā€™s another use case where consistent assignment and finalization would be crucial.

I agree that Rust does an absolutely phenomenal job when it comes to these sort of issues, but Iā€™m not sure I agree that this is a can of worms. Granted my C++ skills are not very good, but I believe you can implement manual memory management thatā€™s very hard to misuse there using the rule of three (or five).

1 Like