[Bug fortran/82009] [F08] ICE with block construct

2019-02-01 Thread jakub at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=82009

Jakub Jelinek  changed:

   What|Removed |Added

 Status|REOPENED|RESOLVED
 CC||jakub at gcc dot gnu.org
 Resolution|--- |DUPLICATE

--- Comment #12 from Jakub Jelinek  ---
Dup.

*** This bug has been marked as a duplicate of bug 89084 ***

[Bug fortran/82009] [F08] ICE with block construct

2018-07-06 Thread jvdelisle at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=82009

--- Comment #11 from Jerry DeLisle  ---
The missing local variable exists in the fortran dump and it shows as the first
 item in the namespace passed to gfc_process_block_locals. However, it has no
backend decl.

I do not understand enough to proceed

[Bug fortran/82009] [F08] ICE with block construct

2018-07-05 Thread jvdelisle at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=82009

--- Comment #10 from Jerry DeLisle  ---
In the tree dump, the declaration for idxs is missing for the first subroutine.
I have modified to the following example so one can see it is not symbol name
conflicts.

MODULE sparse_matrix_csx_benchmark_utils
  IMPLICIT NONE
CONTAINS  
  SUBROUTINE sparse_matrix_csr_benchmark ( )
WRITE(*,*) 'At*x: t1'
block
  integer, dimension(1), parameter :: idxs1=[1]
  integer :: i, idx
  do i = 1, size(idxs1)
 idx = idxs1(i)
  enddo
end block
  END SUBROUTINE sparse_matrix_csr_benchmark
  SUBROUTINE sparse_matrix_csc_benchmark ( )
WRITE(*,*) 'An*x: t2'
block
  integer, dimension(1), parameter :: idxs2=[1]
  integer :: i, idx
  do i = 1, size(idxs2)
 idx = idxs2(i)
  enddo
end block
  END SUBROUTINE sparse_matrix_csc_benchmark
END MODULE sparse_matrix_csx_benchmark_utils

program main
use sparse_matrix_csx_benchmark_utils

call sparse_matrix_csr_benchmark ()
call sparse_matrix_csc_benchmark ()

end program

and the tree dump:

sparse_matrix_csc_benchmark ()
{
  {
integer(kind=4) i;
integer(kind=4) idx;

{
  struct __st_parameter_dt dt_parm.0;

  dt_parm.0.common.filename = &"pr82009.f03"[1]{lb: 1 sz: 1};
  dt_parm.0.common.line = 15;
  dt_parm.0.common.flags = 128;
  dt_parm.0.common.unit = 6;
  _gfortran_st_write (_parm.0);
  _gfortran_transfer_character_write (_parm.0, &"An*x: t2"[1]{lb: 1 sz:
1}, 8);
  _gfortran_st_write_done (_parm.0);
}
i = 1;
while (1)
  {
{
  logical(kind=4) D.3777;

  D.3777 = i > 1;
  if (D.3777) goto L.3;
  idx = idxs2[(integer(kind=8)) i + -1];
  L.2:;
  i = i + 1;
}
  }
L.3:;
L.1:;
  }
}


sparse_matrix_csr_benchmark ()
{
  {
static integer(kind=4) idxs2[1] = {1};
integer(kind=4) i;
integer(kind=4) idx;

{
  struct __st_parameter_dt dt_parm.1;

  dt_parm.1.common.filename = &"pr82009.f03"[1]{lb: 1 sz: 1};
  dt_parm.1.common.line = 5;
  dt_parm.1.common.flags = 128;
  dt_parm.1.common.unit = 6;
  _gfortran_st_write (_parm.1);
  _gfortran_transfer_character_write (_parm.1, &"At*x: t1"[1]{lb: 1 sz:
1}, 8);
  _gfortran_st_write_done (_parm.1);
}
i = 1;
while (1)
  {
{
  logical(kind=4) D.3786;

  D.3786 = i > 1;
  if (D.3786) goto L.6;
  idx = idxs1[(integer(kind=8)) i + -1];
  L.5:;
  i = i + 1;
}
  }
L.6:;
L.4:;
  }
}


MAIN__ ()
{
  sparse_matrix_csr_benchmark ();
  sparse_matrix_csc_benchmark ();
}


__attribute__((externally_visible))
main (integer(kind=4) argc, character(kind=1) * * argv)
{
  static integer(kind=4) options.2[7] = {2116, 4095, 0, 1, 1, 0, 31};

  _gfortran_set_args (argc, argv);
  _gfortran_set_options (7, [0]);
  MAIN__ ();
  return 0;
}

[Bug fortran/82009] [F08] ICE with block construct

2018-07-04 Thread jvdelisle at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=82009

Jerry DeLisle  changed:

   What|Removed |Added

 Status|RESOLVED|REOPENED
 Resolution|FIXED   |---

--- Comment #9 from Jerry DeLisle  ---
(In reply to Dominique d'Humieres from comment #8)
> > Fixed on trunk. Closing
> 
> When compiling the original test, the ICE is gone but I get:
> 
> Undefined symbols for architecture x86_64:
>   "_idxs.3783", referenced from:
>   ___sparse_matrix_csx_benchmark_utils_MOD_sparse_matrix_csc_benchmark
> in ccP98FL2.o
>   "_idxs.3792", referenced from:
>   ___sparse_matrix_csx_benchmark_utils_MOD_sparse_matrix_csr_benchmark
> in ccP98FL2.o
> 
> This looks weird.

Agree, I added a main program to that test case and now I see similar, so
reopening.

[Bug fortran/82009] [F08] ICE with block construct

2018-07-04 Thread dominiq at lps dot ens.fr
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=82009

--- Comment #8 from Dominique d'Humieres  ---
> Fixed on trunk. Closing

When compiling the original test, the ICE is gone but I get:

Undefined symbols for architecture x86_64:
  "_idxs.3783", referenced from:
  ___sparse_matrix_csx_benchmark_utils_MOD_sparse_matrix_csc_benchmark in
ccP98FL2.o
  "_idxs.3792", referenced from:
  ___sparse_matrix_csx_benchmark_utils_MOD_sparse_matrix_csr_benchmark in
ccP98FL2.o

This looks weird.

[Bug fortran/82009] [F08] ICE with block construct

2018-07-04 Thread jvdelisle at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=82009

Jerry DeLisle  changed:

   What|Removed |Added

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

--- Comment #7 from Jerry DeLisle  ---
Fixed on trunk. Closing

[Bug fortran/82009] [F08] ICE with block construct

2018-07-04 Thread jvdelisle at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=82009

--- Comment #6 from Jerry DeLisle  ---
Author: jvdelisle
Date: Wed Jul  4 18:08:16 2018
New Revision: 262416

URL: https://gcc.gnu.org/viewcvs?rev=262416=gcc=rev
Log:
2018-07-04  Jerry DeLisle  

PR fortran/82009
* trans-decl.c (gfc_process_block_locals): Delete assert and set
saved_local_decls = NULL_TREE.

* gfortran.dg/block_16.f08. New test.

Added:
trunk/gcc/testsuite/gfortran.dg/block_16.f08
Modified:
trunk/gcc/fortran/ChangeLog
trunk/gcc/fortran/trans-decl.c
trunk/gcc/testsuite/ChangeLog

[Bug fortran/82009] [F08] ICE with block construct

2018-06-23 Thread jvdelisle at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=82009

Jerry DeLisle  changed:

   What|Removed |Added

 CC||jvdelisle at gcc dot gnu.org

--- Comment #5 from Jerry DeLisle  ---
This seems on the verge of silly.  The ICE is at an assert:

  assert (saved_local_decls == NULL_TREE);

When the function gfc_process_block_locals concludes it does

  saved_local_decls = NULL_TREE;

So as I looked at this I thought it is expected to be already set at NULL_TREE
and it leaves it that way. Why not just set it instead of doing the assert.

So I did this:

diff --git a/gcc/fortran/trans-decl.c b/gcc/fortran/trans-decl.c
index 254768c5828..08c1ebd2d4b 100644
--- a/gcc/fortran/trans-decl.c
+++ b/gcc/fortran/trans-decl.c
@@ -6751,7 +6751,7 @@ gfc_process_block_locals (gfc_namespace* ns)
 {
   tree decl;

-  gcc_assert (saved_local_decls == NULL_TREE);
+  saved_local_decls = NULL_TREE;
   has_coarray_vars = false;

   generate_local_vars (ns);

The problem goes away and it regression tests fine.

saved_local_decls is used only in one other place where it is set in
add_decl_as_local().  It is not reset anywhere else. So I think the pacth above
is likely correct.

[Bug fortran/82009] [F08] ICE with block construct

2018-06-23 Thread kargl at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=82009

kargl at gcc dot gnu.org changed:

   What|Removed |Added

   Priority|P3  |P4

--- Comment #4 from kargl at gcc dot gnu.org ---
(In reply to Valery Weber from comment #0)
> hi all
> 
> the following code is ICEing with gcc 7.2.0
> 
> thanks
> 
> v
> 
> cat sparse_matrix_csx_benchmark_utils.F90
> MODULE sparse_matrix_csx_benchmark_utils
>   IMPLICIT NONE
> CONTAINS  
>   SUBROUTINE sparse_matrix_csr_benchmark ( )
> WRITE(*,*) 'At*x: t'
> block
>   integer, dimension(1), parameter :: idxs=[1]
>   integer :: i, idx
>   do i = 1, size(idxs)
>  idx = idxs(i)
>   enddo
> end block
>   END SUBROUTINE sparse_matrix_csr_benchmark
>   SUBROUTINE sparse_matrix_csc_benchmark ( )
> WRITE(*,*) 'An*x: t'
> block
>   integer, dimension(1), parameter :: idxs=[1]
>   integer :: i, idx
>   do i = 1, size(idxs)
>  idx = idxs(i)
>   enddo
> end block
>   END SUBROUTINE sparse_matrix_csc_benchmark
> END MODULE sparse_matrix_csx_benchmark_utils

This one is weird.  If I move the 2nd WRITE in sparse_matrix_csr_benchmark
to after the BLOCK constructor, the code compiles.  If I leave the 2nd
WRITE in its current location, and comment out the 1st WRITE statement
in sparse_matrix_csr_benchmark, I still get the ICE.  I'm perplexed!

[Bug fortran/82009] [F08] ICE with block construct

2018-06-23 Thread kargl at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=82009

--- Comment #3 from kargl at gcc dot gnu.org ---
(In reply to kargl from comment #2)
> (In reply to janus from comment #1)
> > Confirmed. ICEs with every gfortran version I tried, from 4.7 up to trunk.
> > 
> > Slight reduction:
> > 
> > MODULE csx
> >   IMPLICIT NONE
> > CONTAINS
> >   SUBROUTINE csr
> > block
> > end block
> >   END
> >   SUBROUTINE csc
> > WRITE(*,*) 'An*x: t'
> > block
> >   integer, dimension(1), parameter :: idxs=[1]
> >   print *, idxs(1)
> > end block
> >   END
> > END
> 
> The above code compiles for me on trunk (gcc version 9.0.0 20180609)

Original testcase still causes an ICE.

[Bug fortran/82009] [F08] ICE with block construct

2018-06-23 Thread kargl at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=82009

kargl at gcc dot gnu.org changed:

   What|Removed |Added

 CC||kargl at gcc dot gnu.org

--- Comment #2 from kargl at gcc dot gnu.org ---
(In reply to janus from comment #1)
> Confirmed. ICEs with every gfortran version I tried, from 4.7 up to trunk.
> 
> Slight reduction:
> 
> MODULE csx
>   IMPLICIT NONE
> CONTAINS
>   SUBROUTINE csr
> block
> end block
>   END
>   SUBROUTINE csc
> WRITE(*,*) 'An*x: t'
> block
>   integer, dimension(1), parameter :: idxs=[1]
>   print *, idxs(1)
> end block
>   END
> END

The above code compiles for me on trunk (gcc version 9.0.0 20180609)

[Bug fortran/82009] [F08] ICE with block construct

2017-08-28 Thread janus at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=82009

janus at gcc dot gnu.org changed:

   What|Removed |Added

   Keywords||ice-on-valid-code
 Status|UNCONFIRMED |NEW
   Last reconfirmed||2017-08-28
 CC||janus at gcc dot gnu.org
Summary|ICE with block construct|[F08] ICE with block
   ||construct
 Ever confirmed|0   |1

--- Comment #1 from janus at gcc dot gnu.org ---
Confirmed. ICEs with every gfortran version I tried, from 4.7 up to trunk.

Slight reduction:

MODULE csx
  IMPLICIT NONE
CONTAINS
  SUBROUTINE csr
block
end block
  END
  SUBROUTINE csc
WRITE(*,*) 'An*x: t'
block
  integer, dimension(1), parameter :: idxs=[1]
  print *, idxs(1)
end block
  END
END