public inbox for fortran@gcc.gnu.org
 help / color / mirror / Atom feed
* A gfortran silent "wrong code" bug in the transition from 4.9.0 -> 4.9.1, using OpenMP.
@ 2016-06-30 17:34 Toon Moene
  2016-06-30 18:44 ` Jakub Jelinek
  0 siblings, 1 reply; 4+ messages in thread
From: Toon Moene @ 2016-06-30 17:34 UTC (permalink / raw)
  To: Jakub Jelinek, fortran

[-- Attachment #1: Type: text/plain, Size: 940 bytes --]

Jakub,

A colleague of mine at Meteo France, Toulouse, managed to reduce a 
problem he had with our common weather forecasting code when using 
OpenMP down to the attached code and the transition from 4.9.0 -> 4.9.1.

In 4.9.1 OpenMP 4.0 was introduced. That is of course a big hammer to 
start looking for the culprit, but you are the best person to go to on 
this code.

The attached code produces with 4.9.1, 5.4 and 6.1:

    99999.0000       99999.0000       99999.0000       99999.0000

whereas it should produce four zeros.

Compile with gfortran -fopenmp elkhatib.f90.

Thanks for any help - kind regards,

PS: I will make a Bugzilla report if it doesn't ring a bell immediately.

-- 
Toon Moene - e-mail: toon@moene.org - phone: +31 346 214290
Saturnushof 14, 3738 XG  Maartensdijk, The Netherlands
At home: http://moene.org/~toon/; weather: http://moene.org/~hirlam/
Progress of GNU Fortran: http://gcc.gnu.org/wiki/GFortran#news

[-- Attachment #2: elkhatib.f90 --]
[-- Type: text/x-fortran, Size: 1178 bytes --]

MODULE MYFIELDS_MOD

! The definition of a derived type containing an allocatable array

IMPLICIT NONE
SAVE

TYPE :: MYFIELDS
  REAL, ALLOCATABLE :: GMVT1S(:)
END TYPE MYFIELDS

END MODULE MYFIELDS_MOD

PROGRAM GP_MODEL

! A program to allocate then use a structure containing a allocatable array

USE MYFIELDS_MOD , ONLY : MYFIELDS

IMPLICIT NONE

TYPE(MYFIELDS) :: YRFIELDS

ALLOCATE(YRFIELDS%GMVT1S(4))

YRFIELDS%GMVT1S=99999.

CALL GP_TEST(YRFIELDS)

END PROGRAM GP_MODEL

SUBROUTINE GP_TEST(YDFIELDS)

! A subroutine to initialize the component of a structure, which is an
! allocatable array, via an association

! DOES NOT WORK SINCE GFORTRAN 4.9.2 (4.9.1 ?), UNLESS ONE OF THE FOLLOWING CONDITIONS IS RESPECTED :
! - Open-mp is disabled
! - the attribute is POINTER instead of ALLOCATABLE
! - the association is not used
! COULD BE AN ISSUE WITH Version 4.0 of the OpenMP specification

USE MYFIELDS_MOD , ONLY : MYFIELDS

IMPLICIT NONE

TYPE(MYFIELDS), INTENT(INOUT)      :: YDFIELDS

INTEGER :: J

ASSOCIATE(YDGMV=>YDFIELDS)

!$OMP PARALLEL DO
DO J=1,4
  YDGMV%GMVT1S(J)=0.
ENDDO
!$OMP END PARALLEL DO

print*,YDFIELDS%GMVT1S(:)

END ASSOCIATE

END SUBROUTINE GP_TEST

^ permalink raw reply	[flat|nested] 4+ messages in thread

* Re: A gfortran silent "wrong code" bug in the transition from 4.9.0 -> 4.9.1, using OpenMP.
  2016-06-30 17:34 A gfortran silent "wrong code" bug in the transition from 4.9.0 -> 4.9.1, using OpenMP Toon Moene
@ 2016-06-30 18:44 ` Jakub Jelinek
  2016-06-30 20:00   ` Toon Moene
  0 siblings, 1 reply; 4+ messages in thread
From: Jakub Jelinek @ 2016-06-30 18:44 UTC (permalink / raw)
  To: Toon Moene; +Cc: fortran

On Thu, Jun 30, 2016 at 07:33:53PM +0200, Toon Moene wrote:
> A colleague of mine at Meteo France, Toulouse, managed to reduce a problem
> he had with our common weather forecasting code when using OpenMP down to
> the attached code and the transition from 4.9.0 -> 4.9.1.
> 
> In 4.9.1 OpenMP 4.0 was introduced. That is of course a big hammer to start
> looking for the culprit, but you are the best person to go to on this code.

It is a bug, please file the PR.
Either gfc_omp_predetermined_sharing should not in the
GFC_DECL_ASSOCIATE_VAR_P handling return OMP_CLAUSE_DEFAULT_FIRSTPRIVATE
if gfc_omp_privatize_by_reference is true on it, or conversely we should
make sure gfc_omp_privatize_by_reference for
GFC_DECL_ASSOCIATE_VAR_P decls with POINTER_TYPE returns false.
The former change is probably less dangerous, the latter might be more
efficient, but I'd have to go through all the places where the target hook
is used and argue about ASSOCIATE decls there.

	Jakub

^ permalink raw reply	[flat|nested] 4+ messages in thread

* Re: A gfortran silent "wrong code" bug in the transition from 4.9.0 -> 4.9.1, using OpenMP.
  2016-06-30 18:44 ` Jakub Jelinek
@ 2016-06-30 20:00   ` Toon Moene
  2016-07-01 15:17     ` [committed] Re: A gfortran silent "wrong code" bug in the transition from 4.9.0 -> 4.9.1, using OpenMP. (PR fortran/71717) Jakub Jelinek
  0 siblings, 1 reply; 4+ messages in thread
From: Toon Moene @ 2016-06-30 20:00 UTC (permalink / raw)
  To: Jakub Jelinek; +Cc: fortran

On 06/30/2016 08:43 PM, Jakub Jelinek wrote:

> On Thu, Jun 30, 2016 at 07:33:53PM +0200, Toon Moene wrote:

>> A colleague of mine at Meteo France, Toulouse, managed to reduce a problem
>> he had with our common weather forecasting code when using OpenMP down to
>> the attached code and the transition from 4.9.0 -> 4.9.1.
>>
>> In 4.9.1 OpenMP 4.0 was introduced. That is of course a big hammer to start
>> looking for the culprit, but you are the best person to go to on this code.
>
> It is a bug, please file the PR.

It is bugzilla number 71717 (see 
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=71717)

Thanks for looking into this.

Kind regards,

-- 
Toon Moene - e-mail: toon@moene.org - phone: +31 346 214290
Saturnushof 14, 3738 XG  Maartensdijk, The Netherlands
At home: http://moene.org/~toon/; weather: http://moene.org/~hirlam/
Progress of GNU Fortran: http://gcc.gnu.org/wiki/GFortran#news

^ permalink raw reply	[flat|nested] 4+ messages in thread

* [committed] Re: A gfortran silent "wrong code" bug in the transition from 4.9.0 -> 4.9.1, using OpenMP. (PR fortran/71717)
  2016-06-30 20:00   ` Toon Moene
@ 2016-07-01 15:17     ` Jakub Jelinek
  0 siblings, 0 replies; 4+ messages in thread
From: Jakub Jelinek @ 2016-07-01 15:17 UTC (permalink / raw)
  To: Toon Moene; +Cc: fortran, gcc-patches

On Thu, Jun 30, 2016 at 10:00:23PM +0200, Toon Moene wrote:
> On 06/30/2016 08:43 PM, Jakub Jelinek wrote:
> 
> >On Thu, Jun 30, 2016 at 07:33:53PM +0200, Toon Moene wrote:
> 
> >>A colleague of mine at Meteo France, Toulouse, managed to reduce a problem
> >>he had with our common weather forecasting code when using OpenMP down to
> >>the attached code and the transition from 4.9.0 -> 4.9.1.
> >>
> >>In 4.9.1 OpenMP 4.0 was introduced. That is of course a big hammer to start
> >>looking for the culprit, but you are the best person to go to on this code.
> >
> >It is a bug, please file the PR.
> 
> It is bugzilla number 71717 (see
> https://gcc.gnu.org/bugzilla/show_bug.cgi?id=71717)
> 
> Thanks for looking into this.

Fixed thusly, committed to trunk so far after bootstrap/regtest on
x86_64-linux and i686-linux, queued for backporting.

2016-07-01  Jakub Jelinek  <jakub@redhat.com>

	PR fortran/71717
	* trans-openmp.c (gfc_omp_privatize_by_reference): Return false
	for GFC_DECL_ASSOCIATE_VAR_P with POINTER_TYPE.

	* testsuite/libgomp.fortran/associate3.f90: New test.

--- gcc/fortran/trans-openmp.c.jj	2016-06-30 19:39:19.000000000 +0200
+++ gcc/fortran/trans-openmp.c	2016-07-01 12:57:22.960295589 +0200
@@ -61,6 +61,7 @@ gfc_omp_privatize_by_reference (const_tr
       if (GFC_DECL_GET_SCALAR_POINTER (decl)
 	  || GFC_DECL_GET_SCALAR_ALLOCATABLE (decl)
 	  || GFC_DECL_CRAY_POINTEE (decl)
+	  || GFC_DECL_ASSOCIATE_VAR_P (decl)
 	  || VOID_TYPE_P (TREE_TYPE (TREE_TYPE (decl))))
 	return false;
 
--- libgomp/testsuite/libgomp.fortran/associate3.f90.jj	2016-07-01 13:36:26.208044233 +0200
+++ libgomp/testsuite/libgomp.fortran/associate3.f90	2016-07-01 13:45:07.274602305 +0200
@@ -0,0 +1,20 @@
+! PR fortran/71717
+! { dg-do run }
+
+  type t
+    real, allocatable :: f(:)
+  end type
+  type (t) :: v
+  integer :: i, j
+  allocate (v%f(4))
+  v%f = 19.
+  i = 5
+  associate (u => v, k => i)
+  !$omp parallel do
+  do j = 1, 4
+    u%f(j) = 21.
+    if (j.eq.1) k = 7
+  end do
+  end associate
+  if (any (v%f(:).ne.21.) .or. i.ne.7) call abort
+end


	Jakub

^ permalink raw reply	[flat|nested] 4+ messages in thread

end of thread, other threads:[~2016-07-01 15:17 UTC | newest]

Thread overview: 4+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2016-06-30 17:34 A gfortran silent "wrong code" bug in the transition from 4.9.0 -> 4.9.1, using OpenMP Toon Moene
2016-06-30 18:44 ` Jakub Jelinek
2016-06-30 20:00   ` Toon Moene
2016-07-01 15:17     ` [committed] Re: A gfortran silent "wrong code" bug in the transition from 4.9.0 -> 4.9.1, using OpenMP. (PR fortran/71717) Jakub Jelinek

This is a public inbox, see mirroring instructions
for how to clone and mirror all data and code used for this inbox;
as well as URLs for read-only IMAP folder(s) and NNTP newsgroup(s).