I want to pass a 2d array to a subroutine and treat this array as a 1d argument. I tried to pass it in this way: subroutine(array(1,:)). This works if I define the arrays explicitly. However, if the arrays are allocatable, I get the following error: Actual argument for 'array' must be ALLOCATABLE
How can I make this work?
Here is some short sample code, which gives the error above:
program array
implicit none
integer,dimension(:,:),allocatable::i
allocate(i(2,2))
i(1,1)=1
call array_method(i(1,:))
contains
subroutine array_method(i)
implicit none
integer,allocatable,dimension(:),intent(in)::i
write(*,*) i(1)
end subroutine array_method
end program array
If I change code to explicitly defined arrays, like below, it works. However, I want to do it with allocatable arrays.
program array
implicit none
integer,dimension(2,2)::i
i(1,1)=1
call array_method(i(1,:))
contains
subroutine array_method(i)
implicit none
integer,dimension(2),intent(in)::i
write(*,*) i(1)
end subroutine array_method
end program array
If I change the argument array in the subroutine to allocatable and leave the passed argument in the main program as explicitly defined array (for example (2,2)), I still get the same error.
In the subroutine array_method (first one), you give the allocatable attribute to the dummy argument. This requires that the actual argument also has that attribute.
However, the actual argument is i(1,:) which is not allocatable, even though i itself is.
Now, depending on what you want to do in the first case, the dummy argument doesn't need to have the allocatable attribute. Unless you want to change the allocation status (which you can't given intent(in)), or use the "real" bounds of i, you can do without it.
Related
Let all routines be inside modules.
If I pass the array real*8 aa(5,3) to a routine
subroutine sub(bb)
real*8, intent(in) :: bb(2,5)
...
end subroutine
with the statement call sub(aa) this will compile without a warning and the first 2 columns of aa will fill the bb array. The elements of the arrays aa and bb are aligned very differently.
If instead the routine is written
subroutine sub(bb)
real*8, intent(in) :: bb(:,:)
...
end subroutine
then bb would have the same shape and storage order as aa.
Q: The first behavior is quite dangerous if one forgets that there are explicit-size declarations in a routine. Can I make the compiler warn when explicit-shape arrays change shape/alignment?
I am not aware of a compiler option to warn about this as it is a perfectly legitimate practise using the storage association - we have several questions and answers about this concept. It can be quite useful.
I have a program that seems to work properly,
but I don't understand how it can,
because there seems to be an obvious error.
Main program(which use 'implicit') calls a subroutine:
implicit integer(i-n)
implicit double precision(a-h,o-y)
implicit complex*16(z)
call do_coulomb(zvecs0,zdualvecs0,n_f,n_f,1,
$ nsubfilling,zcorrmatrix,0,aldet01abs,
$ zcoulomb,epsilon)
where arrays, 'zvecs0','zdualvecs0','zcorrmatrix' are declared,
but there is no declaration of 'nsubfilling' anywhere.
(It could be a mistake or remnant of old version.)
Since I could not find
any declaration of array 'nsubfilling' in main program
('grep -i nsubfilling *' ),
I suppose 'nsubfilling' will be treated as an integer variable.
This is a subroutine of question:
subroutine do_coulomb(zvecs,zdualvecs,n_A,n_Ap,n_C,
$ nsubfilling,zcorrmatrix,n1_p0,aldet01abs,
$ zcoulomb,eps)
implicit integer(i-n)
implicit double precision(a-h,o-y)
implicit complex*16(z)
include "input.inc"
dimension zvecs(0:L-1,0:L-1,0:L-1,0:Lt,0:1,0:1,0:n_f-1)
dimension zdualvecs(0:L-1,0:L-1,0:L-1,0:Lt,0:1,0:1,0:n_f-1)
dimension nsubfilling(0:n_Ap-1,0:n_C-1)
dimension zcorrmatrix(0:n_Ap-1,0:n_Ap-1)
('L' 'Lt' are defined in the "input.inc" file.)
Because 'nsubfilling' is defined as an array in the subroutine,
I thought the mismatch between main and subroutine would cause an error.
However, the program seems to run okay even with mismatch.
I tried to print out some variables.('n_f'=4,'n_c'=1 in this run)
This is the output:
Before 1st call in main:
nsubfilling= 1
zcorrmatrix(0,0)= (20.510951695209510,0.13579118691198364)
zcorrmatrix(0,1)= (-1.0490102491588316,0.59453967445518319)
zcorrmatrix(1,0)= (-1.3791781667351797,-0.26247624491732802)
zcorrmatrix(n_f-1,n_f-1)= (20.510951695209513,-0.13579118691198364)
Inside do_coulomb subroutine:
nsubfilling= 1 0 1 1
zcorrmatrix(0,0)= (20.510951695209510,0.13579118691198364)
zcorrmatrix(0,1)= (-1.0490102491588316,0.59453967445518319)
zcorrmatrix(1,0)= (-1.3791781667351797,-0.26247624491732802)
zcorrmatrix(n_f-1,n_f-1)= (20.510951695209513,-0.13579118691198364)
n1p0= 0
After 1st call in main:
nsubfilling= 1
zcorrmatrix(0,0)= (20.510951695209510,0.13579118691198364)
zcorrmatrix(0,1)= (-1.0490102491588316,0.59453967445518319)
zcorrmatrix(1,0)= (-1.3791781667351797,-0.26247624491732802)
zcorrmatrix(n_f-1,n_f-1)= (20.510951695209513,-0.13579118691198364)
The output shows that 'nsubfilling' is treated as an integer in main routine,
but considered as an array in the subroutine and also
the subroutine recognizes 'zcorrmatrix' correctly
even with mismatch.
But, how this can be possible? I think there should be an error.
Could you let me understand how it work?
Thank you.
The main program does not have an explicit interface to subroutine do_coulomb. This means that the main program cannot check at compilation time whether the ranks of the actual arguments in the main program match the ranks of the dummy arguments in the subroutine.
An explicit interface can be provided in a number of ways:
having subroutine do_coulomb as an internal subprogram of the main program (subroutine after main subprogram, after a CONTAINS statement and before the END statement of the main program), this is called host association;
via an interface block in the main program (provide name of subroutine, list of dummy arguments, their types and attributes); or
by including the subroutine inside of a module (foo) and adding a use statement (use module foo) before the implicit declarations, this is called use association.
Why is your program not crashing? Well, because subroutine do_coulomb thinks it has access to a chunk of memory corresponding to nsubfilling of the size specified inside of the subroutine, and it happens to not do anything otherwise illegal when manipulating it - the chunk of memory happens to be in use by the same application. If the declared size of nsubfilling was very very big, and/or you had fewer arrays declared, it is likely that access to nsubfilling led to a segmentation fault.
Note that, even if you have an explicit interface, the ranks and the dimensions may not match - and that can be legal, as long as the total size of the dummy argument in the subroutine is not larger than the total size of the actual argument in the main program.
I have a following code, with an abstract type, inherited type and a short program, where I'm creating an object and storing it in an array.
module m
implicit none
type :: container
class(a), allocatable :: item
end type container
type, abstract :: a
integer, public :: num
end type a
type, extends(a) :: b
integer, public :: num2
end type b
end module m
program mwe
use m
implicit none
class(a), allocatable :: o1
class(container), allocatable :: arr(:)
o1 = b(1, 2)
allocate(arr(2))
arr(1) = container(o1)
select type(t => o1)
type is(b)
write(*,*) t%num, t%num2
end select
select type(t => arr(1)%item)
type is(b)
write(*,*) t%num, t%num2
end select
end program mwe
The problem is, that the output looks like this:
1 2
1 0
As can be seen, the same variable stored in the array has the second variable nullified. Why is that happening? Is it because the array is of type a, which only contains the first variable?
I'm compiling the code with ifort version 18.0.3.
I believe
arr(1) = container(o1)
is invalid Fortran 2008. This is an intrinsic assignment statement, but section 7.2.1.2 of the standard says that
In an intrinsic assignment statement, (1) if the variable is polymorphic it shall be allocatable and not a coarray.
As far as I can see, arr(1) is polymorphic but not allocatable, so a standards-compliant compiler should issue an error and abort compilation.
If my reasoning is correct, the fact that Intel Fortran compiler compiles this code is a compiler bug and should be reported to Intel.
As with ripero's answer one could say that any output from the program is valid. However, we can make a simple modification to the code to make it correct Fortran.1 This answer is concerned with this modified version.
I would call this unexpected output and seek the help of the compiler vendor.
Using a structure constructor with polymorphic allocatable components is one of those new areas in Fortran. Compilers may take a while to catch up or do it correctly.
I have tested your code with Intel Fortran 18.0.2 and see the same output.
For your question
Is it because the array is of type a, which only contains the first variable?
No: in the select type part with the output t is a non-polymorphic entity of type b.
You may work around this problem by avoiding using the structure constructor:
arr(1)%item = o1
I also see that Intel compilers before 18.0.2 do something different still.
1 With the declaration
class(container), allocatable :: arr(:)
arr is polymorphic and allocatable. As ripero notes, this means that arr(1), the element of arr is polymorphic. However, as an array element, arr(1) is not itself polymorphic and so may not be on the left-hand side of an intrinsic assignment statement. We can change the code in two ways: provide defined assignment, or make arr not polymorphic. In the code of the question there seems no reason to have the container polymorphic, so I'll consider
type(container), allocatable :: arr(:)
Further, as discussed in comments on the question, if you wish to work with gfortran 8, or earlier, to see what happens, you should also modify the code in the question so that the definition of the derived type container comes after the definition of the derived type a.
I have a Fortran subroutine that expects a complex array like
subroutine foo(cnumbers, n)
integer :: n
complex :: cnumbers(n)
...
end subroutine foo
and later I want to call it like
real :: rnumbers(40)
...
call foo(rnumbers, 20)
However, I get the compiler error:
error #6633: The type of the actual argument differs from the type of the dummy argument.
Of course, this is comprehensible since a real array is not a complex array. But there must be a way to make it work.
Because if the subroutine foo and the call of foo are in different modules and are written down in different Fortran files, then the compiler does not complain, and everything works fine.
Does someone know how to make it work? How to pass a real array if a complex array is expected?
You can either use transfer(rnumbers, ...) to convert the type (a temporary array is likely to be created) or use equivalence to avoid it
real :: rnumbers(40)
complex :: cnumbers(20)
equivalence (rnumbers, cnumbers)
set the value of rnumbers
call foo(cnumbers, 20)
If you need allocatable arrays the equivalence will not work.
You can also use an external subroutine and lie the compiler about the interface and just pass the real array instead of the complex one. It is not standard conforming, but it is sometimes used. See also Gfortran complex actual to real dummy argument
I'm working on a project, where the results of a numerical simulation program are to be optimized to fit measured behavior. I wrote some freeform Fortran routines to extract specific data and perform some preliminary calculations, which work fine. For the optimization purpose, i plan to use a local search algorithm provided here: http://mat.uc.pt/~zhang/software.html#bobyqa
I pass some arguments like dimensions and parameter vectors into the Fortran 77 routine, and the problem is, that the transferred argument arrays don't reach the other side. Only the first element will show up in an array with dimension 1.
I found some helpful answers in How to use Fortran 77 subroutines in Fortran 90/95? and tried to contain all 77 code in a module but i still don't get it done.
An explicit interface helps to get all variables into level1 f77 subroutine, but when stuff is beeing passed to another (level2), where assumed size arrays are to be constructed, 1-dimensional arrays are generated if at all.
I compile the f77 code first using ifort -c -fixed (and tried -f77rtl), then f90 and link all together.
Why are the assumed size arrays not generated properly?? The test program from vendor works fine!
How can i pass all needed data through and back in a defined way, without using explicit interfaces? Or is there a way to define suitable interfaces?
Here some example code:
program main_f90
use types
implicit none
real(dp) :: array(N)
interface
subroutine sub77_level1(array)
implicit real*8 (a-h,o-z)
real*8, intent(inout) :: array
dimension array(:)
end subroutine
end interface
[...fill array...]
call sub77_level1(array)
end
subroutine sub77_level1(array)
implicit real*8 (a-h,o-z)
integer i1, i2, i3, i4
dimension array(:)
[...modify array...]
call sub77_level2(array(i1), array(i2), array(i3), i4)
return
end
subroutine sub77_level2(array_1, array_2, array_3, i4)
implicit real*8 (a-h,o-z)
dimension array_1(*) array_2(*) array_3( i4, * )
[...modify...]
call sub_f90( <some other arrays, intent(in / out)> )
return
end