intent(out) and allocatable Fortran arrays: what is really done? - fortran

I read on many posts on Stack Overflow that an allocatable array is deallocated when it is passed in a subroutine where the dummy argument is intent(out).
If I consider the following code :
program main
real, dimension(:), allocatable :: myArray
integer :: L=8
allocate(myArray(1:L))
call initArray(myArray)
print *, myArray
contains
subroutine initArray(myArray)
real, dimension(:), intent(out) :: myArray
myArray(:) = 10.0
end subroutine initArray
end program main
the output is right. So, when deallocation occurs, memory is released but the array shape is kept. Is it exact ? Any detailed explanation would be appreciated.
I read different posts on the subject (Can I use allocatable array as an intent(out) matrix in Fortran?, What is the effect of passing an allocatable variable into a subroutine with non-allocatable argument?, ...). So I understand that the array is deallocated but I would like to understand what does it mean because in my code, the size is kept and I am also surprised that this code works.

You are slightly misunderstanding what happens here.
Arrays which are deallocated on entry to a procedure with intent(out) are those allocatable arrays which correspond to an allocatable dummy.
What intent(out) means for an argument depends entirely on the characteristics of the dummy not actual argument.
Allocatable actual arguments which correspond to ordinary dummy arguments are not deallocated. (If they were, the dummy argument which is not allocatable would have to be not allocated!)
Instead, the allocation status of the actual argument remains unchanged and the shape of the assumed (not deferred) shape dummy argument remains the same.
The dummy argument becomes undefined, as an intent(out). For the ordinary dummy argument here, that refers simply to its value (which is immediately defined in that assignment statement).

The deallocation happens when the dummy argument is allocatable and intent(out). Try
real, dimension(:), intent(out), allocatable :: myArray
to achieve that.
The fact that the actual argument in the main program is allocatable is immaterial to a subroutine without an allocatable dummy argument (such as yours).
I strongly suggest to name the array in the main program and the argument in the subroutine differently to better see the difference.
program main
real, dimension(:), allocatable :: mainArray
integer :: L=8
allocate(mainArray(1:L))
call initArray(mainArray)
print *, mainArray
contains
subroutine initArray(argArray)
real, dimension(:), intent(out) :: argArray
argArray(:) = 10.0
end subroutine initArray
end program main
Now, mainArray is the actual argument, argArray is the dummy argument. The dummy argument must be allocatable for deallocation to happen.

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.

User defined type as argument to elemental subroutine?

In my code I have an elemental subroutine which is basically like this:
elemental subroutine calc_stuff (x, a, b, c)
real, intent(in) :: a, b, c
real, intent(out) :: x
x = a/b + c
end subroutine calc_stuff
which I changed to this:
elemental subroutine calc_stuff (x, a, t)
real, intent(in) :: a
type(mytype), intent(in) :: t
real, intent(out) :: x
x = a/t%b + t%c
end subroutine calc_stuff
where mytype is a type containing some scalar real and integer, as well as a real, allocatable array. The members b and c are reals, making the second version basically the same as the first one.
The second version compiles fine on various compilers (Cray, Intel, NEC, GFortran), but now I read that the standard states for elemental subroutines:
All dummy arguments must be scalar, and must not have the ALLOCATABLE or POINTER attribute.
Is my code therefore not standard-conforming when passing a user-defined type to an elemental subroutine, but all the compilers "know" what I want because I am only using scalars from the type and not the allocatable array? Or am I misunderstanding the wording of the standard and everything is fine with the second version?
The dummy argument t is scalar1 and does not have the pointer attribute and does not have the allocatable attribute. It does not violate the condition.
The attributes of components of the type do not have a bearing on the attributes of the type itself.
1 Being of derived type doesn't make an object necessarily non-scalar. Even with multiple, or array components, the object itself may still be scalar. A derived type array is an array with element(s) of that type. Think also of a character object like character(len=3) name: it is scalar but consists of multiple substrings.

"Passed-object dummy argument must be a scalar"

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.

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

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.