This is the mail archive of the gcc-patches@gcc.gnu.org mailing list for the GCC project.


Index Nav: [Date Index] [Subject Index] [Author Index] [Thread Index]
Message Nav: [Date Prev] [Date Next] [Thread Prev] [Thread Next]
Other format: [Raw text]

[fortran] PR40660: fix FE location problem


We are sending input_location, whereas previously we weren't sending
anything at all, so the DWARF location info wasn't changing like it is
erroneously doing now.  I have fixed this by sending UNKNOWN_LOCATION
like before, thus keeping the location intact.

Tested by bootstrapping c,fortran and checking for regressions.  This
fixes the PR.

This is pretty obvious, but just in case... OK for mainline?

Aldy

fortran/
	PR fortran/40660
	* trans-io.c (build_dt): Pass UNKNOWN_LOCATION to build_call_expr_loc.
	(transfer_array_desc): Same.

Index: testsuite/gfortran.dg/PR40660.f90
===================================================================
--- testsuite/gfortran.dg/PR40660.f90	(revision 0)
+++ testsuite/gfortran.dg/PR40660.f90	(revision 0)
@@ -0,0 +1,15 @@
+! { dg-do compile }
+! { dg-options "-fdump-tree-original-lineno" }
+!
+! PR fortran/40660
+
+PROGRAM test
+  INTEGER, DIMENSION(3) :: a1,a2
+  a1 = 1
+  PRINT*, a1
+  a2 = 2
+end program test
+
+! { dg-final { scan-tree-dump-times ": 3\] _gfortran" 0 "original" } }
+! { dg-final { cleanup-tree-dump "original" } }
+
Index: fortran/trans-io.c
===================================================================
--- fortran/trans-io.c	(revision 151000)
+++ fortran/trans-io.c	(working copy)
@@ -1802,7 +1802,7 @@ build_dt (tree function, gfc_code * code
     set_parameter_const (&block, var, IOPARM_common_flags, mask);
 
   tmp = gfc_build_addr_expr (NULL_TREE, var);
-  tmp = build_call_expr_loc (input_location,
+  tmp = build_call_expr_loc (UNKNOWN_LOCATION,
 			 function, 1, tmp);
   gfc_add_expr_to_block (&block, tmp);
 
@@ -2146,7 +2146,7 @@ transfer_array_desc (gfc_se * se, gfc_ty
   kind_arg = build_int_cst (NULL_TREE, ts->kind);
 
   tmp = gfc_build_addr_expr (NULL_TREE, dt_parm);
-  tmp = build_call_expr_loc (input_location,
+  tmp = build_call_expr_loc (UNKNOWN_LOCATION,
 			 iocall[IOCALL_X_ARRAY], 4,
 			 tmp, addr_expr, kind_arg, charlen_arg);
   gfc_add_expr_to_block (&se->pre, tmp);


Index Nav: [Date Index] [Subject Index] [Author Index] [Thread Index]
Message Nav: [Date Prev] [Date Next] [Thread Prev] [Thread Next]