No lifting of scalar arguments to arrays in Fortran - 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.

Related

How to use intent (inout) in a Fortran function

I'm fairly new to Fortran, and while going through some documentation it seems like both subroutines and functions can use the 3 types of parameter intent:
intent (in)
intent (out)
intent (inout)
But when trying to implement intent (inout) in a function something similar to the snippet shown below
function cell_blocked(row,col,ncb) result (ncb)
integer, intent(in) :: row,col
integer, intent(inout):: ncb
if (row == col) then
ncb = ncb + 1
end if
end function cell_blocked
I get the following compiler error:
Symbol 'cell_blocked' at (1) has no IMPLICIT type
ncb is a counter that I would like to pass into the function and update given a condition and return the value.
If I try this with a subroutine I don't get any compiler errors, so I'm confused why the error while using a function
You are quite correct that each of the three intents (or using no intent) can be specified for any dummy argument of a function, just as they can for a subroutine.
However, the dummy arguments for a function are still quite distinct from the function result. The result(ncb) clause here is not saying "the argument ncb is the result of my function". Instead result(ncb) says "the result of the function is called ncb instead of cell_blocked".
You cannot give the function result the same name as one of the function's arguments. (You get an (unhelpful) compiler error saying that cell_blocked is not given an implicit type because the result clause is invalid, so the compiler is ignoring it and considering the function result to be called cell_blocked. A more helpful error message would include the fact that the result clause is itself invalid.)
The function result is a completely separate thing from any of the dummy arguments, and having a function result is what distinguishes a function from a subroutine. You may (whether it's advisable or not) change a dummy argument (intent(inout), intent(out) or no intent) independently of how you specify the result of the function.
Given the function
function f(a, b, c, d)
integer, intent(in) :: a
integer, intent(out) :: b
integer, intent(inout) :: c
integer :: d
integer :: f ! Function result unless there's a result clause
...
f = ...
end function f
the function result is f and the function result is used in the expression in the right-hand side of the assignment
y = f(a, b, c, d)
The value of the function result is whatever was assigned to f by the end of the function's evaluation. Not one of the dummy arguments, however modified, is a "result".
In the function of the question (which is perhaps better left as a subroutine) we are failing to give the function's result a value. If we want the function's value to be either ncb or an incremented version of that we don't use an intent(inout) dummy to do that:
function cell_blocked(row,col,ncb)
integer, intent(in) :: row,col, ncb
integer :: cell_blocked
! One of many ways writing this logic
if (row == col) then
cell_blocked = ncb + 1
else
cell_blocked = ncb
end if
end function cell_blocked
You may then write something like
ncb = cell_blocked(row, col, ncb)
but one then wonders whether a subroutine is what was wanted all along.

Parametrized derived types with kind parameter as subroutine argument

Say we have the following code:
module foo
use :: iso_fortran_env
implicit none
type :: bar (p, q)
integer, kind :: p
integer, len :: q
integer(kind = p), dimension(q) :: x
end type bar
contains
subroutine barsub (this)
class(bar(*,*)), intent(in) :: this
write (*,*) this%x
end subroutine barsub
end module foo
This code does not compile with either gfortran 8 or pgfort 18.4. The pgi compiler says
Illegal selector - KIND value must be non-negative
Assumed type parameter (*) cannot be used with non-length type parameter p
whereas gfortran yields
The KIND parameter 'p' at (1) cannot either be ASSUMED or DEFERRED
If I change above code to
subroutine barsub (this)
class(bar(INT32,*)), intent(in) :: this
write (*,*) this%x
end subroutine barsub
it compiles fine with both compilers.
Is it possible to write a subroutine where the kind parameter does not need to be specified explicitly? In the example above, the code would be the same for INT32, INT64, ... and I don't want to copy paste it for every imaginable value of the kind parameter. It works fine for the len parameter. Why can't I do the same with the kind parameter?
Is it possible to write a subroutine where the kind parameter does not need to be specified explicitly?
No, kind type parameters need to be given by a constant expression or defaulted, see, e.g., the Fortran 2008 standard, definition 1.3.147.12.3.
Why can't I do the same with the kind parameter?
The fact that len and kind type parameters have different uses and requirements is the point of having two types of type parameters, if their characteristics were the same we wouldn't need two of them.
Note that procedures require of the kind parameters of their dummy arguments of parameterized derived types just same they require of the kinds of their dummy arguments of intrinsic types: to have their values defined at compilation time.

What is an assumed length character function result, and why should it be avoided?

In response to a question about character function results of non-constant length, an answer mentions "assumed length function result" but doesn't go into detail.
If I want to return a character result where the length depends on something else, that answer mentions automatic objects and deferred length as possible approaches:
function deferred_length(x)
character(*), intent(in) :: x
character(:), allocatable :: deferred_length
deferred_length = x//'!'
end function
or
function automatic(x)
character(*), intent(in) :: x
character(LEN(x)+1) :: automatic
automatic = x//'!'
end function
What is an assumed length function result and how does it differ from the forms above? Further, why is such mention relegated to a footnote?
An assumed length character function looks like the following:
function assumed_len(x)
character(*), intent(in) :: x
character(*) :: assumed_len
assumed_len = x//'!'
end function
Here the dummy argument x and the function result assumed_len are both assumed length characters.
Much like how x assumes its length from the actual argument when the function is referenced, the function result assumes its length from the function declaration in the referencing place.
With the above function, consider the program
implicit none
character(len=11) :: x='Hello world'
character(len=12) assumed_len
print *, assumed_len(x)
end
During the function's execution the function result has length 12 as declared in the main program. Equally, if we wanted it to have length 5 we simply change the declaration in the main program to character(len=5) assumed_len. In a different program unit the declaration could be something different and the function result would assume that length when referenced.
Well, that doesn't look so harmful: why should we avoid using functions like this?
In summary:
They go against the "philosophy" of modern Fortran.
There are better ways in modern Fortran to accomplish the same thing.
They are quite limited.
In every other aspect of Fortran, the attributes of a function result depend only on the arguments of the function and other accessible information. Here the attributes of the function result may differ with everything else the same through a declaration in an unrelated scope.
To the other points:
the interface of such a function must be implicit in a referencing place (and we don't like implicit interfaces);
we can't reference the same function twice in one place and get different length results, even with differing input;
the function has a much better idea of what length it wants to return.
In those cases where we really do want to control the length in the referencing place we can replace assumed_len with a function with explicit length result like
function replacement(x, n)
character(*), intent(in) :: x
integer, intent(in) :: n
character(n) :: replacement
...
end function
or a subroutine with assumed length dummy argument
subroutine replacement(x, y)
character(*), intent(in) :: x
character(*), intent(out) :: y
...
end subroutine
Finally, assumed length character functions are declared obsolescent in the current Fortran standard, and may be deleted in later revisions.

subroutine argument with unknown rank (shape) in fortran

I am wondering how to best handle in Fortran a subroutine that takes an argument of unknown rank. For instance:
Real * 8 :: array1(2,2),array2(2,2,3)
call mysubroutine(array1)
call mysubroutine(array2)
As for now, I always need to fix the shape (number of rank) in the subroutine.
For instance, the intrinsic subroutine random_number(array) can do. (But maybe it is not coded in Fortran?)
You have to write a specific subroutine for each array rank, but you create a generic interface so that you can use a generic call for all the ranks and don't have to figure out the specific one to call. There is example code at how to write wrapper for 'allocate'
In case you need to fill the arrays elementwise and those operations are independent of each other, you may consider alternative to the suggestion of M. S. B. to use an elemental function. In this case you write the function for a scalar (one element) and it gets automatically applied to all elements of the array irrespective how the shape of the array looks like. However, your scalar function must be satisfy the conditions posed on an elemental routine, basically meaning that is not allowed to cause any side effects, which would make your result depend on the order it is applied to the individual array elements.
Below a demonstration, which multiplies each element of the array by two:
module testmod
implicit none
integer, parameter :: dp = kind(1.0d0)
contains
elemental subroutine mul2(scalar)
real(dp), intent(inout) :: scalar
scalar = scalar * 2.0_dp
end subroutine mul2
end module testmod
program test
use testmod
implicit none
real(dp) :: a1(5), a2(3,2)
a1 = 1.0_dp
a2 = 2.0_dp
call mul2(a1)
call mul2(a2)
print *, a1
print *, a2
end program test

Interface mismatch in dummy procedure 'f' when passing a function to a subroutine

I am trying to write a subroutine (for minimisation) that has two arguments:
an array x of any length
a function f that takes an array of that length and returns a scalar
example module:
module foo
contains
subroutine solve(x, f)
real, dimension(:), intent(inout) :: x
interface
real pure function f(y)
import x
real, dimension(size(x)), intent(in) :: y
end function
end interface
print *, x
print *, f(x)
end subroutine
end module
and test program:
use foo
real, dimension(2) :: x = [1.0, 2.0]
call solve(x, g)
contains
real pure function g(y)
real, dimension(2), intent(in) :: y
g = sum(y)
end function
end
gfortran fails on:
call solve(x, g)
1
Error: Interface mismatch in dummy procedure 'f' at (1): Shape mismatch in dimension 1 of argument 'y'
If I change size(x) => 2 then it compiles (and runs) fine. It also works fine if I change : => 2. But neither of these solutions gets me what I want.
Any ideas on how I can achieve this?
How about:
interface
real pure function f(y)
real, dimension(:), intent(in) :: y
end function
end interface
When you pass the argument of solve to the function, the size of the array will automatically be passed. You don't need to make this part of the interface.
If you want to gain safety as indicated in your comment of M.S.B's solution, you should use -fcheck=bounds and the compiler will generate run-time checks for assumed and deferred shape arrays. See the gfortran man page for more info on -fcheck. However, you will lose some speed.
You have the solution, but for what its worth an explanation... if the dummy argument has an explicit interface (which it does here) then there is a requirement that the characteristics of a procedure passed as an actual argument must match those of the dummy argument, with some exceptions around pureness and elemental intrinsics. The characteristics of a procedure include the characteristics of its dummy arguments, amongst other things.
The characteristics of a dummy argument include its shape, amongst other things. If that shape is not a constant expression - the characteristics include "the exact dependence [of the shape] on the entities in the expression".
The interface block for the dummy argument f declares the array to be of size SIZE(x). x is a host associated assumed shape variable - its size can vary at runtime, so SIZE(x) is not a constant. Hence that expression and the entities in it becomes a characteristic of the dummy argument.
The module procedure g declares the array to be of size 2. That is clearly a constant.
Regardless of the value of the non-constant expression for the size of the dummy argument of f, those array size characteristics (some sort of expression vs a constant) don't match - hence the error.
When you replace SIZE(x) with the constant 2 the characteristics obviously match. When you change the assumed shape x to be a constant size 2 - then SIZE(x) becomes a constant expression of value 2 - because it is a constant expression all that is relevant is its value - hence the characteristics of the two arguments then match. When you change both the dummy argument of f and the dummy argument of g to be assumed shape (:), the characteristics match.
Here is a demo to show how to pass allocatable array.
Some tips:
Use modules to avoid cumbersome interface.
Add extra matrix size information when pass array to the actual function. For example f(y, sizeinfo) so that inside your actual function you can declare the size of the input matrix correctly. The allocatable array can be passed to subroutine solve, so the size can be obtained using size(mat) in your subroutine solve.
So a corrected version looks like:
module foo
contains
subroutine solve(x, f)
real, dimension(:), intent(inout) :: x
real,external::f
integer::sizeinfo
print *,'x=', x
sizeinfo = size(x)
print *, 'f(x)=',f(x,sizeinfo)
end subroutine
real function g(y,sizeinfo)
integer::sizeinfo
real, dimension(sizeinfo) :: y
g = sum(y)
end function
end module
Here is main program:
program main
use foo
real, dimension(2) :: x = (/1.0, 2.0/)
call solve(x, g)
end program
And the result is :
x= 1.000000 2.000000
f(x)= 3.000000