How to implement the REAL cast intrinsic for custom data type in Fortran [duplicate] - casting

This question already has answers here:
A Fortran function/subroutine that could return either a real, an integer or a string.
(1 answer)
Fortran - setting kind/precision of a variable at run time
(1 answer)
Closed 1 year ago.
I have been looking around the internet for a solution to this problem, but I have to admit I am completely stuck.
What I have is a derived data type
TYPE :: MyType
REAL(KIND=MY_REAL_KIND) :: real_val
INTEGER :: int_val
END TYPE
I am overloading operators and intrinsic functions to work with it.
I need to overload the REAL cast to work with this type, so that when is called it gives back the real_val member. So fa so good:
FUNCTION real_mytype (a) RESULT (x)
IMPLICIT NONE
TYPE(MyType), INTENT(IN) :: a
REAL(KIND=MY_REAL_KIND) :: x
# Take advantage of the overloaded (=) operator
x = a
END FUNCTION real_mytype
But then I need to perform a cast with specified precision, let's say like
INTEGER, PUBLIC, PARAMETER :: sp = SELECTED_REAL_KIND( 6, 37)
INTEGER, PUBLIC, PARAMETER :: dp = SELECTED_REAL_KIND(12,307)
TYPE(MyType) :: a
call external_function_that_I_cant_change(REAL(a, sp))
call second_external_function_that_I_cant_change(REAL(a, dp))
I don't know how to write such interface, because the type of the return value (double real or single real) will depend on the value of the INTEGER input parameter (sp or dp) and not on its type, which is kind of forbidden in Fortran. The following does simply not make sense:
FUNCTION real_mytype_1d (a, p) RESULT (x)
IMPLICIT NONE
TYPE(MyType), INTENT(IN) :: a
INTEGER :: p
REAL(KIND=something_that_depends_on_p) :: x
x = a
END FUNCTION real_mytype_1d
I already took a look at the transfer function like suggested here but I was not able to figure out a solution (the type of return val there depends on the mold type).
Any suggestion?

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.)

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

Type-bound function overloading in Fortran 2003

I have a Fortran derived type T that contains data arrays of (many) different ranks and types. These arrays are hidden inside a complicated data structure and I would like to have a getter function of that does the following:
a => T%get(data_id)
where "a" is an array pointer of given type, and data_id is an integer that is used to find the data inside the data structure. I do that by overloading many "get_thistype()" functions under a generic name.
TYPE T
PROCEDURE :: get_real
PROCEDURE :: get_integer
GENERIC :: get => get_real,get_integer
END TYPE
This works if the get_thistype() routines are subroutines, but not if they are written as functions. This means my code looks like:
CALL T%get(a,data_id)
which I find much less readable. Is there a way to overload functions that have the same argument list but different return types? or do I have to use subroutines for that?
When a (pointer) assignment statement gets executed in fortran, the right hand side always gets evaluated fully before the assignment takes place. This happens independently of the left hand side, so there is absolutely no way that the LHS can influence the outcome of the evaluation of the RHS. It's just the way the language is designed.
I just came across this post, so for the benefit of anyone see this in the future:
If I understand the question correctly, you can accomplish this by overloading the assignment operator. Example:
file X.f90:
MODULE XModule
TYPE :: X
INTEGER, DIMENSION(:), POINTER :: IntArray
REAL, DIMENSION(:), POINTER :: RealArray
END TYPE
INTERFACE ASSIGNMENT (=)
MODULE PROCEDURE PointToInt
MODULE PROCEDURE PointToReal
END INTERFACE
CONTAINS
SUBROUTINE PointToInt(Ip, V)
INTEGER, POINTER, DIMENSION(:), INTENT(OUT) :: Ip
TYPE(X), INTENT(IN) :: V
Ip => V%IntArray
END SUBROUTINE PointToInt
SUBROUTINE PointToReal(Rp, V)
REAL, POINTER, DIMENSION(:), INTENT(OUT) :: Rp
TYPE(X), INTENT(IN) :: V
Rp => V%RealArray
END SUBROUTINE PointToReal
END MODULE
test driver file Driver.f90:
PROGRAM Driver
USE XModule
TYPE(X) :: Var
INTEGER, DIMENSION(:), POINTER :: I
REAL, DIMENSION(:), POINTER :: R
ALLOCATE(Var%IntArray(2))
ALLOCATE(Var%RealArray(3))
Var%IntArray = [1, 2]
Var%RealArray = [1., 2., 3.]
I = Var
PRINT*, I
R = Var
PRINT*, R
END PROGRAM
Output:
1 2
1.000000 2.000000 3.000000
Hope this helps.

No lifting of scalar arguments to arrays in Fortran

Why is it that Fortran will promote a scalar expression to an array, in an expression, but not as an argument to a procedure? In particular, why did the standards body make this design decision? Is it solely because of ambiguity, should the procedure be overloaded? Could an error message in that situation be an alternative approach?
For example, In the code below, the last statement, x = foo(7), produces the GFortran error: Error: Rank mismatch in argument 'a' at (1) (1 and 0).
module m
public :: foo
contains
function foo(a) result(b)
integer, dimension(:) :: a
integer, dimension(size(a)) :: b
b = a+1
end function foo
end module m
program p
use m
integer, dimension(4) :: x
integer, parameter, dimension(4) :: y = (/1,2,3,4/)
x = 7
x = foo(x)
x = foo(y)
x = foo(x + 7)
x = foo(7)
end program p
This question should have asked about why an array assignment will promote a scalar value source to an array target; unlike an array function. I expect that's simply a convenient special case though. Any comments gratefully received in the begging caps below.
If you want the function to handle scaler and array arguments, declare it as "elemental" and with scaler dummy arguments. Then it will be able to handle both scaler and array actual arguments, including scaler expressions. Will that meet your need?
The change:
elemental function foo(a) result(b)
integer, intent (in) :: a
integer :: b
b = a+1
end function foo
Perhaps they provided a way to do what you want, and one way was enough?
Procedure calling in Fortran with explicit interfaces (which you get automatically when using module procedures) requires a TKR (type, kind, rank) match. As an array is a different type than a scalar, not to mention the rank mismatch, this is not allowed.
Is it because of ambiguity should the procedure be overloaded?
That would be a problem, yes.
Could an error message in that situation be an alternative approach?
Could pink unicorns exist? Maybe, but to the best of my knowledge they don't. IOW, the Fortran standard currently requires TKR matching, and thus a standard conforming compiler must enforce this requirement. If you want to change that, I recommend making a proposal to the standards committee.
I would think the answer to this is pretty clear. Let's slightly modify your example:
module m
public :: foo
contains
function foo(a) result(b)
integer, dimension(:) :: a
integer, dimension(size(a)) :: b
b = a+1
a(2) = -777 ! new line; modify one element
end function foo
end module m
program p
use m
integer :: x
integer, dimension(4) :: y
x = 7
y = foo(x) ! pass a scalar
end program p
what is x supposed to be after the call to foo?
Now, sure, you could have the semantics of argument passing change depending on whether or not it's an intent(in) variable, but that is not something which is going to clarify things for programmers.
If the function call is supposed to 'distribute' somehow over array elements, then as MSB points out, elemental is the way to go. Otherwise, one just makes sure one's arguments match one's parameters.