[Bug fortran/99840] [9/10/11 Regression] ICE in gfc_simplify_matmul, at fortran/simplify.c:4777

2021-03-31 Thread anlauf at gmx dot de via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=99840

--- Comment #7 from Harald Anlauf  ---
> The simple patch in comment #2 also works.

I know.  But it only covers the issue in gfc_simplify_transpose.

[Bug fortran/95053] [11.0 regression] ICE in f951: gfc_divide()

2020-05-11 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=95053

Harald Anlauf  changed:

   What|Removed |Added

 CC||anlauf at gmx dot de

--- Comment #2 from Harald Anlauf  ---
(In reply to Jürgen Reuter from comment #1)
> I shrank the example even further:
>   SUBROUTINE MNSTIN
>  132  FORMAT (' UNIT',I3,' ALREADY OPENED WITH NAME:',A/
>  +' NEW NAME IGNORED:',A)
>   RETURN
>   END
> 
> It looks like it is the combination of integer format with this special form
> of character line continuation.

Indeed, I found an even shorter reproducer:

  SUBROUTINE MNSTIN ()
* Adding a comma before or after the "/" avoids the ICE
 132  FORMAT (A/
 + ' B')
  END

I am responsible for the change in gfc_divide, but fail to see
where there is a division...

[Bug fortran/84868] [7/8/9 Regression] ICE in gfc_conv_descriptor_offset, at fortran/trans-array.c:208

2019-03-22 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=84868

--- Comment #6 from Harald Anlauf  ---
(In reply to Harald Anlauf from comment #5)
> With the following patch len_trim is accepted in a specification expression:

Just forget that.

[Bug fortran/84868] [7/8/9 Regression] ICE in gfc_conv_descriptor_offset, at fortran/trans-array.c:208

2019-03-22 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=84868

Harald Anlauf  changed:

   What|Removed |Added

 CC||anlauf at gmx dot de

--- Comment #5 from Harald Anlauf  ---
There is a variant that is wrongly rejected:

module m
  implicit none
contains
  function f(n) result(z)
character, save  :: c(3) = ['x', 'y', 'z']
integer,  intent(in) :: n
character(len_trim(c(n))) :: z
z = c(n)
  end
end
program p
  use m
  print *, f(2)
end

pr84868b.f90:7:23:

 character(len_trim(c(n))) :: z
   1
Error: Variable 'c' cannot appear in the expression at (1)

With the following patch len_trim is accepted in a specification expression:

Index: expr.c
===
--- expr.c  (revision 269880)
+++ expr.c  (working copy)
@@ -3402,10 +3402,13 @@
   return false;
 }

-  if (!gfc_simplify_expr (e, 0))
-return false;
+  if (gfc_simplify_expr (e, 0))
+return true;

-  return check_restricted (e);
+  if (check_restricted (e))
+return true;
+
+  return false;
 }

But then we hit the following issue at link time:

pr84868b.f90:(.text+0x12c): undefined reference to `___MOD_c'

[Bug fortran/86277] Presence of optional arguments not recognized for zero length arrays

2019-03-22 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=86277

--- Comment #3 from Harald Anlauf  ---
(In reply to Harald Anlauf from comment #2)
> Actually, the problem is not related to zero length arrays, but to the
> constructor [integer::].  I think this is related to several other PRs.

Looking at the dump-tree parts related to the lines

>   integer, parameter :: m(0) = 42
>   call i(m)
>   call i([integer::])
>   call i([integer::m])

shows that only the first call variant has a sane version of the
actual argument, while the other two have two(!) strange array
descriptors with a NULL data pointer, e.g.:

  struct array01_integer(kind=4) atmp.8;
  struct array01_integer(kind=4) atmp.10;

typedef integer(kind=4) [0];
  atmp.8.dtype = {.elem_len=4, .rank=1, .type=1};
  atmp.8.dim[0].stride = 1;
  atmp.8.dim[0].lbound = 0;
  atmp.8.dim[0].ubound = -1;
  atmp.8.data = 0B;
  atmp.8.offset = 0;
typedef integer(kind=4) [0];
  atmp.10.dtype = {.elem_len=4, .rank=1, .type=1};
  atmp.10.dim[0].stride = 1;
  atmp.10.dim[0].lbound = 0;
  atmp.10.dim[0].ubound = -1;
  atmp.10.data = 0B;
  atmp.10.offset = 0;

A bookkeeping issue?

[Bug fortran/85797] ICE in gfc_element_size, at fortran/target-memory.c:126

2019-03-17 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=85797

Harald Anlauf  changed:

   What|Removed |Added

 CC||anlauf at gmx dot de

--- Comment #3 from Harald Anlauf  ---
Patch submitted:

https://gcc.gnu.org/ml/fortran/2019-03/msg00099.html

[Bug fortran/87045] pointer to array of character

2019-03-08 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=87045

--- Comment #2 from Harald Anlauf  ---
With trunk it appears essential to have at least -fcheck=bounds
as option, otherwise the testcase passes for me.

The dump-tree for the critical code part (with -fcheck=bounds):

p = t;
p.span = (integer(kind=8)) SAVE_EXPR ;
if ((integer(kind=8)) (.p != .t))
  {
_gfortran_runtime_error_at (&"At line 8 of file pr87045.f90"[1]{lb: 1
sz: 1}, &"Unequal character lengths (%ld/%ld) in %s"[1]{lb: 1 sz: 1}, .p, .t,
&"pointer assignment"[1]{lb: 1 sz: 1});
  }
.p = .t;

Has the check been put into the wrong place?

[Bug fortran/60091] Misleading error messages in rank-2 pointer assignment to rank-1 target

2019-03-07 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=60091

Harald Anlauf  changed:

   What|Removed |Added

 CC||anlauf at gmx dot de

--- Comment #2 from Harald Anlauf  ---
Patch posted here:

https://gcc.gnu.org/ml/fortran/2019-03/msg00026.html

[Bug fortran/71203] ICE in add_init_expr_to_sym, at fortran/decl.c:1512 and :1564

2019-03-06 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=71203

--- Comment #12 from Harald Anlauf  ---
The issues related to zero-length strings and zero-size arrays are fixed
on trunk and 8-branch.  Backport to 7-branch would require additional
efforts, and as this PR is not about a regression, not done.

The integer parts in comment#1 need further debugging.
If somebody finds a related PR, this one might be closed as duplicate.

[Bug fortran/71203] ICE in add_init_expr_to_sym, at fortran/decl.c:1512 and :1564

2019-03-05 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=71203

--- Comment #9 from Harald Anlauf  ---
Patch submitted for the character-related issues:

https://gcc.gnu.org/ml/fortran/2019-03/msg00017.html

[Bug fortran/71203] ICE in add_init_expr_to_sym, at fortran/decl.c:1512 and :1564

2019-03-04 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=71203

--- Comment #8 from Harald Anlauf  ---
The following obvious patch fixes the character-related issues
(z1,z2,z3,z3a,z3b):

Index: expr.c
===
--- expr.c  (revision 269357)
+++ expr.c  (working copy)
@@ -1897,8 +1897,14 @@
string_len = 0;

  if (!p->ts.u.cl)
-   p->ts.u.cl = gfc_new_charlen (p->symtree->n.sym->ns,
- NULL);
+   {
+ if (p->symtree)
+   p->ts.u.cl = gfc_new_charlen
(p->symtree->n.sym->ns,
+ NULL);
+ else
+   p->ts.u.cl = gfc_new_charlen (gfc_current_ns,
+ NULL);
+   }
  else
gfc_free_expr (p->ts.u.cl->length);

However, due to my limited understanding of namespace handling,
this might be an improper solution.

The cases z4,z5 are different issues.

[Bug fortran/89266] ICE with TRANSFER of len=0 character array constructor

2019-03-02 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=89266

--- Comment #13 from Harald Anlauf  ---
On 03/02/19 12:48, dominiq at lps dot ens.fr wrote:
> https://gcc.gnu.org/bugzilla/show_bug.cgi?id=89266
> 
> Dominique d'Humieres  changed:
> 
>What|Removed |Added
> 
>  Status|NEW |WAITING
> 
> --- Comment #12 from Dominique d'Humieres  ---
>> This patch also fixes PR88326.
> 
> PR88326 is marked as a [7/8/9 Regression]. Is there any plan to back port
> r269177?

Yes, but I wanted to wait until all related fallout is resolved,
including PR89492 (fixed) and PR89516 (waiting for review).

[Bug fortran/77604] ICE in get_frame_type, at tree-nested.c:208

2019-02-28 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=77604

Harald Anlauf  changed:

   What|Removed |Added

 CC||anlauf at gmx dot de

--- Comment #4 from Harald Anlauf  ---
Does this still fail?  I cannot reproduce with current trunk or 8-branch.

[Bug fortran/68544] ICE trying to pass derived type constructor as a function

2019-02-28 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=68544

--- Comment #9 from Harald Anlauf  ---
(In reply to kargl from comment #8)
> Index: gcc/fortran/resolve.c
> ===
> --- gcc/fortran/resolve.c (revision 266281)
> +++ gcc/fortran/resolve.c (working copy)
> @@ -1863,7 +1863,19 @@ resolve_procedure_expression (gfc_expr* expr)

Steve,

what is the status of your patch?

[Bug fortran/84779] [7/8/9 Regression] Compiling gfortran.fortran-torture/execute/entry_4.f90 with -O1 or -Os and -fdefault-integer-8 gives an ICE

2019-02-25 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=84779

--- Comment #6 from Harald Anlauf  ---
Adding the option -fno-tree-sra to -O1 (or -Os for the original case)
makes the ICE go away for me.

[Bug fortran/89492] [9 Regression] Endless compilation of an invalid TRANSFER after r269177

2019-02-25 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=89492

--- Comment #4 from Harald Anlauf  ---
Patch with slightly extended testcase posted here:

https://gcc.gnu.org/ml/fortran/2019-02/msg00218.html

[Bug fortran/89492] [9 Regression] Endless compilation of an invalid TRANSFER after r269177

2019-02-25 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=89492

--- Comment #3 from Harald Anlauf  ---
I found another issue for uses of transfer('',['']), so here's an updated
version with a clearer error message:

Index: gcc/fortran/check.c
===
--- gcc/fortran/check.c (revision 269177)
+++ gcc/fortran/check.c (working copy)
@@ -5487,6 +5487,26 @@
   if (!gfc_element_size (mold, _elt_size))
 return false;

+  if (result_elt_size == 0 && *source_size > 0)
+{
+  gfc_error ("% argument of % intrinsic at %L "
+ "shall not have storage size 0 when % "
+"argument has size greater than 0", >where);
+  return false;
+}
+
+  /* If MOLD is a scalar and SIZE is absent, the result is a scalar.
+   * If MOLD is an array and SIZE is absent, the result is an array and of
+   * rank one. Its size is as small as possible such that its physical
+   * representation is not shorter than that of SOURCE.
+   */
+  if (result_elt_size == 0 && *source_size == 0 && !size)
+{
+  *result_size = 0;
+  *result_length_p = 0;
+  return true;
+}
+
   if ((result_elt_size > 0 && (mold->expr_type == EXPR_ARRAY || mold->rank))
   || size)
 {

Suggested testcase:

! { dg-do compile }
!
! PR fortran/89492 - Endless compilation of an invalid TRANSFER after r269177 
! Test error recovery for invalid uses of TRANSFER
! Test proper simplification for MOLD with size 0
!
! Derived from original testcase by Dominique d'Humieres

program bug4a
  implicit none
  type bug4
! Intentionally left empty
  end type bug4
  integer, parameter :: k = size(transfer('',['']))  ! k = 0
  integer, parameter :: m(k) = k
  print *,  transfer(1,[''])! { dg-error "shall not have
storage size 0" }
  print *, size(transfer(1,['']))   ! { dg-error "shall not have
storage size 0" }
  print *, size(transfer([1],[bug4()])) ! { dg-error "shall not have
storage size 0" }
  print *, transfer(transfer([1],[bug4()]),[1]) ! { dg-error "shall not have
storage size 0" }
end program bug4a

[Bug fortran/89492] [9 Regression] Endless compilation of an invalid TRANSFER after r269177

2019-02-25 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=89492

Harald Anlauf  changed:

   What|Removed |Added

 CC||anlauf at gmx dot de

--- Comment #1 from Harald Anlauf  ---
Potential patch:

Index: gcc/fortran/check.c
===
--- gcc/fortran/check.c (revision 269177)
+++ gcc/fortran/check.c (working copy)
@@ -5487,6 +5487,13 @@
   if (!gfc_element_size (mold, _elt_size))
 return false;

+  if (result_elt_size == 0 && *source_size > 0)
+{
+  gfc_error ("% argument of % intrinsic at %L "
+ "has storage size 0", >where);
+  return false;
+}
+
   if ((result_elt_size > 0 && (mold->expr_type == EXPR_ARRAY || mold->rank))
   || size)
 {

Can you please verify that your testcases work?

[Bug fortran/84779] [7/8/9 Regression] Compiling gfortran.fortran-torture/execute/entry_4.f90 with -O1 or -Os and -fdefault-integer-8 gives an ICE

2019-02-24 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=84779

--- Comment #5 from Harald Anlauf  ---
With rev. 269177 and on x86_64-pc-linux-gnu, I now see the ICE only at -O1,
but no longer at -Os.

After a frustrating debugging session, I decided to look at the
-fdump-tree-all for all options -O0 ... -O2, but didn't get any idea
what to look for.  Maybe some help from a middle-end expert
would be needed.

[Bug fortran/89266] ICE with TRANSFER of len=0 character array constructor

2019-02-23 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=89266

--- Comment #10 from Harald Anlauf  ---
(In reply to Harald Anlauf from comment #9)
> A patch that does this has been posted here:
> 
> https://gcc.gnu.org/ml/fortran/2019-02/msg00153.html

This patch also fixes PR88326.

[Bug fortran/88227] ICE in gfc_convert_boz, at fortran/target-memory.c:788

2019-02-21 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=88227

Harald Anlauf  changed:

   What|Removed |Added

 CC||anlauf at gmx dot de

--- Comment #2 from Harald Anlauf  ---
There is no suitable integer kind for -m32 to represent a real(kind=16).

target-memory.c:
801   for (index = 0; gfc_integer_kinds[index].kind != 0; ++index)
802 if ((unsigned) gfc_integer_kinds[index].bit_size >= ts_bit_size)
803   break;
804
805   expr->ts.kind = gfc_integer_kinds[index].kind;
806   buffer_size = MAX (buffer_size, size_integer (expr->ts.kind));
(gdb) p expr->ts.kind
$13 = 0

So shall we reject the conversion of the BOZ?

[Bug fortran/87103] [OOP] ICE in gfc_new_symbol() due to overlong symbol name

2019-02-21 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=87103

--- Comment #4 from Harald Anlauf  ---
(In reply to Dominique d'Humieres from comment #3)
> Patch at https://gcc.gnu.org/ml/fortran/2018-09/msg00044.html.

Status of this patch?  (The ICE is still there).

[Bug fortran/83057] OPEN without a filename and without STATUS='SCRATCH' could produce a warning

2019-02-20 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=83057

--- Comment #5 from Harald Anlauf  ---
Patch submitted:

https://gcc.gnu.org/ml/fortran/2019-02/msg00176.html

[Bug fortran/83057] OPEN without a filename and without STATUS='SCRATCH' could produce a warning

2019-02-20 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=83057

Harald Anlauf  changed:

   What|Removed |Added

 CC||anlauf at gmx dot de

--- Comment #4 from Harald Anlauf  ---
The following obvious patch to the logic fixes the NEWUNIT issue:

Index: gcc/fortran/io.c
===
--- gcc/fortran/io.c(revision 269028)
+++ gcc/fortran/io.c(working copy)
@@ -2504,16 +2504,15 @@
  goto cleanup;
}

-  if (!open->file && open->status)
-{
- if (open->status->expr_type == EXPR_CONSTANT
+  if (!open->file &&
+ (!open->status ||
+  (open->status->expr_type == EXPR_CONSTANT
 && gfc_wide_strncasecmp (open->status->value.character.string,
-  "scratch", 7) != 0)
-  {
+ "scratch", 7) != 0)))
+   {
 gfc_error ("NEWUNIT specifier must have FILE= "
"or STATUS='scratch' at %C");
 goto cleanup;
-  }
}
 }
   else if (!open->unit)

I do not think we need to handle the other case,
as many people expect the file fort.20 to be created.
(At least I do.)

[Bug fortran/86248] [7/8/9 Regression] LEN_TRIM in specification expression causes link failure

2019-02-20 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=86248

--- Comment #4 from Harald Anlauf  ---
Some digging shows that the name mangling is done in trans-decl.c,
gfc_sym_mangled_identifier.  Strangely, the funny name mangling comes
from the component fn_result_spec being set in resolve.c, flag_fn_result_spec,
but only when darray_fixed is a PARAMETER.

The code in question was added by pault in rev. 243478:

243478  pault   if (!s->fn_result_spec
243478  pault && s->attr.flavor == FL_PARAMETER)
243478  pault   {
243478  pault /* Function contained in a module */
243478  pault if (ns->proc_name && ns->proc_name->attr.flavor ==
FL_MODULE)
243478  pault   {
243478  pault gfc_symtree *st;
243478  pault s->fn_result_spec = 1;

Maybe he can shine some light on this.

[Bug fortran/88326] [7/8/9 Regression] ICE in gfc_conv_array_initializer, at fortran/trans-array.c:6085

2019-02-19 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=88326

Harald Anlauf  changed:

   What|Removed |Added

 CC||anlauf at gmx dot de

--- Comment #5 from Harald Anlauf  ---
Using my tentative fix for PR89266 I now get:

% gfc-x pr88326-z1.f90
pr88326-z1.f90:3:20:

3 |character :: y(1) = transfer('', x)
  |1
Error: Different shape for array assignment at (1) on dimension 1 (1 and 0)

% gfc-x pr88326-z2.f90
pr88326-z2.f90:3:23:

3 |character(0) :: y(1) = transfer('', x)
  |   1
Error: Different shape for array assignment at (1) on dimension 1 (1 and 0)

% gfc-x pr88326-z3.f90

(No error).

Should be fixed when PR89266 is fixed.

[Bug fortran/86248] [7/8/9 Regression] LEN_TRIM in specification expression causes link failure

2019-02-19 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=86248

Harald Anlauf  changed:

   What|Removed |Added

 CC||anlauf at gmx dot de

--- Comment #3 from Harald Anlauf  ---
It is strange that changing the line

character(len=3),dimension(0:2),parameter :: darray_fixed =
(/"el0","el1","el2"/)

by

character(len=3),dimension(0:2),save :: darray_fixed = (/"el0","el1","el2"/)

I get exactly the same(!) tree-dump with 9-trunk, but different .o,
since running nm on the first case gives:

 R __test_module_MOD__test_module_PROC_darray_fixed

vs.

 D __test_module_MOD_darray_fixed

My poor understanding of the assembler suggests that this is the origin
of all trouble.

The fact that the combined file seems to work (links OK) is not proof that
everything is fine, again seen only from the assembler.

I have no idea where the strange name mangling comes from.

[Bug fortran/89365] Inquiry functions for assumed rank objects fail

2019-02-19 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=89365

Harald Anlauf  changed:

   What|Removed |Added

 CC||anlauf at gmx dot de

--- Comment #2 from Harald Anlauf  ---
The issue is probably not the LBOUND intrinsic, but the proper argument
association of the dummy argument of the subroutines.  (There is at least
another PR regarding POINTER dummy arguments)

The sample code has:

subroutine foo_1(this) 
  real(c_float) :: this(..)

My reading of the F2018 FDIS regarding this case:

15.5.2 Actual arguments, dummy arguments, and argument association

15.5.2.4 Ordinary dummy variables

(1) The requirements in this subclause apply to actual arguments
that correspond to nonallocatable nonpointer dummy data objects.

(17) An actual argument of any rank may correspond to an
 assumed-rank dummy argument. The rank and extents of the dummy
 argument are the rank and extents of the corresponding actual
 argument. The lower bound of each dimension of the dummy
 argument is equal to one. The upper bound is equal to the
 extent, except for the last dimension when the actual argument
 is assumed-size.

That appears to be OK.  Right?

For the POINTER dummy argument (foo_3):

subroutine foo_3(this) 
  real(c_float), pointer :: this(..)

Again, F2018 FDIS:

15.5.2.3 Argument association

(5) A present pointer dummy argument that corresponds to a
  pointer actual argument becomes argument associated with that
  actual argument.

Here I'd expect that we should actually get the same as if a pointer
association had taken place, c.f. PR85868 (so this one could be a duplicate?)

Finally:

subroutine foo_2(this)
  real(c_float), allocatable :: this(..)

I couldn't find an appropriate reference here, so somebody else may have
something to say.

[Bug fortran/89266] ICE with TRANSFER of len=0 character array constructor

2019-02-19 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=89266

--- Comment #9 from Harald Anlauf  ---
(In reply to Harald Anlauf from comment #8)
> I have a 'half-patch' that tries to change gfc_target_expr_size()
> to return a bool which is true for success and false for failure,
> and then deal with this return value.
> 
> It seems that this also needs to be done for gfc_element_size().

A patch that does this has been posted here:

https://gcc.gnu.org/ml/fortran/2019-02/msg00153.html

[Bug fortran/88299] [F18] COMMON in a legacy module produces bogus warnings in dependent code

2019-02-17 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=88299

Harald Anlauf  changed:

   What|Removed |Added

 Status|NEW |RESOLVED
 Resolution|--- |FIXED

--- Comment #7 from Harald Anlauf  ---
Fixed.

[Bug fortran/89077] ICE using * as len specifier for character parameter

2019-02-17 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=89077

--- Comment #19 from Harald Anlauf  ---
The issues reported in comment #0, #1 and #3 should be fixed on trunk.
The fix for comment #0 has been backported to 7- and 8-branches.

Can the OP please confirm that the reported issues have been fixed?

[Bug fortran/89077] ICE using * as len specifier for character parameter

2019-02-15 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=89077

--- Comment #17 from Harald Anlauf  ---
(In reply to Harald Anlauf from comment #16)
> Regarding the unwanted padding with \0, the following patch seems to
> solve the issue with transfer.

Regtested cleanly and submitted here:

https://gcc.gnu.org/ml/fortran/2019-02/msg00126.html

[Bug fortran/89077] ICE using * as len specifier for character parameter

2019-02-14 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=89077

--- Comment #16 from Harald Anlauf  ---
Regarding the unwanted padding with \0, the following patch seems to
solve the issue with transfer.

Index: decl.c
===
--- decl.c  (revision 268897)
+++ decl.c  (working copy)
@@ -1754,6 +1754,12 @@
   free (expr->value.character.string);
   expr->value.character.string = s;
   expr->value.character.length = len;
+  if (expr->representation.length)
+   {
+ expr->representation.length = 0;
+ free (expr->representation.string);
+ expr->representation.string = NULL;
+   }
 }
 }

Testcase:

  character(8) ,parameter :: s = transfer ('ab', 'cd')
  character(8) ,parameter :: t = 2Hxy
  print *, "'", s, "'"
  print *, "'", t, "'"
end

./a.out  | cat -v
 'ab  '
 'xy  '

[Bug fortran/88248] [F18] Bogus warning about obsolescent feature: Labeled DO statement

2019-02-14 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=88248

--- Comment #9 from Harald Anlauf  ---
Fixed.

[Bug fortran/88248] [F18] Bogus warning about obsolescent feature: Labeled DO statement

2019-02-13 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=88248

--- Comment #7 from Harald Anlauf  ---
Patch submitted:

https://gcc.gnu.org/ml/fortran/2019-02/msg00112.html

[Bug fortran/88248] [F18] Bogus warning about obsolescent feature: Labeled DO statement

2019-02-12 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=88248

--- Comment #6 from Harald Anlauf  ---
Moving the check from gfc_define_st_label to gfc_reference_st_label:

Index: symbol.c
===
--- symbol.c(revision 268826)
+++ symbol.c(working copy)
@@ -2743,10 +2743,6 @@
  "DO termination statement which is not END
DO"
  " or CONTINUE with label %d at %C", labelno))
return;
- if (type == ST_LABEL_DO_TARGET
- && !gfc_notify_std (GFC_STD_F2018_OBS, "Labeled DO statement "
- "at %L", label_locus))
-   return;
  break;

default:
@@ -2804,6 +2800,11 @@
  "Shared DO termination label %d at %C", labelno))
 return false;

+  if (type == ST_LABEL_DO_TARGET
+  && !gfc_notify_std (GFC_STD_F2018_OBS, "Labeled DO statement "
+ "at %L", _current_locus))
+return false;
+
   if (lp->referenced != ST_LABEL_DO_TARGET)
 lp->referenced = type;
   rc = true;

fixes the issue for me.  It consequently needs adjustment to the test case
f2018_obs.f90, since it references the line with the "do 99 ..." instead
of the do termination line.

I am wondering about the location of the error marker.  E.g. for

subroutine gfcbug151 ()
  do 99 i = 1, 10
99   continue
end subroutine gfcbug151

I get:

gfcbug151.f90:2:17:

2 |   do 99 i = 1, 10
  | 1
Warning: Fortran 2018 obsolescent feature: Labeled DO statement at (1)

But I think this is ok.

Should I submit the above, or are there better suggestions?

[Bug fortran/88299] [F18] COMMON in a legacy module produces bogus warnings in dependent code

2019-02-11 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=88299

--- Comment #5 from Harald Anlauf  ---
Patch passed regtesting and was submitted:

https://gcc.gnu.org/ml/fortran/2019-02/msg00097.html

[Bug fortran/88299] [F18] COMMON in a legacy module produces bogus warnings in dependent code

2019-02-11 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=88299

--- Comment #4 from Harald Anlauf  ---
I'm currently regtesting the following patch:

Index: gcc/fortran/resolve.c
===
--- gcc/fortran/resolve.c   (revision 268778)
+++ gcc/fortran/resolve.c   (working copy)
@@ -940,7 +940,11 @@
 have been ignored to continue parsing.
 We do the checks again here.  */
   if (!csym->attr.use_assoc)
-   gfc_add_in_common (>attr, csym->name, _block->where);
+   {
+ gfc_add_in_common (>attr, csym->name, _block->where);
+ gfc_notify_std (GFC_STD_F2018_OBS, "COMMON block at %L",
+ _block->where);
+   }

   if (csym->value || csym->attr.data)
{
@@ -998,10 +1002,6 @@

   resolve_common_vars (common_root->n.common, true);

-  if (!gfc_notify_std (GFC_STD_F2018_OBS, "COMMON block at %L",
-  _root->n.common->where))
-return;
-
   /* The common name is a global name - in Fortran 2003 also if it has a
  C binding name, since Fortran 2008 only the C binding name is a global
  identifier.  */

[Bug fortran/89266] ICE with TRANSFER of len=0 character array constructor

2019-02-11 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=89266

--- Comment #8 from Harald Anlauf  ---
It's not as trivial as I had hoped.

The point is that gfc_element_size() and gfc_target_expr_size()
are returning size 0 for the source expression, which is an entirely
correct value.  However, they also return value 0 also for cases
where the sizes could not be determined to be a constant.

I have a 'half-patch' that tries to change gfc_target_expr_size()
to return a bool which is true for success and false for failure,
and then deal with this return value.

It seems that this also needs to be done for gfc_element_size().
However, there is this occurrence in class.c of gfc_element_size():

  /* Build a minimal expression to make use of
 target-memory.c/gfc_element_size for 'size'.  Special handling
 for character arrays, that are not constant sized: to support
 len (str) * kind, only the kind information is stored in the
 vtab.  */
  e = gfc_get_expr ();
  e->ts = *ts;
  e->expr_type = EXPR_VARIABLE;
  c->initializer = gfc_get_int_expr (gfc_size_kind,
 NULL,
 ts->type == BT_CHARACTER
 ? ts->kind
 : gfc_element_size (e));

I am not yet sure how to safely rewrite this.

[Bug fortran/89266] ICE with TRANSFER of len=0 character array constructor

2019-02-10 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=89266

--- Comment #7 from Harald Anlauf  ---
(In reply to Harald Anlauf from comment #6)
> The problem might be here:
> 
> check.c: gfc_calculate_transfer_sizes
> 
> 5482  /* Calculate the size of the source.  */
> 5483  *source_size = gfc_target_expr_size (source);
> 5484  if (*source_size == 0)
> 5485return false;
> 
> Shouldn't the case tested here be handled differently?

Commenting out the lines 5484-5485 makes the testcase compile,
but regtesting fails for transfer_check_3.f90:

/work/gnu/svn/build-trunk/gcc/f951 transfer_check_3.f90 -Wsurprising
transfer_check_3.f90:32:22:

   32 | i = transfer (record_type(1:j), i) ! gave a warning
  |  1
Warning: Intrinsic TRANSFER at (1) has partly undefined result: source size 0 <
result size 4 [-Wsurprising]
 cgbrfsx test

It appears that we shall we need to be able to distinguish size 0 source
from unknown size.  Thus we could change change gfc_target_expr_size
and adjust its other users.

[Bug fortran/89266] ICE with TRANSFER of len=0 character array constructor

2019-02-10 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=89266

--- Comment #6 from Harald Anlauf  ---
The problem might be here:

check.c: gfc_calculate_transfer_sizes

5482  /* Calculate the size of the source.  */
5483  *source_size = gfc_target_expr_size (source);
5484  if (*source_size == 0)
5485return false;

Shouldn't the case tested here be handled differently?

[Bug fortran/89266] ICE with TRANSFER of len=0 character array constructor

2019-02-10 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=89266

--- Comment #5 from Harald Anlauf  ---
Alternative versions to test case #2:

program test
  implicit none
  character(1), save  :: z = transfer ([''], '*') ! ICE
! character(1), save  :: z = transfer ([character(0) :: ''], '*') ! ICE
! character(1), save  :: z = transfer ([character(1) :: ''], '*') ! works
  print *,"'",z,"'",len(z)
end

[Bug fortran/89266] ICE with TRANSFER of len=0 character array constructor

2019-02-10 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=89266

--- Comment #4 from Harald Anlauf  ---
(In reply to Thomas Koenig from comment #1)
> Goes back a long time, at least to gcc 6.
> 
> I also think that this is valid code, but if somebody can find
> language in the standard that says otherwise, please correct.

The second test case is valid, but processor dependent according
to e.g. Fortran 2003:

13.7.121 TRANSFER (SOURCE, MOLD [, SIZE])

Result Value. [...]
If the physical representation of the result is longer than that of SOURCE,
the physical representation of the leading part is that of SOURCE and the
remainder is processor dependent.

Examples:

PGI, flang 1.5 give:
% ./a.out | cat -ve
 '^@ '6$

sunf95, g95:
 '^@^@^@^@^@^@' 6$

[Bug fortran/89266] ICE with TRANSFER of len=0 character array constructor

2019-02-10 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=89266

Harald Anlauf  changed:

   What|Removed |Added

 CC||anlauf at gmx dot de

--- Comment #3 from Harald Anlauf  ---
(In reply to Thomas Koenig from comment #0)
> $ cat tst3.f90 
> program test
>   implicit none
>   integer :: i
>   character(*), parameter :: y = ''
>   character(*), parameter :: z = transfer ([''], y)
> end

Funny, I do not get an ICE for the first test case here with
trunk rev.268753 on x86_64-pc-linux-gnu, even after adding a

  print *, z, len (z)

which gives

% ./a.out | cat -ve
0$

and which seems correct.

[Bug fortran/89077] ICE using * as len specifier for character parameter

2019-02-05 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=89077

--- Comment #12 from Harald Anlauf  ---
Further variant:

==> f4.f90 <==
  character(1), save  :: y = transfer ([('a'(1:1),i=1,1)], 'x')
  print *, y
end

generates exactly the same code as f3, although it passes along slightly
different pathes during simplification.

BTW, I noticed that f1 produces an IMHO insane dump-tree, with a call
to _gfortran_internal_pack!

I'd never expected to get such inefficient code in that case.

[Bug fortran/89077] ICE using * as len specifier for character parameter

2019-02-05 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=89077

--- Comment #11 from Harald Anlauf  ---
I'm currently using the following minimal testcases for further debugging:

==> f1.f90 <==
  character(1), parameter :: u = transfer ([('a'(i:i),i=1,1)], 'x')
  print *, u
end

==> f2.f90 <==
  character(1), save  :: v = transfer ([('a'(i:i),i=1,1)], 'x')
  print *, v
end

==> f3.f90 <==
  character(1), save  :: w = transfer ([('a' ,i=1,1)], 'x')
  print *, w
end


f1 and f3 work, f2 does ICE.

[Bug fortran/89077] ICE using * as len specifier for character parameter

2019-02-04 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=89077

--- Comment #10 from Harald Anlauf  ---
The ICE in comment #0 is fixed on trunk so far.

The ICE is comment #1 is occurring on a different path and is under
further investigation, as well as the other wrong-code issues.

[Bug fortran/89077] ICE using * as len specifier for character parameter

2019-01-31 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=89077

--- Comment #8 from Harald Anlauf  ---
OK, here's another one for fun:

program pr89077_4
  implicit none
  character(*), parameter :: s = 7HForward
  print *, '#', s, '#', len (s)
end program pr89077_4

prints:

 #Forward #   8

This time it is really padded with a space which comes out of the blue.

Oracle sunf95 prints:

 #Forward# 7

Intel rejects it.

[Bug fortran/89077] ICE using * as len specifier for character parameter

2019-01-31 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=89077

--- Comment #7 from Harald Anlauf  ---
(In reply to Harald Anlauf from comment #6)

Playing around and getting completely lost during a gdb session,
I became suspicious that the second issue has to do with missed
padding that interestingly occurs also with Hollerith constants:

program pr89077_3
  implicit none
  integer,  parameter :: m = 20
  character(*), parameter :: s = 'Forward'
  character(m), parameter :: t = s
  character(m), parameter :: u = transfer (s, s)
  character(m), parameter :: v = 7HFORWARD
  character(m), parameter :: w = transfer (s, s) // ""
  print *, t, '#'
  print *, u, '#'
  print *, v, '#'
  print *, w, '#'
end program pr89077_3

This prints:

 % ./a.out | cat -v
 Forward #
 Forward^@^@^@Q^@M-P^@p^@^@^@^@a#
 FORWARD ^@^@Q^@M-P^@M-Pa^H^@M-ha#
 Forward #

[Bug fortran/89077] ICE using * as len specifier for character parameter

2019-01-29 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=89077

--- Comment #6 from Harald Anlauf  ---
(In reply to Harald Anlauf from comment #5)
It does not fix the issue in comment #3.  In fact, the simpler testcase

program pr89077_3
  implicit none
  character(20), parameter :: input = 'Forward'
  integer i
  character(len(input)), parameter :: same = &
   transfer (trim (input), trim (input))
  print *, input, '#', len(input)
  print *, same, '#', len(same)
end program pr89077_3

prints random junk on the second line:

 Forward #  20
 ForwardQÀ@(#  20

:-(

[Bug fortran/89077] ICE using * as len specifier for character parameter

2019-01-29 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=89077

--- Comment #5 from Harald Anlauf  ---
The following patch fixes the testcase and seems to pass regression testing.

Index: gcc/fortran/decl.c
===
--- gcc/fortran/decl.c  (revision 268369)
+++ gcc/fortran/decl.c  (working copy)
@@ -1921,7 +1921,7 @@
}
  else if (init->ts.u.cl && init->ts.u.cl->length)
sym->ts.u.cl->length =
-   gfc_copy_expr (sym->value->ts.u.cl->length);
+   gfc_copy_expr (init->ts.u.cl->length);
}
}
  /* Update initializer character length according symbol.  */


Maybe it needs to be checked against a larger code base.

It changes (and hopefully fixes) almost 10-year old code.

Thanks, Dominique, for pointing to the right area.

[Bug fortran/89077] ICE using * as len specifier for character parameter

2019-01-29 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=89077

Harald Anlauf  changed:

   What|Removed |Added

 CC||anlauf at gmx dot de

--- Comment #4 from Harald Anlauf  ---
Replacing

  character(*), parameter :: str2 = transfer([(str(i:i), i=1,len(str))], str)

by

  character, parameter:: str2a(*) = [(str(i:i), i=1,len(str))]
  character(*), parameter :: str2 = transfer(str2a, str)

'solves' the issue.  I think there are close (code-wise) duplicates to
this issue, where some information of an array constructor is lost in
constant expressions.

[Bug fortran/85868] Subarray of a pointer array associated with a pointer dummy argument

2019-01-28 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=85868

--- Comment #6 from Harald Anlauf  ---
Another testcase suitable for debugging is the following, which better
shows correspondence for pre-F2008 and F2008+ variants:

program test
  implicit none
  integer, pointer :: t(:), u(:)
  integer  :: i
  allocate (t(-1:5))
  do i = -1, 5
 t(i) = i
  end do
  call p (t )  ! Pointer with lower bound = -1 from allocation
  u => t   ! Pointer assignment sets same lower bound
  call p (u)
  !
  u => t( :)   ! Pointer assignment with implicit lower bound (1)
  call p (u)
  call p (t(  :))  ! Full array, behaves the same
  !
  call p (t( 0:))  ! Array section
  u => t(0:)   ! Pointer assignment with implicit lower bound (1)
  call p (u)
  u(0:) => t(0:)   ! Pointer assignment with given lower bound (0)
  call p (u)
contains
  subroutine p (a)
integer, pointer, intent(in) :: a(:)
print *, a(1)
  end subroutine p
end program

NAG and Crayftn both print the supposedly correct result:

 1
 1
 -1
 -1
 0
 0
 1

Current 9-trunk:

   1
   1
  -1
   1
   2
   0
   1

gcc-8.2.1:

   1
   1
  -1
   1
   0
   0
   1

gcc-7.3.1, 6.x, 5.x, 4.6:

   1
   1
  -1
   1
   1
   0
   1

gcc-4.9, 4.8:

   1
   1
  -1
   1
   1
   0
   0

So it is a varying sort of wrong code issue...
Only output lines 1,2,3 and 6 are always correct.

[Bug libfortran/89020] close(status='DELETE') does not remove file

2019-01-26 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=89020

Harald Anlauf  changed:

   What|Removed |Added

 CC||anlauf at gmx dot de

--- Comment #13 from Harald Anlauf  ---
Jerry,

are you sure that the second part of the patch is intended?

remove (u->filename) vs. remove (path)

[Bug fortran/34871] Flavor VARIABLE vs. FUNCTION: Accepts invalid

2019-01-25 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=34871

Harald Anlauf  changed:

   What|Removed |Added

 CC||anlauf at gmx dot de

--- Comment #5 from Harald Anlauf  ---
If the example in comment #0 is changed as follows:

MODULE TESTS
  dimension :: k(4)
CONTAINS
  function k() result (kk)
kk = 35
  end function k
END MODULE TESTS

the code - although still invalid - still compiles, but the dump-tree
is completely different.

I also see big differences in the dump-tree between comment #0 and the
above for 9-trunk, but not for 8-branch.

ISTR a patch (Steve) that fixed a related issue with RESULT(), maybe
that is the place to look for a fix?

[Bug fortran/85868] Subarray of a pointer array associated with a pointer dummy argument

2019-01-24 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=85868

--- Comment #5 from Harald Anlauf  ---
Better testcase for debugging:

program pr85858
  implicit none
  integer, pointer :: t(:)
  integer  :: i, lb
  lb = -1
  allocate (t(lb:5))
  do i = lb, 5
 t(i) = i
  end do
  call te (t(  :))  ! Full array: OK
  call te (t(lb:))  ! Array section, but effectively full array: OK
  call te (t( 0:))  ! Offset should depend on 0-lb !
  call te (t( 1:))  ! Offset should depend on 1-lb !
contains
  subroutine te (a)
integer, pointer, intent(in) :: a(:)
print *, a(1)   !, lbound (a, dim=1)
  end subroutine te
end program

Expected output: four 1s.

Current trunk prints:
   1
   1
   2
   3

(Outputs of 7.x and 8.x are also quite strange).

Dump-tree-original shows for the generated descriptors (excerpt):

for call te (t(lb:))

  D.3893 = (integer(kind=8)) lb;
  parm.3.dim[0].lbound = D.3893;
  D.3901 = t.dim[0].stride;
  parm.3.data = (void *) &(*(integer(kind=4)[0:] *) t.data)[(D.3893 -
t.dim[0].lbound) * D.3901];
  parm.3.offset = t.offset;

for call te (t( 0:))

  parm.4.dim[0].lbound = 0;
  parm.4.data = (void *) &(*(integer(kind=4)[0:] *)
t.data)[-t.dim[0].lbound * D.3909];
  parm.4.offset = t.offset;

while the subroutine references:

(a->data + (sizetype) ((a->offset + NON_LVALUE_EXPR dim[0].stride>) *
a->span))

Can this be right?  If .data changes, shouldn't .offset change accordingly?

[Bug fortran/85868] Subarray of a pointer array associated with a pointer dummy argument

2019-01-23 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=85868

--- Comment #4 from Harald Anlauf  ---
Reduced testcase:

program pr85858
  implicit none
! integer, allocatable, target :: t(:)
  integer, pointer :: t(:) => null()
  integer :: i, lb = 0  ! run under debugger, or set lb to 1
  allocate (t(lb:10))
  do i = lb, 10
 t(i) = i
  end do
  print *, t(1)
  call te (t(1:))   ! Offset should depend on 1-lb !
contains
  subroutine te (a)
integer, pointer, intent(in) :: a(:)
print *, a(1), lbound (a, dim=1)
  end subroutine te
end program


For lb=0 this prints

   1
   2   1

while it should print only 1s (as I get with gfortran 8.2.1).

[Bug fortran/85868] Subarray of a pointer array associated with a pointer dummy argument

2019-01-23 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=85868

--- Comment #3 from Harald Anlauf  ---
Something has changed recently in 9-trunk, I now get with rev.268162
for the testcase in comment #0:

   2.

Printing the array bounds in subroutine te gives the expected values,
so it must be the offset that is off by one.

[Bug fortran/87336] [8/9 regression] wrong output for pointer dummy assiocated to target actual argument

2019-01-23 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=87336

--- Comment #6 from Harald Anlauf  ---
The patch in comment #3 seems to apply to gcc-8, but I haven't regtested it.
Paul, do you intend to backport it?

[Bug fortran/57553] [F08] Valid use of STORAGE_SIZE rejected, bad error message for invalid use

2019-01-22 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=57553

--- Comment #7 from Harald Anlauf  ---
Patch submitted for review:

https://gcc.gnu.org/ml/fortran/2019-01/msg00201.html

[Bug fortran/88579] Calculating power of powers of two

2019-01-20 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=88579

--- Comment #4 from Harald Anlauf  ---
Patch submitted here:

https://gcc.gnu.org/ml/fortran/2019-01/msg00163.html

[Bug libfortran/88776] Namelist read from stdin: loss of data

2019-01-10 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=88776

--- Comment #3 from Harald Anlauf  ---
Created attachment 45407
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=45407=edit
Self-contained testcase

I've been able to produce a self-contained testcase, which may aid
debugging.

While reducing further, I got the impression that it is just a subtle
whitespace issue.

[Bug libfortran/88776] Namelist read from stdin: loss of data

2019-01-09 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=88776

--- Comment #1 from Harald Anlauf  ---
I wrote "loss of data" because the second (valid) namelist could not be
properly read because of stat /= 0.

[Bug libfortran/88776] New: Namelist read from stdin: loss of data

2019-01-09 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=88776

Bug ID: 88776
   Summary: Namelist read from stdin: loss of data
   Product: gcc
   Version: 9.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: libfortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: anlauf at gmx dot de
  Target Milestone: ---

Reading namelist from unit 5 may skip valid data later when an error is
encountered.  This problem does not occur when another unit number is used.

Example:

% cat gfcbug154.f90
program nmlbug
  implicit none
  integer :: i, stat, nnml
  nnml = 5  ! No problem with nnml = 10
! nnml = 10
  open (nnml, file="gfcbug154.dat", action="read")
  do i = 1, 3
 print *, "# Read namelist", i
 call read_nml_type_2
 print *
  end do
contains
  subroutine read_nml_type_2
!--
! variant 2 of namelist input: chan = real char(len=*) real
!--
type t_chan
   real  :: ichan = -1.
   character(len=10) :: flag  = ''
   real  :: band  = -1.
end type t_chan
type(t_chan) :: chan(2)
namelist /CHAN_NML/ chan

chan(:) = t_chan(-1.,'',-1.)
stat = 0
read (nnml, nml=CHAN_NML, iostat=stat, end=99)
print *, "read_nml_type_2: stat=", stat
print *, "chan(1)=", chan(1)
print *, "chan(2)=", chan(2)
return
99  stop "EOF"
  end subroutine read_nml_type_2
end program nmlbug

% cat gfcbug154.dat
_NML
 chan = 3   '#1 '   '0.1'
6   '#1 '   0.8
/

_NML
 chan = 4   '#2 '   0.1
7   '#2 '   0.2
/

_NML
 chan = 5   '#3 '   0.3
8   '#3 '   0.4
/


The above code outputs:

 # Read namelist   1
 read_nml_type_2: stat=5010
 chan(1)=   4. #2  0.10001
 chan(2)=   7. #2  0.20003

 # Read namelist   2
 read_nml_type_2: stat=   0
 chan(1)=   5. #3  0.30012
 chan(2)=   8. #3  0.40006

 # Read namelist   3
STOP EOF

whereas with e.g. unit 10 it (correctly) outputs:

 # Read namelist   1
 read_nml_type_2: stat=5010
 chan(1)=   3. #1  -1.
 chan(2)=  -1. -1.

 # Read namelist   2
 read_nml_type_2: stat=   0
 chan(1)=   4. #2  0.10001
 chan(2)=   7. #2  0.20003

 # Read namelist   3
 read_nml_type_2: stat=   0
 chan(1)=   5. #3  0.30012
 chan(2)=   8. #3  0.40006


For some reason, when an error is encountered during the first read,
it correctly sets the error status, but apparently continues to the
second namelist instance.

[Bug fortran/88748] IS_CONTIGUOUS mishandles arrays of derived type components

2019-01-07 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=88748

Harald Anlauf  changed:

   What|Removed |Added

 Status|WAITING |RESOLVED
 Resolution|--- |INVALID

--- Comment #2 from Harald Anlauf  ---
(In reply to Dominique d'Humieres from comment #1)
> On darwin with r267657 I get
> 
> % gfc pr88748.f90
> % ./a.out
>  T
>  F

Damn, I picked the wrong installation path.  You're right.  Closing.

[Bug fortran/88748] New: IS_CONTIGUOUS mishandles arrays of derived type components

2019-01-07 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=88748

Bug ID: 88748
   Summary: IS_CONTIGUOUS mishandles arrays of derived type
components
   Product: gcc
   Version: 9.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: anlauf at gmx dot de
  Target Milestone: ---

The patch committed to fix to PR 45424 does not handle the examples given
there in comment 1:

type t
  integer :: i, j
end type t
type(t) :: x(5)
print *, is_contiguous(x(:))   ! Shall be (and is) true
print *, is_contiguous(x(:)%i) ! Shall be false - but prints "true".
end

gfortran rev. 267658 prints:

 T
 T

while Intel v15 (and later) and NAG 6.2 print:

 T
 F

(Note to self: need to check PR 45424 comment 2).

[Bug fortran/45424] [F08] Add IS_CONTIGUOUS intrinsic

2019-01-03 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=45424

Harald Anlauf  changed:

   What|Removed |Added

  Attachment #45322|0   |1
is obsolete||

--- Comment #8 from Harald Anlauf  ---
Created attachment 45332
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=45332=edit
Corrected update of Tobias' patch to 9-trunk (except for ChangeLog)

This version corrects the previous attempt which broke the original patch.
It comes with an additional testcase that checks assumed rank/assumed type.

[Bug fortran/45424] [F08] Add IS_CONTIGUOUS intrinsic

2019-01-02 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=45424

Harald Anlauf  changed:

   What|Removed |Added

  Attachment #45292|0   |1
is obsolete||

--- Comment #7 from Harald Anlauf  ---
Created attachment 45322
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=45322=edit
Extended Update of Tobias' patch to 9-trunk (except for ChangeLog)

I've updated Tobias' patch, adding a runtime library function to handle
assumed rank arrays (not sure if this is the right way).  This now works
for the following testcase:

program is_contiguous_2
  implicit none
  real, allocatable :: b(:,:)
  allocate(b(10,10))
  if (fail (b,  .true.) ) stop 1
  if (fail (b(::1,::1), .true.) ) stop 2
  if (fail (b(::2,::1), .false.)) stop 3
  if (fail (b(::1,::2), .false.)) stop 4
  if (fail (b(:10,:10), .true. )) stop 5
  if (fail (b(: 9,:10), .false.)) stop 6
contains
  pure logical function fail (x, expect)
!   type(*), dimension(..), intent(in) :: x  ! This should work, too
real,dimension(..), intent(in) :: x
logical,intent(in) :: expect
fail = is_contiguous (x) .neqv. expect
  end function fail
end program

I don't know how to handle assumed type; I need help by somebody else
who is interested in pursuing this.

Thanks to whoever will pick this up.

[Bug fortran/45424] [F08] Add IS_CONTIGUOUS intrinsic

2018-12-27 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=45424

--- Comment #6 from Harald Anlauf  ---
Created attachment 45292
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=45292=edit
Update of Tobias' patch to 9-trunk (except for ChangeLog)

I've tried to update Tobias' patch so that it compiles with 9-trunk
and adjusted his testcase so that it uses STOP instead of call abort ().

There's one problem left and one question.

The problem is that I'm getting one failure with the following test:

  implicit none
  real, allocatable :: a(:), b(:,:)
  integer :: k = 0

  allocate(a(5), b(10,10))
  call test (a, .true.)
  call test (b, .true.)
  call test (b(::1,::1), .true.)
  call test (b(::2,::1), .false.)
  call test (b(::1,::2), .false.)  ! This test fails currently
contains
  subroutine test (x, res)
!   type(*), dimension(..), intent(in) :: x  ! Should this be allowed?
real,dimension(..), intent(in) :: x
logical,intent(in) :: res
k = k + 1
if (is_contiguous (x) .eqv. res) return
print *, "Failure of test", k
stop "FAIL"
  end subroutine test
end program

Maybe something else needs to be updated.

Furthermore, should type(*), dimension(..) be allowed?  Opinions?
I tend to think so.  Does this need explicit coding as for e.g. SIZEOF,
or are there better ways?

[Bug fortran/45424] [F08] Add IS_CONTIGUOUS intrinsic

2018-12-27 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=45424

--- Comment #5 from Harald Anlauf  ---
Looking at the F2k18 draft, I see some updates and clarifications:

16.9.105 IS_CONTIGUOUS (ARRAY)
Description. Array contiguity test (8.5.7).
Class. Inquiry function.
Argument. ARRAY may be of any type. It shall be assumed-rank or an array. If it
is a pointer it shall be associated.
Result Characteristics. Default logical scalar.
Result Value. The result has the value true if ARRAY has rank zero or is
contiguous, and false otherwise.

[Example elided]

The clarification about rank zero is certainly helpful.

Furthermore:

8.5.7 CONTIGUOUS attribute

NOTE 1
If a derived type has only one component that is not zero-sized, it is
processor dependent whether a structure component of a contiguous array
of that type is contiguous. That is, the derived type might contain padding
on some processors.

This gives some freedom for a "conservative" implementation of the
intrinsic.

[Bug fortran/88579] Calculating power of powers of two

2018-12-23 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=88579

--- Comment #3 from Harald Anlauf  ---
Suggested testcase for the patch in comment #1, derived from power_7.f90:

! { dg-do run }
! { dg-additional-options "-fdump-tree-original" }
! Test optimizations for bases that are powers of 2.
program p
  integer:: i
  integer(8) :: v
   v = 1
   do i=1,7
  v = v * 256_8
  if (v /= 256_8 ** i) stop 1
   end do
   v = 1
   do i=1,3
  v = v * 65536_8
  if (v /= 65536_8 ** i) stop 2
   end do
 end program p
! { dg-final { scan-tree-dump-not "_gfortran_pow" "original" } }


Don't know how to handle optimizations for (-2**m)**n, maybe someone
with better knowledge of the frontend can drop a hint.

[Bug testsuite/80661] make check-gcc RUNTESTFLAGS="dg.exp=g*" runs all the tests in gcc.dg

2018-12-23 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=80661

Harald Anlauf  changed:

   What|Removed |Added

 CC||anlauf at gmx dot de

--- Comment #2 from Harald Anlauf  ---
On OpenSUSE Leap 15 running

make check-fortran RUNTESTFLAGS='dg.exp=power_7.f90'

or

make check-fortran RUNTESTFLAGS='dg.exp=gfortran.dg/power_7.f90'

also runs the libgomp tests.  Weird.

[Bug fortran/88579] Calculating power of powers of two

2018-12-22 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=88579

--- Comment #1 from Harald Anlauf  ---
OK, here's my proof-of-concept patch (not cleaned up):

Index: gcc/fortran/trans-expr.c
===
--- gcc/fortran/trans-expr.c(revision 267353)
+++ gcc/fortran/trans-expr.c(working copy)
@@ -3068,7 +3068,8 @@
  se->expr = build_int_cst (TREE_TYPE (lse.expr), 1);
  return;
}
-  else if (v == 2 || v == 4 || v == 8 || v == 16)
+  //  else if (v == 2 || v == 4 || v == 8 || v == 16)
+  else if (v > 1 && ((v & (v-1)) == 0))
{
  /* 2**n = 1<= 8)
+   {
+ int e = wi::popcount (v-1);
+ shift = fold_build2_loc (input_location, MULT_EXPR,
+  TREE_TYPE (rse.expr),
+  build_int_cst (TREE_TYPE (rse.expr), e),
+  rse.expr);
+   }
+#if 0
  else if (v == 8)
shift = fold_build2_loc (input_location, MULT_EXPR,
 TREE_TYPE (rse.expr),
@@ -3099,6 +3109,7 @@
 TREE_TYPE (rse.expr),
 build_int_cst (TREE_TYPE (rse.expr), 4),
 rse.expr);
+#endif
  else
gcc_unreachable ();


Running

make check-fortran RUNTESTFLAGS='dg.exp=power*.f90'

passes cleanly, but for some reason my setup always wants to run the
libgomp tests...

[Bug fortran/85544] [7/8/9 Regression] ICE in gfc_conv_scalarized_array_ref, at fortran/trans-array.c:3385

2018-12-22 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=85544

--- Comment #13 from Harald Anlauf  ---
(In reply to Thomas Koenig from comment #12)
> (In reply to Harald Anlauf from comment #10)
> 
> > Handling positive powers of 2 should be straightforward:
> > 
> > The condition is sth. like
> > 
> >   if (v > 1 && (v & (v-1) == 0))
> > 
> > and the exponent is derived by bit-counting the number of ones in (v-1)...
> 
> ... which is something I (currently) do not know to do in the
> front end.

Since you already have

  HOST_WIDE_INT v;

you could use wi::popcount (v-1).

> Otherwise: Patches welcome (as always :-)

I'm afraid removing some of your code would cross the magic 10 lines mark...

[Bug fortran/85544] [7/8/9 Regression] ICE in gfc_conv_scalarized_array_ref, at fortran/trans-array.c:3385

2018-12-22 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=85544

--- Comment #10 from Harald Anlauf  ---
(In reply to Thomas Koenig from comment #8)
>   * trans-expr.c (gfc_conv_power_op): Handle cases of 1**integer,
>   (2|4|8|16) ** integer and (-1) ** integer.

Handling positive powers of 2 should be straightforward:

The condition is sth. like

  if (v > 1 && (v & (v-1) == 0))

and the exponent is derived by bit-counting the number of ones in (v-1)...

[Bug tree-optimization/88533] [9 Regression] Higher performance penalty of array-bounds checking for sparse-matrix vector multiply

2018-12-18 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=88533

--- Comment #9 from Harald Anlauf  ---
(In reply to Richard Biener from comment #8)
> Created attachment 45252 [details]
> patch
> 
> Even though the patch doesn't hoist the invariant condition the speed is
> back with it.
> 
> Can you verify that?

I tried this just this patch on top of the 9-revision previously used and
get:

baseline + -funroll-loops -fcheck=bounds :

7: 1.56
8: 1.56
9: 1.93 (unmodified)
9: 1.63 (patched)

baseline + -O3 -funroll-loops -fcheck=bounds :

7: 1.56
8: 1.39
9: 1.57 (unmodified)
9: 1.38 (patched)

Yes, the speed is back for the testcase.

Thanks for the quick fix!

[Bug fortran/88533] [9 Regression] Higher performance penalty of array-bounds checking for sparse-matrix vector multiply

2018-12-17 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=88533

--- Comment #4 from Harald Anlauf  ---
Without CONTIGUOUS, I see -O3 brings gcc-9 to the level of gcc-7 or gcc-8:

baseline + -O3 -funroll-loops -fcheck=bounds :

7: 1.57
8: 1.40
9: 1.57

baseline + -O3 -funroll-loops -fcheck=bounds -fno-tree-ch :

7: 1.76
8: 1.55
9: 1.54

So there's something between -O2 and -O3 that helps sometimes.

[Bug fortran/88533] [9 Regression] Higher performance penalty of array-bounds checking for sparse-matrix vector multiply

2018-12-17 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=88533

--- Comment #3 from Harald Anlauf  ---
(In reply to Thomas Koenig from comment #2)
> Strange.
> 
> I ran the code (with the data) a few times on my Ryzen 7 home
> system.
> 
> Here are some timings (run 10 times):
[snipped]
> Is it possible that the data size of the problem is just at
> the edge of cache size, so that (depending on what else happens
> on the system) it is possible to either get a lot of cache misses
> or not?

The matrix has ~ 250k real elements (~ 1MB), and the meta-data is
roughly the same size, so everything should easily fit into L3,
but probably not into L2.  (My machine reports 6 MB (L3?) cache).

I do not see significant variations in runtime on my system
(but I did usually average over 3 runs and made sure this machine
had no load), and certainly not those that you found.

I perused the vectorization report from Intel (it does heavy inlining
and seems to see the actual arguments) and found that the code can be
further optimized by declaring the array dummy arguments to subroutine
csc_times_vector as CONTIGUOUS, by adding after line 11:

  CONTIGUOUS :: a, ia, ja, x, y

This strongly reduces the runtime, e.g.:

baseline + -funroll-loops + CONTIGUOUS :

7: 0.74
8: 0.77
9: 0.73

(Now *that* is really good!  The same level as PGI on my machine.)

baseline + -funroll-loops -fcheck=bounds + CONTIGUOUS :

7: 1.50
8: 1.36
9: 1.63

(Note the drop in runtime for gcc-8)

baseline + -funroll-loops -fno-tree-ch -fcheck=bounds + CONTIGUOUS :

7: 1.52
8: 1.51
9: 1.52

[Bug fortran/88533] [9 Regression] Higher performance penalty of array-bounds checking for sparse-matrix vector multiply

2018-12-17 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=88533

--- Comment #1 from Harald Anlauf  ---
Created attachment 45250
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=45250=edit
Sparse matrix meta-data

[Bug fortran/88533] New: [9 Regression] Higher performance penalty of array-bounds checking for sparse-matrix vector multiply

2018-12-17 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=88533

Bug ID: 88533
   Summary: [9 Regression] Higher performance penalty of
array-bounds checking for sparse-matrix vector
multiply
   Product: gcc
   Version: 9.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: anlauf at gmx dot de
  Target Milestone: ---

Created attachment 45249
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=45249=edit
Fortran code

I am seeing an increased performance penalty due to array-bounds checking,
in particular for sparse-matrix (CSC) vector multiplication.

The attached, semi-reduced test case, which only needs the provided meta-data
but otherwise uses random elements, should be sufficient for demonstration.

I have tested on an i5-8250U and tuned the "outer loop" so that the testcase
runs in 1-2 seconds on that machine.  For that purpose, I have used some
feedback provided to my initial posting on gcc-help, see
https://gcc.gnu.org/ml/gcc-help/2018-12/msg00041.html

Tested compilers:

gcc-7.3.1 20180323 [gcc-7-branch revision 258812]
gcc-8.2.1 20181202
gcc-9.0.0 20181214

baseline options: -O2 -ftree-vectorize -g -march=skylake -mfpmath=sse

7: 1.12
8: 1.12
9: 1.12

baseline + -funroll-loops :

7: 1.00
8: 1.00
9: 0.99

baseline + -funroll-loops -fcheck=bounds :

7: 1.56
8: 1.56
9: 1.93

baseline + -funroll-loops -fcheck=bounds -fno-tree-ch :

7: 1.78
8: 1.80
9: 1.83


baseline + -funroll-loops -fno-tree-ch :

7: 1.05
8: 1.09
9: 1.09

Preliminary conclusions:

- -funroll-loops is helpful here
- -fcheck=bounds is quite expensive with current 9.0
- -fno-tree-ch brings the different versions in line,
   it benefits 9, but is worse for 7 and 8
- there a no options above that bring 9 to the level of 7 and 8
  as long as bounds-checking is desired.

[Bug fortran/88399] program segmentation faults when out-of-memory

2018-12-13 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=88399

Harald Anlauf  changed:

   What|Removed |Added

 CC||anlauf at gmx dot de

--- Comment #2 from Harald Anlauf  ---
AFAICT the problem seems fixed since 7.1, it is still present at 6.1.

Looking at the tree dump, one can see that gfortran <= 6 initialized
the derived type even when the malloc failed.  It is now protected by
an appropriate if/goto.

I recommend to update to 7.1+

[Bug fortran/87764] gfortran crashes with illegal code

2018-12-12 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=87764

Harald Anlauf  changed:

   What|Removed |Added

 CC||anlauf at gmx dot de

--- Comment #2 from Harald Anlauf  ---
(In reply to Dominique d'Humieres from comment #1)
> Confirmed from 4.8 up to trunk (9.0). An instrumented compiler gives
> 
> f951: Warning: No location in statement
> ../../work/gcc/fortran/trans.c:1768:39: runtime error: member access within
> null pointer of type 'struct gfc_linebuf'
> f951: internal compiler error: Segmentation fault: 11

The warning in comment#0 would be restored by the patch:

Index: gcc/fortran/trans.c
===
--- gcc/fortran/trans.c (revision 267065)
+++ gcc/fortran/trans.c (working copy)
@@ -1765,8 +1765,11 @@
 void
 gfc_set_backend_locus (locus * loc)
 {
-  gfc_current_backend_file = loc->lb->file;
-  input_location = loc->lb->location;
+  if (loc->lb)
+{
+  gfc_current_backend_file = loc->lb->file;
+  input_location = loc->lb->location;
+}
 }

However, this papers over the issue that the locus is not properly set.

[Bug fortran/85750] [7/8/9 Regression] Default initialization of derived type array missing

2018-12-12 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=85750

--- Comment #4 from Harald Anlauf  ---
(In reply to Stephan Kramer from comment #0)

Workaround:

>   function make_list(i)
> integer, intent(in) :: i
> type(ilist), dimension(2) :: make_list

  make_list = ilist()

> make_list(i)%count = 1
> 
>   end function make_list

[Bug fortran/85750] [7/8/9 Regression] Default initialization of derived type array missing

2018-12-12 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=85750

Harald Anlauf  changed:

   What|Removed |Added

 CC||anlauf at gmx dot de

--- Comment #3 from Harald Anlauf  ---
Looking at the dump-tree and comparing the original code with a
variant with the DT component ptr commented out, one wonders where
the initialization of the function result got lost in the original variant.

Without ptr (either pointer or allocatable), one gets the expected result.

[Bug fortran/85544] [7/8/9 Regression] ICE in gfc_conv_scalarized_array_ref, at fortran/trans-array.c:3385

2018-12-12 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=85544

Harald Anlauf  changed:

   What|Removed |Added

 CC||anlauf at gmx dot de

--- Comment #5 from Harald Anlauf  ---
(In reply to Dominique d'Humieres from comment #2)
> The test in comment 0 compiles with -fno-frontend-optimize.

It might make sense to update $subject.

When gfc_conv_array_ref() is reached with -ffrontend-optimize being set,
its arguments are already bad.

[Bug fortran/84779] [7/8/9 Regression] Compiling gfortran.fortran-torture/execute/entry_4.f90 with -O1 or -Os and -fdefault-integer-8 gives an ICE

2018-12-12 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=84779

--- Comment #4 from Harald Anlauf  ---
(In reply to Dominique d'Humieres from comment #3)
> The code in comment 2 compiles for me with -fdefault-integer-8 (I get the
> error without it).

Oh, now I see that the issue is -O1 and/or -Os,
whereas -O0, -Og, -O2, -O3 work.

I looked also at the dump-tree-optimized for e2 being logical(4)
or logical(8) and wondered why this can be so different.

[Bug fortran/84779] [7/8/9 Regression] Compiling gfortran.fortran-torture/execute/entry_4.f90 with -O1 or -Os and -fdefault-integer-8/9 gives an ICE

2018-12-12 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=84779

Harald Anlauf  changed:

   What|Removed |Added

 CC||anlauf at gmx dot de

--- Comment #2 from Harald Anlauf  ---
(In reply to Dominique d'Humieres from comment #0)
> Compiling gfortran.fortran-torture/execute/entry_4.f90 with -O1 or -Os and
> -fdefault-integer-8 gives an ICE for gcc4.9 up to trunk (8.0)
> 
> during RTL pass: expand
> /opt/gcc/p_work/gcc/testsuite/gfortran.fortran-torture/execute/entry_4.f90:
> 14:0:
> 
>   logical e2
>  
> internal compiler error: in gen_lowpart_general, at rtlhooks.c:63

Reducing further gives a traceback:

complex function f2 (a)
implicit none
integer(8) a
!   logical(4) e2   ! Compiles
logical(8) e2   ! ICE
entry e2 (a)
if (a .gt. 0) then
  e2 = a .lt. 46
else
  f2 = 45
endif
end function

during RTL pass: expand
pr84779.f90:5:0:

5 |   logical(8) e2   ! ICE
  | 
internal compiler error: in gen_lowpart_general, at rtlhooks.c:63
0xc334a8 gen_lowpart_general(machine_mode, rtx_def*)
../../trunk/gcc/rtlhooks.c:63
0x90b604 extract_bit_field_1
../../trunk/gcc/expmed.c:1763
0x90c34c extract_bit_field(rtx_def*, poly_int<1u, unsigned long>, poly_int<1u,
unsigned long>, int, rtx_def*, machine_mode, machine_mode, bool, rtx_def**)
../../trunk/gcc/expmed.c:2097
0x928e5f expand_expr_real_1(tree_node*, rtx_def*, machine_mode,
expand_modifier, rtx_def**, bool)
../../trunk/gcc/expr.c:11043
0x9283cb expand_expr_real_1(tree_node*, rtx_def*, machine_mode,
expand_modifier, rtx_def**, bool)
../../trunk/gcc/expr.c:9858
0x7f2193 expand_expr
../../trunk/gcc/expr.h:279
0x7f2193 expand_return
../../trunk/gcc/cfgexpand.c:3588
0x7f2193 expand_gimple_stmt_1
../../trunk/gcc/cfgexpand.c:3691
0x7f2193 expand_gimple_stmt
../../trunk/gcc/cfgexpand.c:3818
0x7f47ff expand_gimple_basic_block
../../trunk/gcc/cfgexpand.c:5854
0x7fa8ee execute
../../trunk/gcc/cfgexpand.c:6476


Without -fdefault-integer-8 one gets:
pr84779.f90:5:15:

5 |   logical(8) e2   ! ICE
  |   1
Error: ENTRY result e2 can't be of type LOGICAL(8) in FUNCTION f2 at (1)

I think this is wrong and maybe points to where to look.

[Bug fortran/88364] [9 Regression] Wrong-code due to CLOBBER

2018-12-09 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=88364

--- Comment #5 from Harald Anlauf  ---
(In reply to Thomas Koenig from comment #4)
> A simple fix is not to do the clobbers if there is a reference:

The fix in c#4 fixes the testcase in c#2 for me.
I'll give it a try.

[Bug fortran/71860] [7/8/9 Regression] [OOP] ICE on pointing to null(mold), verify_gimple failed

2018-12-07 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=71860

Harald Anlauf  changed:

   What|Removed |Added

 CC||anlauf at gmx dot de

--- Comment #5 from Harald Anlauf  ---
Cannot reproduce with 9-trunk rev. 266866, nor gfortran 8.2.1.

Also works for me with:
GNU Fortran (SUSE Linux) 7.3.1 20180323 [gcc-7-branch revision 258812]

Fixed?

[Bug libfortran/88411] [9 Regression] Random crashes for ASYNCHRONOUS writes (bad locking?)

2018-12-07 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=88411

--- Comment #1 from Harald Anlauf  ---
Further data points:
- removing the asynchronous='yes' for the first OPEN has no effect,
- removing the asynchronous='yes' for the second OPEN makes the problem
  disappear

[Bug libfortran/88411] New: [9 Regression] Random crashes for ASYNCHRONOUS writes (bad locking?)

2018-12-07 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=88411

Bug ID: 88411
   Summary: [9 Regression] Random crashes for ASYNCHRONOUS writes
(bad locking?)
   Product: gcc
   Version: 9.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: libfortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: anlauf at gmx dot de
  Target Milestone: ---

Created attachment 45187
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=45187=edit
Compile with -fopenmp, run with OMP_NUM_THREAD=2 or higher.

The attached code crashes randomly with 9.0 trunk gfortran when compiled
with -fopenmp and running with 2 or more threads:

At line 22 of file gfcbug153.f90 (unit = 10, file = 'file2.dat')
Fortran runtime error: Write exceeds length of DIRECT access record

Error termination. Backtrace:
#0  0x7fc02792019d in write_buf
at ../../../trunk/libgfortran/io/transfer.c:906
#1  0x7fc027920200 in unformatted_write
at ../../../trunk/libgfortran/io/transfer.c:1198
#2  0x40117f in gfcbug153
at /work/dwd/git/dace_code/gfcbug153.f90:22
#3  0x401302 in main
at /work/dwd/git/dace_code/gfcbug153.f90:25

Running the code under valgrind prints lots of

==30672== Thread #1: lock order "0x52BF360 before 0x647FBF0" violated
==30672== 
==30672== Observed (incorrect) order is: acquisition of lock at 0x647FBF0
==30672==at 0x4C3291C: ??? (in
/usr/lib64/valgrind/vgpreload_helgrind-amd64-linux.so)
==30672==by 0x506F7D1: __gthread_mutex_trylock (gthr-default.h:757)
==30672==by 0x506F7D1: get_gfc_unit (unit.c:380)
==30672==by 0x505C462: _gfortran_st_close (close.c:64)
==30672==by 0x4012CB: MAIN__ (gfcbug153.f90:24)
==30672==by 0x401302: main (gfcbug153.f90:25)
==30672== 
==30672==  followed by a later acquisition of lock at 0x52BF360
==30672==at 0x4C3273C: ??? (in
/usr/lib64/valgrind/vgpreload_helgrind-amd64-linux.so)
==30672==by 0x507043B: __gthread_mutex_lock (gthr-default.h:748)
==30672==by 0x507043B: close_unit_1 (unit.c:735)
==30672==by 0x4012CB: MAIN__ (gfcbug153.f90:24)
==30672==by 0x401302: main (gfcbug153.f90:25)
==30672== 
==30672== Required order was established by acquisition of lock at 0x52BF360
==30672==at 0x4C3273C: ??? (in
/usr/lib64/valgrind/vgpreload_helgrind-amd64-linux.so)
==30672==by 0x506F73C: __gthread_mutex_lock (gthr-default.h:748)
==30672==by 0x506F73C: get_gfc_unit (unit.c:332)
==30672==by 0x50678E8: _gfortran_st_open (open.c:880)
==30672==by 0x400F82: MAIN__ (gfcbug153.f90:20)
==30672==by 0x401302: main (gfcbug153.f90:25)
==30672== 
==30672==  followed by a later acquisition of lock at 0x647FBF0
==30672==at 0x4C3273C: ??? (in
/usr/lib64/valgrind/vgpreload_helgrind-amd64-linux.so)
==30672==by 0x506F6A9: __gthread_mutex_lock (gthr-default.h:748)
==30672==by 0x506F6A9: insert_unit (unit.c:244)
==30672==by 0x506F8C7: get_gfc_unit (unit.c:356)
==30672==by 0x50678E8: _gfortran_st_open (open.c:880)
==30672==by 0x400F82: MAIN__ (gfcbug153.f90:20)
==30672==by 0x401302: main (gfcbug153.f90:25)
==30672== 
==30672==  Lock at 0x52BF360 was first observed
==30672==at 0x4C3273C: ??? (in
/usr/lib64/valgrind/vgpreload_helgrind-amd64-linux.so)
==30672==by 0x506F73C: __gthread_mutex_lock (gthr-default.h:748)
==30672==by 0x506F73C: get_gfc_unit (unit.c:332)
==30672==by 0x50678E8: _gfortran_st_open (open.c:880)
==30672==by 0x400A96: MAIN__ (gfcbug153.f90:11)
==30672==by 0x401302: main (gfcbug153.f90:25)
==30672==  Address 0x52bf360 is 0 bytes inside data symbol
"_gfortrani_unit_lock"
==30672== 
==30672==  Lock at 0x647FBF0 was first observed
==30672==at 0x4C3273C: ??? (in
/usr/lib64/valgrind/vgpreload_helgrind-amd64-linux.so)
==30672==by 0x506F6A9: __gthread_mutex_lock (gthr-default.h:748)
==30672==by 0x506F6A9: insert_unit (unit.c:244)
==30672==by 0x506F8C7: get_gfc_unit (unit.c:356)
==30672==by 0x50678E8: _gfortran_st_open (open.c:880)
==30672==by 0x400F82: MAIN__ (gfcbug153.f90:20)
==30672==by 0x401302: main (gfcbug153.f90:25)
==30672==  Address 0x647fbf0 is 224 bytes inside a block of size 752 alloc'd
==30672==at 0x4C31645: calloc (in
/usr/lib64/valgrind/vgpreload_helgrind-amd64-linux.so)
==30672==by 0x4E61C42: _gfortrani_xcalloc (memory.c:83)
==30672==by 0x506F667: insert_unit (unit.c:233)
==30672==by 0x506F8C7: get_gfc_unit (unit.c:356)
==30672==by 0x50678E8: _gfortran_st_open (open.c:880)
==30672==by 0x400F82: MAIN__ (gfcbug153.f90:20)
==30672==by 0x401302: main (gfcbug153.f90:25)
==30672==  Block was alloc'd by thread #1

etc.

[Bug fortran/88304] [9 Regression] ICE in use_pointer_in_frame, at tree-nested.c:267

2018-12-07 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=88304

--- Comment #15 from Harald Anlauf  ---
(In reply to Jakub Jelinek from comment #14)
> Author: jakub
> Date: Thu Dec  6 10:28:31 2018
> New Revision: 266847
> 
> URL: https://gcc.gnu.org/viewcvs?rev=266847=gcc=rev

This fixes the original testcase, but not the following variant,
which crashes with a similar backtrace:

MODULE mo_occ
  implicit none
  integer :: ncid
contains
  function nf90_inquire_dimension(ncid, dimid, name, len)
integer,intent( in) :: ncid, dimid
character(*), optional, intent(out) :: name
integer,  optional, intent(out) :: len
integer :: nf90_inquire_dimension
  end function nf90_inquire_dimension
  subroutine read_gpsro_netcdf ()
  contains
function dimlen (dim)
  integer ,intent(in) :: dim
  integer :: dimlen
  integer :: status
  integer :: dimids (10)
  status = nf90_Inquire_Dimension (ncid, dimids(dim), len=dimlen)
end function dimlen
  end subroutine read_gpsro_netcdf
end module mo_occ


% gfc-trunk -c gfcbug152-v3.f90 
gfcbug152-v3.f90:11:0:

   11 |   subroutine read_gpsro_netcdf ()
  | 
internal compiler error: tree check: expected tree that contains 'decl common'
structure, have 'mem_ref' in use_pointer_in_frame, at tree-nested.c:267
0x5ed193 tree_contains_struct_check_failed(tree_node const*,
tree_node_structure_enum, char const*, int, char const*)
../../trunk/gcc/tree.c:9929
0xd44250 contains_struct_check(tree_node*, tree_node_structure_enum, char
const*, int, char const*)
../../trunk/gcc/tree.h:3271
0xd44250 use_pointer_in_frame
../../trunk/gcc/tree-nested.c:267
0xd4a745 convert_local_reference_stmt
../../trunk/gcc/tree-nested.c:2327
0x9d8a56 walk_gimple_stmt(gimple_stmt_iterator*, tree_node*
(*)(gimple_stmt_iterator*, bool*, walk_stmt_info*), tree_node* (*)(tree_node**,
int*, void*), walk_stmt_info*)
../../trunk/gcc/gimple-walk.c:568
0x9d8c70 walk_gimple_seq_mod(gimple**, tree_node* (*)(gimple_stmt_iterator*,
bool*, walk_stmt_info*), tree_node* (*)(tree_node**, int*, void*),
walk_stmt_info*)
../../trunk/gcc/gimple-walk.c:51
0x9d8bb1 walk_gimple_stmt(gimple_stmt_iterator*, tree_node*
(*)(gimple_stmt_iterator*, bool*, walk_stmt_info*), tree_node* (*)(tree_node**,
int*, void*), walk_stmt_info*)
../../trunk/gcc/gimple-walk.c:631
0x9d8c70 walk_gimple_seq_mod(gimple**, tree_node* (*)(gimple_stmt_iterator*,
bool*, walk_stmt_info*), tree_node* (*)(tree_node**, int*, void*),
walk_stmt_info*)
../../trunk/gcc/gimple-walk.c:51
0x9d8b11 walk_gimple_stmt(gimple_stmt_iterator*, tree_node*
(*)(gimple_stmt_iterator*, bool*, walk_stmt_info*), tree_node* (*)(tree_node**,
int*, void*), walk_stmt_info*)
../../trunk/gcc/gimple-walk.c:595
0x9d8c70 walk_gimple_seq_mod(gimple**, tree_node* (*)(gimple_stmt_iterator*,
bool*, walk_stmt_info*), tree_node* (*)(tree_node**, int*, void*),
walk_stmt_info*)
../../trunk/gcc/gimple-walk.c:51
0xd440c8 walk_body
../../trunk/gcc/tree-nested.c:703
0xd44118 walk_function
../../trunk/gcc/tree-nested.c:714
0xd44118 walk_all_functions
../../trunk/gcc/tree-nested.c:779
0xd4e094 lower_nested_functions(tree_node*)
../../trunk/gcc/tree-nested.c:3482
0x836330 cgraph_node::analyze()
../../trunk/gcc/cgraphunit.c:673
0x8397b9 analyze_functions
../../trunk/gcc/cgraphunit.c:1126
0x83a8a2 symbol_table::finalize_compilation_unit()
../../trunk/gcc/cgraphunit.c:2835

[Bug fortran/88304] [9 Regression] ICE in use_pointer_in_frame, at tree-nested.c:267

2018-12-04 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=88304

--- Comment #7 from Harald Anlauf  ---
(In reply to kargl from comment #6)
> (In reply to Harald Anlauf from comment #5)
> > 
> > A derived type with component initialization (like t_fileinfo) should
> > implicitly get the SAVE attribute, which appears to be lost here.
> > Adding it explicitly removes the ICE.  Thus a front-end issue?
> 
> The F2018 standard (n2146.pdf, p. 78) says
> 
> Explicit initialization in a type declaration statement (8.2)
> overrides default initialization (see NOTE 7.32).  Unlike explicit
> initialization, default initialization does not imply that the object
> has the SAVE attribute.
> 
> HTH

Thanks for pointing this out.  And replacing

type(t_fileinfo), save :: gattr ! No ICE

by

type(t_fileinfo)   :: gattr = t_fileinfo() ! No ICE

produces identical code.  So I take back the possible wrong-code issue.
Only the ICE remains.

[Bug fortran/88304] [9 Regression] ICE in use_pointer_in_frame, at tree-nested.c:267

2018-12-04 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=88304

--- Comment #5 from Harald Anlauf  ---
(In reply to Richard Biener from comment #4)
> Confirmed.  We do not expect
> 
> CHAIN.10->gattr = {CLOBBER};
> 
> I believe the FE inserts these now to better share stack slots:

Thanks for pointing to the gimple.  Looking at it with my zero knowledge,
it looks in addition to a wrong code issue.  With this is mind, I further
reduced the complete testcase to this:

MODULE mo_feedbk
  implicit none

  type t_fileinfo
 integer :: nex = -1
 integer :: pad = 0
  end type t_fileinfo

  interface nf90_get_att
 module procedure nf90_get_att_one_FourByteInt
  end interface
contains
  function nf90_get_att_one_FourByteInt(ncid, varid, name, values)
integer,  intent( in) :: ncid, varid
character(len=*), intent( in) :: name
integer , intent(out) :: values
integer   :: nf90_get_att_one_FourByteInt
  end function nf90_get_att_one_FourByteInt

  subroutine convert_cof ()
integer:: dummy = -1
!   type(t_fileinfo), save :: gattr ! No ICE
type(t_fileinfo)   :: gattr ! ICE
  contains
subroutine open_input
  integer :: rc
  rc = nf90_get_att (0, 0, "experiment", dummy ) ! OK
  rc = nf90_get_att (0, 0, "experiment", gattr%nex ) ! ICE
end subroutine open_input
  end subroutine convert_cof
end module mo_feedbk


A derived type with component initialization (like t_fileinfo) should
implicitly get the SAVE attribute, which appears to be lost here.
Adding it explicitly removes the ICE.  Thus a front-end issue?

[Bug fortran/88298] Bogus conversion warning for CSHIFT with -fno-range-check -m64

2018-12-03 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=88298

--- Comment #1 from Harald Anlauf  ---
The problem appears here:

Breakpoint 1, gfc_resolve_cshift (f=0x2431950, array=0x23bc1f0, 
shift=0x23bc880, dim=0x23bcce0) at ../../trunk/gcc/fortran/iresolve.c:836
836   gfc_resolve_dim_arg (dim);
(gdb) p dim->ts.kind
$1 = 4
(gdb) n
838   if (dim->ts.kind != shift->ts.kind)
(gdb) p dim->ts.kind
$2 = 8
(gdb) l
833 }
834   else
835 {
836   gfc_resolve_dim_arg (dim);
837   /* Convert dim to shift's kind to reduce variations.  */
838   if (dim->ts.kind != shift->ts.kind)
839 gfc_convert_type_warn (dim, >ts, 2, 0);
840 }
841 }
842

Function gfc_resolve_dim_arg converts the kind and is the cause of the
warning.

The above code points to this rather old commit:

r130391 | jvdelisle | 2007-11-24 01:25:01 +0100 (Sat, 24 Nov 2007) | 20 lines

However, the real point probably is that gfc_index_integer_kind = 8 for -m64,
and gfc_resolve_dim_arg does the conversion from default kind = 4 to the
gfc_index_integer_kind:

  if (dim->ts.kind != gfc_index_integer_kind)
{
  gfc_typespec ts;

  gfc_clear_ts ();
  ts.type = BT_INTEGER;
  ts.kind = gfc_index_integer_kind;

  gfc_convert_type_warn (dim, , 2, 0);
}

Deep down the -f(no-)range-check apparently controls whether we get
the warning.

Wouldn't it be better/safer to convert dim/shift to their largest kind
involved?

[Bug fortran/88299] [9 Regression] COMMON in a legacy module produces bogus warnings in dependent code

2018-12-03 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=88299

--- Comment #1 from Harald Anlauf  ---
The warning was introduced in:

r260705 | janus | 2018-05-25 08:09:10 +0200 (Fri, 25 May 2018) | 16 lines

2018-05-25  Janus Weil  

PR fortran/85839
* match.c (gfc_match_block_data): Call gfc_notify_std to warn about
an obsolescent feature in Fortran 2018.
(gfc_match_equivalence): Ditto.
* resolve.c (resolve_common_blocks): Ditto.
(gfc_resolve_forall): Ditto.
* symbol.c (gfc_define_st_label): Ditto.


Maybe the warning can be restricted to those files / compilation units
where the COMMON is declared?

The COMMON unfortunately pollutes all upstream module files (*.mod),
even if no symbol is imported (see e.g. mod2 in the testcase).

[Bug fortran/88304] [9 Regression] ICE in use_pointer_in_frame, at tree-nested.c:267

2018-12-03 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=88304

--- Comment #3 from Harald Anlauf  ---
Created attachment 45147
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=45147=edit
Minimal netcdf-fortran part for the reproducer

Compile the netcdf.f90 header before the testcase.

[Bug fortran/88304] [9 Regression] ICE in use_pointer_in_frame, at tree-nested.c:267

2018-12-02 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=88304

--- Comment #1 from Harald Anlauf  ---
No special options used, just:

% gfc-trunk -c -I/opt/gcc/9/pkg/netcdf/include gfcbug152.f90

(where above path hold the gfortran-9 specific netcdf.mod & friends).

[Bug fortran/88304] New: [9 Regression] ICE in use_pointer_in_frame, at tree-nested.c:267

2018-12-02 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=88304

Bug ID: 88304
   Summary: [9 Regression] ICE in use_pointer_in_frame, at
tree-nested.c:267
   Product: gcc
   Version: 9.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: anlauf at gmx dot de
  Target Milestone: ---

Created attachment 45136
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=45136=edit
Reproducer

Current 9-trunk crashes for me on the attached code with the following:

gfcbug152.f90:33:0:

   33 |   subroutine convert_cof ()
  | 
internal compiler error: tree check: expected tree that contains 'decl common'
structure, have 'component_ref' in use_pointer_in_frame, at tree-nested.c:267
0x5ed50f tree_contains_struct_check_failed(tree_node const*,
tree_node_structure_enum, char const*, int, char const*)
../../trunk/gcc/tree.c:9929
0xd43bc0 contains_struct_check(tree_node*, tree_node_structure_enum, char
const*, int, char const*)
../../trunk/gcc/tree.h:3268
0xd43bc0 use_pointer_in_frame
../../trunk/gcc/tree-nested.c:267
0xd4a035 convert_local_reference_stmt
../../trunk/gcc/tree-nested.c:2312
0x9d8b66 walk_gimple_stmt(gimple_stmt_iterator*, tree_node*
(*)(gimple_stmt_iterator*, bool*, walk_stmt_info*), tree_node* (*)(tree_node**,
int*, void*), walk_stmt_info*)
../../trunk/gcc/gimple-walk.c:568
0x9d8d80 walk_gimple_seq_mod(gimple**, tree_node* (*)(gimple_stmt_iterator*,
bool*, walk_stmt_info*), tree_node* (*)(tree_node**, int*, void*),
walk_stmt_info*)
../../trunk/gcc/gimple-walk.c:51
0x9d8cc1 walk_gimple_stmt(gimple_stmt_iterator*, tree_node*
(*)(gimple_stmt_iterator*, bool*, walk_stmt_info*), tree_node* (*)(tree_node**,
int*, void*), walk_stmt_info*)
../../trunk/gcc/gimple-walk.c:631
0x9d8d80 walk_gimple_seq_mod(gimple**, tree_node* (*)(gimple_stmt_iterator*,
bool*, walk_stmt_info*), tree_node* (*)(tree_node**, int*, void*),
walk_stmt_info*)
../../trunk/gcc/gimple-walk.c:51
0x9d8c21 walk_gimple_stmt(gimple_stmt_iterator*, tree_node*
(*)(gimple_stmt_iterator*, bool*, walk_stmt_info*), tree_node* (*)(tree_node**,
int*, void*), walk_stmt_info*)
../../trunk/gcc/gimple-walk.c:595
0x9d8d80 walk_gimple_seq_mod(gimple**, tree_node* (*)(gimple_stmt_iterator*,
bool*, walk_stmt_info*), tree_node* (*)(tree_node**, int*, void*),
walk_stmt_info*)
../../trunk/gcc/gimple-walk.c:51
0x9d8c21 walk_gimple_stmt(gimple_stmt_iterator*, tree_node*
(*)(gimple_stmt_iterator*, bool*, walk_stmt_info*), tree_node* (*)(tree_node**,
int*, void*), walk_stmt_info*)
../../trunk/gcc/gimple-walk.c:595
0x9d8d80 walk_gimple_seq_mod(gimple**, tree_node* (*)(gimple_stmt_iterator*,
bool*, walk_stmt_info*), tree_node* (*)(tree_node**, int*, void*),
walk_stmt_info*)
../../trunk/gcc/gimple-walk.c:51
0xd43a38 walk_body
../../trunk/gcc/tree-nested.c:703
0xd43a88 walk_function
../../trunk/gcc/tree-nested.c:714
0xd43a88 walk_all_functions
../../trunk/gcc/tree-nested.c:779
0xd4d8c4 lower_nested_functions(tree_node*)
../../trunk/gcc/tree-nested.c:3467
0x8364b0 cgraph_node::analyze()
../../trunk/gcc/cgraphunit.c:673
0x839939 analyze_functions
../../trunk/gcc/cgraphunit.c:1126
0x83aa22 symbol_table::finalize_compilation_unit()
../../trunk/gcc/cgraphunit.c:2835
Please submit a full bug report,
with preprocessed source if appropriate.
Please include the complete backtrace with any bug report.
See <https://gcc.gnu.org/bugs/> for instructions.

% gfc-trunk --version
GNU Fortran (GCC) 9.0.0 20181202 (experimental)


Reprocing required netcdf-4.6 with netcdf-fortran-4.4.4 installed.

I will try to reduce the netcdf-fortran module files.

[Bug fortran/88300] New: [9 Regression] Bogus 'Labeled DO statement' for a labeled CONTINUE

2018-12-01 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=88300

Bug ID: 88300
   Summary: [9 Regression] Bogus 'Labeled DO statement' for a
labeled CONTINUE
   Product: gcc
   Version: 9.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: anlauf at gmx dot de
  Target Milestone: ---

I get with 9-trunk:

% cat gfcbug151.f90
subroutine gfcbug151 ()
!  goto 999
999 continue
end subroutine gfcbug151

% gfc-trunk -c -std=f2018 gfcbug151.f90
gfcbug151.f90:3:3:

3 | 999 continue
  |   1
Warning: Fortran 2018 obsolescent feature: Labeled DO statement at (1)

The message should be triggered on an actual DO statement,
not on a label that might have different uses.

  1   2   3   4   5   6   7   >