Consider working with a defined “base” class instead of the unlimited polymorphic type in the standard, the resultant code will be easier on the current crop of Fortran compilers you are likely to use and for readers of your code, who may be you yourself in a future incarnation less enamored with Fortran and others who may prefer to focus on scientific / technical domain expertise rather than the artifacts around object-oriented (OO) code design in Fortran!
So you think you like Fortran!
! Defined base class
module base_m
type, abstract :: base_t
! Base / common data
character(len=:), allocatable :: message
end type
end module
module store_m
use base_m, only : base_t
type :: store_t
private
class(base_t), allocatable :: item
contains
procedure :: fetch => fetch_b
procedure :: store => store_b
end type
contains
subroutine fetch_b( store, b )
class(store_t), intent(inout) :: store
class(base_t), allocatable, intent(inout) :: b
call move_alloc( from=store%item, to=b )
end subroutine
subroutine store_b( store, b )
class(store_t), intent(inout) :: store
class(base_t), allocatable, intent(inout) :: b
call move_alloc( from=b, to=store%item )
end subroutine
end module
use base_m, only : base_t
use store_m, only : store_t
type, extends(base_t) :: my_type
integer :: key = 0
end type
class(base_t), allocatable :: first_object
type(store_t) :: storage
class(base_t), allocatable :: second_object
allocate(my_type :: first_object)
first_object % message = "I like Fortran!"
select type ( o => first_object )
type is ( my_type )
o%key = 42
class default
end select
! store away the object
call storage%store( first_object )
! fetch the item back
call storage%fetch( second_object )
! work with it
print *, second_object%message
select type ( o => second_object )
type is ( my_type )
print *, "object%key: ", o%key
class default
end select
end
C:\temp>gfortran -ffree-form p.f -o p.exe
C:\temp>p.exe
I like Fortran!
object%key: 42