Suppressing copy and assignment

In C++ it is possible to suppress copy and assignment of class objects (i.e. derived types in Fortran) by deleting the corresponding operators. I’ve seen this used in libraries like preCICE and librsb, where it is desirable that object instances have a certain level of immutability, by disabling inadvertent shallow copying, which may lead to silent corruption of data, or deep copying which may be too expensive in case of very large objects.

Here is a small example:

// NonCopyable.hpp
#include <iostream>

class NonCopyable {
public:
    // Constructor
    NonCopyable() {
        std::cout << "NonCopyable object created" << std::endl;
    }

    // Destructor
    ~NonCopyable() {
        std::cout << "NonCopyable object destroyed" << std::endl;
    }

    // Delete the copy constructor
    NonCopyable(const NonCopyable&) = delete;

    // Delete the copy assignment operator
    NonCopyable& operator=(const NonCopyable&) = delete;

    // Delete the move constructor (optional)
    NonCopyable(NonCopyable&&) = delete;

    // Delete the move assignment operator (optional)
    NonCopyable& operator=(NonCopyable&&) = delete;
};

Such objects can be created and referenced where needed, but not assigned or copied:

int main() {
    NonCopyable obj1;
    // The following will result in a compilation error because copy is deleted
    // NonCopyable obj2 = obj1;        // Error: copy constructor is deleted
    // NonCopyable obj3;
    // obj3 = obj1;                    // Error: copy assignment is deleted
    return 0;
}

This example is rather un-amusing, but you can imagine a class with methods that do useful work.

The issue of being able to suppress assignment was discussed in an earlier thread: Should we avoid assignment of derived types in robust programs?

I’ve realized today that the C++ semantics can be matched (to a certain extent at least) in Fortran by means of a non-definable object in an associate block:

associate(obj => default_noncopyable())
    ! ...
end associate

Within the associate block, it is invalid to assign to the associating entity obj. As long as the type of the entity is kept private, it remains impossible to make a (shallow) copy, in other words use obj on the right-hand side of an assignment. The snippet relies on the associate statement triggering a finalizer that calls the C++ destructor, see: Should associate trigger automatic finalization?

One problem with hiding the type is that it cannot be used as a dummy argument in procedures which is not the case in C++, but perhaps not all situations require the ability to pass the associating entity forward to a procedure.

Unfortunately there appear to be some unhandled corner cases among Fortran implementations. For instance the snippet:

associate(obj => default_noncopyable())
   associate(obj2 => obj)

   end associate
end associate

results in an internal compiler error in ifort and ifx. At first glance, I don’t know if this is allowed (gfortran and flang-new accept it), and if allowed, how many times should the finalizer be invoked? (My guess is only for the first association to an expression, but not in the second case, when associating with a variable.)

Attached below is the full example:

// NonCopyable_c.cpp
#include "NonCopyable.hpp"

extern "C" {

void *default_noncopyable() {
    NonCopyable *obj = new NonCopyable();
    return static_cast<void *>(obj);
}
void destroy(void *obj_p) {
    auto obj = static_cast<NonCopyable *>(obj_p);
    delete obj;
}

} // extern "C"

#ifdef STANDALONE
int main() {
    void *handle = default_noncopyable();
    destroy(handle);
    return 0;
}
#endif
! main.f90

module NonCopyable
use, intrinsic :: iso_c_binding
implicit none
private

public :: default_noncopyable

type :: NonCopyable_type
    private
    type(c_ptr) :: ptr
contains
    final :: destroy
end type

contains

    function default_noncopyable() result(this)
        type(NonCopyable_type) :: this
        interface
            function c_default_noncopyable() bind(c,name="default_noncopyable")
                import c_ptr
                type(c_ptr) :: c_default_noncopyable
            end function
        end interface
        this%ptr = c_default_noncopyable()
    end function

    subroutine destroy(this)
        type(NonCopyable_type), intent(in) :: this
        interface
            subroutine c_destroy(obj_p) bind(c,name="destroy")
                import c_ptr
                type(c_ptr), value :: obj_p
            end subroutine
        end interface
        call c_destroy(this%ptr)
    end subroutine

end module


program main
use NonCopyable

! not allowed, type is private
! type(NonCopyable_type) :: obj 

associate(obj => default_noncopyable())

end associate

end program

To compile:

$ clang++ -std=c++11 -c NonCopyable_c.cpp
$ ifort main.f90 NonCopyable_c.o -lstdc++
$ ./a.out 
NonCopyable object created
NonCopyable object destroyed
1 Like

Yes, indeed, if you hide the definition of the type, you can kind of prevent copying (actually, I was playing with a similar idea recently as well). User can then use the instance returned by the default_noncopyable() function either in the associate construct as you demonstrate above, or as an argument to any procedure which your library provides. But the actual practice is a mess. Whatever you want to do with such an instance, it must happen in the same associate block, so you can not pass the instance to any other procedure outside of the original library. Also, it does not prevent copying by all means, as

class(*), allocatable :: inst1, inst2
inst1 = default_noncopyable()
allocate(inst2, source=default_noncopyable())

would be still possible. So, IMO, it comes with a lot of painful consequences without offering a real protection against data corruption.

This is very limiting, I agree. The entity also can’t be referenced in internal procedures, because it does not exist outside of the associate block.

If the type were public, you could suggest users to only use the type as a dummy argument of a procedure (with intent(in), or via an associate statement, but never as a declared (definable) variable. But the compiler can’t enforce it.

The class(*) situation is unfortunate; given that one cannot do anything with such an object, hopefully no one would ever do something like that, even if the language allows it. (Edit: the module where the type is defined could still use it as unlimited polymorphic object.)

This is exactly the solution I ended up with.

What would be the least invasive language addition to fix this?

Would a new attribute be sufficient?

type, non_definable :: NonCopyable_type
   ! ...
end type

This would prohibit use of the type as local variables, but still allow them as procedure dummy arguments.

I feel somewhat reserved about the non_definable attribute as it would still force you to use the associate construct with a temporary variable (as returned by the function call) in order to do anything useful with the instance. IMO the associate constructs main purpose is the simplification of the written code (by offering abbreviations) and not to provide workarounds of language deficits.

So, if the language has to be changed anyway, one should probably go for the original purpose, rather for the hack: Why not introducing a non_copyable attribute instead, which allows the creation of an instance, but prohibits the creation of a copy by assignment or by sourced allocation?

When I want to prevent direct assignment of derived type objects, I just overload the “=” operator with a procedure that aborts on runtime. This (strangely) doesn’t prevent the sourced allocation, though.

Is that using a type-bound method or just a module procedure bound to the assignment operator?

use NonCopyable: NonCopyable_type, operator(=)

The expectation that clients will import an assignment operator is fraught with problems. See this discussion: Should we avoid assignment of derived types in robust programs?

Yes

module foo
implicit none

    type mytype
        real, pointer :: a => null()
    contains
        procedure :: mytype_assign
        generic :: assignment(=) => mytype_assign
    end type

contains

    subroutine mytype_assign(this,that)
    class(mytype), intent(inout) :: this
    type(mytype), intent(in) :: that
    error stop "WWIII initiated..."
    end subroutine

end module foo

Worse than that. Overloading the assignment leads to segfault if the client tries to assign an instance to an unallocated allocatable entry, as discussed in the thread @ivanpribec linked in.

type(type_with_user_def_alloc), allocatable :: inst
! This would likely lead to a crash
inst = type_with_user_def_alloc()

This is actually a serious caveat in the language! Isn’t there a way to fix it in the standard? What could prevent extending the (re)allocation on assignment feature to work also with an overloaded assignment?

1 Like

FWIW, I’ve tried the above code based on a type-bound procedure for assignment, and the results were something like this (CompilerExplorer):

  • if I use the combination (A.1) and (A.2), the program stops when entering Mytype_assign().
  • If I comment out (A.1) and (A.2) while uncommenting (B.1) and (B.2), the program prints m2 = 100.
  • The combination (B.1) and (A.2) gives segmentation fault because ‘Mytype_assign()’ overwrites the assignment, while this is not automatically allocated anywhere. (I think this is reasonable, and in this case one needs to allocate m2 manually.)
module test_m
    implicit none
    
    type Mytype
        integer :: n = 0
    contains
        procedure :: Mytype_assign
        generic :: assignment(=) => Mytype_assign
    endtype

contains

subroutine Mytype_assign(this, other)
    class(Mytype), intent(inout) :: this
    class(Mytype), intent(in)    :: other

    stop "Mytype_assign: stop"     !! (A.1)

    !! print *, "copying Mytype"   !! (B.1)
    !! this% n = other% n          !! (B.1)
end

end module

program main
    use test_m, only: Mytype
    implicit none
    type(Mytype), allocatable :: m1, m2

    allocate( m1, source=Mytype(n=100) )
    print *, "m1 = ", m1

    m2 = m1   !! (A.2)

    !! allocate( m2 )  !! (B.2)
    !! m2 = m1         !! (B.2)

    print *, "m2 = ", m2

contains
subroutine sub( x )
    type(Mytype), value :: x
    print *, "x = ", x
end
end program

(Sourced allocation and subroutine call with value attribute are not prohibited by Mytype_assign() because they are not assignment in Fortran (but rather involve copy constructor?))

If the goal is to create an object only once properly (e.g. via init()) while prohibiting the use of “duplicated” objects, another approach might be to define accessors and apply check() in each routine to reject a duplicated object…? (though I am not sure if the accessors can be written so that they keep computational efficiency…) (CompilerExplorer)

module test_m
    implicit none

    type Mytype
        private
        integer :: n = 0
        logical :: inited = .false.
        integer(8) :: addr = 0
    contains
        procedure :: init, show, set, check
    endtype

contains

subroutine init(this)
    class(Mytype) :: this

    if (this% inited) stop "Mytype.init(): invalid object"

    this% addr = loc(this)
    this% inited = .true.
end
subroutine set(this, n)
    class(Mytype) :: this
    integer, intent(in) :: n
    call this% check()

    this% n = n
end
subroutine show(this)
    class(Mytype) :: this
    call this% check()

    print *, "n = ", this% n
end
subroutine check(this)
    class(Mytype) :: this

    if ( (.not. this% inited) .or. &
        (this% addr /= loc(this)) ) then
        stop "Mytype.check(): invalid obj"
    endif
end

end module

program main
    use test_m, only: Mytype
    implicit none
    type(Mytype) :: m1
    type(Mytype), allocatable :: m2

    call m1% init()
    call m1% set( n=100 )
    call m1% show()

    m2 = m1    !! copy or assignment allowed, but m2 cannot call any method

    !! call m2% init()          !! error
    !! call m2% set( n=200 )    !! error
    !! call m2% show()          !! error

    call sub( mx=m1 )
contains

subroutine sub( mx )
    type(Mytype), value :: mx   !! cannot call any method

    call mx% show()   !! error
end

end program

An interesting idea. But as far as I can see, the program is not standard conforming. Formally, you would have to use c_loc() instead of loc() in the init() routine, the addr field should be of type type(c_ptr) and finally class(MyType) :: this would additionally need the target attribute.

But even then, unfortunately there is no warranty, that the address stored in the init() routine is still valid after the code execution leaves the routine. (Unless the user has set the target attribute for the class instance in the calling scope (in program main in your case), but that is easy to forget, and the compiler will not be any help as it won’t give any warning…)

1 Like

It appears that the (re)allocation on assignment could work for most of cases of defined assignment (either a type bound one with generic :: assignment(=) => ... or through a generic interface interface asignment(=)), but not not all of them.

A case that would always work is when the underlying procedure is elemental, because in this case the compiler can easily infer the size of the LHS from the size of the RHS.

I think the standard should specify that the (re)allocation on assignment work also for a defined assignment that overloads the intrinsic assignment, if the underlying procedure is elemental.

I actually think that the only case of authorized defined assignment is the one that overloads the intrinsic assignment, and with an elemental procedure. All other cases look more or less bad practices to me, with too many ambiguities. But it’s of course too late now to change that in the standard…

The more I think about it, the more I agree with you: it would be really helpful to have the option to disallow the intrinsic assignment and/or the sourcing of a derived type (the syntax is just illustrative):

type, noassign, nosource :: sometype
   ...
contains
   ! assignments other than overloaded intrinsic are still possible
   procedure :: assign_from_integer
   generic :: assignment(=) => assign_from_integer
end type

type(sometype) :: x, y
integer :: i
type(sometype), allocatable :: z

y = x    ! compilation error
y = i    !  OK (not intrinsic assignment)
allocate( z, source=x )   ! compilation error
2 Likes