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