public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/47839] New: ICE in dwarf2out.c:add_AT_specification
@ 2011-02-21 16:55 rguenth at gcc dot gnu.org
  2011-02-21 16:56 ` [Bug fortran/47839] " rguenth at gcc dot gnu.org
                   ` (5 more replies)
  0 siblings, 6 replies; 7+ messages in thread
From: rguenth at gcc dot gnu.org @ 2011-02-21 16:55 UTC (permalink / raw)
  To: gcc-bugs

http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47839

           Summary: ICE in dwarf2out.c:add_AT_specification
           Product: gcc
           Version: 4.6.0
            Status: UNCONFIRMED
          Keywords: lto
          Severity: normal
          Priority: P3
         Component: fortran
        AssignedTo: unassigned@gcc.gnu.org
        ReportedBy: rguenth@gcc.gnu.org


Building 459.GemsFDTD (and 416.gamess) with -O3 -ffast-math -flto -g ICEs
because the Fortran frontend seemingly puts imported variables in the
BLOCK tree of the imported function and does not mark them external.

The variable in question is huy_param from huygens_mod, imported from
nft_store

SUBROUTINE NFT_Store(Ex,Ey,Ez,Hx,Hy,Hz,t,ts)

USE excite_mod,  ONLY : excitation
USE huygens_mod, ONLY : Huy_param, HuyPulseType

and

MODULE Huygens_mod
...
real(kind=rfp), dimension(excite_max_no_param), PUBLIC :: Huy_param


I tried to create a small testcase but failed sofar.  It doesn't ICE
with -flto-partition=none but it does with -flto-partition=1to1.

With partially linking 459.GemsFDTD I get the ICE with

/abuild/rguenther/install-trunk/usr/local/bin/gfortran globalvar.f90 PEC.f90 -o
GemsFDTD -flto -flto-partition=none -r -nostdlib -O -g

which is then obviously related to a different variable.  Trying to
reduce the sources now.


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

* [Bug fortran/47839] ICE in dwarf2out.c:add_AT_specification
  2011-02-21 16:55 [Bug fortran/47839] New: ICE in dwarf2out.c:add_AT_specification rguenth at gcc dot gnu.org
@ 2011-02-21 16:56 ` rguenth at gcc dot gnu.org
  2011-02-21 17:14 ` rguenth at gcc dot gnu.org
                   ` (4 subsequent siblings)
  5 siblings, 0 replies; 7+ messages in thread
From: rguenth at gcc dot gnu.org @ 2011-02-21 16:56 UTC (permalink / raw)
  To: gcc-bugs

http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47839

--- Comment #1 from Richard Guenther <rguenth at gcc dot gnu.org> 2011-02-21 16:19:20 UTC ---
--- a.f90

MODULE globalvar_mod
integer        :: xstart, ystart, zstart, xstop, ystop, zstop
CONTAINS
END MODULE globalvar_mod

--- b.f90

MODULE PEC_mod
CONTAINS
SUBROUTINE PECapply(Ex,Ey,Ez)
USE globalvar_mod, ONLY : xstart, ystart, zstart, xstop, ystop, zstop
real(kind=8), dimension(xstart:xstop+1,ystart:ystop+1,zstart:zstop+1),      &
                intent(inout) :: Ex, Ey, Ez
END SUBROUTINE PECapply
END MODULE PEC_mod


> gfortran a.f90 b.f90 -flto -flto-partition=none -r -nostdlib -g
lto1: internal compiler error: in add_AT_specification, at dwarf2out.c:7558
Please submit a full bug report,
with preprocessed source if appropriate.
See <http://gcc.gnu.org/bugs.html> for instructions.


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

* [Bug fortran/47839] ICE in dwarf2out.c:add_AT_specification
  2011-02-21 16:55 [Bug fortran/47839] New: ICE in dwarf2out.c:add_AT_specification rguenth at gcc dot gnu.org
  2011-02-21 16:56 ` [Bug fortran/47839] " rguenth at gcc dot gnu.org
@ 2011-02-21 17:14 ` rguenth at gcc dot gnu.org
  2011-02-22 11:56 ` rguenth at gcc dot gnu.org
                   ` (3 subsequent siblings)
  5 siblings, 0 replies; 7+ messages in thread
From: rguenth at gcc dot gnu.org @ 2011-02-21 17:14 UTC (permalink / raw)
  To: gcc-bugs

http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47839

Richard Guenther <rguenth at gcc dot gnu.org> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|UNCONFIRMED                 |NEW
   Last reconfirmed|                            |2011.02.21 17:04:46
     Ever Confirmed|0                           |1

--- Comment #2 from Richard Guenther <rguenth at gcc dot gnu.org> 2011-02-21 17:04:46 UTC ---
We merge the decls during symtab merging.  The prevailing one looks for example
like

(gdb) call debug_tree (prevailing->decl)
 <var_decl 0x7ffff5b3b0a0 zstart
    type <integer_type 0x7ffff7ee3498 int public SI
        size <integer_cst 0x7ffff7ed36e0 constant 32>
        unit size <integer_cst 0x7ffff7ed33e8 constant 4>
        align 32 symtab 0 alias set -1 canonical type 0x7ffff7ee3498 precision
32 min <integer_cst 0x7ffff7ed3668 -2147483648> max <integer_cst 0x7ffff7ed3690
2147483647>
        pointer_to_this <pointer_type 0x7ffff7ef03f0>>
    used public static SI file mod.f90 line 2 col 0 size <integer_cst
0x7ffff7ed36e0 32> unit size <integer_cst 0x7ffff7ed33e8 4>
    align 32 context <namespace_decl 0x7ffff5b31678 globalvar_mod>>

while the non-prevailing one is

 <var_decl 0x7ffff5b3b640 zstart
    type <integer_type 0x7ffff7ee3498 int public SI
        size <integer_cst 0x7ffff7ed36e0 constant 32>
        unit size <integer_cst 0x7ffff7ed33e8 constant 4>
        align 32 symtab 0 alias set -1 canonical type 0x7ffff7ee3498 precision
32 min <integer_cst 0x7ffff7ed3668 -2147483648> max <integer_cst 0x7ffff7ed3690
2147483647>
        pointer_to_this <pointer_type 0x7ffff7ef03f0>>
    used public ignored external SI file t.f90 line 4 col 0 size <integer_cst
0x7ffff7ed36e0 32> unit size <integer_cst 0x7ffff7ed33e8 4>
    align 32>

note that it is public and external and has a NULL DECL_CONTEXT.

The C frontend for a local extern declaration has

 <var_decl 0x7ffff5b481e0 i
    type <integer_type 0x7ffff7ee6498 int public SI
        size <integer_cst 0x7ffff7ed36e0 constant 32>
        unit size <integer_cst 0x7ffff7ed33e8 constant 4>
        align 32 symtab 0 alias set -1 canonical type 0x7ffff7ee6498 precision
32 min <integer_cst 0x7ffff7ed3668 -2147483648> max <integer_cst 0x7ffff7ed3690
2147483647>
        pointer_to_this <pointer_type 0x7ffff7ef7540>>
    used public external common SI defer-output file t.c line 8 col 15 size
<integer_cst 0x7ffff7ed36e0 32> unit size <integer_cst 0x7ffff7ed33e8 4>
    align 32 context <function_decl 0x7ffff5b49000 foo>>

thus puts it into function context.  This decl is solely used for the BLOCK
tree, in the function a public external global var is used (which is
then merged with the static one from the other TU).

void foo (void)
{
  extern int i;
  i = 0;
}

---

int i;



Simplified Fortran testcase:

MODULE globalvar_mod
integer        :: xstop
CONTAINS
END MODULE globalvar_mod

---

MODULE PEC_mod
CONTAINS
SUBROUTINE PECapply(Ex)
USE globalvar_mod, ONLY : xstop
real(kind=8), dimension(1:xstop), intent(inout) :: Ex
END SUBROUTINE PECapply
END MODULE PEC_mod

it's important that PECapply is inside a module.

The decl is built by gfc_get_symbol_decl and put into the function via
gfc_add_decl_to_function - which is I think in general bogus for
imported decls.  Its context is later cleared in pushdecl, but the
variable isn't removed from BLOCK_VARS.

I think we want to avoid gfc_add_decl_to_function in the first place.


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

* [Bug fortran/47839] ICE in dwarf2out.c:add_AT_specification
  2011-02-21 16:55 [Bug fortran/47839] New: ICE in dwarf2out.c:add_AT_specification rguenth at gcc dot gnu.org
  2011-02-21 16:56 ` [Bug fortran/47839] " rguenth at gcc dot gnu.org
  2011-02-21 17:14 ` rguenth at gcc dot gnu.org
@ 2011-02-22 11:56 ` rguenth at gcc dot gnu.org
  2011-02-22 12:42 ` rguenth at gcc dot gnu.org
                   ` (2 subsequent siblings)
  5 siblings, 0 replies; 7+ messages in thread
From: rguenth at gcc dot gnu.org @ 2011-02-22 11:56 UTC (permalink / raw)
  To: gcc-bugs

http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47839

--- Comment #3 from Richard Guenther <rguenth at gcc dot gnu.org> 2011-02-22 11:46:04 UTC ---
I think this also hints at possible DECL issues with imported vars.  You can
see how the C frontend handles the function/block local externs around
c-decl.c:1206

          else if (VAR_OR_FUNCTION_DECL_P (p))
            {
              /* For block local externs add a special
                 DECL_EXTERNAL decl for debug info generation.  */
              tree extp = copy_node (p);
...

The following fixes the testcase for me (not further tested):

Index: gcc/fortran/f95-lang.c
===================================================================
--- gcc/fortran/f95-lang.c      (revision 170359)
+++ gcc/fortran/f95-lang.c      (working copy)
@@ -498,13 +498,20 @@ poplevel (int keep, int reverse, int fun
 tree
 pushdecl (tree decl)
 {
-  /* External objects aren't nested, other objects may be.  */
-  if (DECL_EXTERNAL (decl))
-    DECL_CONTEXT (decl) = NULL_TREE;
-  else if (global_bindings_p ())
+  if (global_bindings_p ())
     DECL_CONTEXT (decl) = current_translation_unit;
   else
-    DECL_CONTEXT (decl) = current_function_decl;
+    {
+      /* External objects aren't nested.  For debug info insert a copy
+         of the decl into the binding level.  */
+      if (DECL_EXTERNAL (decl))
+       {
+         tree orig = decl;
+         decl = copy_node (decl);
+         DECL_CONTEXT (orig) = NULL_TREE;
+       }
+      DECL_CONTEXT (decl) = current_function_decl;
+    }

   /* Put the declaration on the list.  The list of declarations is in reverse
      order. The list will be reversed later if necessary.  This needs to be


there might be still multiple backend-decls for USE associated vars in
different subroutines (they should share a single global one).


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

* [Bug fortran/47839] ICE in dwarf2out.c:add_AT_specification
  2011-02-21 16:55 [Bug fortran/47839] New: ICE in dwarf2out.c:add_AT_specification rguenth at gcc dot gnu.org
                   ` (2 preceding siblings ...)
  2011-02-22 11:56 ` rguenth at gcc dot gnu.org
@ 2011-02-22 12:42 ` rguenth at gcc dot gnu.org
  2011-02-24 10:35 ` rguenth at gcc dot gnu.org
  2011-02-24 10:39 ` rguenth at gcc dot gnu.org
  5 siblings, 0 replies; 7+ messages in thread
From: rguenth at gcc dot gnu.org @ 2011-02-22 12:42 UTC (permalink / raw)
  To: gcc-bugs

http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47839

Richard Guenther <rguenth at gcc dot gnu.org> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
           Keywords|                            |wrong-debug

--- Comment #4 from Richard Guenther <rguenth at gcc dot gnu.org> 2011-02-22 12:01:03 UTC ---
With the patch and

MODULE PEC_mod
CONTAINS
SUBROUTINE PECapply(Ex)
USE globalvar_mod, ONLY : xstop
real(kind=8), dimension(1:xstop), intent(inout) :: Ex
write(*,*) xstop
END SUBROUTINE PECapply
SUBROUTINE PECapply2(Ex)
USE globalvar_mod, ONLY : xstop
real(kind=8), dimension(1:xstop), intent(inout) :: Ex
write(*,*) xstop
END SUBROUTINE PECapply2
END MODULE PEC_mod

you see

pecapply2 (real(kind=8)[0:] * restrict ex)
{
  extern integer(kind=4)D.8 xstopD.1540;

  {
    struct __st_parameter_dt dt_parm.0D.1539;

    dt_parm.0D.1539.commonD.1458.filenameD.1355 = &"t.f90"[1]{lb: 1 sz: 1};
    dt_parm.0D.1539.commonD.1458.lineD.1356 = 11;
    dt_parm.0D.1539.commonD.1458.flagsD.1353 = 128;
    dt_parm.0D.1539.commonD.1458.unitD.1354 = 6;
    _gfortran_st_write (&dt_parm.0D.1539);
    _gfortran_transfer_integer_write (&dt_parm.0D.1539, &xstopD.1538, 4);
    _gfortran_st_write_done (&dt_parm.0D.1539);
  }
}

pecapply (real(kind=8)[0:] * restrict ex)
{
  {
    struct __st_parameter_dt dt_parm.1D.1543;

    dt_parm.1D.1543.commonD.1458.filenameD.1355 = &"t.f90"[1]{lb: 1 sz: 1};
    dt_parm.1D.1543.commonD.1458.lineD.1356 = 6;
    dt_parm.1D.1543.commonD.1458.flagsD.1353 = 128;
    dt_parm.1D.1543.commonD.1458.unitD.1354 = 6;
    _gfortran_st_write (&dt_parm.1D.1543);
    _gfortran_transfer_integer_write (&dt_parm.1D.1543, &xstopD.1538, 4);
    _gfortran_st_write_done (&dt_parm.1D.1543);
  }
}

which is half-way sane (same backend-decl used for the actual USE
associated variable).  But still the 2nd function misses the copy
in its BLOCK tree, so I guess if that function would be nested
in another that has a local of the same name gdb would confuse
references to the USE associated vars with that of the local
parent function decl like with

MODULE PEC_mod
CONTAINS
SUBROUTINE test
integer :: xstop,xbar
write(*,*) xstop
CONTAINS
SUBROUTINE PECapply(Ex)
USE globalvar_mod, ONLY : xstop
real(kind=8), dimension(1:xstop), intent(inout) :: Ex
write(*,*) xstop,xbar
END SUBROUTINE PECapply
END SUBROUTINE test
SUBROUTINE PECapply2(Ex)
USE globalvar_mod, ONLY : xstop
real(kind=8), dimension(1:xstop), intent(inout) :: Ex
write(*,*) xstop
END SUBROUTINE PECapply2
END MODULE PEC_mod

remains to a more Fortran affine person to verify the above wrong-debug
idea with gdb.  The key is

pecapply (real(kind=8)[0:] * restrict ex)
{
  {
    struct __st_parameter_dt dt_parm.1D.1545;

    dt_parm.1D.1545.commonD.1458.filenameD.1355 = &"t.f90"[1]{lb: 1 sz: 1};
    dt_parm.1D.1545.commonD.1458.lineD.1356 = 10;
    dt_parm.1D.1545.commonD.1458.flagsD.1353 = 128;
    dt_parm.1D.1545.commonD.1458.unitD.1354 = 6;
    _gfortran_st_write (&dt_parm.1D.1545);
    _gfortran_transfer_integer_write (&dt_parm.1D.1545, &xstopD.1535, 4);
    _gfortran_transfer_integer_write (&dt_parm.1D.1545, &xbarD.1546, 4);
    _gfortran_st_write_done (&dt_parm.1D.1545);
  }
}

(no extern integer(kind=4)D.8 xstopD.1537; here) and in the parent:

test ()
{
  integer(kind=4)D.8 xbarD.1546;
  integer(kind=4)D.8 xstopD.1547;
  static voidD.27 pecapplyD.1541 (real(kind=8)D.18[0:] * restrict);

  {
    struct __st_parameter_dt dt_parm.2D.1548;

    dt_parm.2D.1548.commonD.1458.filenameD.1355 = &"t.f90"[1]{lb: 1 sz: 1};
    dt_parm.2D.1548.commonD.1458.lineD.1356 = 5;
    dt_parm.2D.1548.commonD.1458.flagsD.1353 = 128;
    dt_parm.2D.1548.commonD.1458.unitD.1354 = 6;
    _gfortran_st_write (&dt_parm.2D.1548);
    _gfortran_transfer_integer_write (&dt_parm.2D.1548, &xstopD.1547, 4);
    _gfortran_st_write_done (&dt_parm.2D.1548);
  }
}

we have integer(kind=4)D.8 xstopD.1547 which shadows the global xstop
from the module.


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

* [Bug fortran/47839] ICE in dwarf2out.c:add_AT_specification
  2011-02-21 16:55 [Bug fortran/47839] New: ICE in dwarf2out.c:add_AT_specification rguenth at gcc dot gnu.org
                   ` (3 preceding siblings ...)
  2011-02-22 12:42 ` rguenth at gcc dot gnu.org
@ 2011-02-24 10:35 ` rguenth at gcc dot gnu.org
  2011-02-24 10:39 ` rguenth at gcc dot gnu.org
  5 siblings, 0 replies; 7+ messages in thread
From: rguenth at gcc dot gnu.org @ 2011-02-24 10:35 UTC (permalink / raw)
  To: gcc-bugs

http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47839

--- Comment #5 from Richard Guenther <rguenth at gcc dot gnu.org> 2011-02-24 09:53:30 UTC ---
Author: rguenth
Date: Thu Feb 24 09:53:26 2011
New Revision: 170463

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=170463
Log:
2011-02-24  Richard Guenther  <rguenther@suse.de>

    PR fortran/47839
    * f95-lang.c (pushdecl): For externs in non-global scope push
    a copy of the decl into the BLOCK.

    * gfortran.dg/lto/pr47839_0.f90: New testcase.
    * gfortran.dg/lto/pr47839_1.f90: Likewise.

Added:
    trunk/gcc/testsuite/gfortran.dg/lto/pr47839_0.f90
    trunk/gcc/testsuite/gfortran.dg/lto/pr47839_1.f90
Modified:
    trunk/gcc/fortran/ChangeLog
    trunk/gcc/fortran/f95-lang.c
    trunk/gcc/testsuite/ChangeLog


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

* [Bug fortran/47839] ICE in dwarf2out.c:add_AT_specification
  2011-02-21 16:55 [Bug fortran/47839] New: ICE in dwarf2out.c:add_AT_specification rguenth at gcc dot gnu.org
                   ` (4 preceding siblings ...)
  2011-02-24 10:35 ` rguenth at gcc dot gnu.org
@ 2011-02-24 10:39 ` rguenth at gcc dot gnu.org
  5 siblings, 0 replies; 7+ messages in thread
From: rguenth at gcc dot gnu.org @ 2011-02-24 10:39 UTC (permalink / raw)
  To: gcc-bugs

http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47839

Richard Guenther <rguenth at gcc dot gnu.org> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|NEW                         |RESOLVED
         Resolution|                            |FIXED

--- Comment #6 from Richard Guenther <rguenth at gcc dot gnu.org> 2011-02-24 09:54:19 UTC ---
The ICE is fixed.  The wrong-debug issue remains as soon as two USE
associations for the same variable exist.


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

end of thread, other threads:[~2011-02-24  9:54 UTC | newest]

Thread overview: 7+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2011-02-21 16:55 [Bug fortran/47839] New: ICE in dwarf2out.c:add_AT_specification rguenth at gcc dot gnu.org
2011-02-21 16:56 ` [Bug fortran/47839] " rguenth at gcc dot gnu.org
2011-02-21 17:14 ` rguenth at gcc dot gnu.org
2011-02-22 11:56 ` rguenth at gcc dot gnu.org
2011-02-22 12:42 ` rguenth at gcc dot gnu.org
2011-02-24 10:35 ` rguenth at gcc dot gnu.org
2011-02-24 10:39 ` rguenth at gcc dot gnu.org

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).