Automatic LHS reallocation with overloaded assignment - fortran

I have a code, which segfaults with all compilers I have at hand, when doing an assignment to an unallocted allocatable on the LHS with a structure constructor on the RHS. The structure (derived type) itself has an overloaded assignment. I thought, that automatic reallocation of the LHS should occur before the assignment routine is called, but it does not seem to be the case.
Below the code, demonstrating the issue. Uncommenting the allocate statement makes everything working, but I do not understand, why the explicit allocation is necessary in this case. Funny enough, if I remove the overloaded assignment, things work as well.
Any hints?
module dummy
implicit none
type :: DummyType
integer :: ii
contains
procedure :: assignDummyType
generic :: assignment(=) => assignDummyType
end type DummyType
interface DummyType
module procedure DummyType_init
end interface DummyType
contains
function DummyType_init(initValue) result(this)
integer, intent(in) :: initValue
type(DummyType) :: this
this%ii = initValue
end function DummyType_init
subroutine assignDummyType(this, other)
class(DummyType), intent(out) :: this
type(DummyType), intent(in) :: other
this%ii = other%ii + 1
end subroutine assignDummyType
end module dummy
program test_dummy
use dummy
implicit none
type(DummyType), allocatable :: aa
!allocate(aa) ! Should be covered via automatic reallocation...
aa = DummyType(42)
end program test_dummy

There is a recent discussion on comp.lang.fortran dealing with this topic.
An assignment statement is either an intrinsic assignment or a defined assignment. Intrinsic assignment permits [re]allocation of the left hand side, defined assignment does not.
When you provide a procedure for the assignment generic identifier, your assignment is defined assignment. The characteristics of the argument that corresponds to the left hand side then require that the left hand side be allocated.

Related

Using user-defined derived type assignments in subroutine calls [duplicate]

This question already has an answer here:
what's the meaning of "iostat" argument in open statement?
(1 answer)
Closed 1 year ago.
I want to overcome the lousy and non-intuitive string handling in fortran by writing a more pythonic string type, but I stumpled across a mean issue with derived-type (overloaded) assignment.
The main type should look like
TYPE t_string
CHARACTER(:), ALLOCATABLE :: str
contains
...
END TYPE t_string
with its power in the derived-type procedures. Of course the new string type should be as indistinguishable from the intrinsic CHARACTER(len=*) type as possible. Especially I want to use intrinsic routines (which use the character type) without any extra type conversions. Therefore I defined an assignment operator between CLASS(t_string) and CHARACTER(len=*). E.g. opening a file with the new type should look like this:
type(t_string) :: filename
filename = '...'
open(file = filename, ...)
! ^ assignment here
Since there is an assignment file=filename between t_string and CHARACTER(len=*) there should be no problem in the call to open. But I get an error due to mismatch in types.
I guess the problem is, that the assignment in the subroutine call is not really an assignment but just some syntax convention.
Any ideas how to fix this?
What is the reason (in term of design of the fortran language) for the "subroutine assignment" not to be a real assignment?
I do not want to call open(file = filename%str, ...)
Here is a mwe:
MODULE m_string
IMPLICIT NONE
SAVE
INTERFACE ASSIGNMENT(=)
MODULE PROCEDURE :: string_operator_equal_s, string_operator_equal_c
END INTERFACE ASSIGNMENT(=)
TYPE t_string
CHARACTER(:), ALLOCATABLE :: str
END TYPE t_string
CONTAINS
ELEMENTAL SUBROUTINE string_operator_equal_s(lhs,rhs)
IMPLICIT NONE
CLASS(t_string), INTENT(inout) :: lhs
CLASS(t_string), INTENT(in) :: rhs
lhs%str = rhs%str
END SUBROUTINE string_operator_equal_s
ELEMENTAL SUBROUTINE string_operator_equal_c(lhs,rhs)
IMPLICIT NONE
CLASS(t_string), INTENT(inout) :: lhs
CHARACTER(len=*), INTENT(in) :: rhs
lhs%str = rhs
END SUBROUTINE string_operator_equal_c
SUBROUTINE routine(char)
CHARACTER(len=*) :: char
END SUBROUTINE routine
END MODULE m_string
PROGRAM test
USE m_string
TYPE(t_string) :: str
CHARACTER(len=10) :: char
CALL routine(char) ! no error
CALL routine(char=str) ! error: #6633: The type of the actual argument differs from the type of the dummy argument. [STR]
END PROGRAM test
Since there is an assignment file=filename between t_string and CHARACTER(len=*) there should be no problem in the call to open.
No such assignment is present. You are only using the specifier name to specify which argument of the statement you are passing (similar to keyword/named arguments in Python, but not the same). open is in fact not a procedure, it is a statement, but it also has its "arguments" (specifiers) distinguished by their names.
Hence no derived assignment shall be invoked. You must convert to character yourself.

Generic interface to convert user type to array

I have a simple user-defined type
use, intrinsic :: iso_fortran_env
implicit none
type :: vector
real(real64) :: data(3)
end type
that has various interfaces defined as well as the assignment operator to and from arrays.
What I need is an abstract interface
interface assignment(=)
procedure v_to_a_assign, a_to_v_assign
end interface
which means I can do things like
type(vector) :: v
real(real64) :: a(3)
a = v
But what I want to do is an array-constructor such as
type(vector) :: v
real(real64) :: q(4)
q = [1d0, v]
! error #8209: The assignment operation or the binary expression operation is
! invalid for the data types of the two operands. [v]
which I could do if v was an array of real(real64). My question here is what binary operation do I need to define to make the above work?
The above is just one example of an implicit conversion of a user type to an array. I want to define the correct operator such that my user type is automaticall converted to an array when needed, like in function arguments, and/or other constructs.
Solution
define an interface for the conversion using the keyword real.
interface real
procedure v_to_array
end interface
contains
function v_to_array(v) result(a)
type(vector), intent(in) :: v
real(real64), dimension(3) :: a
a = v%data
end function
and use it as
q = [1d0, real(v)]
References Array Constructors
The language does not support the implicit conversion you are after.
Reference the array component, either directly using the component within the array constructor:
q = [1.0_real64, v%data]
or write an appropriate accessor function/unary operator.
q = [1.0_real64, .getdata. v]
The implicit conversion you seek would be problematic given the way generic resolution is defined by the language.
As a matter of style, explicit conversions are often preferred - for example user a structure constructor as the expression instead of the user defined assignment when assigning to an object of type vector, use an accessor function or unary operator when assigning to an array of real. Beyond clarity, user defined assignment does not invoke automatic (re)allocation of the variable on the left hand side of an assignment.
(Fortran does not have an assignment operator - it has an assignment statement.)

Passing size as argument VS assuming shape in Fortran procedures

I'm trying to decide which one of these two options would be the best:
subroutine sqtrace( Msize, Matrix, Value )
integer, intent(in) :: Msize
real*8, intent(in) :: Matrix(Msize, Msize)
real*8, intent(out) :: Value
[instructions...]
end subroutine sqtrace
VS
subroutine sqtrace( Matrix, Value )
real*8, intent(in) :: Matrix(:,:)
real*8, intent(out) :: Value
if ( size(Matrix,1) /= size(Matrix,2) ) then
[error case instructions]
end if
[instructions...]
end subroutine sqtrace
I understand that when you compile with warnings, the first case should automatically check at compile time if calls to sqtrace comply with the size indicated. However, I don't know if the compiler can perform those checks when the given arguments are allocatable, for example (more so if such allocation depends on other things that are determined at runtime). The second one requires an explicit interface and has more code (the checks), but would seem to catch more errors.
Which are the advantages/disadvantages of using each and in which cases should one go with one over the other?
First, some terminology. Consider the dummy arguments declared as
real :: a(n) ! An explicit shape array
real :: b(:) ! An assumed shape array
real, allocatable :: c(:) ! A deferred shape array (allocatable)
real, pointer :: d(:) ! A deferred shape array (pointer)
real :: e(*) ! An assumed size array
real :: f(..) ! An assumed rank array/scalar
I won't answer in terms of which is better in a given situation, but will simply detail some of the important characteristics leaving choice, where there is one, to the programmer. Crudely (and incorrectly), many view explicit shape arrays as "Fortran 77" and assumed and deferred shape arrays as "Fortran 90+".
Assumed size and assumed rank arguments are beyond the scope of this question and answer.
Shape:
the shape of an explicit shape array follows its declaration;
the shape of an assumed shape array dummy argument is that of the actual argument;
the shape of a deferred shape dummy argument may be undefined, becoming defined in the procedure, or that of the actual argument.
Contiguousness:
an explicit shape array is simply contiguous;
an assumed shape array dummy argument's contiguousness relates to that of the associated actual argument;
a deferred shape dummy argument may be that of the actual argument, or depending on the procedure's execution.
Restrictions on actual argument:
an actual argument associated with an explicit shape array must have at least as many elements as the dummy argument;
an actual argument associated with an assumed shape array must not itself be assumed size;
an actual argument associated with an assumed or deferred shape array must be of the same rank as the dummy argument.
Interfaces in the calling scope:
if a dummy argument is of assumed or deferred shape, the referencing scope must have accessible an explicit interface for the procedure.
Consider real a(6). This may be an actual argument to the dummies
real b(3)
real c(2,3)
real d(:) ! With an explicit interface available
a(1::2) may be associated with b but as b is contiguous copy-in/copy-out will be involved. Copy-in/copy-out needn't be involved when associated with d, but it may be.
There are plenty of other aspects, but hopefully this is an initial high-level introduction.

Proper way to pass pointers into many subroutines

I'm not a very good programmer and I'm just trying to interface with a model that provides data as pointers. These pointers are passed down through several subroutines before data is written to them. I'm not sure how to do this so that I avoid memory leaks.
Let's say I have an array pointer A that is passed to several subroutines before being written to, how do I handle the declarations, allocations, and deallocations?
module data
implicit none
contains
subroutine s1(a)
real, pointer, intent(out) :: a(5,5)
call s2(a)
end subroutine s1
subroutine s2(a)
real, pointer, intent(out) :: a(5,5)
integer :: i
do i = 1,5
a(:,i) = 5.0
end do
end subroutine s2
end module data
Program test
use data, only : s1, s2
real, pointer, dimension(:,:) :: A => NULL()
allocate(A(5,5))
call s1(A)
write(*,*) A
deallocate(A)
end Program test
Please note that your code is not Fortran 90. The intent attribute for dummy (formal) arguments that are pointers was introduced in Fortran 2003.
The intent refers to the association status of the pointer, not to its target. Also, if the argument is a derived type with
pointer components, the intent applies to the type object itself, not the targets of the pointers. That is, if, for example, intent(in) is used, the data area that the pointer is targeted at can be modified:
module MyType_mod
implicit none
private
type, public :: MyType
integer, pointer :: ptr(:)
contains
procedure :: sub => my_type_sub
end type MyType
contains
subroutine my_type_sub(self)
! Dummy argument
class(MyType), intent(in) :: self
! The following is perfectly legal,
! even though intent(in) was specified
self%ptr = 42
end subroutine my_type_sub
end module MyType_mod
program main
use MyType_mod, only: &
MyType
implicit none
type(MyType) :: foo
integer :: alloc_stat
allocate( integer :: foo%ptr(100), stat=alloc_stat )
call foo%sub()
end program main
Even though not required, in a case such as the previous example, it is better to state intent(inout) to indicate to the reader that modification of data is taking place.
On another note, you may find this answer useful Fortran subroutine returning wrong values

Nested derived type with overloaded assignment

I have a derived type (wrapper) containing an other derived type (over). For the latter the assignment operator have been overloaded. As the assignment of derived types happens per default componentwise, I'd expect that assigning two instances of wrapper would invoke the overloaded assignment for over at some point. However, using the program below, it does not seem to be the case. The overloaded assignment is only invoked if I also overload the assignment for wrapper containing an explicit assignment between instances of over (by uncommenting the commented code lines). Why? I find it somewhat counter intuitive. Is there any way to avoid the overloading in the wrapping type?
module test_module
implicit none
type :: over
integer :: ii = 0
end type over
type :: wrapper
type(over) :: myover
end type wrapper
interface assignment(=)
module procedure over_assign
!module procedure wrapper_assign
end interface assignment(=)
contains
subroutine over_assign(other, self)
type(over), intent(out) :: other
type(over), intent(in) :: self
print *, "Assignment of over called"
other%ii = -1
end subroutine over_assign
!subroutine wrapper_assign(other, self)
! type(wrapper), intent(out) :: other
! type(wrapper), intent(in) :: self
!
! other%myover = self%myover
!
!end subroutine wrapper_assign
end module test_module
program test
use test_module
implicit none
type(wrapper) :: w1, w2
print *, "Assigning wrapper instances:"
w2 = w1
end program test
This [unfortunate] situation is a consequence of the rules of the language (F90+) for intrinsic assignment of derived types. The details are spelled out in F2008 7.2.1p13. As a summary, intrinsic assignment of derived types (the assignment that happens with the wrapper_assign specific commented out) does not invoke non-type bound defined assignment for any components that are of derived type. In F90/F95, if you want defined assignment at some lower level of the component hierarchy then you need to have defined assignment for all the parent components up to the base object.
F2003 added type bound defined assignment to the language and this is invoked by intrinsic assignment of derived types. Use that instead of the stand-alone generic form of specifying defined assignment. (This also avoids a potential problem with the type name being accessible but the defined assignment procedure not being accessible.)
Just to complete the thread: the concrete realisation of IanH's suggestion (please upvote his original answer rather than this one) which worked for me was the following one:
module test_module
implicit none
type :: over
integer :: ii = 0
contains
procedure :: over_assign
generic :: assignment(=) => over_assign
end type over
type :: wrapper
type(over) :: myover
end type wrapper
contains
subroutine over_assign(other, self)
class(over), intent(out) :: other
class(over), intent(in) :: self
print *, "Assignment of over called"
other%ii = -1
end subroutine over_assign
end module test_module
program test
use test_module
implicit none
type(wrapper) :: w1, w2
print *, "Assigning wrapper instances:"
w2 = w1
end program test