forall index an associating entity? - fortran

I tried to compile this program with two different versions of gfortran:
program main
integer, dimension(1:2) :: iii
real, dimension(1:4,1:4,1:2) :: myArray
associate(iix => iii(1), iiy=> iii(2) )
forall( iix=1:4, iiy=1:4 )
myArray(iix,iiy,1) = iix + iiy
myArray(iix,iiy,2) = (iix + iiy)*10
endforall
end associate
print *, myArray(:,:,1)
print *, myArray(:,:,2)
end program main
There is no problem with GNU Fortran (GCC) 12.1.1 20220507 (Red Hat 12.1.1-1) version
But with GNU Fortran (Debian 10.2.1-6) 10.2.1 20210110 version, I get a compilation error
7 | forall( iix=1:4, iiy=1:4 )
| 1 internal compiler error: Segmentation fault
This version is not so old (2021/01/10)
From which gfortran version, is it possible to use associate in a forall statement?
And does this program conform to the standard?
It works with do loops
integer, dimension(1:2) :: iii
real, dimension(1:4,1:4,1:2) :: myArray
associate(iix => iii(1), iiy=> iii(2) )
do iix = 1,4
do iiy = 1,4
myArray(iix,iiy,1) = iix + iiy
myArray(iix,iiy,2) = (iix + iiy)*10
enddo
enddo
end associate
print *, myArray(:,:,1)
print *, myArray(:,:,2)
end program main
Following the comment of Jonathan Wakely, I sum up. In my initial code, there is also a do loop between the associate line and the forall line.
program main
integer, dimension(1:2) :: iii
real, dimension(1:4,1:4,1:2) :: myArray
integer :: i
myArray = 0.0
associate( iix => iii(1), iiy => iii(2) )
do i=1,2
forall( iix=1:4, iiy=1:4 )
myArray(iix,iiy,i) = (iix+iiy)*10*i
endforall
enddo
end associate
print *, myArray(:,:,1)
print *, myArray(:,:,2)
end program main

In comments we've addressed that the failure to compile with GCC 10 is a compiler bug which has been fixed in/by GCC 12. You offered to report this bug, but Jonathan Wakely has identified where this was fixed: there's little point reporting.
That said, there's still something we can say about code validity and workarounds.
Actually, I won't comment on validity, because what I'll say about the code itself makes that concept redundant.
Based on previous questions you've asked, you're using the ASSOCIATE with the FORALL to allow you to use an array element as the index. Something like
integer :: i(2)
forall (i(1)=1:4) ...
isn't allowed, so like with DO constructs and arrays you're associating a scalar variable with the element.
With FORALLs, though, that's entirely unhelpful.
The scope of an index in a FORALL statement/construct is that statement/construct. There's no connection between the array iii (in the question example) outside the FORALL and inside. There's simply no point associating the arrays elements with scalars to use those scalars in the FORALL.1
Note that you can2 "create" a new name specific to the FORALL itself, so you don't need to re-use names:
forall (integer :: iix=1:4, iiy=1:4, iiz=1:4) ...
instead of
integer iii(3)
associate (iix=>iii(1), iiy=>iii(2), iiz=>iii(3)
forall (iix=1:4, iiy=1:4, iiz=1:4) ...
end associate
FORALLs and DOs are very different things.
Some Fortran developers would say that the appropriate workaround for GCC 10 is to simply avoid using FORALLs at all. FORALLs are obsolescent in the Fortran standard and may be removed in the future. It's a reasonable position to hold that they should be avoided in new code.
1 If you don't have compiler support for what I mention next, then there is a (weak) point in using an ASSOCIATE to tidy up the number of declared scalar variables - in this case use a BLOCK construct to at least keep them local. It's hard to see the ASSOCIATE example above as any tidier than
block
integer iix, iiy, iiz
forall (iix=1:4, iiy=1:4, iiz1:4) ...
end block
Or avoid the obsolescent FORALL altogether.
2 If you have compiler support for this Fortran 2008 feature. GCC at the time of answering is missing this support.

Related

Compiler optimization when variables are reused

While benchmarking 'subtracting a vector from a matrix', I noticed Fortran compilers appear to be performing some sort of optimization when I reuse variables/code. It looks like the arrays are being reused from cache memory, however I'm not sure.
I believe this optimization is causing discrepancies in my benchmark results and would like to identify the specific type of optimization and, if possible, turn it off.
For example, in the following code that compares 2 cases, an additional Case 3 is introduced which is identical to Case 1. However, the time taken to run Case 3 is reported to be much lesser than that for Case 1.
program main
implicit none
integer :: n = 1E7
real*8, dimension(3) :: a
real*8, allocatable, dimension(:, :) :: b, c
real :: start, finish
integer :: i
allocate(b(n, 3))
allocate(c(n, 3))
call random_number(a)
call random_number(b)
! Case 1: Do loop
call cpu_time(start)
do i = 1, 3
c(:, i) = b(:, i) - a(i)
enddo
call cpu_time(finish)
print*, 'do-loop : ', finish-start
! Case 2: Spread
call cpu_time(start)
c = b - spread(a, dim=1, ncopies=n)
call cpu_time(finish)
print*, 'spread : ', finish-start
! Case 3: Do loop (again)
call cpu_time(start)
do i = 1, 3
c(:, i) = b(:, i) - a(i)
enddo
call cpu_time(finish)
print*, 'do-loop : ', finish-start
end program main
This produces similar results with Intel and GNU compilers as shown below. I have tried investigating using flags like -O0 and -qopt-report, but cannot understand why the code behaves so. Because the arrays are large, ulimit -s unlimited might be required (on Linux) to avoid a segmentation fault.
$ ifort reuse.f90 && ./a.out
do-loop : 0.2072840
spread : 0.4781271
do-loop : 3.6670923E-02
$ gfortran reuse.f90 && ./a.out
do-loop : 0.232345015
spread : 0.342370987
do-loop : 4.52849865E-02
At least in Linux, the memory allocator uses the "optimistic memory allocation strategy" (or see Why can Fortran allocate such large arrays? for Fortran). It assumes that there will be enough memory, assigns the virtual address space and that is all. The memory pages are only assigned when you access the memory by assigning some values (or trying to read the undefined garbage).
That has two implication.
If you requested too much memory, the allocate may still succeed and the program may crash later.
The first access will take more time.
To remove the problem with the latter, initialize the memory first, e.g. C = 0.
There are other reasons why you should disregard the first runs of any tests and always run them multiple times - not just one long test, but multiple short runs. There are various turbo modes in modern CPUs that may take some time to start, for example.

Moment of inertia in fortran [duplicate]

This question already has answers here:
Modern Fortran equivalent of an action statement shared by nested DO and GO TO
(1 answer)
Function has no implicit type
(4 answers)
Closed 1 year ago.
I am trying to calculate the moment of inertia in fortran. The formula I am using is following: The code I am using:
program moment
implicit none
real :: cR,h,rho0,a,b,c,d,resultV,pi,resultMI,aMass,exactresMI,exactresV,r,res,z,rho
integer :: m,n
! rho0 = density, cR=capital R( radius),h= height )
rho0=10000
cR=0.05
h=0.1
a=0.d0
b=h
c=0.d0
d=cR
m=1000
n=1000
call cheb2(a,b,m,c,d,n,funV,res)
pi=4*datan(1.d0)
resultV=res*2*pi
exactresV= pi/3*cR**2*h
write(*,*)
write(*,*) "Numerical volume result =", resultV
write(*,*) "Exact volume result = ",exactresV
call cheb2(a,b,m,c,d,n,funV,res)
resultMI=res*2*pi
aMass=exactresV*rho0
exactresMI=3/10.*aMass*cR**2
write(*,*)
write(*,*) "Numerical Moment of Inertia result =", resultMI
write(*,*) "Exact Moment of Inertia result = ",exactresMI
end program
function funV(z,r)
if (r.gt.z*cR/h) then
rho=0.d0
else
rho=1.d0
end if
funV=rho*r
return
end
function funMI(z,r)
if (r.gt.z*cR/h) then
rho=rho0
else
rho=1.d0
endif
funMI=rho*r**3
return
end
include "CHEB.FOR"
Our instructor does not use "implicit none" , so I am really new to this operator. Out instructor gave us CHEB.FOR code for calculating 2 dimensional integrals. I am writing it here:
subroutine ch4xy(al,bl,cl,dl,f,ri)
implicit double precision (a-h,o-z)
common/ttxy/ t1,t2
dimension xx(4),yy(4)
c1=(al+bl)/2.d0
c2=(dl+cl)/2.d0
d1=(-al+bl)/2.d0
d2=(dl-cl)/2.d0
xx(1)=c1+d1*t1
xx(2)=c1+d1*t2
yy(1)=c2+d2*t1
yy(2)=c2+d2*t2
xx(3)=c1-d1*t1
xx(4)=c1-d1*t2
yy(3)=c2-d2*t1
yy(4)=c2-d2*t2
ss=0
do 3 i=1,4
do 3 j=1,4
ss=ss+f(xx(i),yy(j))
3 continue
ri=ss*d1*d2/4.d0
return
end
subroutine cheb2(a,b,m,c,d,n,f,r)
implicit double precision (a-h,o-z)
external f
common/ttxy/ t1,t2
t1=0.187592
t2=0.794654
hx=(b-a)/m
hy=(d-c)/n
rr=0
do 5 i=1,m
do 5 j=1,n
aa=a+(i-1)*hx
bb=aa+hx
cc=c+(j-1)*hy
dd=cc+hy
call ch4xy(aa,bb,cc,dd,f,ri)
rr=rr+ri
5 continue
r=rr
return
end
When I compile the file, a couple of errors and a warning appear:
CHEB.FOR:19:17:
19 | do 3 j=1,4
| 1
Warning: Fortran 2018 deleted feature: Shared DO termination label 3 at (1)
CHEB.FOR:36:11:
36 | do 5 j=1,n
| 1
Warning: Fortran 2018 deleted feature: Shared DO termination label 5 at (1)
momentOFinertia.f95:17:27:
17 | call cheb2(a,b,m,c,d,n,funV,res)
| 1
Error: Symbol 'funv' at (1) has no IMPLICIT type
First, I dont understand why funV is unclassifiable statement, it classifies as a function. Second, our instructor used some old operations which is apparently not valid in new fortran. I dont know what could replace "shared do".
The main problem (fixed by your edit)is that your code misses an end or end program at the end. Alternatively, you could put an end program after your functions and contains between the subroutine and the main program body. That would make the functions to be internal subprograms and would fix your other problem - no implicit type for the functions.
This - putting the functions inside the program as internal subprograms, allows the program to "see" them and then the program can correctly pass them to other procedures. Alternatively, you could make an interface block for them or declare their type and let them be external. See Why do I have to specify implicitly for a double precision return value of a function in Fortran? for more.
You also have a type mismatch. The code you got from your instructor uses double precision but your code uses the default real. You have to synchronize that. Update your code to double precision, either using double precision or using real kinds.
The compiler also warns you that your program is using deleted features. These features were deleted in modern revisions of the Fortran standards. However, the compiler remain largely backwards compatible and will compile the code including those features anyway, unless you request strictly a certain standard revision.
In this case two do-loops use one common continue statement
do 5 ...
do 5 ...
5 continue
This is not allowed and can be fixed by inserting another continue with another label or, better, by using end do.

Output formatting with the write statement via gfortran [duplicate]

This question already has an answer here:
Variable format
(1 answer)
Closed 2 years ago.
I used to the Intel fortran compiler which supports using the <n> extension like
write(*, '(<n>(2I4))') (i, 2*i, i=1,n)
To illustrate, I give a s1_fprint.f90 subroutine as follows
subroutine fprint(name,bb)
IMPLICIT NONE
character(len=*), intent(in) :: name
real, intent(in) :: bb(:,:)
integer :: column=10
integer i,j,k,m,n
n = size(bb,1)
m = size(bb,2)
write(*,'(1a)')name
do k=0,m/column-1
write(*, '(1x,<column>i16)')(i,i=k*column+1,(k+1)*column)
write(*,'(1i10,<column>f)')(i,(bb(i,j),j=k*column+1,(k+1)*column),i=1,n)
write(*,'(/)')
end do
if(mod(m,column)/=0)then
write(*, '(1x,<m-m/column*column>i16)')(i,i=m/column*column+1,m)
write(*,'(1i10,<m-m/column*column>f)')(i,(bb(i,j),j=m/column*column+1,m),i=1,n)
write(*,'(/)')
endif
end subroutine fprint
Now, I change the Intel fortran compiler to gfortran, then I test (t1_useSur.f90)
above subroutine in gfortran as follows:
program main
implicit none
real :: A(2,3) = reshape([1.2, 2.3, 3.4, 4.5, 5.6, 6.7], [2,3])
call fprint('A',A)
end program main
which should show us something like
A
1 2 3
1 1.2000000 3.4000001 5.5999999
2 2.3000000 4.5000000 6.6999998
However, in gfortran compiler when I run
gfortran t1_useSur.f90 s1_fprint.f90 -o out
./out
there are many errors as
.\s1_fprint.f90:14.17:
write(*, '(1x,<column>i16)')(i,i=k*column+1,(k+1)*column)
1
Error: Unexpected element '<' in format string at (1)
.\s1_fprint.f90:15.19:
write(*,'(1i10,<column>f)')(i,(bb(i,j),j=k*column+1,(k+1)*column),i=1,n)
1
Error: Unexpected element '<' in format string at (1)
.\s1_fprint.f90:19.17:
write(*, '(1x,<m-m/column*column>i16)')(i,i=m/column*column+1,m)
1
Error: Unexpected element '<' in format string at (1)
.\s1_fprint.f90:20.19:
write(*,'(1i10,<m-m/column*column>f)')(i,(bb(i,j),j=m/column*column+1,m),i=
1
Error: Unexpected element '<' in format string at (1)
Since the <n> extension is not supported by gfortran, how can fix these problems?
Near dupe Variable format statement when porting from Intel to GNU gfortran
For the 1-dim cases like (i,i=...) :
If you have (or get) a version of gfortran that supports F08, which browsing https://gcc.gnu.org/onlinedocs/ appears to be around 4.6.4 up, use * as the count like (1x,*i16)
Otherwise, use the old-as-the-hillsF77 trick: since format repetitions or items 'beyond' the data list are ignored, just use a repetition count that is at least as big as the data will ever be (but not more than HUGE(0)) here (1x,10i16) is actually enough but something like (1x,999i16) makes it much more obvious
or if you like extra work, do on-the-fly like the 2-dim case below
For the 2-dim cases like (i,(bb(i,j),j=...),i=...) which currently use format looping to insert record breaks either:
reduce to 1-dim by making the record breaks into separate WRITEs:
do i=...
write(*,'(1i10,*f)') i,(bb(i,j),j=...)
end do !i
generate the correct count on-the-fly:
character(len=20) fmt
...
write(fmt,'(a,i0,a)') '(1i10,', numcols_expression, 'f)'
write(*, trim(fmt)) (i,(bb(i,j),j=...),i=...)
... or ...
write(fmt,'(i0)') numcols_expression
write(*, '(1i10,'//trim(fmt)//'f)') (i,bb(i,j),j=...),i=...)
PS: you don't actually need 1i10 just i10, but I left it for consistency. Also rather than a loop for the full chunks then an if for the partial chunk, which have to be kept in sync, I would probably do:
do k=1,m,column
l=min(k+column-1,m)
... print chunk for i=k,l (numcols is l-k+1) ...
end do !k

Have a function in fortran return a reference that can be placed on the left-hand-side of an assignment

As stated in the title, I want to directly modify data that I access through a pointer retrieved from a function. Having a reference returned by a function appearing on the l.h.s. of an assignment(=) is no issue in C++ but the following minimal example in fortran errors out:
module test_mod
implicit none
integer, target :: a=1, b=2, c=3 ! some member variables
contains
function get(i)
integer, pointer :: get
integer, intent(in) :: i
select case (i)
case (1)
get => a
case (2)
get => b
case (3)
get => c
end select
end function get
end module test_mod
program test
use test_mod
implicit none
integer, pointer :: i_p
!> prints out 1 2 3
print*, get(1), get(2), get(3)
!> this is what I want but I get the error
!> Error: 'get' at (1) is not a variable
get(2) = 5
!> this works but is not what I want
i_p => get(2)
i_p = 5
end program test
Is there any way to accomplish this behaviour; maybe I'm missing some attributes? I would like to bypass writing any setter routines such as
set(i,value)
since it should mimic the appearance of an array.
In my application, the member variables a,b,c are actually arrays of different size
a = [a1, a2, a3]
b = [b1, b2]
c = [c1]
and I want the getter get(i,j) to mimic a matrix of pointers
j = 1 2 3
i = 1: [[a1, a2, a3],
i = 2: [b1, b2, XX],
i = 3: [c1, XX, XX]]
wehre XX would be referencing to null().
Update:
I am using gfortran (version 5.2.0) and the deployment machines would have only versions starting from 4.6.x and upwards. Therefore, the suggested fortran 2008 standard features are unfortunately not available to me. Is it possible to mimic the behaviour described above without having a compiler supporting it out of the box?
Update 2:
So I ended up implementing a structure as follows
type Vec_t
integer, allocatable, dimension(:) :: vec
end type Vec_t
type(Vec_t), allocatable, dimension(:), target :: data
which I initialise like this (my triangular matrix application I mention at the end)
allocate(data(max))
do i=1,max
allocate(data(i)%vec(i))
end do
and I access & write to it through
print*, data(2)%vec(1)
data(2)%vec(1) = 5
which is not precisely what I was after but good enough for my application.
Let's look at what you want to do:
get(2)=5
and the error message
Error: 'get' at (1) is not a variable
That looks pretty comprehensive: you can't do what you want. Or, perhaps...
get(2) is indeed, under the rules of Fortran 2003, not a variable. In Fortran 2003 a variable is given by the rules R601 and R603, which is a list of designators.
The left-hand side of an assignment must be a variable.
But look at Fortran 2008 and its definition of a variable. Now a variable is either one of those same designators (or ones related to coarrays or complex parts), but it could also (C602 to R602) be a function reference which
shall have a data pointer result.
This is summarized in the introduction of Fortran 2008, detailing the extensions over Fortran 2003, as
A pointer function reference can denote a variable in any variable definition context.
get(2) is a reference to a function that has a data pointer result. get(2) then may appear on the left-hand side of an assignment statement under the rules of Fortran 2008.
Alas, this interpretation of Fortran is not widely supported by current compilers: at the time of answering just the Cray compiler.
This means that this answer is really saying that you have two options: switch compiler or wait until this feature is more widespread. As both of these are likely impractical, you probably want another answer which gives something slightly more portable as a workaround.
I prefer my link to that given by innoSPG, as although this latter is based on the former, the description of the appropriate field "Pointer functions - pointer function ref is a variable" is slightly more clear. This is, though, a more accessible document and a viable alternative.

Zero sized arrays and array bounds checking

When compiled with either GNU Fortran (v4.4.3) or Sun Studio F95 (v8.3) and no array bounds checking the following program runs without error. However, when array bounds checking is switched on (gfortran -fbounds-check and f95 -C, respectively) the GNU compiled executable runs again without error, whereas the Sun Studio compiled executable gives the run-time error,
****** FORTRAN RUN-TIME SYSTEM ******
Subscript out of range. Location: line 44 column 20 of 'nosize.f90'
Subscript number 2 has value 1 in array 't$27'
That's an error in the call to sub2(), which uses an automatic array dummy argument for x. The sub1() calls run fine with either compiler and any flags.
To my knowledge this program is "legal", in that a zero sized array may be referenced like a non-zero sized array, and there is no explicit indexing of the zero length dimension of x. But is there some zero sized array slicing or automatic array subtlety that I'm missing here? And should I expect array bounds checking to behave the same across different compilers, or should I consider it a vendor-specific extension?
MODULE subs
IMPLICIT NONE
CONTAINS
SUBROUTINE sub1(x)
IMPLICIT NONE
REAL :: x(:,:)
PRINT*,'------------------------------------'
PRINT*,SHAPE(x)
PRINT*,SIZE(x)
END SUBROUTINE sub1
SUBROUTINE sub2(n1,n3,x)
IMPLICIT NONE
INTEGER,INTENT(in) :: n1, n3
REAL :: x(n1,n3)
PRINT*,'------------------------------------'
PRINT*,SHAPE(x)
PRINT*,SIZE(x)
END SUBROUTINE sub2
END MODULE subs
PROGRAM nosize
USE subs
IMPLICIT NONE
INTEGER :: n1 = 2, n2 = 2, n3 = 0
REAL,ALLOCATABLE :: x(:,:,:)
ALLOCATE(x(n1,n2,n3))
x(:,:,:) = -99.9
PRINT*,'ALLOCATED? ',ALLOCATED(x)
PRINT*,'SHAPE =',SHAPE(x)
PRINT*,'SIZE =',SIZE(x)
PRINT*,'X =',x
CALL sub1(x(:,1,:))
CALL sub2(n1,n3,x(:,1,:))
END PROGRAM nosize
It doesn't give any problems with intel's fortran compiler with -check bounds; and IBM's xlf, which in my experience is extremely strict, also didn't complain with -qcheck.
But more broadly, yes, there's no standard about what bounds checking should or shouldn't do. I can certainly see why some compilers would flag an assignment to a zero-length array as being bad/wrong/weird; it is a strange corner-case.