public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/99506] New: internal compiler error: in record_reference, at cgraphbuild.c:64
@ 2021-03-10  6:32 furue at hawaii dot edu
  2021-03-10  7:53 ` [Bug fortran/99506] " marxin at gcc dot gnu.org
                   ` (7 more replies)
  0 siblings, 8 replies; 9+ messages in thread
From: furue at hawaii dot edu @ 2021-03-10  6:32 UTC (permalink / raw)
  To: gcc-bugs

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

            Bug ID: 99506
           Summary: internal compiler error: in record_reference, at
                    cgraphbuild.c:64
           Product: gcc
           Version: unknown
            Status: UNCONFIRMED
          Severity: normal
          Priority: P3
         Component: fortran
          Assignee: unassigned at gcc dot gnu.org
          Reporter: furue at hawaii dot edu
  Target Milestone: ---

Created attachment 50346
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=50346&action=edit
tar including all the source files.

The internal compiler error happens with GNU Fortran (Homebrew GCC 10.2.0_4)
10.2.0 .  The homebrew maintainer confirms this error and further reports that
the same error occurs on Ubuntu, too (I don't know the version of gfortran).
See https://github.com/Homebrew/homebrew-core/issues/72865 .  The maintainer
recommends submitting this report here.

Expand the attached tar file, cd to that directory, and on the command line:
````
$ gfortran -c numeric_kinds.f90
$ gfortran -c indices.f90
$ gfortran fix-track-partials-00.f90 indices.o
f951: internal compiler error: in record_reference, at cgraphbuild.c:64
libbacktrace could not find executable to open
Please submit a full bug report,
with preprocessed source if appropriate.
See <https://github.com/Homebrew/homebrew-core/issues> for instructions.
````
In the above the dollar symbols is the command prompt.

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

* [Bug fortran/99506] internal compiler error: in record_reference, at cgraphbuild.c:64
  2021-03-10  6:32 [Bug fortran/99506] New: internal compiler error: in record_reference, at cgraphbuild.c:64 furue at hawaii dot edu
@ 2021-03-10  7:53 ` marxin at gcc dot gnu.org
  2021-03-10  8:00 ` kargl at gcc dot gnu.org
                   ` (6 subsequent siblings)
  7 siblings, 0 replies; 9+ messages in thread
From: marxin at gcc dot gnu.org @ 2021-03-10  7:53 UTC (permalink / raw)
  To: gcc-bugs

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

Martin Liška <marxin at gcc dot gnu.org> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|UNCONFIRMED                 |NEW
           Priority|P3                          |P4
   Last reconfirmed|                            |2021-03-10
            Version|unknown                     |11.0
     Ever confirmed|0                           |1
                 CC|                            |marxin at gcc dot gnu.org

--- Comment #1 from Martin Liška <marxin at gcc dot gnu.org> ---
Reduced test-case:

module numeric_kinds
  integer, parameter :: single = kind(1.0)
  integer, parameter :: double = selected_real_kind(2*precision(1.0_single))
end module  numeric_kinds
module indices
contains
  function find_idx(x, xx) result(idx)
  end function find_idx
  function nearest_idx(x, xx) result(idx)
      if (x < xx0) then
         if (xx0 - x < 0/2) then
         end if
      end if
      do
         if (dl >= 0 .and. last_dl <= 0) then
         end if
      end do
   end function nearest_idx
  function close_enough_idx(x, xx, eps, verbose) result(res)
    logical, intent(in), optional:: verbose
    if (abs0 <= eps) then
      if (present(verbose)) then
        if (verbose .eqv. .true.) then
        end if
      end if
    end if
  end function close_enough_idx
end module indices
program fix_track_partials
  use numeric_kinds, only: double
  character(*), parameter:: &
      youf = "track-partial-nws200-y-grid.dat"
  integer, parameter:: &
      lonw100 = 10000, lats100 = -4000, dlon100 = 10, dlat100 = 10
  integer, parameter:: imax = 50, jmax = 350
  integer, dimension(*), parameter:: &
      latt100 = [((lats100 + dlat100 * j - dlat100/2), j=1,jmax)]
  real(double), dimension(*), parameter:: &
      latt = [(latt100(i)/100.d0, j=1,jmax)]
  real(double), dimension(:), allocatable:: xs, ys, xs_fixed, ys_fixed
  call move_to_nearest(ys_fixed, pnts=ys, axis=latt)
contains
  subroutine read_track(xs, ys, file)
  end subroutine read_track
  subroutine save_track(xs, ys, file)
  end subroutine save_track
  subroutine move_to_nearest(res, pnts, axis)
    real(double), intent(out):: res(:)
    real(double), intent(in) :: pnts(:), axis(:)
  end subroutine move_to_nearest
  subroutine extend_arr_double(arr, idx, mes)
  end subroutine extend_arr_double
  subroutine shrink_arr_double(arr, idx, mes)
  end subroutine shrink_arr_double
end program fix_track_partials


It's very old, at least as old as GCC 4.8.0.

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

* [Bug fortran/99506] internal compiler error: in record_reference, at cgraphbuild.c:64
  2021-03-10  6:32 [Bug fortran/99506] New: internal compiler error: in record_reference, at cgraphbuild.c:64 furue at hawaii dot edu
  2021-03-10  7:53 ` [Bug fortran/99506] " marxin at gcc dot gnu.org
@ 2021-03-10  8:00 ` kargl at gcc dot gnu.org
  2021-03-10  8:18 ` furue at hawaii dot edu
                   ` (5 subsequent siblings)
  7 siblings, 0 replies; 9+ messages in thread
From: kargl at gcc dot gnu.org @ 2021-03-10  8:00 UTC (permalink / raw)
  To: gcc-bugs

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

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 ---
First, the compiler should not ICE.
Second, your program likely has a bug, which is the cause of the ICE.
Third, it's not clear if the middle-end can detect the issue.
Fourth, it's clear the Fortran front-end does not catch the problem.
Finally, here's a better reduced testcase.

program fix_track_partials

  implicit none

  integer, parameter :: double = 8
  integer, parameter :: lats100 = -4000,  dlat100 = 10
  integer, parameter :: jmax = 350
  integer  i, j

  integer, parameter:: &
      latt100(jmax) = [((lats100 + dlat100 * j - dlat100/2), j=1,jmax)]

   real(double),  parameter:: latt(jmax) = [(latt100(i)/100.d0, j=1,jmax)]

   real(double), allocatable:: ys(:), ys_fixed(:)

   ys = [1]
   call move_to_nearest(ys_fixed, pnts=ys, axis=latt)

   contains

      subroutine move_to_nearest(res, pnts, axis)
         real(double), intent(out):: res(:)
         real(double), intent(in) :: pnts(:), axis(:)
      end subroutine move_to_nearest

end program fix_track_partials

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

* [Bug fortran/99506] internal compiler error: in record_reference, at cgraphbuild.c:64
  2021-03-10  6:32 [Bug fortran/99506] New: internal compiler error: in record_reference, at cgraphbuild.c:64 furue at hawaii dot edu
  2021-03-10  7:53 ` [Bug fortran/99506] " marxin at gcc dot gnu.org
  2021-03-10  8:00 ` kargl at gcc dot gnu.org
@ 2021-03-10  8:18 ` furue at hawaii dot edu
  2021-03-10  8:39 ` rguenth at gcc dot gnu.org
                   ` (4 subsequent siblings)
  7 siblings, 0 replies; 9+ messages in thread
From: furue at hawaii dot edu @ 2021-03-10  8:18 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #3 from Ryo Furue <furue at hawaii dot edu> ---
After posting the initial report, I tried my code with another compiler and
found a few bugs in there.  In the most reduced code, one of them is still
there:

> real(double),  parameter:: latt(jmax) = [(latt100(i)/100.d0, j=1,jmax)]

The "i" in "latt100(i)" is wrong.  I meant "j".

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

* [Bug fortran/99506] internal compiler error: in record_reference, at cgraphbuild.c:64
  2021-03-10  6:32 [Bug fortran/99506] New: internal compiler error: in record_reference, at cgraphbuild.c:64 furue at hawaii dot edu
                   ` (2 preceding siblings ...)
  2021-03-10  8:18 ` furue at hawaii dot edu
@ 2021-03-10  8:39 ` rguenth at gcc dot gnu.org
  2021-03-10 16:52 ` sgk at troutmask dot apl.washington.edu
                   ` (3 subsequent siblings)
  7 siblings, 0 replies; 9+ messages in thread
From: rguenth at gcc dot gnu.org @ 2021-03-10  8:39 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #4 from Richard Biener <rguenth at gcc dot gnu.org> ---
This is a frontend issue, the FE produces an invalid static initializer for
'latt' (DECL_INITIAL):

{(real(kind=8)) latt100[(integer(kind=8)) i + -1] / 1.0e+2, (real(kind=8))
latt100[(integer(kind=8)) i + -1] / 1.0e+2,... }

if this should be dynamic initialization FEs are responsible for lowering
this.

I don't know fortran enough for what 'parameter' means in this context:

   real(double),  parameter:: latt(jmax) = [(latt100(i)/100.d0, j=1,jmax)]

but the middle-end sees a readonly global (TREE_STATIC) variable.

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

* [Bug fortran/99506] internal compiler error: in record_reference, at cgraphbuild.c:64
  2021-03-10  6:32 [Bug fortran/99506] New: internal compiler error: in record_reference, at cgraphbuild.c:64 furue at hawaii dot edu
                   ` (3 preceding siblings ...)
  2021-03-10  8:39 ` rguenth at gcc dot gnu.org
@ 2021-03-10 16:52 ` sgk at troutmask dot apl.washington.edu
  2021-03-10 22:22 ` anlauf at gcc dot gnu.org
                   ` (2 subsequent siblings)
  7 siblings, 0 replies; 9+ messages in thread
From: sgk at troutmask dot apl.washington.edu @ 2021-03-10 16:52 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #5 from Steve Kargl <sgk at troutmask dot apl.washington.edu> ---
On Wed, Mar 10, 2021 at 08:39:19AM +0000, rguenth at gcc dot gnu.org wrote:
> https://gcc.gnu.org/bugzilla/show_bug.cgi?id=99506
> 
> --- Comment #4 from Richard Biener <rguenth at gcc dot gnu.org> ---
> This is a frontend issue, the FE produces an invalid static initializer for
> 'latt' (DECL_INITIAL):
> 
> {(real(kind=8)) latt100[(integer(kind=8)) i + -1] / 1.0e+2, (real(kind=8))
> latt100[(integer(kind=8)) i + -1] / 1.0e+2,... }
> 
> if this should be dynamic initialization FEs are responsible for lowering
> this.
> 
> I don't know fortran enough for what 'parameter' means in this context:
> 
>    real(double),  parameter:: latt(jmax) = [(latt100(i)/100.d0, j=1,jmax)]
> 
> but the middle-end sees a readonly global (TREE_STATIC) variable.
> 

'parameter' means that latt(jmax) is a named constant array.
Haven't thought about it too much, but for comparison, it should
be equivalent to C's 'static const latt[jmax] = {1, 2, ...}'.

This bug likely goes back to when g95 was initially added to GCC.
Implied-do loops are a rather special/odd construct.  AFAI[CT|K],
gfortran has never done a proper checking of the ac-value-list
(See F2018, R773).   Here, the ac-value is the expression
'latt100(i)', which must reduce to a constant expression because
the implied-do loop appears in an initialization expression.
Well, 'i' is an uninitialized variable, which certainly is not
constant.

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

* [Bug fortran/99506] internal compiler error: in record_reference, at cgraphbuild.c:64
  2021-03-10  6:32 [Bug fortran/99506] New: internal compiler error: in record_reference, at cgraphbuild.c:64 furue at hawaii dot edu
                   ` (4 preceding siblings ...)
  2021-03-10 16:52 ` sgk at troutmask dot apl.washington.edu
@ 2021-03-10 22:22 ` anlauf at gcc dot gnu.org
  2021-03-10 22:59 ` sgk at troutmask dot apl.washington.edu
  2021-03-11  1:38 ` sgk at troutmask dot apl.washington.edu
  7 siblings, 0 replies; 9+ messages in thread
From: anlauf at gcc dot gnu.org @ 2021-03-10 22:22 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #6 from anlauf at gcc dot gnu.org ---
(In reply to Richard Biener from comment #4)
> I don't know fortran enough for what 'parameter' means in this context:
> 
>    real(double),  parameter:: latt(jmax) = [(latt100(i)/100.d0, j=1,jmax)]
> 
> but the middle-end sees a readonly global (TREE_STATIC) variable.

There is a possibly related issue in pr91960.

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

* [Bug fortran/99506] internal compiler error: in record_reference, at cgraphbuild.c:64
  2021-03-10  6:32 [Bug fortran/99506] New: internal compiler error: in record_reference, at cgraphbuild.c:64 furue at hawaii dot edu
                   ` (5 preceding siblings ...)
  2021-03-10 22:22 ` anlauf at gcc dot gnu.org
@ 2021-03-10 22:59 ` sgk at troutmask dot apl.washington.edu
  2021-03-11  1:38 ` sgk at troutmask dot apl.washington.edu
  7 siblings, 0 replies; 9+ messages in thread
From: sgk at troutmask dot apl.washington.edu @ 2021-03-10 22:59 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #7 from Steve Kargl <sgk at troutmask dot apl.washington.edu> ---
On Wed, Mar 10, 2021 at 10:22:45PM +0000, anlauf at gcc dot gnu.org wrote:
> https://gcc.gnu.org/bugzilla/show_bug.cgi?id=99506
> 
> --- Comment #6 from anlauf at gcc dot gnu.org ---
> (In reply to Richard Biener from comment #4)
> > I don't know fortran enough for what 'parameter' means in this context:
> > 
> >    real(double),  parameter:: latt(jmax) = [(latt100(i)/100.d0, j=1,jmax)]
> > 
> > but the middle-end sees a readonly global (TREE_STATIC) variable.
> 
> There is a possibly related issue in pr91960.
> 

Yes, same problem.  An uninitialized *variable* is used in
an implied-do loop, which is an ac-value expression.  Perhaps,
resolve.c(resolve_fl_parameter) needs to do some deeper 
checking.

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

* [Bug fortran/99506] internal compiler error: in record_reference, at cgraphbuild.c:64
  2021-03-10  6:32 [Bug fortran/99506] New: internal compiler error: in record_reference, at cgraphbuild.c:64 furue at hawaii dot edu
                   ` (6 preceding siblings ...)
  2021-03-10 22:59 ` sgk at troutmask dot apl.washington.edu
@ 2021-03-11  1:38 ` sgk at troutmask dot apl.washington.edu
  7 siblings, 0 replies; 9+ messages in thread
From: sgk at troutmask dot apl.washington.edu @ 2021-03-11  1:38 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #8 from Steve Kargl <sgk at troutmask dot apl.washington.edu> ---
On Wed, Mar 10, 2021 at 10:59:39PM +0000, sgk at troutmask dot
apl.washington.edu wrote:
> https://gcc.gnu.org/bugzilla/show_bug.cgi?id=99506
> 
> --- Comment #7 from Steve Kargl <sgk at troutmask dot apl.washington.edu> ---
> On Wed, Mar 10, 2021 at 10:22:45PM +0000, anlauf at gcc dot gnu.org wrote:
> > https://gcc.gnu.org/bugzilla/show_bug.cgi?id=99506
> > 
> > --- Comment #6 from anlauf at gcc dot gnu.org ---
> > (In reply to Richard Biener from comment #4)
> > > I don't know fortran enough for what 'parameter' means in this context:
> > > 
> > >    real(double),  parameter:: latt(jmax) = [(latt100(i)/100.d0, j=1,jmax)]
> > > 
> > > but the middle-end sees a readonly global (TREE_STATIC) variable.
> > 
> > There is a possibly related issue in pr91960.
> > 
> 
> Yes, same problem.  An uninitialized *variable* is used in
> an implied-do loop, which is an ac-value expression.  Perhaps,
> resolve.c(resolve_fl_parameter) needs to do some deeper 
> checking.
> 

This patch fixes both 99506 and 91960.  I cannot commit.
Whoever decides to commit the patch needs to convert the
code in 91960 into a testcase.  Otherwise, this patch 
will fester in bugzilla with other 20 or so patches I've
included in audit trails of those PRs.

diff --git a/gcc/fortran/resolve.c b/gcc/fortran/resolve.c
index 2a91ae743ea..84e93dbc1fd 100644
--- a/gcc/fortran/resolve.c
+++ b/gcc/fortran/resolve.c
@@ -15179,6 +15186,20 @@ resolve_fl_parameter (gfc_symbol *sym)
       return false;
     }

+  /* Some programmers can have a typo when using an implied-do loop to 
+     initialize an array constant.  For example, 
+       INTEGER I,J
+       INTEGER, PARAMETER :: A(3) = [(I, I = 1, 3)]    ! OK
+       INTEGER, PARAMETER :: B(3) = [(A(J), I = 1, 3)]  ! Not OK
+     This check catches the typo.  */
+  if (sym->attr.dimension
+      && sym->value && sym->value->expr_type == EXPR_ARRAY
+      && !gfc_is_constant_expr (sym->value))
+    {
+      gfc_error ("Expecting constant expression near %L", &sym->value->where);
+      return false;
+    }
+
   return true;
 }

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

end of thread, other threads:[~2021-03-11  1:38 UTC | newest]

Thread overview: 9+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2021-03-10  6:32 [Bug fortran/99506] New: internal compiler error: in record_reference, at cgraphbuild.c:64 furue at hawaii dot edu
2021-03-10  7:53 ` [Bug fortran/99506] " marxin at gcc dot gnu.org
2021-03-10  8:00 ` kargl at gcc dot gnu.org
2021-03-10  8:18 ` furue at hawaii dot edu
2021-03-10  8:39 ` rguenth at gcc dot gnu.org
2021-03-10 16:52 ` sgk at troutmask dot apl.washington.edu
2021-03-10 22:22 ` anlauf at gcc dot gnu.org
2021-03-10 22:59 ` sgk at troutmask dot apl.washington.edu
2021-03-11  1:38 ` sgk at troutmask dot apl.washington.edu

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