Nested derived type with overloaded assignment - fortran

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

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.

Using derived type public procedure for array declaration in other derived type [duplicate]

I have a derived type declared in a module like this:
MODULE dmotifs
TYPE :: PRM
INTEGER, PRIVATE :: nsp=4,nrx=8,maxprx=4
REAL, PRIVATE :: cref=1e-6,tref=1
REAL, DIMENSION(nrx,maxprx) :: k
REAL :: input
END TYPE PRM
CONTAINS
SUBROUTINE unreg(y,param,r,s)
TYPE(PRM), INTENT(IN) :: param
REAL, DIMENSION(param%nsp), INTENT(IN) :: y
INTEGER, DIMENSION(param%nsp,param%nrx), INTENT(OUT) :: s=0
REAL, DIMENSION(param%nrx,1), INTENT(OUT) :: r=0
REAL :: mOut, mCtrl, pOut, pCtrl
mOut=y(ind_mOut)
mCtrl=y(ind_mCtrl)
pOut=y(ind_pOut)
pCtrl=y(ind_pCtrl)
! <some operations on "r" and "s">
RETURN
END SUBROUTINE unreg
END MODULE dmotifs
On compilation I get this error:
Error: Variable 'nrx' at (1) in this context must be constant
What is the meaning of "must be a constant"; should it be immutable during compilation i.e. like a PARAMETER?
But there is another issue, I cannot declare PARAMETERS within derived types. How to deal with this error? Would moving these objects out of the derived type and making them PARAMETERS, be the only option?
Most importantly I wish to understand why does this happen.
I was compiling using gfortran: gfortran -Wall -c "dmotifs.f90"
Yes. Declaring an explicit-shape array in a non-parameterized derived type requires a constant expression. You could either
make k allocatable,dimension(:,:) (and (de-)allocation), or
make nrx and maxprx global/module constants (or replace them right away).
If your compiler supports it, you can use parameterized derived types:
type :: PRM(nrx,maxprx) ! parameterized derived type definition
integer, len :: nrx
integer, len :: maxprx
real :: k(nrx,maxprx)
! ...
end type PRM
(Taken and adjusted from here.)

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

Fortran procedure pointer to subroutines in derived type

In Fortran, I need a procedure pointer inside a derived type that can point to one of several subroutines. This problem seems to be common on SO:
Fortran save procedure as property in derived type
Type bound procedure overloading in Fortran 2003
There is no matching specific subroutine for this type bound generic subroutine call
Generic type-bound procedures with procedure arguments
Type bound procedure as arguments
to name a few. The answer to this question for functions is provided very nicely in the first reference.
However, I'm still not clear on a methodology to develop such code well in the case that the type-bound procedure pointer is pointing to a subroutine. The difficulty seems to be that there is no type associated with what is returned (since nothing is really "returned").
I would also like to point out the nuance that, although a simple solution may exist in a more recent standard of fortran (2003,2008), this solution may not work on all compilers, which may be problematic in the future. So I'm interested in compiler-friendly solutions.
I have a small code (shown below) that currently works, but in my big code, I'm getting an internal compiler error (also shown below) in the file where I use procedure pointers in derived types. My question is: what can I do to the code below to
1) Strictly use explicit interfaces
2) Maximize information passed to the compiler
3) Ensure the code is portable between as many compilers as possible (i.e. use fortran 90 / 95 standards).
To what degree can the above be satisfied (1 being most important)? Is it possible to satisfy all of these criteria above? I know that's "satisfy all of these criteria" is subjective, but I would argue that the answer is 'yes' for the same question regarding functions instead of subroutines.
gcc version 5.1.0 (i686-posix-dwarf-rev0, Built by MinGW-W64 project)
The small code:
module subs_mod
implicit none
public :: add,mult
contains
subroutine add(x,y,z)
implicit none
integer,intent(inout) :: x
integer,intent(in) :: y,z
x = y+z
end subroutine
subroutine mult(x,y,z)
implicit none
integer,intent(inout) :: x
integer,intent(in) :: y,z
x = y*z
end subroutine
end module
module type_A_mod
use subs_mod
implicit none
public :: type_A,init,operate
type type_A
procedure(),pointer,nopass :: op
end type
contains
subroutine init(A,op)
implicit none
external :: op
type(type_A),intent(inout) :: A
A%op => op
end subroutine
subroutine operate(A,x,y,z)
implicit none
type(type_A),intent(in) :: A
integer,intent(inout) :: x
integer,intent(in) :: y,z
call A%op(x,y,z)
end subroutine
end module
program test
use type_A_mod
use subs_mod
implicit none
type(type_A) :: A
integer :: x
call init(A,mult)
call operate(A,x,3,5)
write(*,*) 'x = ',x
end program
Compiler error in big code:
f951.exe: internal compiler error: Segmentation fault
libbacktrace could not find executable to open
Please submit a full bug report,
with preprocessed source if appropriate.
See <http://sourceforge.net/projects/mingw-w64> for instructions.
UPDATE
Here's a small modification that gives the compiler more information, but I have not tried this on the big code. However, it seems arbitrary, and I have no idea if it will help or not.
...
function add(x,y,z) result(TF)
...
logical :: TF
x = y+z
TF = .true.
end function
function mult(x,y,z) result(TF)
...
logical :: TF
x = y*z
TF = .true.
end function
end module
module type_A_mod
...
type type_A
procedure(logical),pointer,nopass :: op
end type
...
subroutine init(A,op)
implicit none
logical,external :: op
...
end subroutine
subroutine operate(A,x,y,z)
...
logical :: TF
TF = A%op(x,y,z)
end subroutine
end module
program test
...
end program
SOLUTION COMMENTS
Just to comment on the solution (provided by #IanH): there was one additional wrinkle, and that was that I had some derived types entering the abstract interface, which according to The New Features of Fortran 2003, the Import statement should be included to make the abstract interface aware of any entering derived types. Here is a small working example, which, applied to the big code, mitigates the internal compiler error I was having :)
module DT_mod
implicit none
private
public :: DT
type DT
integer :: i
end type
contains
end module
module subs_mod
use DT_mod
implicit none
private
public :: add,mult,op_int
abstract interface
subroutine op_int(d,x,y,z)
import :: DT
implicit none
type(DT),intent(inout) :: d
integer,intent(inout) :: x
integer,intent(in) :: y,z
end subroutine
end interface
contains
subroutine add(d,x,y,z)
implicit none
type(DT),intent(inout) :: d
integer,intent(inout) :: x
integer,intent(in) :: y,z
x = y+z
d%i = 1
end subroutine
subroutine mult(d,x,y,z)
implicit none
type(DT),intent(inout) :: d
integer,intent(inout) :: x
integer,intent(in) :: y,z
x = y*z
d%i = 2
end subroutine
end module
module type_A_mod
use DT_mod
use subs_mod
implicit none
private
public :: type_A,init,operate
type type_A
procedure(op_int),pointer,nopass :: op
end type
contains
subroutine init(A,op)
implicit none
procedure(op_int) :: op
type(type_A),intent(inout) :: A
A%op => op
end subroutine
subroutine operate(A,d,x,y,z)
implicit none
type(DT),intent(inout) :: d
type(type_A),intent(in) :: A
integer,intent(inout) :: x
integer,intent(in) :: y,z
call A%op(d,x,y,z)
end subroutine
end module
program test
use type_A_mod
use subs_mod
use DT_mod
implicit none
type(type_A) :: A
type(DT) :: d
integer :: x,y,z
y = 3; z = 5
call init(A,mult)
call operate(A,d,x,y,z)
write(*,*) 'x,y,x = ',y,z,x
write(*,*) 'd%i = ',d%i
end program
Any help is greatly appreciated.
Procedure pointers were not part of the standard language until Fortran 2003, so if you want to use them at all, then Fortran 95 compatibility is irrelevant.
An internal compiler error is a error with the compiler, regardless of the source provided to the compiler.
There is no such thing as a type bound procedure pointer. You either have a type bound procedure - which is a thing declared after the CONTAINS in a derived type construct, or you have a procedure pointer - which can be a component of a type or a stand-alone object. A procedure pointer that is a component is part of the value of an object of the derived type - it can be associated with different procedures at runtime. A type bound procedure is a fixed property of the type declaration.
If you want a procedure pointer (or dummy procedure) to have an explicit interface, then you must provide an interface name inside the parenthesis of the procedure declaration statement.
procedure(interface_name_goes_here) [, pointer, ...] :: thing_being_declared
The interface name provided can be the name of an accessible specific procedure (including one previously declared by a different procedure declaration statement), or the name of an abstract interface.
(If the interface name in a procedure declaration statement is a type, as it is for the component in your example code, the procedure that is declared is a function with a result of the given type, with an implicit interface.
If the interface name in a procedure declaration statement is completely missing, the procedure that is declared may be a function or subroutine (its subsequent use in that must be consistent with one or the other) with an implicit interface.)
So assuming you want to declare a procedure pointer component with an explicit interface to a function (contrary to the question title) with the same characteristics as add or mult in your second stretch of code:
TYPE type_A
PROCEDURE(the_interface), POINTER, NOPASS :: op
END TYPE type_A
ABSTRACT INTERFACE
FUNCTION the_interface(x, y, z) RESULT(tf)
IMPLICIT NONE
! function modifying arguments - poor style!!!
INTEGER, INTENT(INOUT) :: x
INTEGER, INTENT(IN) :: y, z
LOGICAL :: tf
END FUNCTION the_interface
END INTERFACE
If you want the procedure pointer to be a subroutine with an explicit interface (which is preferable to a function that modifies its arguments) - change the abstract interface appropriately.
The dummy procedure in the init subroutine does not have to be a pointer - inside init you are not changing what the op thing references - you are merely pointing another pointer at it:
PROCEDURE(the_interface) :: op
When your dummy procedures and procedure pointers are declared with an explicit interface, I would expect a reasonable compiler to diagnose any mismatches in characteristics.
Here's my working example:
module obj_mod
integer, parameter :: n = 5
type obj_type
procedure(sub_interface), pointer, nopass :: obj_sub => NULL()
end type
interface
subroutine sub_interface(y, x)
import n
double precision, dimension(n) :: x, y
end subroutine sub_interface
end interface
contains
subroutine sq_sub(x, y)
double precision, dimension(n) :: x, y
y = x ** 2
end subroutine
subroutine exp_sub(x, y)
double precision, dimension(n) :: x, y
y = exp(x)
end subroutine
end module
program member_subroutine
use obj_mod
type(obj_type) obj
double precision, dimension(n) :: x, y
x = (/ 1, 2, 3, 4, 5 /)
write(*,*) 'x =', x
obj%obj_sub => sq_sub
call obj%obj_sub(x, y)
write(*,*) 'y1 =', y
obj%obj_sub => exp_sub
call obj%obj_sub(x, y)
write(*,*) 'y2 =', y
end program member_subroutine

Automatic LHS reallocation with overloaded assignment

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.