This is the mail archive of the fortran@gcc.gnu.org mailing list for the GNU Fortran project.


Index Nav: [Date Index] [Subject Index] [Author Index] [Thread Index]
Message Nav: [Date Prev] [Date Next] [Thread Prev] [Thread Next]
Other format: [Raw text]

Re: Problem with OpenMP Reduction Clause


On Tue, May 02, 2006 at 05:34:46PM +0200, Benjamin R?veill? wrote:
> On 5/2/06, Diego Novillo <dnovillo@redhat.com> wrote:
> >
>>Benjamin R?veill? wrote:
>>
>>>   integer, dimension(n), intent(out) :: sumarray
>>>   !
>>>   integer :: i,j
>>>   !
>>>   sumarray(:)=0
>>>
>>2.8.3.  Restrictions to the reduction clause:
>>
>>? Fortran pointers, Cray pointers, assumed-size arrays and allocatable
>>arrays may not appear in a reduction clause.
> 
> Yep that is exactly what I also read...
> 
>>I'm not too familiar with Fortran, but sumarray seems to be an
>>assumed-size array here?  If so, then we should probably emit a
>>diagnostic.  In either case, we shouldn't ICE, could you file a PR?
> 
> I'm not too familiar either... But I tried looking it up...
> And I thought
> integer, dimension(*), intent(out) :: sumarray  --> would make
> sumarray assumed-size
> 
> 
> c.f. http://www.nsc.liu.se/~boein/f77to90/a9.html
> ############################################################
> assumed-size array:
> The array has a variable dimension, like in Fortran 77, through that
> both the array name and the parameters of the dimension are dummy
> arguments, except the last dimension, which is given by a *
> 
>                SUBROUTINE SUB (A, NA1, NA2)
>                REAL, DIMENSION (NA1, NA2,*) :: A
> 
> In Fortran 66 the concept "assumed-size array" was not defined, but it
> was simulated by placing the digit "1" where the "*" is in Fortran 77.
> This custom violates the index check and is of course forbidden by
> modern compilers, for example the NAG Fortran 90 compiler. Many old
> programs still use this way of simulating dynamic memory allocation.
> ############################################################
> 
> What about this other variant:
> array_reduction2.f90
> program array_reduction
>   implicit none
>   integer, parameter :: n=10,m=1000
>   integer :: i
>   !
>   call foo(n,m)
> 
> end program array_reduction
> 
> subroutine foo(n,m)
>   use omp_lib, only : omp_get_thread_num
>   implicit none
>   integer, intent(in) :: n,m
>   !
>   integer :: i,j
>   integer, dimension(n) :: sumarray
>   !
>   sumarray(:)=0
> !$OMP PARALLEL DEFAULT(shared)
>   print*,'hello from thread ',omp_get_thread_num()
> !$OMP DO PRIVATE(j,i), REDUCTION(+:sumarray)
>   do j=1,m
>      do i=1,n
>         sumarray(i)=sumarray(i)+i
>      end do
>   end do
> !$OMP END DO
> !$OMP END PARALLEL
>   do i=1,n
>      print*,sumarray(i)
>   end do
> end subroutine foo
> 
> Which passes on intel, xlf, pgi but segfaults on gfortran.
> 
> Do I file a seperate PR Or put both test cases in the PR ???
> 

File 1 bug report with both test programs.  Note that
one program should issue an error and the other 
should compile.   You'll probably want to add the
URL to the head of this thread, and you might want
to ping Jakub, who knows gfoftran's openmp implementation
better than anyone else, to ensure that he see the problem.

-- 
Steve


Index Nav: [Date Index] [Subject Index] [Author Index] [Thread Index]
Message Nav: [Date Prev] [Date Next] [Thread Prev] [Thread Next]