> Consider a comment pointing back to the relevant dwarf2 code that
> enforces the invariant.

I added the comment and installed the patch yesterday, but it breaks the 
Fortran compiler in some cases because, unlike the C family of compilers or 
the Ada compiler, the front-end builds TYPE_DECLs with DECL_ORIGINAL_TYPE for 
anonymous types (and even sets DECL_ORIGINAL_TYPE to TREE_TYPE for them).
That's useless and DECL_ORIGINAL_TYPE is skipped in this case by the DWARF 
back-end, but my patch inadvertently turns anonymous types into named types so 
the DWARF back-end now chokes.

Fixed by attached patchlet, tested on x86_64-suse-linux, applied as obvious.


2016-06-24  Eric Botcazou  <ebotca...@adacore.com>

        PR debug/71642
        * tree-inline.c (remap_decl): When fixing up DECL_ORIGINAL_TYPE, just
        copy the type name.


2016-06-24  Eric Botcazou  <ebotca...@adacore.com>

        * gfortran.dg/pr71642.f90: New test.

-- 
Eric Botcazou
diff --git a/gcc/tree-inline.c ./gcc/tree-inline.c
index dca972d..8a7e0e2 100644
--- a/gcc/tree-inline.c
+++ ./gcc/tree-inline.c
@@ -377,7 +377,7 @@ remap_decl (tree decl, copy_body_data *id)
 	    {
 	      tree x = build_variant_type_copy (TREE_TYPE (t));
 	      TYPE_STUB_DECL (x) = TYPE_STUB_DECL (TREE_TYPE (t));
-	      TYPE_NAME (x) = t;
+	      TYPE_NAME (x) = TYPE_NAME (TREE_TYPE (t));
 	      DECL_ORIGINAL_TYPE (t) = x;
 	    }
 	}
! PR debug/71642
! { dg-do compile }
! { dg-options "-g" }

MODULE gauss_colloc
  INTEGER, PARAMETER :: dp=8
CONTAINS
SUBROUTINE collocGauss(h,h_inv,grid,poly,alphai,posi,max_r2,&
        periodic,gdim,local_bounds,local_shift,poly_shift,scale,lgrid,error)
    REAL(dp), DIMENSION(0:, 0:, 0:), &
      INTENT(inout)                          :: grid
    INTEGER, INTENT(inout), OPTIONAL :: lgrid
    CONTAINS
    SUBROUTINE kloop6
    IF (kJump/=1 .AND. (ikstart+kmax-kstart>=ndim(2)+l_shift(2) .OR.&
        ikstart2+kmin-kstart2<=l_ub(2)-ndim(2))) THEN
        DO
            DO k=kstart2,kend2,-1
                IF ( PRESENT ( lgrid ) ) THEN
                  grid(ik,ij,ii) = grid(ik,ij,ii) + p_v*res_k
                END IF
            END DO
        END DO
    END IF
    END SUBROUTINE
END SUBROUTINE
END MODULE gauss_colloc

Reply via email to