"Passed-object dummy argument must be a scalar" - fortran

I have type-bound procedures which I want to accept an array as their passed dummy argument (getMean and assignEachThatInThis below). This does not compile though. I have read Metcalf et al. and they do not say that the passed dummy argument must be scalar and I don't really understand why that would have to be the case anyway.
If I use the nopass attribute it does compile and so it does when the procedures are not type-bound ones.
Can someone, please, explain what is going on and what is and is not safe to do?
Here is my example:
module types
implicit none
integer, parameter :: DP = selected_real_kind(r=250,p=13)
type :: my_type1
real(KIND=DP), dimension(:), allocatable :: elem1 ! interest rate
contains
procedure :: getMean => getMean_my_type1
procedure :: assignThatInThis_my_type1
procedure :: assignEachThatInThis_my_type1
generic :: assignment (=) => assignThatInThis_my_type1, assignEachThatInThis_my_type1
end type my_type1
contains
subroutine assignThatInThis_my_type1(this,that)
! Defines the overloaded `=` operator for the 'my_type1' class
! this = that
class(my_type1), intent(inout) :: this
class(my_type1), intent(in) :: that
this%elem1 = that%elem1
end subroutine assignThatInThis_my_type1
subroutine assignEachThatInThis_my_type1(this,that)
!--> this is apparently illegal, 'this' has to be a scalar :-(
!--> in principle it could work with the 'nopass' attribute (see 'getMean_my_type1') but that won't work with the assignment operator '='
class(my_type1), dimension(:), intent(inout) :: this
class(my_type1), dimension(:), intent(in) :: that
integer :: i
do i = 1,size(this,1)
this(i) = that(i)
end do
end subroutine assignEachThatInThis_my_type1
subroutine getMean_my_type1(this,that)
class(my_type1), dimension(:), intent(inout) :: this
class(my_type1), intent(inout) :: that
integer :: nTypes
integer :: n
integer :: j
nTypes = size(this,1)
n = size(this(1)%elem1,1) ! length of the simulation
! sum all elem1
do j = 1,nTypes
that%elem1 = that%elem1 + this(j)%elem1
end do
! divide by the number of elements
that%elem1 = that%elem1 / real(nTypes)
end subroutine getMean_my_type1
end module types
program pdatest
implicit none
end program pdatest
The following works, where I use the nopass attribute for getMean and don't have the assignment subroutines type-bound:
type :: my_type1
real(KIND=DP), dimension(:), allocatable :: elem1 ! interest rate
contains
procedure, nopass :: getMean => getMean_my_type1
end type my_type1
interface assignment (=)
module procedure assignEachThatInThis_my_type1, assignThatInThis_my_type1
end interface

To start, the passed-object dummy is required to be scalar (among other things) directly because of the rules of Fortran. Consider F2008, C456:
The passed-object dummy argument shall be a scalar, nonpointer, nonallocatable dummy data object with the same declared type as the type being defined; ...
With the nopass attribute the type-bound procedure reference has no passed-object, so this restriction does not apply. Equally, if you make the subroutine reference not from its type binding, the restriction doesn't apply.
With the getMean binding, the desire is to reduce an array to a scalar, but with the assignment the wish is to have an input array and an output array of the same shape. This latter is a case for an elemental subroutine.

Related

Valid programs showing difference between intent(out) and intent(inout) in Fortran

This is a follow up to a post that I found on SO: Difference between intent(out) and intent(inout)
The linked question asked about the difference between intent(out) and intent(inout) in Fortran by asking an invalid program.
Could anyone come up with a simple valid program(s) that give different results by changing intent(inout) to intent(out) or vice versa?
Here you go...
program intent_test
implicit none
integer, allocatable :: a(:)
a = [1,2,3,4,5]
call intent_inout (a)
call intent_out (a)
contains
subroutine intent_inout (a)
integer, allocatable, intent(inout) :: a(:)
if (allocated(a)) then
print *, a
else
print *, "Unallocated"
end if
end subroutine intent_inout
subroutine intent_out (a)
integer, allocatable, intent(out) :: a(:)
if (allocated(a)) then
print *, a
else
print *, "Unallocated"
end if
end subroutine intent_out
end program intent_test
1 2 3 4 5
Unallocated
As Steve Lionel's answer, and the comments in my original answer which perhaps sparked this interest, the effects of intent(out) on the initial state of the dummy argument (and the actual argument) are a way in to answering this question.
intent(inout) has the dummy argument reflect the value of the actual argument on entry to the procedure. intent(out) "resets" the dummy argument. In the case of the linked question, this "undefinition" is the cause of the invalid nature of the program.
More precisely, we can say the following things about intent(out) dummy arguments:
allocatable actual arguments become deallocated;
the pointer association of pointer actual arguments becomes undefined;
for a non-pointer dummy argument any component not default initialized becomes undefined.
The linked question fell foul of the third point by trying to reference such an newly undefined value. However, default initialized components are not undefined, leading us to our first class of valid programs:
implicit none
type t
integer :: x=1
end type t
type(t) :: x=t(0)
call s1(x)
call s2(x)
contains
subroutine s1(x)
type(t), intent(inout) :: x
print*, x%x
end subroutine s1
subroutine s2(x)
type(t), intent(out) :: x
print*, x%x
end subroutine s2
end
Crucially, the default initialization of the component means that x%x isn't undefined even on entry to s2, but it takes a potentially different value from the actual argument's component prior to procedure entry.
Coming up with a suitable program with pointer arguments is tricky: a pointer with undefined pointer association status can't be referenced/queried before its pointer association status is redefined.
Which leaves us looking at allocatable components. Unlike with the pointers, where we can't query pointer association status when that's undefined, we can ask about the allocation status. An actual argument corresponding to an intent(out) dummy is deallocated; with intent(inout) the allocation status is unchanged:
implicit none
integer, allocatable :: i
allocate (i)
call s1(i); print*, allocated(i)
call s2(i); print*, allocated(i)
contains
subroutine s1(i)
integer, allocatable, intent(inout) :: i
end subroutine s1
subroutine s2(i)
integer, allocatable, intent(out) :: i
end subroutine s2
end
(This is a simpler version of Steve Lionel's example.)
This all shows that it's possible to have differences. Using intent incorrectly can lead to invalid programs or to significant changes in meaning. Understanding what intent(in), intent(inout), intent(out) and no specified intent mean is a crucial part of being a Fortran programmer.

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

Error in Derived type declaration: Variable at (1) in this context must be constant

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

How to declare the type of a function that returns an array in Fortran?

I have function that returns an array, say
function f(A)
implicit none
real, intent(in) :: A(5)
real, intent(out) :: f(5)
f = A+1
end
My question is, how can I define f in the main program unit? E.g.
program main
implicit none
real :: A(5)
real, dimension(5), external :: f ! does not work
...
end
You need an explicit interface. You can do this in a few ways.
Explicitly in the scoping unit that calls f:
interface
function f(A)
implicit none
real, intent(in) :: A(5)
real :: f(5)
end function
end interface
Place the function in your program host scope as an internal function:
program main
...
contains
function f(A)
implicit none
real, intent(in) :: A(5)
real :: f(5)
f = A+1
end
end program
Place the function in a module:
module A
contains
function f(A)
implicit none
real, intent(in) :: A(5)
real :: f(5)
f = A+1
end
end module
program main
use A
...
end program
Use the explicit interface from a different procedure with the same arguments and return type, kind and rank.
program main
interface
function r5i_r5o(r5)
implicit none
real, intent(in) :: r5(5)
real :: r5i_r5o(5)
end function
end interface
procedure(r5i_r5o) :: f
...
end program
function f(A)
implicit none
real, intent(in) :: A(5)
real :: f(5)
f = A+1
end
The cleanest way of doing this is option #3 using modules. This gives you the benefit of an automatic explicit interface (not needing to do option #1 everywhere you call f) and makes your function available everywhere the module is used rather than limited to a specific scoping unit as in option #2. Option #4 can be handy if you have many procedures with the same argument and return types since one explicit interface can be re-used for all of them.
This shows three different ways to specify function results, and how to use modules to organize your functions:
module so_func
INTEGER, PARAMETER :: MAX_SIZE = 5
TYPE MY_DATA
INTEGER :: SIZE
REAL, DIMENSION(MAX_SIZE) :: DATA
ENDTYPE
contains
FUNCTION f1(A,N) RESULT(X)
implicit none
INTEGER, INTENT(IN) :: N
REAL, INTENT(IN) :: A(N)
REAL :: X(N)
! ....
X = 1.0+A
END FUNCTION f1
TYPE(MY_DATA) FUNCTION f2(A,N)
implicit none
INTEGER, INTENT(IN) :: N
REAL, INTENT(IN) :: A(N)
! ....
f2%SIZE = N
f2%DATA(1:N) = 1.0+A
END FUNCTION f2
FUNCTION f3(A,N)
implicit none
INTEGER, INTENT(IN) :: N
REAL, INTENT(IN) :: A(N)
REAL :: f3(N)
! ....
f3 = 1.0+A
END FUNCTION f3
end module
program SO_RESULT
use so_func
implicit none
integer, parameter :: n=5
REAL :: A(n), y1(n), y3(n)
TYPE(MY_DATA) :: y2
INTEGER :: i
! Variables
A =(/ (i, i=1,n) /)
y1 = f1(A,n)
y2 = f2(A,n)
y3 = f3(A,n)
end program SO_RESULT

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.