Google Groups no longer supports new Usenet posts or subscriptions. Historical content remains viewable.
Dismiss

Examples of FORALL and nested FORALL

92 views
Skip to first unread message

Steven G. Kargl

unread,
Jan 13, 2007, 11:13:49 PM1/13/07
to
Anyone have code that uses FORALL and nested FORALLs that
they may be willing to permit the gfortran developers to use
in testing a bug fix and then optimization work?

--
Steve
http://troutmask.apl.washington.edu/~kargl/

Tom Micevski

unread,
Jan 15, 2007, 8:22:52 AM1/15/07
to
Steven G. Kargl wrote:
> Anyone have code that uses FORALL and nested FORALLs that
> they may be willing to permit the gfortran developers to use
> in testing a bug fix and then optimization work?

give me a few days (or so) and i'll try to email you something.

note, though, i don't think that i'm doing anything too complex with my
FORALLs (simple/masked assignments, user-defined pure functions) ---
hopefully they'll still be useful.

Herman D. Knoble

unread,
Jan 15, 2007, 10:25:03 AM1/15/07
to
Direct quote from IBM Web page:
http://publib.boulder.ibm.com/infocenter/lnxpcomp/v8v101/index.jsp?topic=/com.ibm.xlf101l.doc/xlflr/forcons.htm

FORALL statement or construct

Evaluate, in any order, the subscript and stride expressions in the
forall_triplet_spec_list for the active combinations of the outer FORALL statement or
construct. The valid combinations are the Cartesian product of combination sets of the
inner and outer FORALL constructs. The scalar_mask_expr determines the active combinations
for the inner FORALL construct. Statements and constructs for these active combinations
are executed.

! Same as FORALL (I=1:100,J=1:100,I.NE.J) A(I,J)=A(J,I)

INTEGER A(100,100)
OUTER: FORALL (I=1:100)
INNER: FORALL (J=1:100,I.NE.J)
A(I,J)=A(J,I)
END FORALL INNER
END FORALL OUTER
END

Skip Knoble

On Sun, 14 Jan 2007 04:13:49 +0000 (UTC), ka...@troutmask.apl.washington.edu (Steven G.
Kargl) wrote:


-|Anyone have code that uses FORALL and nested FORALLs that
-|they may be willing to permit the gfortran developers to use
-|in testing a bug fix and then optimization work?
-|

Michael Metcalf

unread,
Jan 15, 2007, 10:49:54 AM1/15/07
to

"Steven G. Kargl" <ka...@troutmask.apl.washington.edu> wrote in message
news:eocalt$ofb$1...@gnus01.u.washington.edu...

> Anyone have code that uses FORALL and nested FORALLs that
> they may be willing to permit the gfortran developers to use
> in testing a bug fix and then optimization work?

! From Section 6.9 of MR&C
implicit none
integer, parameter :: n= 10
integer :: i, j
real :: a(n, n), b(n, n)

a= reshape( (/ (i, i = 1, n**2) /) , (/n, n/) )

forall (i = 1:n-1)
forall (j = i+1:n)
a(i, j) = a(j, i) ! a is a rank-2 array
end forall
end forall

!assigns the transpose of the lower triangle of a to the upper triangle
!of a

a(n/2, :) = 0
forall (i = 1:n)
where ( a(i, :) == 0) a(i, :) = i
b(i, :) = i / a(i, :)
end forall

print *, b(1,1), b(n, n)
!each zero element of a is replaced by the value of the row index
!and, following this complete operation, the elements of the
!rows of b are assigned the reciprocals of the corresponding elements
!of a multiplied by the corresponding row index.
end


Joost

unread,
Jan 15, 2007, 11:51:35 AM1/15/07
to
Steven G. Kargl wrote:
> Anyone have code that uses FORALL and nested FORALLs that
> they may be willing to permit the gfortran developers to use
> in testing a bug fix and then optimization work?

This is maybe for the bug fix category:

> cat mytest.f90
INTEGER :: i(2,2)=RESHAPE((/1,2,3,4/),(/2,2/)), r(2,2)
FORALL(k=1:2,any(i(k,:)>2))
FORALL(l=1:2,any(i(:,k)>2)) r(l,k)=1
END FORALL
END

yields with gfortran (version 4.3.0 20070114)

mytest.f90:3.13:

FORALL(l=1:2,any(i(:,k)>2)) r(l,k)=1
1
Error: 'any' at (1) is not a function
mytest.f90:3.13:

FORALL(l=1:2,any(i(:,k)>2)) r(l,k)=1
1
Error: FORALL mask clause at (1) requires a LOGICAL expression
mytest.f90:2.13:

FORALL(k=1:2,any(i(k,:)>2))
1
Error: 'any' at (1) is not a function
mytest.f90:2.13:

FORALL(k=1:2,any(i(k,:)>2))
1
Error: FORALL mask clause at (1) requires a LOGICAL expression

Cheers,

Joost

Steven G. Kargl

unread,
Jan 15, 2007, 1:10:21 PM1/15/07
to
In article <CoNqh.6833$Wz.2836@trndny06>,

"Michael Metcalf" <michael...@compuserve.com> writes:
>
> "Steven G. Kargl" <ka...@troutmask.apl.washington.edu> wrote in message
> news:eocalt$ofb$1...@gnus01.u.washington.edu...
>> Anyone have code that uses FORALL and nested FORALLs that
>> they may be willing to permit the gfortran developers to use
>> in testing a bug fix and then optimization work?
>
> ! From Section 6.9 of MR&C

Thanks Mike.

In case you (and others) want to see the gory details, here's a link

http://gcc.gnu.org/ml/fortran/2007-01/msg00298.html

--
Steve
http://troutmask.apl.washington.edu/~kargl/

Steven G. Kargl

unread,
Jan 15, 2007, 1:22:35 PM1/15/07
to
In article <1168879894....@s34g2000cwa.googlegroups.com>,

"Joost" <jv...@cam.ac.uk> writes:
> Steven G. Kargl wrote:
>> Anyone have code that uses FORALL and nested FORALLs that
>> they may be willing to permit the gfortran developers to use
>> in testing a bug fix and then optimization work?
>
> This is maybe for the bug fix category:
>
>> cat mytest.f90
> INTEGER :: i(2,2)=RESHAPE((/1,2,3,4/),(/2,2/)), r(2,2)
> FORALL(k=1:2,any(i(k,:)>2))
> FORALL(l=1:2,any(i(:,k)>2)) r(l,k)=1
> END FORALL
> END
>
> yields with gfortran (version 4.3.0 20070114)
>
> mytest.f90:3.13:
>
> FORALL(l=1:2,any(i(:,k)>2)) r(l,k)=1
> 1
> Error: 'any' at (1) is not a function

Thanks Joost. We're aware of this bug, which
is documented here.

http://gcc.gnu.org/bugzilla/show_bug.cgi?id=30400

The problem and fix that I'm trying to gather info
on is described here:

http://gcc.gnu.org/ml/fortran/2007-01/msg00298.html

PS: It is interesting that in all the code I've taken
from the web, the use of FORALL occurs zero times.

LOC in *.f90: 223862 total
LOC in *.f: 961966 total
LOC in *.F90: 121 total

At one time I had many more LOC until I fat fingered a
'rm -rf *' command. :)

--
Steve
http://troutmask.apl.washington.edu/~kargl/

Tim Prince

unread,
Jan 15, 2007, 9:19:22 PM1/15/07
to
Steven G. Kargl wrote:

> PS: It is interesting that in all the code I've taken
> from the web, the use of FORALL occurs zero times.
>

I translated the Levine-Callahan-Dongarra benchmark to use FORALL for
those cases where it appears appropriate (15 of them). However, there
appear to be large schools of thought where FORALL is at best equivalent
to a DO loop. It doesn't support OpenMP, requires more analysis from
the compiler to optimize, and, according to the standard and gfortran,
doesn't allow statement functions.

Steven G. Kargl

unread,
Jan 15, 2007, 10:55:42 PM1/15/07
to
In article <LCWqh.16165$Gw4....@newssvr23.news.prodigy.net>,

Tim Prince <tpr...@nospamcomputer.org> writes:
> Steven G. Kargl wrote:
>
>> PS: It is interesting that in all the code I've taken
>> from the web, the use of FORALL occurs zero times.
>>
> I translated the Levine-Callahan-Dongarra benchmark to use FORALL for
> those cases where it appears appropriate (15 of them).

Is this code available?

> However, there appear to be large schools of thought where FORALL
> is at best equivalent to a DO loop.

Nay, it's a parallel assignment. :)

> It doesn't support OpenMP, requires more analysis from
> the compiler to optimize, and, according to the standard and gfortran,
> doesn't allow statement functions.

Unfortunately, gfortran is a Fortran 95 compiler, so it must
offer FORALL. There are several programs in the testsuite, but
these are vastily different than what a user may have cleverly
done in an application. It just approved the patch that rewrites
how gfortran builds a mask for nested FORALLs, but I'd like to
find some additional real-world apps that can be used for
optimization development.

--
Steve
http://troutmask.apl.washington.edu/~kargl/

Tim Prince

unread,
Jan 16, 2007, 12:13:57 AM1/16/07
to
Steven G. Kargl wrote:
> In article <LCWqh.16165$Gw4....@newssvr23.news.prodigy.net>,
> Tim Prince <tpr...@nospamcomputer.org> writes:
>> Steven G. Kargl wrote:
>>
>>> PS: It is interesting that in all the code I've taken
>>> from the web, the use of FORALL occurs zero times.
>>>
>> I translated the Levine-Callahan-Dongarra benchmark to use FORALL for
>> those cases where it appears appropriate (15 of them).
>
> Is this code available?
>

forttime() in f90_msrdtsc.c is a functional near equivalent to
cpu_time() for those (common) cases where cpu_time doesn't give
sufficient resolution, and system_clock is vulnerable to default integer
wrap-around. Use one of those, if you want pure Fortran.
There are 2 or 3 additional tests where FORALL could be used, if giving
up OpenMP, for example.
Changes from the vectors benchmark on netlib.org, including f95 and
OpenMP syntax, are purely my own responsibility. Not all changes are
suitable for performance.

Typical compilation:
gfortran -O -c -mfpmath=387 -fopenmp mains.f
gfortran -O3 -funroll-loops -ftree-vectorize -fopenmp -c loops90.f
gcc -O3 -c -DCLOCK_RATE=2933000000 f90_msrdtsc.c (choose your own clock)
gfortran -fopenmp mains.o loops90.o forttime.o
./a.out > vectors.log

loops90.f
mains.f
f90_msrdtsc.c

Steven G. Kargl

unread,
Jan 16, 2007, 12:54:06 AM1/16/07
to
In article <45AC5F0F...@nospamcomputer.org>,
Tim Prince <tpr...@nospamcomputer.org> writes:
> This is a multi-part message in MIME format.
> --------------090805070605020507010807
> Content-Type: text/plain; charset=ISO-8859-1; format=flowed
> Content-Transfer-Encoding: 7bit

Thanks, Tim!

This code may be helpful with gfortran development.

--
Steve
http://troutmask.apl.washington.edu/~kargl/

spam.bri...@gmail.com

unread,
Jan 16, 2007, 1:21:22 AM1/16/07
to

On Jan 15, 8:19 pm, Tim Prince <tpri...@nospamcomputer.org> wrote:
> Steven G. Kargl wrote:
> > PS: It is interesting that in all the code I've taken

> > from the web, the use of FORALL occurs zero times.I translated the Levine-Callahan-Dongarra benchmark to use FORALL for


> those cases where it appears appropriate (15 of them). However, there
> appear to be large schools of thought where FORALL is at best equivalent
> to a DO loop. It doesn't support OpenMP, requires more analysis from
> the compiler to optimize, and, according to the standard and gfortran,
> doesn't allow statement functions.

Please note that FORALL statements / constructs are, in fact, supported
as a parallel construct in OpenMP (see page 44, lines 15-16 of the
OpenMP 2.5 specification**), and have been since late 2000, in the
OpenMP 2.0 specification. They are not simply loop-parallel
constructs, however - support is provided via the "workshare"
directive. It's really a shame that so few codes use FORALL, as it
provides a simple but powerful way to express parallelism within a
program. If only compilers would take advantage of this and enable
automatic parallelization of FORALL constructs; surely the analysis is
simpler than what is required to parallelize a general DO loop.
Sigh...

**http://www.openmp.org/drupal/mp-documents/spec25.pdf

Joost

unread,
Jan 16, 2007, 3:13:43 AM1/16/07
to

On Jan 16, 3:19 am, Tim Prince <tpri...@nospamcomputer.org> wrote:
> and, according to the standard and gfortran,
> doesn't allow statement functions.

If this is the case, I rather think this is a bug in gfortran (it does
fail with gcc version 4.3.0 20070114). I don't think the standard
prohibits:

INTEGER :: J,I,K,M(3)
I(J)=J**2
FORALL(K=1:3) M(K)=I(K)
END

and in fact it is accepted by e.g. g95 and xlf90.

Joost

glen herrmannsfeldt

unread,
Jan 16, 2007, 4:46:05 AM1/16/07
to
Joost wrote:

> On Jan 16, 3:19 am, Tim Prince <tpri...@nospamcomputer.org> wrote:

>>and, according to the standard and gfortran,
>>doesn't allow statement functions.

> If this is the case, I rather think this is a bug in gfortran (it does
> fail with gcc version 4.3.0 20070114). I don't think the standard
> prohibits:

> INTEGER :: J,I,K,M(3)
> I(J)=J**2
> FORALL(K=1:3) M(K)=I(K)
> END

I don't see any restriction on statement functions in F2003.

-- glen

Tobias Burnus

unread,
Jan 16, 2007, 5:04:00 AM1/16/07
to
Hi,

Joost wrote:
> If this is the case, I rather think this is a bug in gfortran (it does
> fail with gcc version 4.3.0 20070114). I don't think the standard
> prohibits:
>
> INTEGER :: J,I,K,M(3)
> I(J)=J**2
> FORALL(K=1:3) M(K)=I(K)
> END
>
> and in fact it is accepted by e.g. g95 and xlf90.

Hmm, unless I have somewhere a half-applied patch lurking, this example
is also accepted by
gfortran 4.3.0 20070116.

My a bit older gfortran 4.1 and today's gfortran 4.2 gives the same
error as NAG f95:
Error: reference to non-PURE function 'i' at (1) inside a FORALL block

NAG f95 rejects it with:
Error: ccc.f90, line 3: Non PURE procedure I referenced in FORALL

Sunf95, ifort and g95 also accept the code, which I think is valid.

Tobias

Joost

unread,
Jan 16, 2007, 5:27:13 AM1/16/07
to
> Hmm, unless I have somewhere a half-applied patch lurking, this example
> is also accepted by
> gfortran 4.3.0 20070116.

see http://gcc.gnu.org/ml/fortran/2007-01/msg00364.html ;-)

>
> My a bit older gfortran 4.1 and today's gfortran 4.2 gives the same
> error as NAG f95:
> Error: reference to non-PURE function 'i' at (1) inside a FORALL block

IIRC, I've once filed a bug with NAG for this one..

Cheers,

Joost

Beliavsky

unread,
Jan 16, 2007, 8:40:22 AM1/16/07
to

If in 2006 compilers do not optimize a feature of Fortran 95 (and even
earlier, High Performance Fortran), I'd guess that FORALL is not easier
to optimize than an array expression or a DO loop. Dick Hendrickson is
a wise man and IIUC in general does not recommend using FORALL --
Google "Hendrikson forall" in this newsgroup. In Fortran 2008 there are
plans for a DO CONCURRENT construct.

Craig Powers

unread,
Jan 16, 2007, 11:09:18 AM1/16/07
to
Tobias Burnus wrote:
> Hi,
>
> Joost wrote:
>> If this is the case, I rather think this is a bug in gfortran (it does
>> fail with gcc version 4.3.0 20070114). I don't think the standard
>> prohibits:
>>
>> INTEGER :: J,I,K,M(3)
>> I(J)=J**2
>> FORALL(K=1:3) M(K)=I(K)
>> END
>>
>> and in fact it is accepted by e.g. g95 and xlf90.
>
> Hmm, unless I have somewhere a half-applied patch lurking, this example
> is also accepted by
> gfortran 4.3.0 20070116.
>
> My a bit older gfortran 4.1 and today's gfortran 4.2 gives the same
> error as NAG f95:
> Error: reference to non-PURE function 'i' at (1) inside a FORALL block

If I'm remembering right, this is something that was fixed (or at least,
somewhat fixed) within the last few days.

Tom Micevski

unread,
Jan 19, 2007, 10:49:00 PM1/19/07
to

here is my promised test program. i've just stripped down an old
program (but you could strip even more away, eg. data statements and
write statements). hope it's helpful.

in case the code gets wrapped by my news program, i've also uploaded it
here:
http://www.mytempdir.com/1176091

tom

program forall_test_flike
implicit none
integer, parameter :: rk = selected_real_kind(p=10,r=100) ! double precision
! test data (0.0 = missing data)
real(rk), parameter :: q1(30) = (/
34.1,45.1,38.5,60.9,75.4,71.6,365.7,93.1,49.0,98.2,516.9,&

51.6,361.1,75.5,0.0,26.7,30.4,29.7,49.0,45.9,50.0,18.5,73.4,26.1,92.4,71.0,48.0,0.0,1216.3,0.0
/)
real(rk), parameter :: q2(30) = (/
169.2,469.9,305.7,566.1,317.0,492.5,150.0,795.4,764.3,1372.9,&

3366.0,62.2,418.9,261.8,158.5,345.3,8516.7,206.6,71.3,42.5,210.9,0.0,0.0,0.0,0.0,0.0,670.3,712.6,178.6,748.3
/)
real(rk), parameter :: q3(30) = (/
353.8,0.0,2135.5,0.0,3677.0,2123.0,1631.0,3693.7,1826.6,1852.4,&

146.6,433.4,614.3,393.5,54.8,1073.4,1368.6,1492.5,155.6,361.5,1616.8,182.8,259.3,570.6,1302.4,1301.8,0.0,0.0,0.0,0.0
/)
real(rk), parameter :: q4(30) = (/
38.4,12.7,12.4,39.1,175.3,0.0,0.0,0.0,0.0,0.0,&

0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,101.1,16.2,59.5,366.4,0.0
/)
real(rk), parameter :: q5(30) = (/ 0.0,0.0,0.0,0.0,0.0,0.3,0.6,1.2,0.9,4.5,&

4.3,5.6,1.5,1.6,2.4,3.0,1.6,4.4,10.1,2.1,3.9,4.4,2.4,0.7,3.1,3.2,1.6,1.8,5.0,3.2
/)
real(rk), parameter :: q6(30) = (/
1372.9,279.9,202.4,40416.9,7522.6,2533.5,3304.0,1231.3,1390.4,12536.6,&
3639.8,448.7,478.4,180.2,164.2,229.3,2123.0,965.3,27416.5,49.0,&
76.4,571.5,925.6,468.8,348.2,5412.3,3632.3,942.6,1006.5,335.2 /)
real(rk), parameter :: q7(30) = (/ 0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,&

0.0,22.9,53.4,44.5,14.4,36.6,216.5,34.0,25.0,33.0,8.5,10.7,25.1,0.0,0.0,4.5,44.0,0.0,0.0,0.0
/)
real(rk) :: q(30,7) = reshape( (/q1,q2,q3,q4,q5,q6,q7/), (/30,7/) )
! vars
integer :: npos_min = 15
real(rk) :: zero = 0.0_rk, miss = -999.0_rk
integer :: nsite, nyear, i, j
integer, allocatable :: npos(:)
real(rk), allocatable :: mn(:), sd(:)
character*20, allocatable :: text(:)
! start program
nyear = size(q, dim=1)
nsite = size(q, dim=2)
! mark/flag missing data (2 versions [1 using forall])
where (q <= zero .and. q > miss) q = miss - 10.0
forall (i=1:nsite, j=1:nyear, q(j,i) <= zero .and. q(j,i) > miss)
q(j,i) = miss - 10.0
end forall
do i=1,nyear
write(*,'(999f8.1)') (real(q(i,j)), j=1,nsite)
enddo
! count no. of positive values (2 versions [1 using forall])
allocate (npos(nsite))
npos = count(q > zero, dim=1)
write(*,*) npos
forall (i=1:nsite) npos(i) = count(q(:,i) > miss)
write(*,*) npos
! calc mead/sd (outer forall [with mask] calling pure subroutines [1
with inner forall])
allocate (mn(nsite), sd(nsite))
mn = zero; sd = zero
forall (i=1:nsite, npos(i) >= npos_min)
mn(i) = getmean (x=pack(q(:,i), q(:,i) > miss))
sd(i) = getsd (x=pack(q(:,i), q(:,i) > miss), m=mn(i))
end forall
write(*,*) real(mn)
write(*,*) real(sd)
! now just add a string-based forall
allocate (text(nsite))
forall (i=1:nsite) text(i) = 'site='//number_string(i)
write(*,*) text
continue
stop
contains
! ======================================================
pure function getmean (x)
IMPLICIT NONE
REAL(rk), INTENT(IN) :: x(:)
REAL(rk) :: getmean
real(rk) :: nr
nr = real(size(x),rk)
getmean = sum(x)/nr
end function getmean
! ======================================================
pure function getsd (x, m)
IMPLICIT NONE
REAL(rk), INTENT(IN) :: x(:), m
REAL(rk) :: getsd
INTEGER :: i
real(rk) :: nr1, resid(size(x))
nr1 = real(size(x)+1,rk)
forall (i=1:size(x)) resid(i) = x(i) - m
getsd = dot_product(resid,resid)/nr1
getsd = sqrt(getsd)
end function getsd
! ======================================================
pure function number_string (int)
implicit none
integer, intent(in) :: int
character(len=20) :: number_string
write(number_string,'(i0)') int
END function number_string

end program forall_test_flike

Steven G. Kargl

unread,
Jan 19, 2007, 11:06:33 PM1/19/07
to
In article <45b1912d$0$1028$61c6...@un-2park-reader-01.sydney.pipenetworks.com.au>,

Tom Micevski <no...@none.au> writes:
> Tom Micevski wrote:
>> Steven G. Kargl wrote:
>>> Anyone have code that uses FORALL and nested FORALLs that
>>> they may be willing to permit the gfortran developers to use
>>> in testing a bug fix and then optimization work?
>>
>> give me a few days (or so) and i'll try to email you something.
>>
>> note, though, i don't think that i'm doing anything too complex with my
>> FORALLs (simple/masked assignments, user-defined pure functions) ---
>> hopefully they'll still be useful.
>
> here is my promised test program. i've just stripped down an old
> program (but you could strip even more away, eg. data statements and
> write statements). hope it's helpful.
>
> in case the code gets wrapped by my news program, i've also uploaded it
> here:
> http://www.mytempdir.com/1176091

Thanks!

--
Steve
http://troutmask.apl.washington.edu/~kargl/

0 new messages