[Patch] Fortran/OpenMP: Add memory routines existing for C/C++

2021-08-18 Thread Tobias Burnus

The added routines existed before for C/C++ (being part of OpenMP 5.0)
but not for Fortran (new there since OpenMP 5.1) – as those are all bind(C),
it only affects 'omp_lib' and uses the C interface otherwise.

Note 1: OpenMP 5.1 added additional (target) memory routines for
C/C++ and Fortran; those are not included here.

 Note 2 ---
'omp_lib.h' is included in as declaration-construct in the
specification-part of a file (i.e. possibly after an implicit statement);
hence, it cannot contain a use-stmt.  Additionally, it needs to support
both free- and fixed-form source files.
While thought to be compatible with Fortran 77, nothing actually requires
that only Fortran 77 code is used and gfortran only supports -std=f95 or
higher.

Hence, (rightly!) assuming that only gfortran compiles that file,
Fortran 90 + 95 features can be used; the code already uses TYPE.

However, the the attached patch also BIND(C) + IMPORT, which are
Fortran 2003 features, effectively preventing the compilation with
-std=f95.

My impression is that old code (Fortran IV, 66, 77, older 90/95) code
tends to use vendor extension (preventing the compilation with -std=f*)
and users do not care about setting -std=f* flags.
Or the code is old but still maintained. But in that case, new features
of Fortran 2003 (and later) intentionally and/or accidentally get used,
already preventing the compilation with -std=f95.

Thus, I think it is okay to use a Fortran 2003 feature.
 End of Note 2 ---

The testcases are those for C/C++ converted to Fortran.
Comments? OK?

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
Fortran/OpenMP: Add memory routines existing for C/C++

This patch adds the Fortran interface for omp_alloc/omp_free
and the omp_target_* memory routines, which were added in
OpenMP 5.0 for C/C++ but only OpenMP 5.1 added them for Fortran.

Those functions use BIND(C), i.e. on the libgomp side, the same
interface as for C/C++ is used.

Note: By using BIND(C) in omp_lib.h, files including this file
no longer compiler with -std=f95 but require at least -std=f2003.

libgomp/ChangeLog:

	* omp_lib.f90.in (omp_alloc, omp_free, omp_target_alloc,
	omp_target_free. omp_target_is_present, omp_target_memcpy,
	omp_target_memcpy_rect, omp_target_associate_ptr,
	omp_target_disassociate_ptr): Add interface.
	* omp_lib.h.in (omp_alloc, omp_free, omp_target_alloc,
	omp_target_free. omp_target_is_present, omp_target_memcpy,
	omp_target_memcpy_rect, omp_target_associate_ptr,
	omp_target_disassociate_ptr): Add interface.
	* testsuite/libgomp.fortran/alloc-1.F90: Remove local
	interface block for omp_alloc + omp_free.
	* testsuite/libgomp.fortran/alloc-4.f90: Likewise.
	* testsuite/libgomp.fortran/refcount-1.f90: New test.
	* testsuite/libgomp.fortran/target-12.f90: New test.

 libgomp/omp_lib.f90.in   |  94 +++
 libgomp/omp_lib.h.in |  97 +++
 libgomp/testsuite/libgomp.fortran/alloc-1.F90|  16 ---
 libgomp/testsuite/libgomp.fortran/alloc-4.f90|  16 ---
 libgomp/testsuite/libgomp.fortran/refcount-1.f90 |  61 ++
 libgomp/testsuite/libgomp.fortran/target-12.f90  | 147 +++
 6 files changed, 399 insertions(+), 32 deletions(-)

diff --git a/libgomp/omp_lib.f90.in b/libgomp/omp_lib.f90.in
index 6394e65bbf7..a36a5626123 100644
--- a/libgomp/omp_lib.f90.in
+++ b/libgomp/omp_lib.f90.in
@@ -670,6 +670,100 @@
   end subroutine omp_display_env_8
 end interface
 
+interface
+  function omp_alloc (size, allocator) bind(c)
+use, intrinsic :: iso_c_binding, only : c_ptr, c_size_t
+import :: omp_allocator_handle_kind
+type(c_ptr) :: omp_alloc
+integer(c_size_t), value :: size
+integer(omp_allocator_handle_kind), value :: allocator
+  end function omp_alloc
+end interface
+
+interface
+  subroutine omp_free(ptr, allocator) bind(c)
+use, intrinsic :: iso_c_binding, only : c_ptr
+import :: omp_allocator_handle_kind
+type(c_ptr), value :: ptr
+integer(omp_allocator_handle_kind), value :: allocator
+  end subroutine
+end interface
+
+interface
+  function omp_target_alloc (size, device_num) bind(c)
+use, intrinsic :: iso_c_binding, only : c_ptr, c_size_t, c_int
+type(c_ptr) :: omp_target_alloc
+integer(c_size_t), value :: size
+integer(c_int), value :: device_num
+  end function omp_target_alloc
+end interface
+
+interface
+  subroutine omp_target_free (device_ptr, device_num) bind(c)
+use, 

Re: [Patch] Fortran/OpenMP: Add memory routines existing for C/C++

2021-08-18 Thread Jakub Jelinek via Fortran
On Wed, Aug 18, 2021 at 11:00:47AM +0200, Tobias Burnus wrote:
>  Note 2 ---
> 'omp_lib.h' is included in as declaration-construct in the
> specification-part of a file (i.e. possibly after an implicit statement);
> hence, it cannot contain a use-stmt.  Additionally, it needs to support
> both free- and fixed-form source files.
> While thought to be compatible with Fortran 77, nothing actually requires
> that only Fortran 77 code is used and gfortran only supports -std=f95 or
> higher.
> 
> Hence, (rightly!) assuming that only gfortran compiles that file,
> Fortran 90 + 95 features can be used; the code already uses TYPE.
> 
> However, the the attached patch also BIND(C) + IMPORT, which are
> Fortran 2003 features, effectively preventing the compilation with
> -std=f95.
> 
> My impression is that old code (Fortran IV, 66, 77, older 90/95) code
> tends to use vendor extension (preventing the compilation with -std=f*)
> and users do not care about setting -std=f* flags.
> Or the code is old but still maintained. But in that case, new features
> of Fortran 2003 (and later) intentionally and/or accidentally get used,
> already preventing the compilation with -std=f95.
> 
> Thus, I think it is okay to use a Fortran 2003 feature.

Perhaps we could add some new !GCC$ extension that would temporarily
turn off errors about new language features (or temporarily switch language
version), slightly similar to
#pragma GCC push_options
#pragma GCC ...
...
#pragma GCC pop_options
except that in C/C++ one can't change the language version (but on the other
side we have __extension__ and system headers surpressing some diagnostics).

> libgomp/ChangeLog:
> 
>   * omp_lib.f90.in (omp_alloc, omp_free, omp_target_alloc,
>   omp_target_free. omp_target_is_present, omp_target_memcpy,
>   omp_target_memcpy_rect, omp_target_associate_ptr,
>   omp_target_disassociate_ptr): Add interface.
>   * omp_lib.h.in (omp_alloc, omp_free, omp_target_alloc,
>   omp_target_free. omp_target_is_present, omp_target_memcpy,
>   omp_target_memcpy_rect, omp_target_associate_ptr,
>   omp_target_disassociate_ptr): Add interface.
>   * testsuite/libgomp.fortran/alloc-1.F90: Remove local
>   interface block for omp_alloc + omp_free.
>   * testsuite/libgomp.fortran/alloc-4.f90: Likewise.
>   * testsuite/libgomp.fortran/refcount-1.f90: New test.
>   * testsuite/libgomp.fortran/target-12.f90: New test.
> 
>  libgomp/omp_lib.f90.in   |  94 +++
>  libgomp/omp_lib.h.in |  97 +++
>  libgomp/testsuite/libgomp.fortran/alloc-1.F90|  16 ---
>  libgomp/testsuite/libgomp.fortran/alloc-4.f90|  16 ---
>  libgomp/testsuite/libgomp.fortran/refcount-1.f90 |  61 ++
>  libgomp/testsuite/libgomp.fortran/target-12.f90  | 147 
> +++
>  6 files changed, 399 insertions(+), 32 deletions(-)

Ok.

Jakub



Re: [PATCH] PR fortran/100950 - ICE in output_constructor_regular_field, at varasm.c:5514

2021-08-18 Thread Tobias Burnus

Hi Harald,

sorry for the belated review.

On 03.08.21 23:17, Harald Anlauf wrote:

allocate(x%str2, source="abd")
if (len (x%str)) /= 1) ...
if (len (x%str2(1:2) /= 2) ...
etc.

Namely: Search the last_ref = expr->ref->next->next ...?
and then check that lastref?

The mentioned search is now implemented.

Note, however, that gfc_simplify_len still won't handle neither
deferred strings nor their substrings.

I think there is nothing to simplify at compile time here.


Obviously, nonsubstrings cannot be simplified but I do not
see why  len(str(1:2))  cannot or should not be simplified.

(Not that I regard substring length inquiries as that common.)

Regarding:


Otherwise
there would be a conflict/inconsistency with type parameter inquiry,
see F2018:9.4.5(2):

"A deferred type parameter of a pointer that is not associated or
of an unallocated allocatable variable shall not be inquired about."


That's a requirement for the user not to do:
  character(len=:), allocatable :: str
  n = len(str)  ! unallocated 'str'

which makes sense as 'len(str)' is not meaningful in this case and
the compiler might even access invalid memory in this case
and definitely undefined memory.

However, there is no reason why the user cannot do:
  if (allocated(str)) then
n = len(str)
m = len(str(5:8))
  end if
and why the compiler cannot replace the latter by 'm = 4'.

But, IMHO, the latter remark does _not_ imply that we
shall/must/have to accept code like:

if (allocated(str)) then
  block
 integer, parameter :: n = len(str(:5))
  end block
endif



+static bool
+substring_has_constant_len (gfc_expr *e)
+{
+  gfc_ref *ref;
+  HOST_WIDE_INT istart, iend, length;
+  bool equal_length = false;
+
+  if (e->ts.type != BT_CHARACTER || e->ts.deferred)
+return false;

cf. above.

+
+  for (ref = e->ref; ref; ref = ref->next)
+if (ref->type != REF_COMPONENT)
+  break;
+
+  if (!ref
+  || ref->type != REF_SUBSTRING
+  || !ref->u.ss.start


With the caveat from above that len() is rather special,
there is no real reason why:  str_array(:)(4:5)  cannot be handled.
(→ len = 2).

[I do note that "len(str(:5))" appears in your examples, hence,
I assume that ss.start is set in that case to '1'.]


The updated patch regtests fine.  OK?

Looks good to me except for the caveats.

In particular:

 * * *

I think at least the array case should be handled.
On current mainline (i.e. without your patch),
I get (-fdump-tree-original)

  x = 5;  // Wrong - should be 1
  y = 1;  // OK

for

character(len=5) :: str2(4)
type t
   character(len=5) :: str(4)
end type t
type(t) :: var
integer :: x, y
x = len(var%str(:)(1:1))
y = len(str2(:)(1:1))
end

I don't know what's the result with your patch - but if
it is 'x = 5', it must be fixed.

 * * *

And while the following works

x = var%str(:)%len  ! ok, yields 5
y = str2(:)%len ! ok, yields 5

the following is wrongly rejected:

x = var%str(:)(1:1)%len  ! Bogus: 'Invalid character in name'
y = str2(:)(1:1)%len ! Bogus: 'Invalid character in name'

(likewise with '%kind')

(As "SUBSTRING % LEN", it also appears in the '16.9.99 INDEX',
but '9.4.5 Type parameter inquiry's 'R916 type-param-inquiry'
is the official reference.)

If you don't want to spend time on this subpart - you could
fill a PR.

 * * *

For deferred length, I have no strong opinion; in
any case, the upper substring bound > stringlen check
cannot be done in that case (at compile time). I think
I slightly prefer doing the optimization – but as is
is a special case and has some caveats (must be allocated,
upper bound check not possible, ...) I also see reasons
not to do it. Hence, it also can remain as in your patch.

Thanks,

Tobias


Fortran - simplify length of substring with constant bounds

gcc/fortran/ChangeLog:

  PR fortran/100950
  * simplify.c (substring_has_constant_len): New.
  (gfc_simplify_len): Handle case of substrings with constant
  bounds.

gcc/testsuite/ChangeLog:

  PR fortran/100950
  * gfortran.dg/pr100950.f90: New test.


-
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: [committed] openmp: Add nothing directive support)

2021-08-18 Thread Tobias Burnus

On 18.08.21 11:18, Jakub Jelinek wrote:


As has been clarified, it is intentional that nothing directive is accepted
in substatements of selection and looping statements and after labels and
is handled as if the directive just isn't there ...


And here is the Fortran version; as ST_NONE is used, it is also just ignored 
like a comment.

However, there is a pure-procedure check, which triggers. I think that's
fine and a spec issue. (Tracked on the OpenMP side as Issue 2913.)

I think otherwise the patch is boring - as boring as 'omp nothing' itself
(outside its use in metadirectives).

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
Fortran: Add OpenMP's nothing directive support

Fortran version of commit 5079b7781a2c506dcdfb241347d74c7891268225

gcc/fortran/ChangeLog:

	* match.h (gfc_match_omp_nothing): New.
	* openmp.c (gfc_match_omp_nothing): New.
	* parse.c (decode_omp_directive): Match 'nothing' directive.

gcc/testsuite/ChangeLog:

	* gfortran.dg/nothing-1.f90: New test.
	* gfortran.dg/nothing-2.f90: New test.

 gcc/fortran/match.h |  1 +
 gcc/fortran/openmp.c| 11 +++
 gcc/fortran/parse.c |  3 +++
 gcc/testsuite/gfortran.dg/nothing-1.f90 | 26 ++
 gcc/testsuite/gfortran.dg/nothing-2.f90 |  7 +++
 5 files changed, 48 insertions(+)

diff --git a/gcc/fortran/match.h b/gcc/fortran/match.h
index aac16a8d3d0..5127b4b8ea3 100644
--- a/gcc/fortran/match.h
+++ b/gcc/fortran/match.h
@@ -175,6 +175,7 @@ match gfc_match_omp_masked_taskloop_simd (void);
 match gfc_match_omp_master (void);
 match gfc_match_omp_master_taskloop (void);
 match gfc_match_omp_master_taskloop_simd (void);
+match gfc_match_omp_nothing (void);
 match gfc_match_omp_ordered (void);
 match gfc_match_omp_ordered_depend (void);
 match gfc_match_omp_parallel (void);
diff --git a/gcc/fortran/openmp.c b/gcc/fortran/openmp.c
index 9675b658409..fd219dc9c4d 100644
--- a/gcc/fortran/openmp.c
+++ b/gcc/fortran/openmp.c
@@ -4797,6 +4797,17 @@ gfc_match_omp_ordered (void)
   return match_omp (EXEC_OMP_ORDERED, OMP_ORDERED_CLAUSES);
 }
 
+match
+gfc_match_omp_nothing (void)
+{
+  if (gfc_match_omp_eos () != MATCH_YES)
+{
+  gfc_error ("Unexpected junk after $OMP NOTHING statement at %C");
+  return MATCH_ERROR;
+}
+  /* Will use ST_NONE; therefore, no EXEC_OMP_ is needed.  */
+  return MATCH_YES;
+}
 
 match
 gfc_match_omp_ordered_depend (void)
diff --git a/gcc/fortran/parse.c b/gcc/fortran/parse.c
index 24cc9bfb9f1..d004732677c 100644
--- a/gcc/fortran/parse.c
+++ b/gcc/fortran/parse.c
@@ -1005,6 +1005,9 @@ decode_omp_directive (void)
 	  ST_OMP_MASTER_TASKLOOP);
   matcho ("master", gfc_match_omp_master, ST_OMP_MASTER);
   break;
+case 'n':
+  matcho ("nothing", gfc_match_omp_nothing, ST_NONE);
+  break;
 case 'l':
   matcho ("loop", gfc_match_omp_loop, ST_OMP_LOOP);
   break;
diff --git a/gcc/testsuite/gfortran.dg/nothing-1.f90 b/gcc/testsuite/gfortran.dg/nothing-1.f90
new file mode 100644
index 000..2bc3688e2ac
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/nothing-1.f90
@@ -0,0 +1,26 @@
+module m
+  implicit none (type, external)
+  !$omp nothing
+
+  type t
+!$omp nothing
+integer s
+  end type
+
+contains
+
+integer function foo (i)
+  integer :: i
+
+  !$omp nothing
+  if (.false.) &
+& &!$omp nothing
+i = i + 1
+
+  if (.false.) &
+&   & !$omp nothing
+then
+  end if
+  foo = i
+end
+end module
diff --git a/gcc/testsuite/gfortran.dg/nothing-2.f90 b/gcc/testsuite/gfortran.dg/nothing-2.f90
new file mode 100644
index 000..74a4a5a22b0
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/nothing-2.f90
@@ -0,0 +1,7 @@
+pure subroutine foo
+  !$omp nothing  ! { dg-error "OpenMP directives other than SIMD or DECLARE TARGET at .1. may not appear in PURE procedures" }
+end subroutine
+
+subroutine bar
+  !$omp nothing foo  ! { dg-error "Unexpected junk after $OMP NOTHING statement" }
+end


Re: (Re: [committed] openmp: Add nothing directive support)

2021-08-18 Thread Jakub Jelinek via Fortran
On Wed, Aug 18, 2021 at 01:10:12PM +0200, Tobias Burnus wrote:
> I think otherwise the patch is boring - as boring as 'omp nothing' itself
> (outside its use in metadirectives).

Yeah, I think nobody sane will use it for anything but metadirective
except in compiler testsuites.

> Fortran: Add OpenMP's nothing directive support
> 
> Fortran version of commit 5079b7781a2c506dcdfb241347d74c7891268225
> 
> gcc/fortran/ChangeLog:
> 
>   * match.h (gfc_match_omp_nothing): New.
>   * openmp.c (gfc_match_omp_nothing): New.
>   * parse.c (decode_omp_directive): Match 'nothing' directive.
> 
> gcc/testsuite/ChangeLog:
> 
>   * gfortran.dg/nothing-1.f90: New test.
>   * gfortran.dg/nothing-2.f90: New test.

LGTM, thanks.

> +  !$omp nothing
> +  if (.false.) &
> +& &!$omp nothing
> +i = i + 1
> +
> +  if (.false.) &
> +&   & !$omp nothing
> +then
> +  end if

I'm actually not sure if the above really is valid (well, treated as OpenMP
directive, rather than just an arbitrary comment), e.g. 5.0 2.2.2 says:
The sentinel can appear in any column but must be preceded only by white space;
which is not the case above.  And I think that is the reason we don't have a
Fortran counterpart to the stand-alone and declarative directive
restrictions C/C++ has that they can't appear in certain contexts.

So, do we actually parse
  if (.true.) &
& & !$omp barrier
as if with barrier construct in it?

Jakub



Re: (Re: [committed] openmp: Add nothing directive support)

2021-08-18 Thread Tobias Burnus

On 18.08.21 13:18, Jakub Jelinek wrote:


gcc/testsuite/ChangeLog:
 * gfortran.dg/nothing-1.f90: New test.
 * gfortran.dg/nothing-2.f90: New test.


While testing manually with -fopenmp, I did manage to place it for the
testsuite run outside the 'gomp/' subdirectory. – Now fixed → attachment.

For completeness (as already discussed on IRC):


+  !$omp nothing
+  if (.false.) &
+& &!$omp nothing
+i = i + 1


This indeed does not trigger the sentinel (as also discussed on IRC and as 
comment in the test).
While
  if (x) &
!$omp nothing
gives an error but it is not obviously invalid. → That's now OpenMP spec bug 
#2914.

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
commit f0fca213bc52644ba896da622b35842a6157bd98
Author: Tobias Burnus 
Date:   Wed Aug 18 21:47:04 2021 +0200

Fortran: Add OpenMP's nothing directive support (con't)

Fix directory to enable -fopenmp processing.

gcc/testsuite/
PR testsuite/101963
* gfortran.dg/nothing-1.f90: Moved to ...
* gfortran.dg/gomp/nothing-1.f90: ... here.
* gfortran.dg/nothing-2.f90: Moved to ...
* gfortran.dg/gomp/nothing-2.f90: ... here;
avoid $ issue in $OMP in dg-error.
---
 gcc/testsuite/gfortran.dg/{ => gomp}/nothing-1.f90 | 0
 gcc/testsuite/gfortran.dg/{ => gomp}/nothing-2.f90 | 2 +-
 2 files changed, 1 insertion(+), 1 deletion(-)

diff --git a/gcc/testsuite/gfortran.dg/nothing-1.f90 b/gcc/testsuite/gfortran.dg/gomp/nothing-1.f90
similarity index 100%
rename from gcc/testsuite/gfortran.dg/nothing-1.f90
rename to gcc/testsuite/gfortran.dg/gomp/nothing-1.f90
diff --git a/gcc/testsuite/gfortran.dg/nothing-2.f90 b/gcc/testsuite/gfortran.dg/gomp/nothing-2.f90
similarity index 75%
rename from gcc/testsuite/gfortran.dg/nothing-2.f90
rename to gcc/testsuite/gfortran.dg/gomp/nothing-2.f90
index 74a4a5a22b0..554d4ef99ca 100644
--- a/gcc/testsuite/gfortran.dg/nothing-2.f90
+++ b/gcc/testsuite/gfortran.dg/gomp/nothing-2.f90
@@ -3,5 +3,5 @@ pure subroutine foo
 end subroutine
 
 subroutine bar
-  !$omp nothing foo  ! { dg-error "Unexpected junk after $OMP NOTHING statement" }
+  !$omp nothing foo  ! { dg-error "Unexpected junk after .OMP NOTHING statement" }
 end


F2018 C949

2021-08-18 Thread Steve Kargl via Fortran
For those that might care, I draw your attention to

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=101967

Good opportunity for a lurker to step forward and
become a gfortran committer.  Otherwise, this patch
will fester in bugzilla with the dozen or so other
patches I've attached to PRs over the lastr few
years.

-- 
Steve


Re: [PATCH] PR fortran/100950 - ICE in output_constructor_regular_field, at varasm.c:5514

2021-08-18 Thread Harald Anlauf via Fortran
Hi Tobias,

> Gesendet: Mittwoch, 18. August 2021 um 12:22 Uhr
> Von: "Tobias Burnus" 

> > Note, however, that gfc_simplify_len still won't handle neither
> > deferred strings nor their substrings.
> >
> > I think there is nothing to simplify at compile time here.
> 
> Obviously, nonsubstrings cannot be simplified but I do not
> see why  len(str(1:2))  cannot or should not be simplified.
> 
> (Not that I regard substring length inquiries as that common.)

well, here's an example that Intel rejects:

  type u
 character(8)  :: s(4)
 character(:), allocatable :: str
  end type u
  type(u) :: q
  integer, parameter :: k2 = len (q% s(:)(3:4)) ! OK
  integer, parameter :: k3 = len (q% str (3:4)) ! Rejected by Intel
  print *, k2
  if (k2 /= 2) stop 2
  print *, k3
  if (k3 /= 2) stop 3
end

pr100950-ww.f90(7): error #6814: When using this inquiry function, the length 
of this object cannot be evaluated to a constant.   [LEN]
  integer, parameter :: k3 = len (q% str (3:4)) ! Rejected by Intel
-^
pr100950-ww.f90(7): error #7169: Bad initialization expression.   [LEN]
  integer, parameter :: k3 = len (q% str (3:4)) ! Rejected by Intel
-^

Of course we could accept it regardless what others do.
I have therefore removed the check for deferred length
in the attached patch (but read on).

> However, there is no reason why the user cannot do:
>if (allocated(str)) then
>  n = len(str)
>  m = len(str(5:8))
>end if
> and why the compiler cannot replace the latter by 'm = 4'.

Maybe you can enlighten me here.  I thought one of the
purposes of gfc_simplify_len is to evaluate constant
expressions.  Of course the length is constant, provided
bounds are respected.  Otherwise the result is, well, ...

(It will then eveluate at runtime, which I thought was fine).

> But, IMHO, the latter remark does _not_ imply that we
> shall/must/have to accept code like:
> 
> if (allocated(str)) then
>block
>   integer, parameter :: n = len(str(:5))
>end block
> endif

So shall we not simplify here (and thus reject it)?
This is important!  Or silently simplify and accept it?

> With the caveat from above that len() is rather special,
> there is no real reason why:  str_array(:)(4:5)  cannot be handled.
> (→ len = 2).

Good point.  This is fixed in the revised patch and tested for.

> > The updated patch regtests fine.  OK?
> Looks good to me except for the caveats.

Regtested again.

>   * * *
> 
> And while the following works
> 
> x = var%str(:)%len  ! ok, yields 5
> y = str2(:)%len ! ok, yields 5
> 
> the following is wrongly rejected:
> 
> x = var%str(:)(1:1)%len  ! Bogus: 'Invalid character in name'
> y = str2(:)(1:1)%len ! Bogus: 'Invalid character in name'
> 
> (likewise with '%kind')
> 
> (As "SUBSTRING % LEN", it also appears in the '16.9.99 INDEX',
> but '9.4.5 Type parameter inquiry's 'R916 type-param-inquiry'
> is the official reference.)
> 
> If you don't want to spend time on this subpart - you could
> fill a PR.

Well, there's already

 https://gcc.gnu.org/bugzilla/show_bug.cgi?id=101735

which is a much better suited place for discussion.

>   * * *
> 
> For deferred length, I have no strong opinion; in
> any case, the upper substring bound > stringlen check
> cannot be done in that case (at compile time). I think
> I slightly prefer doing the optimization – but as is
> is a special case and has some caveats (must be allocated,
> upper bound check not possible, ...) I also see reasons
> not to do it. Hence, it also can remain as in your patch.

Actually, this is now an important point.  If we really want
to allow to handle substrings of deferred length strings
in constant expressions, the new patch would be fine,
otherwise I would have to reintroduce the hunk

+  if (e->ts.deferred)
+return NULL;

and adjust the testcase.

Your choice.  See above.

Of course there may be more corner cases which I did not
think of...

Thanks,
Harald
diff --git a/gcc/fortran/simplify.c b/gcc/fortran/simplify.c
index c27b47aa98f..cf0a4387788 100644
--- a/gcc/fortran/simplify.c
+++ b/gcc/fortran/simplify.c
@@ -4512,6 +4512,69 @@ gfc_simplify_leadz (gfc_expr *e)
 }


+/* Check for constant length of a substring.  */
+
+static bool
+substring_has_constant_len (gfc_expr *e)
+{
+  gfc_ref *ref;
+  HOST_WIDE_INT istart, iend, length;
+  bool equal_length = false;
+
+  if (e->ts.type != BT_CHARACTER || e->ts.deferred)
+return false;
+
+  for (ref = e->ref; ref; ref = ref->next)
+if (ref->type != REF_COMPONENT && ref->type != REF_ARRAY)
+  break;
+
+  if (!ref
+  || ref->type != REF_SUBSTRING
+  || !ref->u.ss.start
+  || ref->u.ss.start->expr_type != EXPR_CONSTANT
+  || !ref->u.ss.end
+  || ref->u.ss.end->expr_type != EXPR_CONSTANT
+  || !ref->u.ss.length
+  || !ref->u.ss.length->length
+  || ref->u.ss.length->length->expr_type != EXPR_CONSTANT)
+return false;
+
+  /* Basic checks on substrin

[PATCH, Fortran] Revert to non-multilib-specific ISO_Fortran_binding.h

2021-08-18 Thread Sandra Loosemore

This is a follow-up to commit fef67987cf502fe322e92ddce22eea7ac46b4d75:

https://gcc.gnu.org/git/?p=gcc.git;a=commit;h=fef67987cf502fe322e92ddce22eea7ac46b4d75

I realized last week that having multilib-specific versions of 
ISO_Fortran_binding.h (generated by running the compiler to ask what 
kinds it supports) was still broken outside of the test support; the 
directory where it's being installed isn't on GCC's normal search path. 
It seemed to me that it was better to try to find some other solution 
for this problem than to venture down what appears to be a rat hole.


I've come up with this patch to return to a single ISO_Fortran_binding.h 
file that uses preprocessor magic to identify the Fortran kind 
corresponding to the standard C long double type and the GCC extension 
types __float128 and int128_t.  I haven't attempted to undo the 
follow-up patches that fixed in-tree testing; the static .h file is 
still copied to the build directory, and it can still be referenced with 
<> syntax during testing.


Any complaints about either the overall strategy here, or the logic to 
infer the C type -> kind mapping?  Or OK to commit?


-Sandra
commit bf52fcb46ee62ff2f7c552397d58914b934b130f
Author: Sandra Loosemore 
Date:   Fri Aug 13 17:46:19 2021 -0700

Fortran: Revert to non-multilib-specific ISO_Fortran_binding.h

Commit fef67987cf502fe322e92ddce22eea7ac46b4d75 changed the
libgfortran build process to generate multilib-specific versions of
ISO_Fortran_binding.h from a template, by running gfortran to identify
the values of the Fortran kind constants C_LONG_DOUBLE, C_FLOAT128,
and C_INT128_T.  This caused multiple problems with search paths, both
for build-tree testing and installed-tree use, not all of which have
been fixed.

This patch reverts to a non-multilib-specific .h file that uses GCC's
predefined preprocessor symbols to detect the supported types and map
them to kind values in the same way as the Fortran front end.

2021-08-18  Sandra Loosemore  

libgfortran/
	* ISO_Fortran_binding-1-tmpl.h: Deleted.
	* ISO_Fortran_binding-2-tmpl.h: Deleted.
	* ISO_Fortran_binding-3-tmpl.h: Deleted.
	* ISO_Fortran_binding.h: New file to replace the above.
	* Makefile.am (gfor_cdir): Remove MULTISUBDIR.
	(ISO_Fortran_binding.h): Simplify to just copy the file.
	* Makefile.in: Regenerated.
	* mk-kinds-h.sh: Revert pieces no longer needed for
	ISO_Fortran_binding.h.

diff --git a/libgfortran/ISO_Fortran_binding-1-tmpl.h b/libgfortran/ISO_Fortran_binding-1-tmpl.h
deleted file mode 100644
index 8852c99..000
--- a/libgfortran/ISO_Fortran_binding-1-tmpl.h
+++ /dev/null
@@ -1,196 +0,0 @@
-/* Declarations for ISO Fortran binding.
-   Copyright (C) 2018-2021 Free Software Foundation, Inc.
-   Contributed by Daniel Celis Garza  
-
-This file is part of the GNU Fortran runtime library (libgfortran).
-
-Libgfortran is free software; you can redistribute it and/or modify
-it under the terms of the GNU General Public License as published by
-the Free Software Foundation; either version 3, or (at your option)
-any later version.
-
-Libgfortran is distributed in the hope that it will be useful,
-but WITHOUT ANY WARRANTY; without even the implied warranty of
-MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
-GNU General Public License for more details.
-
-Under Section 7 of GPL version 3, you are granted additional
-permissions described in the GCC Runtime Library Exception, version
-3.1, as published by the Free Software Foundation.
-
-You should have received a copy of the GNU General Public License and
-a copy of the GCC Runtime Library Exception along with this program;
-see the files COPYING3 and COPYING.RUNTIME respectively.  If not, see
-.  */
-
-#ifndef ISO_FORTRAN_BINDING_H
-#define ISO_FORTRAN_BINDING_H
-
-#ifdef __cplusplus
-extern "C" {
-#endif
-
-#include   /* Standard ptrdiff_t tand size_t. */
-#include   /* Integer types. */
-
-/* Constants, defined as macros. */
-#define CFI_VERSION 1
-#define CFI_MAX_RANK 15
-
-/* Attributes. */
-#define CFI_attribute_pointer 0
-#define CFI_attribute_allocatable 1
-#define CFI_attribute_other 2
-
-/* Error codes.
-   Note that CFI_FAILURE and CFI_INVALID_STRIDE are specific to GCC
-   and not part of the Fortran standard   */
-#define CFI_SUCCESS 0
-#define CFI_FAILURE 1
-#define CFI_ERROR_BASE_ADDR_NULL 2
-#define CFI_ERROR_BASE_ADDR_NOT_NULL 3
-#define CFI_INVALID_ELEM_LEN 4
-#define CFI_INVALID_RANK 5
-#define CFI_INVALID_TYPE 6
-#define CFI_INVALID_ATTRIBUTE 7
-#define CFI_INVALID_EXTENT 8
-#define CFI_INVALID_STRIDE 9
-#define CFI_INVALID_DESCRIPTOR 10
-#define CFI_ERROR_MEM_ALLOCATION 11
-#define CFI_ERROR_OUT_OF_BOUNDS 12
-
-/* CFI type definitions. */
-typedef ptrdiff_t CFI_index_t;
-typedef int8_t CFI_rank_t;
-typedef int8_t CFI_attribute_t;
-typedef int16_t CFI_type_t;
-
-/* CFI_dim_t. */
-typedef struct CFI_dim_t
-  {

[patch, libgfortran] Further fixes for GFC/CFI descriptor conversions

2021-08-18 Thread Sandra Loosemore
This patch addresses several bugs in converting from GFC to CFI 
descriptors and vice versa.  It incorporates bits and pieces of an 
earlier patch from José


https://gcc.gnu.org/pipermail/fortran/2021-June/056154.html

that is now quite bit-rotten.

The root of all the problems addressed here is that GFC descriptors 
contain incomplete information; in particular, they only encode the size 
of the data type and not its kind.  Changing the GFC descriptors to 
include more information would be an ABI change for pure Fortran code 
and not just interoperability, so I've been trying to avoid that.  OTOH, 
making at least some things work with the existing ABI that formerly 
didn't seems like a reasonable thing to do.  Alternatively, I suppose we 
could throw up our hands and give an internal error when encountering 
the ambiguous cases and focus on designing the ABI changes necessary to 
solve the problems for real.


In addition to José's test cases included with this patch, I've added 
some additional test coverage to my TS29113 testsuite which I will be 
reposting soon.


-Sandra

commit bce396d541d65029e2897e59c6e0baeed090e340
Author: Sandra Loosemore 
Date:   Wed Aug 18 07:22:03 2021 -0700

libgfortran: Further fixes for GFC/CFI descriptor conversions.

This patch is for:
PR100907 - Bind(c): failure handling wide character
PR100911 - Bind(c): failure handling C_PTR
PR100914 - Bind(c): errors handling complex
PR100915 - Bind(c): failure handling C_FUNPTR
PR100917 - Bind(c): errors handling long double real

All of these problems are related to the GFC descriptors constructed
by the Fortran front end containing ambigous or incomplete
information.  This patch does not attempt to change the GFC data
structure or the front end, and only makes the runtime interpret it in
more reasonable ways.  It's not a complete fix for any of the listed
issues.

The Fortran front end does not distinguish between C_PTR and
C_FUNPTR, mapping both onto BT_VOID.  That is what this patch does also.

The other bugs are related to GFC descriptors only containing elem_len
and not kind.  For complex types, the elem_len needs to be divided by
2 and then mapped onto a real kind.  On x86 targets, the kind
corresponding to C long double is different than its elem_len; since
we cannot accurately disambiguate between a 16-byte kind 10 long
double from __float128, this patch arbitrarily prefers to interpret that as
the standard long double type rather than the GNU extension.

Similarly, for character types, the GFC descriptor cannot distinguish
between character(kind=c_char, len=4) and character(kind=ucs4, len=1).
But since the front end currently rejects anything other than len=1
(PR92482) this patch uses the latter interpretation.

2021-08-18  Sandra Loosemore  
	José Rui Faustino de Sousa  

gcc/testsuite/
	PR fortran/100911
	PR fortran/100915
	PR fortran/100916
	* gfortran.dg/PR100911.c: New file.
	* gfortran.dg/PR100911.f90: New file.
	* gfortran.dg/PR100914.c: New file.
	* gfortran.dg/PR100914.f90: New file.
	* gfortran.dg/PR100915.c: New file.
	* gfortran.dg/PR100915.f90: New file.

libgfortran/
	PR fortran/100907
	PR fortran/100911
	PR fortran/100914
	PR fortran/100915
	PR fortran/100917
	* ISO_Fortran_binding.h (CFI_type_cfunptr): Make equivalent to
	CFI_type_cptr.
	* runtime/ISO_Fortran_binding.c (cfi_desc_to_gfc_desc): Fix
	handling of CFI_type_cptr and CFI_type_cfunptr.  Additional error
	checking and code cleanup.
	(gfc_desc_to_cfi_desc): Likewise.  Also correct kind mapping
	for character, complex, and long double types.

diff --git a/gcc/testsuite/gfortran.dg/PR100911.c b/gcc/testsuite/gfortran.dg/PR100911.c
new file mode 100644
index 000..f3345ad
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/PR100911.c
@@ -0,0 +1,82 @@
+/* Test the fix for PR100911 */
+
+#include 
+#include 
+#include 
+
+#include 
+
+#define _CFI_type_mask 0xFF
+#define _CFI_type_kind_shift 8
+
+#define _CFI_decode_type(NAME) (signed char)((NAME) & CFI_type_mask)
+#define _CFI_decode_kind(NAME) (signed char)(((NAME) >> CFI_type_kind_shift) & CFI_type_mask)
+
+#define _CFI_encode_type(TYPE, KIND) (int16_t)\
+KIND) & CFI_type_mask) << CFI_type_kind_shift)\
+ | ((TYPE) & CFI_type_mask))
+
+#define N 11
+#define M 7
+
+#define CFI_type_Cptr CFI_type_cptr
+
+typedef int* c_ptr;
+
+bool c_vrfy_cptr (const CFI_cdesc_t *restrict);
+ 
+void check_tk (const CFI_cdesc_t*restrict, const CFI_type_t, const signed char, const size_t, const size_t);
+
+bool
+c_vrfy_cptr (const CFI_cdesc_t *restrict auxp)
+{
+  CFI_index_t i, lb, ub, ex;
+  size_t sz;
+  c_ptr *ip = NULL;
+
+  assert (auxp);
+  assert (auxp->base_addr);
+  assert (auxp->elem_len>0);
+  lb = auxp->dim[0].lower_bound;
+  ex = auxp->dim[0].extent;
+  assert (ex==11);
+

Re: F2018 C937

2021-08-18 Thread Arjen Markus via Fortran
Hi Steve,

I am willing to take up this challenge ;), as well as the patch for C949.
It would be my next attempt to get acquainted with the source code (a first
step hopefully to actively contribute).

Regards,

Arjen

Op di 17 aug. 2021 om 21:02 schreef Steve Kargl via Fortran <
fortran@gcc.gnu.org>:

> For those that might care, I draw your attention to
>
> https://gcc.gnu.org/bugzilla/show_bug.cgi?id=101951
>
> Good opportunity for a lurker to step forward and
> become a gfortran committer.  Otherwise, this patch
> will fester in bugzilla the dozen or so other patches
> I've attached to PRs.
>
> --
> Steve
>