Reputation: 7591
I want to create an array of polymorphic objects which have constructors taking different dummy arguments depending on their dynamic type. Having read about user-defined and structure constructors, I see no way to apply these concepts to dynamically allocated objects. Having a background in C++, I was used to the notion that I could use one and the same constructor "member function" when allocating objects either dynamically or on the stack, but how can I explicitly call user-defined Fortran constructors on allocated objects?
Instead, I tried to fiddle with generic and type-bound init functions:
module mod
type :: basis_t
contains
procedure, public :: init_func => init_base
! I want a generic constructor function
generic, public :: init => init_func
end type
type, extends(basis_t) :: extended_t
contains
! cannot work, init_extended has a different signature from init_base
procedure, public :: init => init_extended
end type
type wrapper_t
type(basis_t), pointer :: obj
end type
contains
subroutine init_base(this)
class(base_t), intent(inout) :: this
end subroutine
subroutine init_extended(this, param)
class(extended_t), intent(inout) :: this
integer :: param
end subroutine
end module
program
use mod
implicit none
type(wrapper_t) :: arr(2)
allocate(basis_t::arr(1)%obj)
allocate(extended_t::arr(2)%obj)
call arr(1)%obj%init ! calls init_basis
call arr(2)%obj%init(4) ! calls init_extended
end program
But I don't believe that I am on the right track, as in e.g. C++ I would rather do e.g.
basis_t* arr[2];
arr[0] = new basis_t;
arr[1] = new extended_t{ 4 };
The important difference is that the constructors in C++ are not type-bound/virtual, as in my Fortran approach. What can I do?
Upvotes: 3
Views: 548
Reputation: 21431
The role of a constructor in Fortran can be provided by:
The language provided structure constructor.
A function with a result that is of the type of the object being constructed. The language allows a generic function to have the same name as a derived type, and further allows a reference to such a function to overload what would otherwise be a reference to a structure constructor for the type.
A subroutine that defines an intent(out) argument of the appropriate type.
What you use depends on circumstances and personal preference to an extent. The language provided structure constructor can be used in constant expressions in some circumstances, but only permits simple value definition of components (no executable code); the function reference form permits you to execute arbitrary code as part of object construction, cannot be used in constant expressions, cannot easily indicate construction failure and might be expensive (depending on Fortran processor implementation details) if the constructed object is large; the subroutine form requires a separate call statement (the constructor cannot be part of a larger expression) and cannot take advantage of the generic name/structure overload language feature.
None of those three methods involve a type bound procedure. There are some circumstances where a type bound procedure might be appropriate for object definition (a type bound procedure intended to read an object value from a file, for example - all types in the extension hierarchy require the same information about the file to be passed to them), but it doesn't make general sense for construction, where you are defining the type of the object as well as defining its value.
Pointers in Fortran are mostly used for reference semantics (because they are references). You generally do not want to use them if you want value semantics - use allocatables.
TYPE :: ta
INTEGER :: a
END TYPE ta
TYPE, EXTENDS(ta) :: tb
REAL :: b
END TYPE :: tb
INTERFACE tb
PROCEDURE :: tb_construct
END INTERFACE tb
TYPE, EXTENDS(ta) :: tc
END TYPE tc
TYPE :: ta_item
CLASS(ta), ALLOCATABLE :: item
END TYPE ta_item
!...
FUNCTION tb_construct(arg)
INTEGER, INTENT(IN) :: arg
TYPE(tb) :: tb_construct
tb_construct%a = arg + 1
tb_construct%b = arg / 2.0
END FUNCTION tb_construct
SUBROUTINE ConstructTC(obj, arg, stat)
CLASS(ta), INTENT(OUT), ALLOCATABLE :: obj
INTEGER, INTENT(IN) :: arg
INTEGER, INTENT(OUT) :: stat
TYPE(tc), ALLOCATABLE :: tmp
IF (arg < 0) THEN
! Construction failed.
stat = 1
RETURN
END IF
tmp%a = arg + 4
CALL MOVE_ALLOC(tmp, obj)
stat = 0 ! Construction succeeded.
END SUBROUTINE ConstructTC
!...
TYPE(ta_item) :: the_items(3)
INTEGER :: stat
! Structure constructor
the_items(1)%item = ta(1)
! Overloaded function.
the_items(2)%item = tb(2)
! Subroutine.
CALL ConstructTC(the_items(3)%item, 3, stat)
IF (stat /= 0) ERROR STOP 'It failed.'
Upvotes: 5