[Patch] Fortran: Update use_device_ptr for OpenMP 5.1 [PR105318]

2022-09-30 Thread Tobias Burnus

While has_device_addr has been implemented (in GCC 12), updating
use_device_ptr for Fortran was missed.

This patch fixes it: Removing the restrictions and mapping to
has_device_addr where applicable.

For use_device_ptr something similar was done, albeit I think
this has no semantic effect.

And 'device(omp_initial_device)' printed a warning in Fortran.
(BTW: C/C++ silently accepts any negative value.)

OK for mainline?

Tobias

PS: There were several important clarifications/fixes to
{has,is,use}_device_{addr,ptr} after the 5.2 release. However,
the fixes part mostly affect the user and not the implementation.


-
Siemens Electronic Design Automation GmbH; Anschrift: Arnulfstraße 201, 80634 
München; Gesellschaft mit beschränkter Haftung; Geschäftsführer: Thomas 
Heurung, Frank Thürauf; Sitz der Gesellschaft: München; Registergericht 
München, HRB 106955
Fortran: Update use_device_ptr for OpenMP 5.1 [PR105318]

OpenMP 5.1 added has_device_addr and relaxed the restrictions for
use_device_ptr, including processing non-type(c_ptr) arguments as
if has_device_addr was used. (There is a semantic difference.)

For completeness, the likewise change was done for 'use_device_ptr',
where non-type(c_ptr) arguments now use use_device_addr.

Finally, a warning for 'device(omp_{initial,invalid}_device)' was
silenced on the way as affecting the new testcase.

gcc/fortran/ChangeLog:

	* openmp.cc (resolve_omp_clauses): Update is_device_ptr restrictions
	for OpenMP 5.1 and map to has_device_addr where applicable; map
	use_device_ptr to use_device_addr where applicable.
	Silence integer-range warning for device(omp_{initial,invalid}_device).

libgomp/ChangeLog:

	* testsuite/libgomp.fortran/is_device_ptr-2.f90: New test.

gcc/testsuite/ChangeLog:

	* gfortran.dg/gomp/is_device_ptr-1.f90: Remove dg-error.
	* gfortran.dg/gomp/is_device_ptr-2.f90: Likewise.
	* gfortran.dg/gomp/is_device_ptr-3.f90: Update tree-scan-dump.

 gcc/fortran/openmp.cc  |  81 +++---
 gcc/testsuite/gfortran.dg/gomp/is_device_ptr-1.f90 |   9 +-
 gcc/testsuite/gfortran.dg/gomp/is_device_ptr-2.f90 |   2 +-
 gcc/testsuite/gfortran.dg/gomp/is_device_ptr-3.f90 |   3 +-
 .../testsuite/libgomp.fortran/is_device_ptr-2.f90  | 167 +
 5 files changed, 235 insertions(+), 27 deletions(-)

diff --git a/gcc/fortran/openmp.cc b/gcc/fortran/openmp.cc
index 457e983663b..313d4e2de1b 100644
--- a/gcc/fortran/openmp.cc
+++ b/gcc/fortran/openmp.cc
@@ -6511,7 +6511,7 @@ static void
 resolve_omp_clauses (gfc_code *code, gfc_omp_clauses *omp_clauses,
 		 gfc_namespace *ns, bool openacc = false)
 {
-  gfc_omp_namelist *n;
+  gfc_omp_namelist *n, *last;
   gfc_expr_list *el;
   int list;
   int ifc;
@@ -7369,30 +7369,58 @@ resolve_omp_clauses (gfc_code *code, gfc_omp_clauses *omp_clauses,
 		}
 	break;
 	  case OMP_LIST_IS_DEVICE_PTR:
-	for (n = omp_clauses->lists[list]; n != NULL; n = n->next)
+	last = NULL;
+	for (n = omp_clauses->lists[list]; n != NULL; )
 	  {
-		if (!n->sym->attr.dummy)
-		  gfc_error ("Non-dummy object %qs in %s clause at %L",
-			 n->sym->name, name, &n->where);
-		if (n->sym->attr.allocatable
-		|| (n->sym->ts.type == BT_CLASS
-			&& CLASS_DATA (n->sym)->attr.allocatable))
-		  gfc_error ("ALLOCATABLE object %qs in %s clause at %L",
-			 n->sym->name, name, &n->where);
-		if (n->sym->attr.pointer
-		|| (n->sym->ts.type == BT_CLASS
-			&& CLASS_DATA (n->sym)->attr.pointer))
-		  gfc_error ("POINTER object %qs in %s clause at %L",
-			 n->sym->name, name, &n->where);
-		if (n->sym->attr.value)
-		  gfc_error ("VALUE object %qs in %s clause at %L",
-			 n->sym->name, name, &n->where);
+		if (n->sym->ts.type == BT_DERIVED
+		&& n->sym->ts.u.derived->ts.is_iso_c
+		&& code->op != EXEC_OMP_TARGET)
+		  /* Non-TARGET (i.e. DISPATCH) requires a C_PTR.  */
+		  gfc_error ("List item %qs in %s clause at %L must be of "
+			 "TYPE(C_PTR)", n->sym->name, name, &n->where);
+		else if (n->sym->ts.type != BT_DERIVED
+			 || !n->sym->ts.u.derived->ts.is_iso_c)
+		  {
+		/* For TARGET, non-C_PTR are deprecated and handled as
+		   has_device_addr.  */
+		gfc_omp_namelist *n2 = n;
+		n = n->next;
+		if (last)
+		  last->next = n;
+		else
+		  omp_clauses->lists[list] = n;
+		n2->next = omp_clauses->lists[OMP_LIST_HAS_DEVICE_ADDR];
+		omp_clauses->lists[OMP_LIST_HAS_DEVICE_ADDR] = n2;
+		continue;
+		  }
+		last = n;
+		n = n->next;
 	  }
 	break;
 	  case OMP_LIST_HAS_DEVICE_ADDR:
-	  case OMP_LIST_USE_DEVICE_PTR:
 	  case OMP_LIST_USE_DEVICE_ADDR:
-	/* FIXME: Handle OMP_LIST_USE_DEVICE_PTR.  */
+	break;
+	  case OMP_LIST_USE_DEVICE_PTR:
+	/* Non-C_PTR are deprecated and handled as use_device_ADDR.  */
+	last = NULL;
+	for (n = omp_clauses->lists[list]; n != NULL; )
+	  {
+		gfc_omp_namelist *n2 = n;
+		if (n->sym->ts.type != BT_DERIVED
+		|| !n->sym->ts.u.derived->ts

Re: [Patch] Fortran: Update use_device_ptr for OpenMP 5.1 [PR105318]

2022-09-30 Thread Tobias Burnus

On 30.09.22 12:41, Tobias Burnus wrote:

Fortran: Update use_device_ptr for OpenMP 5.1 [PR105318]

The following two lines slipped in – which I have now removed in my version of 
the patch:

--- a/gcc/testsuite/gfortran.dg/gomp/is_device_ptr-1.f90
+++ b/gcc/testsuite/gfortran.dg/gomp/is_device_ptr-1.f90
@@ -1,4 +1,5 @@
! { dg-do compile }
+! First


(Leftover - I wanted to refer to PR105318 - but then decided against it.)



+++ b/libgomp/testsuite/libgomp.fortran/is_device_ptr-2.f90
@@ -0,0 +1,167 @@
+! { dg-do compile }


Likewise leftover - I had an intermittent problem with device testing; hence, I 
disabled it. It turned out to be unrelated, but it remained.

Side remark: An issue I found with device testing was that I missed the "xx => 
null()"; in principle obvious (as GCC tried to map the pointer target of the 
uninitialized pointer), but still easy to miss.

Side note: The OpenMP spec (post-5.2) also clarified the mapping of undefined 
pointers / requiring the two null init here.

(The second null() is to avoid issues with firstprivatizing/copy-in of the 
internal pointer representation vs. simply using it (host fallback, unified 
shared memory). This forces the pointer after the target region to be the same 
as before the region (now required by the spec!), permitting either 
implementation without unexpected side effects for the user.)

Tobias

-
Siemens Electronic Design Automation GmbH; Anschrift: Arnulfstraße 201, 80634 
München; Gesellschaft mit beschränkter Haftung; Geschäftsführer: Thomas 
Heurung, Frank Thürauf; Sitz der Gesellschaft: München; Registergericht 
München, HRB 106955


Re: [Patch] Fortran: Update use_device_ptr for OpenMP 5.1 [PR105318]

2022-09-30 Thread Jakub Jelinek via Fortran
On Fri, Sep 30, 2022 at 12:41:19PM +0200, Tobias Burnus wrote:
> While has_device_addr has been implemented (in GCC 12), updating
> use_device_ptr for Fortran was missed.
> 
> This patch fixes it: Removing the restrictions and mapping to
> has_device_addr where applicable.
> 
> For use_device_ptr something similar was done, albeit I think
> this has no semantic effect.
> 
> And 'device(omp_initial_device)' printed a warning in Fortran.
> (BTW: C/C++ silently accepts any negative value.)

I think that is what the standard wants.
E.g. in 5.2 device Clause chapter, there is just
"If the device_num device-modifier is specified and target-offload-var is not 
mandatory,
device-description must evaluate to a conforming device number."
restriction, which is something that can't be checked at compile time,
you don't know if target-offload-var is mandatory or not.
>if (omp_clauses->device)
> -resolve_nonnegative_int_expr (omp_clauses->device, "DEVICE");
> +{
> +  resolve_scalar_int_expr (omp_clauses->device, "DEVICE");
> +  /* omp_initial_device == 1, omp_invalid_device = -4 (in GCC).  */
> +  if (omp_clauses->device->expr_type == EXPR_CONSTANT
> +   && omp_clauses->device->ts.type == BT_INTEGER
> +   && mpz_cmp_si (omp_clauses->device->value.integer, -1) < 0
> +   && mpz_cmp_si (omp_clauses->device->value.integer, -4) != 0)
> + gfc_warning (0,
> +  "INTEGER expression of DEVICE clause at %L must be non-"
> +  "negative or omp_initial_device or omp_invalid_device",
> +  &omp_clauses->device->where);
> +}

So I think we should just resolve_scalar_int_expr and be done with that.

Otherwise LGTM.

Jakub



Re: [Patch] Fortran: Update use_device_ptr for OpenMP 5.1 [PR105318]

2022-09-30 Thread Tobias Burnus

Hi Jakub,

On 30.09.22 13:04, Jakub Jelinek via Fortran wrote:

On Fri, Sep 30, 2022 at 12:41:19PM +0200, Tobias Burnus wrote:


And 'device(omp_initial_device)' printed a warning in Fortran.
(BTW: C/C++ silently accepts any negative value.)


I think that is what the standard wants.
E.g. in 5.2 device Clause chapter, there is just
"If the device_num device-modifier is specified and target-offload-var is not 
mandatory,
device-description must evaluate to a conforming device number."
restriction, which is something that can't be checked at compile time,
you don't know if target-offload-var is mandatory or not.


Admittedly, it is valid to use a non-conforming device number with
target-offload-var being 'mandatory'; however, the result is still
it it has a "non-conforming device number, is as if the
omp_invalid_device device number was used." (Which implies error
termination.)

Thus, while not invalid (iff using 'mandatory'), it is still odd
code and using 'device(omp_invalid_device)' is more sensible.

I think it is legitimate to warn in this case - but not to
print an error. It is likewise fine to accept it silently.



  if (omp_clauses->device)
-resolve_nonnegative_int_expr (omp_clauses->device, "DEVICE");
+{
+  resolve_scalar_int_expr (omp_clauses->device, "DEVICE");
+  /* omp_initial_device == 1, omp_invalid_device = -4 (in GCC).  */
+  if (omp_clauses->device->expr_type == EXPR_CONSTANT
+ && omp_clauses->device->ts.type == BT_INTEGER
+ && mpz_cmp_si (omp_clauses->device->value.integer, -1) < 0
+ && mpz_cmp_si (omp_clauses->device->value.integer, -4) != 0)
+   gfc_warning (0,
+"INTEGER expression of DEVICE clause at %L must be non-"
+"negative or omp_initial_device or omp_invalid_device",
+&omp_clauses->device->where);
+}



So I think we should just resolve_scalar_int_expr and be done with that.

Otherwise LGTM.


I have now done as suggested - and committed it as 
https://gcc.gnu.org/r13-2980-g10a116104969b3ecc9ea4abdd5436c66fd78d537

Thanks for the review!

Tobias


-
Siemens Electronic Design Automation GmbH; Anschrift: Arnulfstraße 201, 80634 
München; Gesellschaft mit beschränkter Haftung; Geschäftsführer: Thomas 
Heurung, Frank Thürauf; Sitz der Gesellschaft: München; Registergericht 
München, HRB 106955


Re: [PATCH v3 06/11] OpenMP: Pointers and member mappings

2022-09-30 Thread Julian Brown
On Fri, 23 Sep 2022 14:10:51 +0200
Tobias Burnus  wrote:

> Hi Julian and Jakub, hi all,
> 
> On 23.09.22 09:29, Julian Brown wrote:
> > How about this version? (Re-tested.)  
> 
> Some more generic (pre)remarks – not affecting the patch code,
> but possibly the commit log message:
> 
> > This follows OMP 5.0, 2.19.7.1 "map Clause":  
> 
> which is also in "OMP 5.2, 5.8.3 map Clause [152:1-4]". It might
> make sense to add this ref in addition (or instead):
> 
> >"If a list item in a map clause is an associated pointer and the
> > pointer is not the base pointer of another list item in a map
> > clause on the same construct, then it is treated as if its pointer
> > target is implicitly mapped in the same clause. For the purposes of
> > the map clause, the mapped pointer target is treated as if its base
> > pointer is the associated pointer."  

I've changed the wording in the commit log text...

> Thus, the following restriction was proposed for OpenMP 6.0 (TR11):
> 
> "The association status of a list item that is a pointer must not be
>   undefined unless it is a structure component and it results from a
>   predefined default mapper."
> 
> which makes my example invalid. (Add some caveat here about TR11 not
> yet being released and also TRs being not final named-version
> releases.)

(But not this bit, for now.)

> > and then instead we should follow:
> >
> >"If the structure sibling list item is a pointer then it is
> > treated as if its association status is undefined, unless it
> > appears as the base pointer of another list item in a map clause on
> > the same construct."  
> 
> 
> This wording disappeared in 5.1 due to some cleanup (cf. Issue 2152,
> which has multiple changes; this one is Pull Req. 2379).
> 
> I think the matching current / OpenMP 5.2 wording (5.8.3 map Clause
> [152:5-8, 11-13 (,14-16)]) is
> 
> "For map clauses on map-entering constructs, if any list item has a
> base pointer for which a corresponding pointer exists in the data
> environment upon entry to the region and either a new list item or
> the corresponding pointer is created in the device data environment
> on entry to the region, then: (Fortran)
> 1. The corresponding pointer variable is associated with a pointer
> target that has the same rank and bounds as the pointer target of the
> original pointer, such that the corresponding list item can be
> accessed through the pointer in a target region. ..."
> 
> I think here 'a new list item ... is created ... on entry' applies.
> However, this should not affect what you wrote later on.

I changed the text here too.

> > But, that's not implemented quite right at the moment [...]
> > The solution is to detect when we're mapping a smaller part of the
> > array (or a subcomponent) on the same directive, and only map the
> > descriptor in that case. So we get mappings like this instead:
> >
> >map(to: tvar%arrptr)   -->
> >GOMP_MAP_ALLOC  tvar%arrptr  (the descriptor)
> >
> >map(tofrom: tvar%arrptr(3:8)   -->
> >GOMP_MAP_TOFROM tvar%arrptr%data(3) (size 8-3+1, etc.)
> >GOMP_MAP_ALWAYS_POINTER tvar%arrptr%data (bias 3, etc.)  
> 
> (I concur.)

Thank you!

> > --- a/gcc/fortran/trans-openmp.cc
> > +++ b/gcc/fortran/trans-openmp.cc
> > ...
> > @@ -2470,22 +2471,18 @@ gfc_trans_omp_array_section (stmtblock_t
> > *block, gfc_omp_namelist *n, }
> > if (GFC_DESCRIPTOR_TYPE_P (TREE_TYPE (decl)))
> >   {
> > ...
> > +  if (ptr_kind != GOMP_MAP_ALWAYS_POINTER)
> > {
> > ...
> > + /* For OpenMP, the descriptor must be mapped with its
> > own explicit
> > +map clause (e.g. both "map(foo%arr)" and
> > "map(foo%arr(:))" must
> > +be present in the clause list if "foo%arr" is a
> > pointer to an
> > +array).  So, we don't create a GOMP_MAP_TO_PSET node
> > here.  */
> > + node2 = build_omp_clause (input_location,
> > OMP_CLAUSE_MAP);
> > + OMP_CLAUSE_SET_MAP_KIND (node2, GOMP_MAP_TO_PSET);  
> 
> I found the last sentence of the comment and the set_map_kind
> confusing: The comment says no MAP_TO_PSET and the SET_MAP_KIND use
> it.
> 
> I wonder whether that should be something like 'if (openacc)' instead,
> which kind of matches the first way gfc_trans_omp_array_section is
> called:

I agree it was confusing -- I've tweaked the wording of the comment.
The condition changes in the "address tokenization" follow-up patch
anyway.

> inner, element, kind, node, node2, node3,
> node4);
> However, there is also a second call to it:
> 
>/* An array element or array section which is not
> part of a derived type, etc.  */
> ...
>gomp_map_kind k = GOMP_MAP_POINTER;
> ...
>gfc_trans_omp_array_section (block, n, decl,
> element, k, node, node2, node3, node4);

> And without following all 'if' conditions through, I don't see why
> that should be handled differently.

GOMP_MAP_POINTER is used for non-component a

Re: [PATCH v3 06/11] OpenMP: Pointers and member mappings

2022-09-30 Thread Tobias Burnus

Hi Julian,

On 30.09.22 15:30, Julian Brown wrote:

  i = 1; j = 2
  map (foo(i)%dt_ptr(1:3), foo(j)%dt_ptr)


Good catch! In that gfc_dep_resolver considers those terms to have a
dependency, and that triggers the mapping node transformation. But I
don't think OpenMP allows you to write this: IIUC if "foo" is an array,
you're not allowed to separately map two parts of the array because of
(OpenMP 5.2, "5.8.3 map Clause"):

 "Two list items of the map clauses on the same construct must not
  share original storage unless they are the same list item or unless
  one is the containing structure of the other."


I was thinking of something like:

type t
 integer, pointer :: p(:)
end t
type(t2) :: var(2)
allocate (var(1)%p, source=[1,2,3,5])
allocate (var(2)%p, source=[2,3,5])

!$omp target map (  )
 var(1)%p(1) = 5
 var(2)%p(2) = 7
!$omp end target


Similarly for C:

struct st {
 int *p;
};
struct st s[2];
s[0].p = (int*)__malloc(sizeof(int)*5);
s[1].p = (int*)__malloc(sizeof(int)*3);

#pragma omp target map(  )
{
 s[0].p[0] = 5;
 s[1].p[1] = 7;
}


And now I somehow need to map "p" in both the C and the Fortran case.
And I believe that should be possible...
and my
  i = 1; j = 2
  map (var(i)%p(1:3), var(j)%p)
or
 map (s[0].p[:3], s[1].p[:7])

does not look to far fetched to get this result ...

Tobias


-
Siemens Electronic Design Automation GmbH; Anschrift: Arnulfstraße 201, 80634 
München; Gesellschaft mit beschränkter Haftung; Geschäftsführer: Thomas 
Heurung, Frank Thürauf; Sitz der Gesellschaft: München; Registergericht 
München, HRB 106955


Re: [PATCH v3 06/11] OpenMP: Pointers and member mappings

2022-09-30 Thread Tobias Burnus

On 30.09.22 15:30, Julian Brown wrote:
On Fri, 23 Sep 2022 14:10:51 +0200 Tobias Burnus 
 wrote:
...

I added n->expr->expr_type == EXPR_VARIABLE to the condition -- I think
that should suffice for now?

Yes.


A similar mean way to write code would be:

integer, target :: A(5)
integer, pointer :: p(:), p2(:)
type(t) :: var

allocate(p2(1:20))
p => A
var%p2 => p2
!$omp target map(A(3:4), p2(4:8), p, var%p2)
 
!$omp end target

which has a similar issue – it is not clear from the syntax whether
p's or var%p2's pointer target has been mapped or not.


Again, I don't think you're allowed to write that: that's "different
list items" sharing the same "original storage", IIUC. (It'd be nice to
diagnose it at compile time, but that's probably not that easy...)

Hmm, isn't that implied to be valid per:

"[Fortran] If a list item in a map clause is an associated pointer and the 
pointer
is not the base pointer of another list item in a map clause on the same
construct, then it is treated as if its pointer target is implicitly
mapped in the same clause."
(OpenMP 5.2, 5.8.3 map Clause [152:1-4]; seems to be identical to
OpenMP 5.1, 2.21.7.1 map Clause [349:9-12])

Admittedly, in 5.0 I only see the wording (OpenMP 5.0, [316:22-25]),
which is also not handled - but different:

"[Fortran] Each pointer component that is a list item that results from
a mapped derived type variable is treated as if its association status
is undefined, unless the pointer component appears as another list
item or as the base pointer of another list item in a map clause on
the same construct."

I think the that's for the following case (which is also covered by the
more general 5.1/5.2 wording):
type t

 integer, pointer :: p(:)
 integer, pointer :: p2(:)
end type t
type(t) :: var
integer, target :: tgt(5), tgt2(1000)
var%p => tgt
var%p => tgt2

!$omp target map(tgt, tgt2(4:6), var)
 var%p(1) = 5
 var%p2(5) = 7
!$omp end target

and I think GCC does not handled this, but I might be wrong.

Tobias


-
Siemens Electronic Design Automation GmbH; Anschrift: Arnulfstraße 201, 80634 
München; Gesellschaft mit beschränkter Haftung; Geschäftsführer: Thomas 
Heurung, Frank Thürauf; Sitz der Gesellschaft: München; Registergericht 
München, HRB 106955