program helpme
implicit none
! this could be any type
! what is important is that is is large, therefore we would like
! to avoid making copies
type my_type
character(len=30) :: message = ""
end type
class(my_type), allocatable :: first_object
! this is some generic storage -- for example, this could be
! somewhere inside a generic linked list or dictionary implementation
class(*), allocatable :: storage
class(my_type), allocatable :: second_object
allocate(my_type :: first_object)
first_object % message = "I like Fortran"
! move my object to a generic storage
call move_alloc(first_object, storage)
! now, I would like to retreive it into second_object - WITHOUT A COPY
! obviously, will not work
! call move_alloc(storage, second_object)
! also does not work
! select type(storage)
! class is (my_type)
! call move_alloc(storage, second_object)
! end select
! how do I get my object back? or is it not retrievable via move_alloc
! after stored in class(*) allocatable?
end program
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
Using a class pointer seems to work (with gfortran, ifort, and ifx, tested here). I wonder if move_alloc()
cannot recognize the effect of select type
because it is a separate subroutineā¦?
program main
implicit none
type my_type
character(len=30) :: message = "hi"
end type
class(*), allocatable, target :: storage
class(my_type), allocatable :: var1
class(my_type), pointer :: var2
allocate( my_type :: var1 )
var1 % message = "yo"
print *, loc(var1)
call move_alloc( var1, storage )
select type (storage)
class is (my_type) ; var2 => storage
class default ; stop "not my_type"
end select
print *, var2 % message
print *, loc(var2)
end
The problem here is the language of Fortran which effectively takes the opposite approach to most, if not all, modern languages that place great importance on programmer productivity and program safety and to help authors protect against program vulnerabilities.
So here, one can end up with multiple āownersā of data, each of whom can be wielded to drive the program off the cliff while Fortran offers little to no guardrails.
! NONCONFORMING program - NO help from most processors; onus on the author
type :: t
integer :: n = 42
end type
class(*), allocatable, target :: a
class(*), pointer :: x, y
integer :: astat
allocate( t :: a )
x => a ; y => a
deallocate( x, stat=astat ) !<-- NOT supposed to do this but no guards against it
print *, "astat = ", astat
print *, "allocated(a)? ", allocated(a)
print *, "associated(x)? ", associated(x)
print *, "associated(y)? ", associated(y)
if ( allocated(a) ) then
select type ( a )
type is ( t )
print *, "a%n = ", a%n
end select
end if
end
C:\temp>gfortran -ffree-form p.f -o p.exe
C:\temp>p.exe
astat = 0
allocated(a)? T
associated(x)? F
associated(y)? T
a%n = -826717632
C:\temp>ifort /free /standard-semantics p.f
Intel(R) Fortran Intel(R) 64 Compiler Classic for applications running on Intel(R) 64, Version 2021.10.0 Build 20230609_000000
Copyright (C) 1985-2023 Intel Corporation. All rights reserved.
Microsoft (R) Incremental Linker Version 14.36.32537.0
Copyright (C) Microsoft Corporation. All rights reserved.
-out:p.exe
-subsystem:console
p.obj
C:\temp>p.exe
astat = 0
allocated(a)? T
associated(x)? F
associated(y)? T
a%n = 42
A good processor shall detect the issue with DEALLOCATE
statement on line 9 and issue some diagnostics. However such a diagnostic might at best be at run-time, a bit too late.
On the other hand, as shown above, most of the Fortran processors will lead to processor-dependent behavior that can differ vastly, including āstart WW3ā as some readers appear fond to state.
This is because the onus is almost entirely on the programmers to ensure the TARGET
remains valid and that is too difficult in practice. Itās almost impossible for many teams to work with Fortran under such circumstances.
Thus, caveat emptor as always with objects of POINTER
and TARGET
attributes.
I think I am aware of the potential pitfalls of pointers (and that Fortran prefers allocatable variables). Here, my question is why the assignment of class pointers in the downward direction (downcast) is allowed in the select type
block, while the corresponding use of move_alloc()
is prohibited in the downward direction. This is pretty counter-intuitive to me, because class, allocatable
and class, pointer
variables seem to have almost the same internal information for actual dynamic data.
Iāve thought about this a bit more, and now I think the reason might be because the āassociate-nameā in the select type
loses the ALLOCATABLE attribute of the āselectorā (in a way similar to associate
constructs). More specifically, I guess
select type (storage)
is a short-hand form of
select type (storage => storage)
and so the storage
in the select type
blocks now represents āassoc-nameā rather than the original variable. If I assume a behavior similar to associate
constructs, the āassoc-nameā does not have ALLOCATALBE attribute, so cannot be passed to move_alloc()
as an argument. Indeed, the error message is like this:
class(*), allocatable, target :: storage
class(my_type), allocatable :: var1, var2
allocate( my_type :: var1 )
call move_alloc( var1, storage )
select type (storage)
class is (my_type) ; call move_alloc( storage, var2 )
end select
17 | class is (my_type) ; call move_alloc( storage, var2 )
1
Error: āfromā argument of āmove_allocā intrinsic at (1)
must be ALLOCATABLE
Things become more clear if I rewrite the code as
select type (x => storage)
class is (my_type) ; call move_alloc( x, var2 )
end select
17 | class is (my_type) ; call move_alloc( x, var2 )
1
Error: āfromā argument of āmove_allocā intrinsic at (1)
must be ALLOCATABLE
If the above interpretation is correct, it means that there is no way to achieve an ownership transfer of ALLOCATABLE class variables in the downward direction (in contrast to downcast of class pointers). Possibly, are there other approaches to achieve the same goal with ALLOCATABLEā¦? (I mean, not to use select type
every time one needs to access some fields, but more directly transfer the ownership of data among ALLOCATABLE class variables.)
EDIT: The usual assignment of class, allocatable
variables (with implicit allocation of LHS) could also be used, but the copy of the entire data seems to occur (because the address of var1
and var2
becomes different).
class(*), allocatable, target :: storage
class(my_type), allocatable :: var1, var2
allocate( my_type :: var1 )
...
call move_alloc( var1, storage )
select type (storage)
class is (my_type)
var2 = storage !! alloc (with copy)
!! allocate( var2, source=storage ) !! with copy
class default ; stop "not my_type"
end select
deallocate( storage )
The absolute reality is with most semantics starting Fortran 90, the programmer is only given the possibility of some benefit in terms of performance, etc. but that rarely turns into practice and the practitioner is mostly left with convenience that is much improved compared to FORTRAN 77
. This holds true with DO CONCURRENT
as seen in some recent threads, with coarrays, with array semantics, on and on the list goes and the same applies with `MOVE_ALLOC also.
Under the circumstances here, for example, a typical implementation is not all that different from
..
class(*), allocatable :: storage
class(my_type), allocatable :: second_object
..
select type ( s => storage )
class is ( my_type )
allocate( second_object, source=s, stat=astat )
if ( astat == 0 ) deallocate( storage )
end select
So thatās always an option, to do two-stepping to get back the object.
I didnāt suggest it the first time around because the use of unlimited polymorphic as a poor Fortrannerās substitute for Generics (generic containers), as OP is attempting, is generally fraught and I like to try to dissuade readers away from unlimited polymorphic types when I think it to be so,
I found a great explanation of reference counting at Reference counting in Fortran 95 (incomplete). See also this Stack Overflow answer.
I think it would be worth exploring the use of this library to for just such a purpose.
Thank you @FortranFan and @septc all the responses! Seems to confirm my feeling that it is not possible.
I am trying to implement a simple dictionary in Fortan (to store and access elements by string keys), a pretty standard thing to require. The items of the dictionary might be large arrays of data, hence I want to avoid any copies. This is why I used class(*)
, although I also think it is a poor choice, this is the only way to implement a semi-generic data structure without re-writing a dictionary for every-single-type. I also tend to avoid pointers because of the memory safety.
I once attempted to write reference counting in Fortran, but I failed, since every compiler seemed to have random rules of invoking final
procedures. It become especially messy with assignments. I simply could not get it to work.
As a workaround, I decided to use a fixed-size (sic, in 2023!) array of fixed-length strings and their hashes, where I can easily look up indices of items that are contained in same-size data-array. It is ugly and does not have dynamic size, but I do not see any other solution.
type :: hashed_str_item_t
logical :: used = .false.
integer :: hash
character(len=64) :: key
end type
type :: int_dict_t
type(hashed_item_str_t) :: keys(128)
integer :: values(128)
end type
type(int_dict_t) :: intdict
! implementation of keyindex omitted, but it returns index of the key or first non-used item index
intdict % values(keyindex(intdict % keys, "key")) = 42
At the same time, I started to learn Rust.
Dominik
PS. @everythingfunctional I have seen your response last moment. I will certainly have a look! Refcounting in Fortran has been a dream of mine for some time.
There is a Fortran library to work with dictionaries and lists as Python programmers are used to.
It is called futile:
Unfortunately, it does not natively use FPM as a build system. Recently, I have made bash scripts which apply the required changes to its futile V1.9.1 and generate fpm.toml and fpm.rsp so that it can be built using FPM.
Here is another dictionary library. I havenāt looked at the source code yet, but it looks interesting and may have nice inspiration for making, e.g. newer libs.
The above library seems to be part of the Electronic Structure Library (ESL):
Indeed, the test suite for the library I referenced illuminated a variety of bugs in pretty much every compiler with regards to when final procedures should be invoked. We submitted relevant bug reports to all of them, and the most recent version of gfortran has all the fixes necessary. nagfor also works correctly.
You might find my fhash library useful since it supports key-value storage of any datatype, also using class(*)
. (It is also an fpm package)
github: https://github.com/LKedward/fhash
Documentation: https://lkedward.github.io/fhash/index.html
At first glance, I donāt think your tests conform to the standard vis-a-vis the standard semantics; the caller must have the TARGET
attribute but it doesnāt:
And the drawback here is there is no way to enforce this requirement among the consumers of such āclassesā and therefore, I wouldnāt recommend such a design and such a solution to users.